{-# LANGUAGE CPP #-}
{-# LANGUAGE Trustworthy #-}
module Data.These.Combinators (
bimapThese,
mapHere,
mapThere,
bitraverseThese,
swapThese,
assocThese,
unassocThese,
justThis,
justThat,
justThese,
justHere,
justThere,
catThis,
catThat,
catThese,
catHere,
catThere,
isThis,
isThat,
isThese,
hasHere,
hasThere,
mapThis,
mapThat,
mapThese,
) where
import Control.Applicative (Applicative (..))
import Data.Bifunctor (bimap, first, second)
import Data.Bitraversable (bitraverse)
import Data.Maybe (isJust, mapMaybe)
import Data.These
import Prelude (Bool (..), Maybe (..), curry, uncurry, (.))
#ifdef MIN_VERSION_assoc
import Data.Bifunctor.Assoc (assoc, unassoc)
import Data.Bifunctor.Swap (swap)
#endif
bimapThese :: (a -> c) -> (b -> d) -> These a b -> These c d
bimapThese :: forall a c b d. (a -> c) -> (b -> d) -> These a b -> These c d
bimapThese = (a -> c) -> (b -> d) -> These a b -> These c d
forall a c b d. (a -> c) -> (b -> d) -> These a b -> These c d
forall (p :: * -> * -> *) a b c d.
Bifunctor p =>
(a -> b) -> (c -> d) -> p a c -> p b d
bimap
mapHere :: (a -> c) -> These a b -> These c b
mapHere :: forall a c b. (a -> c) -> These a b -> These c b
mapHere = (a -> c) -> These a b -> These c b
forall a c b. (a -> c) -> These a b -> These c b
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first
mapThere :: (b -> d) -> These a b -> These a d
mapThere :: forall b d a. (b -> d) -> These a b -> These a d
mapThere = (b -> d) -> These a b -> These a d
forall b d a. (b -> d) -> These a b -> These a d
forall (p :: * -> * -> *) b c a.
Bifunctor p =>
(b -> c) -> p a b -> p a c
second
bitraverseThese :: Applicative f => (a -> f c) -> (b -> f d) -> These a b -> f (These c d)
bitraverseThese :: forall (f :: * -> *) a c b d.
Applicative f =>
(a -> f c) -> (b -> f d) -> These a b -> f (These c d)
bitraverseThese = (a -> f c) -> (b -> f d) -> These a b -> f (These c d)
forall (f :: * -> *) a c b d.
Applicative f =>
(a -> f c) -> (b -> f d) -> These a b -> f (These c d)
forall (t :: * -> * -> *) (f :: * -> *) a c b d.
(Bitraversable t, Applicative f) =>
(a -> f c) -> (b -> f d) -> t a b -> f (t c d)
bitraverse
swapThese :: These a b -> These b a
#ifdef MIN_VERSION_assoc
swapThese :: forall a b. These a b -> These b a
swapThese = These a b -> These b a
forall a b. These a b -> These b a
forall (p :: * -> * -> *) a b. Swap p => p a b -> p b a
swap
#else
swapThese (This a) = That a
swapThese (That b) = This b
swapThese (These a b) = These b a
#endif
assocThese :: These (These a b) c -> These a (These b c)
#ifdef MIN_VERSION_assoc
assocThese :: forall a b c. These (These a b) c -> These a (These b c)
assocThese = These (These a b) c -> These a (These b c)
forall a b c. These (These a b) c -> These a (These b c)
forall (p :: * -> * -> *) a b c.
Assoc p =>
p (p a b) c -> p a (p b c)
assoc
#else
assocThese (This (This a)) = This a
assocThese (This (That b)) = That (This b)
assocThese (That c) = That (That c)
assocThese (These (That b) c) = That (These b c)
assocThese (This (These a b)) = These a (This b)
assocThese (These (This a) c) = These a (That c)
assocThese (These (These a b) c) = These a (These b c)
#endif
unassocThese :: These a (These b c) -> These (These a b) c
#ifdef MIN_VERSION_assoc
unassocThese :: forall a b c. These a (These b c) -> These (These a b) c
unassocThese = These a (These b c) -> These (These a b) c
forall a b c. These a (These b c) -> These (These a b) c
forall (p :: * -> * -> *) a b c.
Assoc p =>
p a (p b c) -> p (p a b) c
unassoc
#else
unassocThese (This a) = This (This a)
unassocThese (That (This b)) = This (That b)
unassocThese (That (That c)) = That c
unassocThese (That (These b c)) = These (That b) c
unassocThese (These a (This b)) = This (These a b)
unassocThese (These a (That c)) = These (This a) c
unassocThese (These a (These b c)) = These (These a b) c
#endif
justHere :: These a b -> Maybe a
justHere :: forall a b. These a b -> Maybe a
justHere (This a
a) = a -> Maybe a
forall a. a -> Maybe a
Just a
a
justHere (That b
_) = Maybe a
forall a. Maybe a
Nothing
justHere (These a
a b
_) = a -> Maybe a
forall a. a -> Maybe a
Just a
a
justThere :: These a b -> Maybe b
justThere :: forall a b. These a b -> Maybe b
justThere (This a
_) = Maybe b
forall a. Maybe a
Nothing
justThere (That b
b) = b -> Maybe b
forall a. a -> Maybe a
Just b
b
justThere (These a
_ b
b) = b -> Maybe b
forall a. a -> Maybe a
Just b
b
justThis :: These a b -> Maybe a
justThis :: forall a b. These a b -> Maybe a
justThis (This a
a) = a -> Maybe a
forall a. a -> Maybe a
Just a
a
justThis These a b
_ = Maybe a
forall a. Maybe a
Nothing
justThat :: These a b -> Maybe b
justThat :: forall a b. These a b -> Maybe b
justThat (That b
x) = b -> Maybe b
forall a. a -> Maybe a
Just b
x
justThat These a b
_ = Maybe b
forall a. Maybe a
Nothing
justThese :: These a b -> Maybe (a, b)
justThese :: forall a b. These a b -> Maybe (a, b)
justThese (These a
a b
x) = (a, b) -> Maybe (a, b)
forall a. a -> Maybe a
Just (a
a, b
x)
justThese These a b
_ = Maybe (a, b)
forall a. Maybe a
Nothing
catThis :: [These a b] -> [a]
catThis :: forall a b. [These a b] -> [a]
catThis = (These a b -> Maybe a) -> [These a b] -> [a]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe These a b -> Maybe a
forall a b. These a b -> Maybe a
justThis
catThat :: [These a b] -> [b]
catThat :: forall a b. [These a b] -> [b]
catThat = (These a b -> Maybe b) -> [These a b] -> [b]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe These a b -> Maybe b
forall a b. These a b -> Maybe b
justThat
catThese :: [These a b] -> [(a, b)]
catThese :: forall a b. [These a b] -> [(a, b)]
catThese = (These a b -> Maybe (a, b)) -> [These a b] -> [(a, b)]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe These a b -> Maybe (a, b)
forall a b. These a b -> Maybe (a, b)
justThese
catHere :: [These a b] -> [a]
catHere :: forall a b. [These a b] -> [a]
catHere = (These a b -> Maybe a) -> [These a b] -> [a]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe These a b -> Maybe a
forall a b. These a b -> Maybe a
justHere
catThere :: [These a b] -> [b]
catThere :: forall a b. [These a b] -> [b]
catThere = (These a b -> Maybe b) -> [These a b] -> [b]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe These a b -> Maybe b
forall a b. These a b -> Maybe b
justThere
isThis, isThat, isThese :: These a b -> Bool
isThis :: forall a b. These a b -> Bool
isThis = Maybe a -> Bool
forall a. Maybe a -> Bool
isJust (Maybe a -> Bool) -> (These a b -> Maybe a) -> These a b -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. These a b -> Maybe a
forall a b. These a b -> Maybe a
justThis
isThat :: forall a b. These a b -> Bool
isThat = Maybe b -> Bool
forall a. Maybe a -> Bool
isJust (Maybe b -> Bool) -> (These a b -> Maybe b) -> These a b -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. These a b -> Maybe b
forall a b. These a b -> Maybe b
justThat
isThese :: forall a b. These a b -> Bool
isThese = Maybe (a, b) -> Bool
forall a. Maybe a -> Bool
isJust (Maybe (a, b) -> Bool)
-> (These a b -> Maybe (a, b)) -> These a b -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. These a b -> Maybe (a, b)
forall a b. These a b -> Maybe (a, b)
justThese
hasHere, hasThere :: These a b -> Bool
hasHere :: forall a b. These a b -> Bool
hasHere = Maybe a -> Bool
forall a. Maybe a -> Bool
isJust (Maybe a -> Bool) -> (These a b -> Maybe a) -> These a b -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. These a b -> Maybe a
forall a b. These a b -> Maybe a
justHere
hasThere :: forall a b. These a b -> Bool
hasThere = Maybe b -> Bool
forall a. Maybe a -> Bool
isJust (Maybe b -> Bool) -> (These a b -> Maybe b) -> These a b -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. These a b -> Maybe b
forall a b. These a b -> Maybe b
justThere
mapThis :: (a -> a) -> These a b -> These a b
mapThis :: forall a b. (a -> a) -> These a b -> These a b
mapThis a -> a
f (This a
x) = a -> These a b
forall a b. a -> These a b
This (a -> a
f a
x)
mapThis a -> a
_ These a b
y = These a b
y
mapThat :: (b -> b) -> These a b -> These a b
mapThat :: forall b a. (b -> b) -> These a b -> These a b
mapThat b -> b
f (That b
x) = b -> These a b
forall a b. b -> These a b
That (b -> b
f b
x)
mapThat b -> b
_ These a b
y = These a b
y
mapThese :: ((a, b) -> (a, b)) -> These a b -> These a b
mapThese :: forall a b. ((a, b) -> (a, b)) -> These a b -> These a b
mapThese (a, b) -> (a, b)
f (These a
x b
y) = (a -> b -> These a b) -> (a, b) -> These a b
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry a -> b -> These a b
forall a b. a -> b -> These a b
These (((a, b) -> (a, b)) -> a -> b -> (a, b)
forall a b c. ((a, b) -> c) -> a -> b -> c
curry (a, b) -> (a, b)
f a
x b
y)
mapThese (a, b) -> (a, b)
_ These a b
z = These a b
z