{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveTraversable #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}

-- | The 'Both' type and operations. Like 'Maybe', but not.
module Data.Both where

import           Control.Applicative
import           Control.Monad
import           Data.Data
import           Data.Foldable
import           Data.Maybe
import           Data.Monoid         hiding ((<>))
import           Data.Semigroup
import           Data.Traversable
import           Data.Zero
import           GHC.Generics

newtype Both a = Both { Both a -> Maybe a
getBoth :: Maybe a }
  deriving (Both a -> Both a -> Bool
(Both a -> Both a -> Bool)
-> (Both a -> Both a -> Bool) -> Eq (Both a)
forall a. Eq a => Both a -> Both a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Both a -> Both a -> Bool
$c/= :: forall a. Eq a => Both a -> Both a -> Bool
== :: Both a -> Both a -> Bool
$c== :: forall a. Eq a => Both a -> Both a -> Bool
Eq, Eq (Both a)
Eq (Both a)
-> (Both a -> Both a -> Ordering)
-> (Both a -> Both a -> Bool)
-> (Both a -> Both a -> Bool)
-> (Both a -> Both a -> Bool)
-> (Both a -> Both a -> Bool)
-> (Both a -> Both a -> Both a)
-> (Both a -> Both a -> Both a)
-> Ord (Both a)
Both a -> Both a -> Bool
Both a -> Both a -> Ordering
Both a -> Both a -> Both a
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall a. Ord a => Eq (Both a)
forall a. Ord a => Both a -> Both a -> Bool
forall a. Ord a => Both a -> Both a -> Ordering
forall a. Ord a => Both a -> Both a -> Both a
min :: Both a -> Both a -> Both a
$cmin :: forall a. Ord a => Both a -> Both a -> Both a
max :: Both a -> Both a -> Both a
$cmax :: forall a. Ord a => Both a -> Both a -> Both a
>= :: Both a -> Both a -> Bool
$c>= :: forall a. Ord a => Both a -> Both a -> Bool
> :: Both a -> Both a -> Bool
$c> :: forall a. Ord a => Both a -> Both a -> Bool
<= :: Both a -> Both a -> Bool
$c<= :: forall a. Ord a => Both a -> Both a -> Bool
< :: Both a -> Both a -> Bool
$c< :: forall a. Ord a => Both a -> Both a -> Bool
compare :: Both a -> Both a -> Ordering
$ccompare :: forall a. Ord a => Both a -> Both a -> Ordering
$cp1Ord :: forall a. Ord a => Eq (Both a)
Ord, ReadPrec [Both a]
ReadPrec (Both a)
Int -> ReadS (Both a)
ReadS [Both a]
(Int -> ReadS (Both a))
-> ReadS [Both a]
-> ReadPrec (Both a)
-> ReadPrec [Both a]
-> Read (Both a)
forall a. Read a => ReadPrec [Both a]
forall a. Read a => ReadPrec (Both a)
forall a. Read a => Int -> ReadS (Both a)
forall a. Read a => ReadS [Both a]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Both a]
$creadListPrec :: forall a. Read a => ReadPrec [Both a]
readPrec :: ReadPrec (Both a)
$creadPrec :: forall a. Read a => ReadPrec (Both a)
readList :: ReadS [Both a]
$creadList :: forall a. Read a => ReadS [Both a]
readsPrec :: Int -> ReadS (Both a)
$creadsPrec :: forall a. Read a => Int -> ReadS (Both a)
Read, Int -> Both a -> ShowS
[Both a] -> ShowS
Both a -> String
(Int -> Both a -> ShowS)
-> (Both a -> String) -> ([Both a] -> ShowS) -> Show (Both a)
forall a. Show a => Int -> Both a -> ShowS
forall a. Show a => [Both a] -> ShowS
forall a. Show a => Both a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Both a] -> ShowS
$cshowList :: forall a. Show a => [Both a] -> ShowS
show :: Both a -> String
$cshow :: forall a. Show a => Both a -> String
showsPrec :: Int -> Both a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> Both a -> ShowS
Show, Typeable (Both a)
DataType
Constr
Typeable (Both a)
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> Both a -> c (Both a))
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c (Both a))
-> (Both a -> Constr)
-> (Both a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c (Both a)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Both a)))
-> ((forall b. Data b => b -> b) -> Both a -> Both a)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> Both a -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> Both a -> r)
-> (forall u. (forall d. Data d => d -> u) -> Both a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Both a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> Both a -> m (Both a))
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Both a -> m (Both a))
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Both a -> m (Both a))
-> Data (Both a)
Both a -> DataType
Both a -> Constr
(forall d. Data d => c (t d)) -> Maybe (c (Both a))
(forall b. Data b => b -> b) -> Both a -> Both a
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Both a -> c (Both a)
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Both a)
forall a. Data a => Typeable (Both a)
forall a. Data a => Both a -> DataType
forall a. Data a => Both a -> Constr
forall a.
Data a =>
(forall b. Data b => b -> b) -> Both a -> Both a
forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> Both a -> u
forall a u. Data a => (forall d. Data d => d -> u) -> Both a -> [u]
forall a r r'.
Data a =>
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Both a -> r
forall a r r'.
Data a =>
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Both a -> r
forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d) -> Both a -> m (Both a)
forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d) -> Both a -> m (Both a)
forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Both a)
forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Both a -> c (Both a)
forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (Both a))
forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Both a))
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Both a -> u
forall u. (forall d. Data d => d -> u) -> Both a -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Both a -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Both a -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Both a -> m (Both a)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Both a -> m (Both a)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Both a)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Both a -> c (Both a)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (Both a))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Both a))
$cBoth :: Constr
$tBoth :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> Both a -> m (Both a)
$cgmapMo :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d) -> Both a -> m (Both a)
gmapMp :: (forall d. Data d => d -> m d) -> Both a -> m (Both a)
$cgmapMp :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d) -> Both a -> m (Both a)
gmapM :: (forall d. Data d => d -> m d) -> Both a -> m (Both a)
$cgmapM :: forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d) -> Both a -> m (Both a)
gmapQi :: Int -> (forall d. Data d => d -> u) -> Both a -> u
$cgmapQi :: forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> Both a -> u
gmapQ :: (forall d. Data d => d -> u) -> Both a -> [u]
$cgmapQ :: forall a u. Data a => (forall d. Data d => d -> u) -> Both a -> [u]
gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Both a -> r
$cgmapQr :: forall a r r'.
Data a =>
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Both a -> r
gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Both a -> r
$cgmapQl :: forall a r r'.
Data a =>
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Both a -> r
gmapT :: (forall b. Data b => b -> b) -> Both a -> Both a
$cgmapT :: forall a.
Data a =>
(forall b. Data b => b -> b) -> Both a -> Both a
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Both a))
$cdataCast2 :: forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Both a))
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c (Both a))
$cdataCast1 :: forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (Both a))
dataTypeOf :: Both a -> DataType
$cdataTypeOf :: forall a. Data a => Both a -> DataType
toConstr :: Both a -> Constr
$ctoConstr :: forall a. Data a => Both a -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Both a)
$cgunfold :: forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Both a)
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Both a -> c (Both a)
$cgfoldl :: forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Both a -> c (Both a)
$cp1Data :: forall a. Data a => Typeable (Both a)
Data, Typeable, (forall x. Both a -> Rep (Both a) x)
-> (forall x. Rep (Both a) x -> Both a) -> Generic (Both a)
forall x. Rep (Both a) x -> Both a
forall x. Both a -> Rep (Both a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (Both a) x -> Both a
forall a x. Both a -> Rep (Both a) x
$cto :: forall a x. Rep (Both a) x -> Both a
$cfrom :: forall a x. Both a -> Rep (Both a) x
Generic, (forall a. Both a -> Rep1 Both a)
-> (forall a. Rep1 Both a -> Both a) -> Generic1 Both
forall a. Rep1 Both a -> Both a
forall a. Both a -> Rep1 Both a
forall k (f :: k -> *).
(forall (a :: k). f a -> Rep1 f a)
-> (forall (a :: k). Rep1 f a -> f a) -> Generic1 f
$cto1 :: forall a. Rep1 Both a -> Both a
$cfrom1 :: forall a. Both a -> Rep1 Both a
Generic1, a -> Both b -> Both a
(a -> b) -> Both a -> Both b
(forall a b. (a -> b) -> Both a -> Both b)
-> (forall a b. a -> Both b -> Both a) -> Functor Both
forall a b. a -> Both b -> Both a
forall a b. (a -> b) -> Both a -> Both b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> Both b -> Both a
$c<$ :: forall a b. a -> Both b -> Both a
fmap :: (a -> b) -> Both a -> Both b
$cfmap :: forall a b. (a -> b) -> Both a -> Both b
Functor, Functor Both
a -> Both a
Functor Both
-> (forall a. a -> Both a)
-> (forall a b. Both (a -> b) -> Both a -> Both b)
-> (forall a b c. (a -> b -> c) -> Both a -> Both b -> Both c)
-> (forall a b. Both a -> Both b -> Both b)
-> (forall a b. Both a -> Both b -> Both a)
-> Applicative Both
Both a -> Both b -> Both b
Both a -> Both b -> Both a
Both (a -> b) -> Both a -> Both b
(a -> b -> c) -> Both a -> Both b -> Both c
forall a. a -> Both a
forall a b. Both a -> Both b -> Both a
forall a b. Both a -> Both b -> Both b
forall a b. Both (a -> b) -> Both a -> Both b
forall a b c. (a -> b -> c) -> Both a -> Both b -> Both c
forall (f :: * -> *).
Functor f
-> (forall a. a -> f a)
-> (forall a b. f (a -> b) -> f a -> f b)
-> (forall a b c. (a -> b -> c) -> f a -> f b -> f c)
-> (forall a b. f a -> f b -> f b)
-> (forall a b. f a -> f b -> f a)
-> Applicative f
<* :: Both a -> Both b -> Both a
$c<* :: forall a b. Both a -> Both b -> Both a
*> :: Both a -> Both b -> Both b
$c*> :: forall a b. Both a -> Both b -> Both b
liftA2 :: (a -> b -> c) -> Both a -> Both b -> Both c
$cliftA2 :: forall a b c. (a -> b -> c) -> Both a -> Both b -> Both c
<*> :: Both (a -> b) -> Both a -> Both b
$c<*> :: forall a b. Both (a -> b) -> Both a -> Both b
pure :: a -> Both a
$cpure :: forall a. a -> Both a
$cp1Applicative :: Functor Both
Applicative, Applicative Both
Both a
Applicative Both
-> (forall a. Both a)
-> (forall a. Both a -> Both a -> Both a)
-> (forall a. Both a -> Both [a])
-> (forall a. Both a -> Both [a])
-> Alternative Both
Both a -> Both a -> Both a
Both a -> Both [a]
Both a -> Both [a]
forall a. Both a
forall a. Both a -> Both [a]
forall a. Both a -> Both a -> Both a
forall (f :: * -> *).
Applicative f
-> (forall a. f a)
-> (forall a. f a -> f a -> f a)
-> (forall a. f a -> f [a])
-> (forall a. f a -> f [a])
-> Alternative f
many :: Both a -> Both [a]
$cmany :: forall a. Both a -> Both [a]
some :: Both a -> Both [a]
$csome :: forall a. Both a -> Both [a]
<|> :: Both a -> Both a -> Both a
$c<|> :: forall a. Both a -> Both a -> Both a
empty :: Both a
$cempty :: forall a. Both a
$cp1Alternative :: Applicative Both
Alternative, Applicative Both
a -> Both a
Applicative Both
-> (forall a b. Both a -> (a -> Both b) -> Both b)
-> (forall a b. Both a -> Both b -> Both b)
-> (forall a. a -> Both a)
-> Monad Both
Both a -> (a -> Both b) -> Both b
Both a -> Both b -> Both b
forall a. a -> Both a
forall a b. Both a -> Both b -> Both b
forall a b. Both a -> (a -> Both b) -> Both b
forall (m :: * -> *).
Applicative m
-> (forall a b. m a -> (a -> m b) -> m b)
-> (forall a b. m a -> m b -> m b)
-> (forall a. a -> m a)
-> Monad m
return :: a -> Both a
$creturn :: forall a. a -> Both a
>> :: Both a -> Both b -> Both b
$c>> :: forall a b. Both a -> Both b -> Both b
>>= :: Both a -> (a -> Both b) -> Both b
$c>>= :: forall a b. Both a -> (a -> Both b) -> Both b
$cp1Monad :: Applicative Both
Monad, Monad Both
Alternative Both
Both a
Alternative Both
-> Monad Both
-> (forall a. Both a)
-> (forall a. Both a -> Both a -> Both a)
-> MonadPlus Both
Both a -> Both a -> Both a
forall a. Both a
forall a. Both a -> Both a -> Both a
forall (m :: * -> *).
Alternative m
-> Monad m
-> (forall a. m a)
-> (forall a. m a -> m a -> m a)
-> MonadPlus m
mplus :: Both a -> Both a -> Both a
$cmplus :: forall a. Both a -> Both a -> Both a
mzero :: Both a
$cmzero :: forall a. Both a
$cp2MonadPlus :: Monad Both
$cp1MonadPlus :: Alternative Both
MonadPlus, a -> Both a -> Bool
Both m -> m
Both a -> [a]
Both a -> Bool
Both a -> Int
Both a -> a
Both a -> a
Both a -> a
Both a -> a
(a -> m) -> Both a -> m
(a -> m) -> Both a -> m
(a -> b -> b) -> b -> Both a -> b
(a -> b -> b) -> b -> Both a -> b
(b -> a -> b) -> b -> Both a -> b
(b -> a -> b) -> b -> Both a -> b
(a -> a -> a) -> Both a -> a
(a -> a -> a) -> Both a -> a
(forall m. Monoid m => Both m -> m)
-> (forall m a. Monoid m => (a -> m) -> Both a -> m)
-> (forall m a. Monoid m => (a -> m) -> Both a -> m)
-> (forall a b. (a -> b -> b) -> b -> Both a -> b)
-> (forall a b. (a -> b -> b) -> b -> Both a -> b)
-> (forall b a. (b -> a -> b) -> b -> Both a -> b)
-> (forall b a. (b -> a -> b) -> b -> Both a -> b)
-> (forall a. (a -> a -> a) -> Both a -> a)
-> (forall a. (a -> a -> a) -> Both a -> a)
-> (forall a. Both a -> [a])
-> (forall a. Both a -> Bool)
-> (forall a. Both a -> Int)
-> (forall a. Eq a => a -> Both a -> Bool)
-> (forall a. Ord a => Both a -> a)
-> (forall a. Ord a => Both a -> a)
-> (forall a. Num a => Both a -> a)
-> (forall a. Num a => Both a -> a)
-> Foldable Both
forall a. Eq a => a -> Both a -> Bool
forall a. Num a => Both a -> a
forall a. Ord a => Both a -> a
forall m. Monoid m => Both m -> m
forall a. Both a -> Bool
forall a. Both a -> Int
forall a. Both a -> [a]
forall a. (a -> a -> a) -> Both a -> a
forall m a. Monoid m => (a -> m) -> Both a -> m
forall b a. (b -> a -> b) -> b -> Both a -> b
forall a b. (a -> b -> b) -> b -> Both a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
product :: Both a -> a
$cproduct :: forall a. Num a => Both a -> a
sum :: Both a -> a
$csum :: forall a. Num a => Both a -> a
minimum :: Both a -> a
$cminimum :: forall a. Ord a => Both a -> a
maximum :: Both a -> a
$cmaximum :: forall a. Ord a => Both a -> a
elem :: a -> Both a -> Bool
$celem :: forall a. Eq a => a -> Both a -> Bool
length :: Both a -> Int
$clength :: forall a. Both a -> Int
null :: Both a -> Bool
$cnull :: forall a. Both a -> Bool
toList :: Both a -> [a]
$ctoList :: forall a. Both a -> [a]
foldl1 :: (a -> a -> a) -> Both a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> Both a -> a
foldr1 :: (a -> a -> a) -> Both a -> a
$cfoldr1 :: forall a. (a -> a -> a) -> Both a -> a
foldl' :: (b -> a -> b) -> b -> Both a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> Both a -> b
foldl :: (b -> a -> b) -> b -> Both a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> Both a -> b
foldr' :: (a -> b -> b) -> b -> Both a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> Both a -> b
foldr :: (a -> b -> b) -> b -> Both a -> b
$cfoldr :: forall a b. (a -> b -> b) -> b -> Both a -> b
foldMap' :: (a -> m) -> Both a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> Both a -> m
foldMap :: (a -> m) -> Both a -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> Both a -> m
fold :: Both m -> m
$cfold :: forall m. Monoid m => Both m -> m
Foldable, Functor Both
Foldable Both
Functor Both
-> Foldable Both
-> (forall (f :: * -> *) a b.
    Applicative f =>
    (a -> f b) -> Both a -> f (Both b))
-> (forall (f :: * -> *) a.
    Applicative f =>
    Both (f a) -> f (Both a))
-> (forall (m :: * -> *) a b.
    Monad m =>
    (a -> m b) -> Both a -> m (Both b))
-> (forall (m :: * -> *) a. Monad m => Both (m a) -> m (Both a))
-> Traversable Both
(a -> f b) -> Both a -> f (Both b)
forall (t :: * -> *).
Functor t
-> Foldable t
-> (forall (f :: * -> *) a b.
    Applicative f =>
    (a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
    Monad m =>
    (a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a. Monad m => Both (m a) -> m (Both a)
forall (f :: * -> *) a. Applicative f => Both (f a) -> f (Both a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Both a -> m (Both b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Both a -> f (Both b)
sequence :: Both (m a) -> m (Both a)
$csequence :: forall (m :: * -> *) a. Monad m => Both (m a) -> m (Both a)
mapM :: (a -> m b) -> Both a -> m (Both b)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Both a -> m (Both b)
sequenceA :: Both (f a) -> f (Both a)
$csequenceA :: forall (f :: * -> *) a. Applicative f => Both (f a) -> f (Both a)
traverse :: (a -> f b) -> Both a -> f (Both b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Both a -> f (Both b)
$cp2Traversable :: Foldable Both
$cp1Traversable :: Functor Both
Traversable)

-- | The '(<>)' for 'Maybe' is 'Just' if /either/ of the operands
-- are, whereas here /both/ must be.
instance Semigroup a => Semigroup (Both a) where
  Both (Just a
x) <> :: Both a -> Both a -> Both a
<> Both (Just a
y) = Maybe a -> Both a
forall a. Maybe a -> Both a
Both (Maybe a -> Both a) -> (a -> Maybe a) -> a -> Both a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Maybe a
forall a. a -> Maybe a
Just (a -> Both a) -> a -> Both a
forall a b. (a -> b) -> a -> b
$ a
x a -> a -> a
forall a. Semigroup a => a -> a -> a
<> a
y
  Both a
_ <> Both a
_ = Maybe a -> Both a
forall a. Maybe a -> Both a
Both Maybe a
forall a. Maybe a
Nothing

instance (Monoid a, Semigroup a) => Monoid (Both a) where
  mempty :: Both a
mempty  = Maybe a -> Both a
forall a. Maybe a -> Both a
Both (Maybe a -> Both a) -> Maybe a -> Both a
forall a b. (a -> b) -> a -> b
$ a -> Maybe a
forall a. a -> Maybe a
Just a
forall a. Monoid a => a
mempty
  mappend :: Both a -> Both a -> Both a
mappend = Both a -> Both a -> Both a
forall a. Semigroup a => a -> a -> a
(<>)

instance Semigroup a => Zero (Both a) where
  zero :: Both a
zero = Maybe a -> Both a
forall a. Maybe a -> Both a
Both Maybe a
forall a. Maybe a
Nothing

-- | The 'both' function takes a default value, a function, and a
-- 'Both' value. If the inner 'Maybe' value is 'Nothing', the function
-- returns the default value. Otherwise, it applies the function to
-- the value inside the 'Just' and returns the result.
both :: b -> (a -> b) -> Both a -> b
both :: b -> (a -> b) -> Both a -> b
both b
z a -> b
f = b -> (a -> b) -> Maybe a -> b
forall b a. b -> (a -> b) -> Maybe a -> b
maybe b
z a -> b
f (Maybe a -> b) -> (Both a -> Maybe a) -> Both a -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Both a -> Maybe a
forall a. Both a -> Maybe a
getBoth

-- | The 'fromBoth' function takes a default value and a 'Both'
-- value. If the inner 'Maybe' is 'Nothing', it returns the default
-- value; otherwise, it returns the value contained within.
fromBoth :: a -> Both a -> a
fromBoth :: a -> Both a -> a
fromBoth a
z = a -> Maybe a -> a
forall a. a -> Maybe a -> a
fromMaybe a
z (Maybe a -> a) -> (Both a -> Maybe a) -> Both a -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Both a -> Maybe a
forall a. Both a -> Maybe a
getBoth