both-0.1.1.2: Like Maybe, but with a different Monoid instance.
Safe HaskellNone
LanguageHaskell2010

Data.Both

Description

The Both type and operations. Like Maybe, but not.

Synopsis

Documentation

newtype Both a Source #

Constructors

Both 

Fields

Instances

Instances details
Monad Both Source # 
Instance details

Defined in Data.Both

Methods

(>>=) :: Both a -> (a -> Both b) -> Both b #

(>>) :: Both a -> Both b -> Both b #

return :: a -> Both a #

Functor Both Source # 
Instance details

Defined in Data.Both

Methods

fmap :: (a -> b) -> Both a -> Both b #

(<$) :: a -> Both b -> Both a #

Applicative Both Source # 
Instance details

Defined in Data.Both

Methods

pure :: a -> Both a #

(<*>) :: Both (a -> b) -> Both a -> Both b #

liftA2 :: (a -> b -> c) -> Both a -> Both b -> Both c #

(*>) :: Both a -> Both b -> Both b #

(<*) :: Both a -> Both b -> Both a #

Foldable Both Source # 
Instance details

Defined in Data.Both

Methods

fold :: Monoid m => Both m -> m #

foldMap :: Monoid m => (a -> m) -> Both a -> m #

foldMap' :: Monoid m => (a -> m) -> Both a -> m #

foldr :: (a -> b -> b) -> b -> Both a -> b #

foldr' :: (a -> b -> b) -> b -> Both a -> b #

foldl :: (b -> a -> b) -> b -> Both a -> b #

foldl' :: (b -> a -> b) -> b -> Both a -> b #

foldr1 :: (a -> a -> a) -> Both a -> a #

foldl1 :: (a -> a -> a) -> Both a -> a #

toList :: Both a -> [a] #

null :: Both a -> Bool #

length :: Both a -> Int #

elem :: Eq a => a -> Both a -> Bool #

maximum :: Ord a => Both a -> a #

minimum :: Ord a => Both a -> a #

sum :: Num a => Both a -> a #

product :: Num a => Both a -> a #

Traversable Both Source # 
Instance details

Defined in Data.Both

Methods

traverse :: Applicative f => (a -> f b) -> Both a -> f (Both b) #

sequenceA :: Applicative f => Both (f a) -> f (Both a) #

mapM :: Monad m => (a -> m b) -> Both a -> m (Both b) #

sequence :: Monad m => Both (m a) -> m (Both a) #

Alternative Both Source # 
Instance details

Defined in Data.Both

Methods

empty :: Both a #

(<|>) :: Both a -> Both a -> Both a #

some :: Both a -> Both [a] #

many :: Both a -> Both [a] #

MonadPlus Both Source # 
Instance details

Defined in Data.Both

Methods

mzero :: Both a #

mplus :: Both a -> Both a -> Both a #

Eq a => Eq (Both a) Source # 
Instance details

Defined in Data.Both

Methods

(==) :: Both a -> Both a -> Bool #

(/=) :: Both a -> Both a -> Bool #

Data a => Data (Both a) Source # 
Instance details

Defined in Data.Both

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Both a -> c (Both a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Both a) #

toConstr :: Both a -> Constr #

dataTypeOf :: Both a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Both a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Both a)) #

gmapT :: (forall b. Data b => b -> b) -> Both a -> Both a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Both a -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Both a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Both a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Both a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Both a -> m (Both a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Both a -> m (Both a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Both a -> m (Both a) #

Ord a => Ord (Both a) Source # 
Instance details

Defined in Data.Both

Methods

compare :: 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 #

max :: Both a -> Both a -> Both a #

min :: Both a -> Both a -> Both a #

Read a => Read (Both a) Source # 
Instance details

Defined in Data.Both

Show a => Show (Both a) Source # 
Instance details

Defined in Data.Both

Methods

showsPrec :: Int -> Both a -> ShowS #

show :: Both a -> String #

showList :: [Both a] -> ShowS #

Generic (Both a) Source # 
Instance details

Defined in Data.Both

Associated Types

type Rep (Both a) :: Type -> Type #

Methods

from :: Both a -> Rep (Both a) x #

to :: Rep (Both a) x -> Both a #

Semigroup a => Semigroup (Both a) Source #

The (<>) for Maybe is Just if either of the operands are, whereas here both must be.

Instance details

Defined in Data.Both

Methods

(<>) :: Both a -> Both a -> Both a #

sconcat :: NonEmpty (Both a) -> Both a #

stimes :: Integral b => b -> Both a -> Both a #

(Monoid a, Semigroup a) => Monoid (Both a) Source # 
Instance details

Defined in Data.Both

Methods

mempty :: Both a #

mappend :: Both a -> Both a -> Both a #

mconcat :: [Both a] -> Both a #

Semigroup a => Zero (Both a) Source # 
Instance details

Defined in Data.Both

Methods

zero :: Both a #

zconcat :: [Both a] -> Both a #

Generic1 Both Source # 
Instance details

Defined in Data.Both

Associated Types

type Rep1 Both :: k -> Type #

Methods

from1 :: forall (a :: k). Both a -> Rep1 Both a #

to1 :: forall (a :: k). Rep1 Both a -> Both a #

type Rep (Both a) Source # 
Instance details

Defined in Data.Both

type Rep (Both a) = D1 ('MetaData "Both" "Data.Both" "both-0.1.1.2-A996bZyIZMeFpPiS1OoO99" 'True) (C1 ('MetaCons "Both" 'PrefixI 'True) (S1 ('MetaSel ('Just "getBoth") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe a))))
type Rep1 Both Source # 
Instance details

Defined in Data.Both

type Rep1 Both = D1 ('MetaData "Both" "Data.Both" "both-0.1.1.2-A996bZyIZMeFpPiS1OoO99" 'True) (C1 ('MetaCons "Both" 'PrefixI 'True) (S1 ('MetaSel ('Just "getBoth") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 Maybe)))

both :: b -> (a -> b) -> Both a -> b Source #

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.

fromBoth :: a -> Both a -> a Source #

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.