either-semigroup-0.0.0: Either with a stricter Semigroup instance
Safe HaskellSafe-Inferred
LanguageGHC2021

Data.Either.Semigroup

Synopsis

Documentation

data EitherS l r Source #

The EitherS type represents values with two possibilities: a value of type EitherS a b is either LeftS a or RightS b.

The EitherS type is sometimes used to represent a value which is either correct or an error; by convention, the LeftS constructor is used to hold an error value and the RightS constructor is used to hold a correct value (mnemonic: "right" also means "correct").

This type differs from Either in the Semigroup instance, requiring the LeftS type to be a Semigroup in the first place.

Constructors

LeftS l 
RightS r 

Instances

Instances details
Bifoldable EitherS Source # 
Instance details

Defined in Data.Either.Semigroup

Methods

bifold :: Monoid m => EitherS m m -> m #

bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> EitherS a b -> m #

bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> EitherS a b -> c #

bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> EitherS a b -> c #

Bifoldable1 EitherS Source # 
Instance details

Defined in Data.Either.Semigroup

Methods

bifold1 :: Semigroup m => EitherS m m -> m #

bifoldMap1 :: Semigroup m => (a -> m) -> (b -> m) -> EitherS a b -> m #

Bifunctor EitherS Source # 
Instance details

Defined in Data.Either.Semigroup

Methods

bimap :: (a -> b) -> (c -> d) -> EitherS a c -> EitherS b d #

first :: (a -> b) -> EitherS a c -> EitherS b c #

second :: (b -> c) -> EitherS a b -> EitherS a c #

Bitraversable EitherS Source # 
Instance details

Defined in Data.Either.Semigroup

Methods

bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> EitherS a b -> f (EitherS c d) #

Eq2 EitherS Source # 
Instance details

Defined in Data.Either.Semigroup

Methods

liftEq2 :: (a -> b -> Bool) -> (c -> d -> Bool) -> EitherS a c -> EitherS b d -> Bool #

Ord2 EitherS Source # 
Instance details

Defined in Data.Either.Semigroup

Methods

liftCompare2 :: (a -> b -> Ordering) -> (c -> d -> Ordering) -> EitherS a c -> EitherS b d -> Ordering #

Generic1 (EitherS l :: Type -> Type) Source # 
Instance details

Defined in Data.Either.Semigroup

Associated Types

type Rep1 (EitherS l) :: k -> Type #

Methods

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

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

Monoid l => MonadFix (EitherS l) Source # 
Instance details

Defined in Data.Either.Semigroup

Methods

mfix :: (a -> EitherS l a) -> EitherS l a #

Foldable (EitherS l) Source # 
Instance details

Defined in Data.Either.Semigroup

Methods

fold :: Monoid m => EitherS l m -> m #

foldMap :: Monoid m => (a -> m) -> EitherS l a -> m #

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

foldr :: (a -> b -> b) -> b -> EitherS l a -> b #

foldr' :: (a -> b -> b) -> b -> EitherS l a -> b #

foldl :: (b -> a -> b) -> b -> EitherS l a -> b #

foldl' :: (b -> a -> b) -> b -> EitherS l a -> b #

foldr1 :: (a -> a -> a) -> EitherS l a -> a #

foldl1 :: (a -> a -> a) -> EitherS l a -> a #

toList :: EitherS l a -> [a] #

null :: EitherS l a -> Bool #

length :: EitherS l a -> Int #

elem :: Eq a => a -> EitherS l a -> Bool #

maximum :: Ord a => EitherS l a -> a #

minimum :: Ord a => EitherS l a -> a #

sum :: Num a => EitherS l a -> a #

product :: Num a => EitherS l a -> a #

Eq l => Eq1 (EitherS l) Source # 
Instance details

Defined in Data.Either.Semigroup

Methods

liftEq :: (a -> b -> Bool) -> EitherS l a -> EitherS l b -> Bool #

Ord l => Ord1 (EitherS l) Source # 
Instance details

Defined in Data.Either.Semigroup

Methods

liftCompare :: (a -> b -> Ordering) -> EitherS l a -> EitherS l b -> Ordering #

Traversable (EitherS l) Source # 
Instance details

Defined in Data.Either.Semigroup

Methods

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

sequenceA :: Applicative f => EitherS l (f a) -> f (EitherS l a) #

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

sequence :: Monad m => EitherS l (m a) -> m (EitherS l a) #

Monoid l => Applicative (EitherS l) Source # 
Instance details

Defined in Data.Either.Semigroup

Methods

pure :: a -> EitherS l a #

(<*>) :: EitherS l (a -> b) -> EitherS l a -> EitherS l b #

liftA2 :: (a -> b -> c) -> EitherS l a -> EitherS l b -> EitherS l c #

(*>) :: EitherS l a -> EitherS l b -> EitherS l b #

(<*) :: EitherS l a -> EitherS l b -> EitherS l a #

Functor (EitherS l) Source # 
Instance details

Defined in Data.Either.Semigroup

Methods

fmap :: (a -> b) -> EitherS l a -> EitherS l b #

(<$) :: a -> EitherS l b -> EitherS l a #

Monoid l => Monad (EitherS l) Source # 
Instance details

Defined in Data.Either.Semigroup

Methods

(>>=) :: EitherS l a -> (a -> EitherS l b) -> EitherS l b #

(>>) :: EitherS l a -> EitherS l b -> EitherS l b #

return :: a -> EitherS l a #

(Data l, Data r) => Data (EitherS l r) Source # 
Instance details

Defined in Data.Either.Semigroup

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> EitherS l r -> c (EitherS l r) #

gunfold :: (forall b r0. Data b => c (b -> r0) -> c r0) -> (forall r1. r1 -> c r1) -> Constr -> c (EitherS l r) #

toConstr :: EitherS l r -> Constr #

dataTypeOf :: EitherS l r -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (EitherS l r)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (EitherS l r)) #

gmapT :: (forall b. Data b => b -> b) -> EitherS l r -> EitherS l r #

gmapQl :: (r0 -> r' -> r0) -> r0 -> (forall d. Data d => d -> r') -> EitherS l r -> r0 #

gmapQr :: forall r0 r'. (r' -> r0 -> r0) -> r0 -> (forall d. Data d => d -> r') -> EitherS l r -> r0 #

gmapQ :: (forall d. Data d => d -> u) -> EitherS l r -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> EitherS l r -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> EitherS l r -> m (EitherS l r) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EitherS l r -> m (EitherS l r) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EitherS l r -> m (EitherS l r) #

Monoid l => Monoid (EitherS l r) Source # 
Instance details

Defined in Data.Either.Semigroup

Methods

mempty :: EitherS l r #

mappend :: EitherS l r -> EitherS l r -> EitherS l r #

mconcat :: [EitherS l r] -> EitherS l r #

Semigroup l => Semigroup (EitherS l r) Source # 
Instance details

Defined in Data.Either.Semigroup

Methods

(<>) :: EitherS l r -> EitherS l r -> EitherS l r #

sconcat :: NonEmpty (EitherS l r) -> EitherS l r #

stimes :: Integral b => b -> EitherS l r -> EitherS l r #

Generic (EitherS l r) Source # 
Instance details

Defined in Data.Either.Semigroup

Associated Types

type Rep (EitherS l r) :: Type -> Type #

Methods

from :: EitherS l r -> Rep (EitherS l r) x #

to :: Rep (EitherS l r) x -> EitherS l r #

(Read l, Read r) => Read (EitherS l r) Source # 
Instance details

Defined in Data.Either.Semigroup

(Show l, Show r) => Show (EitherS l r) Source # 
Instance details

Defined in Data.Either.Semigroup

Methods

showsPrec :: Int -> EitherS l r -> ShowS #

show :: EitherS l r -> String #

showList :: [EitherS l r] -> ShowS #

(Eq l, Eq r) => Eq (EitherS l r) Source # 
Instance details

Defined in Data.Either.Semigroup

Methods

(==) :: EitherS l r -> EitherS l r -> Bool #

(/=) :: EitherS l r -> EitherS l r -> Bool #

(Ord l, Ord r) => Ord (EitherS l r) Source # 
Instance details

Defined in Data.Either.Semigroup

Methods

compare :: EitherS l r -> EitherS l r -> Ordering #

(<) :: EitherS l r -> EitherS l r -> Bool #

(<=) :: EitherS l r -> EitherS l r -> Bool #

(>) :: EitherS l r -> EitherS l r -> Bool #

(>=) :: EitherS l r -> EitherS l r -> Bool #

max :: EitherS l r -> EitherS l r -> EitherS l r #

min :: EitherS l r -> EitherS l r -> EitherS l r #

type Rep1 (EitherS l :: Type -> Type) Source # 
Instance details

Defined in Data.Either.Semigroup

type Rep1 (EitherS l :: Type -> Type) = D1 ('MetaData "EitherS" "Data.Either.Semigroup" "either-semigroup-0.0.0-5WwuG8pZdMj2XWe6dQdloY" 'False) (C1 ('MetaCons "LeftS" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l)) :+: C1 ('MetaCons "RightS" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))
type Rep (EitherS l r) Source # 
Instance details

Defined in Data.Either.Semigroup

type Rep (EitherS l r) = D1 ('MetaData "EitherS" "Data.Either.Semigroup" "either-semigroup-0.0.0-5WwuG8pZdMj2XWe6dQdloY" 'False) (C1 ('MetaCons "LeftS" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l)) :+: C1 ('MetaCons "RightS" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 r)))

toEither :: EitherS l r -> Either l r Source #

Turn an EitherS value into a plain Either value.

eitherS :: (l -> x) -> (r -> x) -> EitherS l r -> x Source #

leftsS :: [EitherS l r] -> [l] Source #

rightsS :: [EitherS l r] -> [r] Source #