strict-base-types-0.7: Strict variants of the types provided in base.

Copyright(c) 2006-2007 Roman Leshchinskiy
(c) 2013 Simon Meier
LicenseBSD-style (see the file LICENSE)
MaintainerSimon Meier <iridcode@gmail.com>
Stabilityexperimental
PortabilityGHC
Safe HaskellNone
LanguageHaskell2010

Data.Either.Strict

Description

The strict variant of the standard Haskell Either type and the corresponding variants of the functions from Data.Either.

Note that the strict Either type is not an applicative functor, and therefore also no monad. The reasons are the same as the ones for the strict Maybe type, which are explained in Data.Maybe.Strict.

Synopsis

Documentation

data Either a b #

The strict choice type.

Constructors

Left !a 
Right !b 
Instances
Bifunctor Either 
Instance details

Defined in Data.Strict.Either

Methods

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

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

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

Swap Either 
Instance details

Defined in Data.Strict.Either

Methods

swap :: Either a b -> Either b a #

Assoc Either 
Instance details

Defined in Data.Strict.Either

Methods

assoc :: Either (Either a b) c -> Either a (Either b c) #

unassoc :: Either a (Either b c) -> Either (Either a b) c #

Bitraversable Either 
Instance details

Defined in Data.Strict.Either

Methods

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

Bifoldable Either 
Instance details

Defined in Data.Strict.Either

Methods

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

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

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

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

Eq2 Either 
Instance details

Defined in Data.Strict.Either

Methods

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

Ord2 Either 
Instance details

Defined in Data.Strict.Either

Methods

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

Read2 Either 
Instance details

Defined in Data.Strict.Either

Methods

liftReadsPrec2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> Int -> ReadS (Either a b) #

liftReadList2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> ReadS [Either a b] #

liftReadPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec (Either a b) #

liftReadListPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec [Either a b] #

Show2 Either 
Instance details

Defined in Data.Strict.Either

Methods

liftShowsPrec2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> Int -> Either a b -> ShowS #

liftShowList2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> [Either a b] -> ShowS #

NFData2 Either 
Instance details

Defined in Data.Strict.Either

Methods

liftRnf2 :: (a -> ()) -> (b -> ()) -> Either a b -> () #

Hashable2 Either 
Instance details

Defined in Data.Strict.Either

Methods

liftHashWithSalt2 :: (Int -> a -> Int) -> (Int -> b -> Int) -> Int -> Either a b -> Int #

Functor (Either a) 
Instance details

Defined in Data.Strict.Either

Methods

fmap :: (a0 -> b) -> Either a a0 -> Either a b #

(<$) :: a0 -> Either a b -> Either a a0 #

Foldable (Either e) 
Instance details

Defined in Data.Strict.Either

Methods

fold :: Monoid m => Either e m -> m #

foldMap :: Monoid m => (a -> m) -> Either e a -> m #

foldr :: (a -> b -> b) -> b -> Either e a -> b #

foldr' :: (a -> b -> b) -> b -> Either e a -> b #

foldl :: (b -> a -> b) -> b -> Either e a -> b #

foldl' :: (b -> a -> b) -> b -> Either e a -> b #

foldr1 :: (a -> a -> a) -> Either e a -> a #

foldl1 :: (a -> a -> a) -> Either e a -> a #

toList :: Either e a -> [a] #

null :: Either e a -> Bool #

length :: Either e a -> Int #

elem :: Eq a => a -> Either e a -> Bool #

maximum :: Ord a => Either e a -> a #

minimum :: Ord a => Either e a -> a #

sum :: Num a => Either e a -> a #

product :: Num a => Either e a -> a #

Traversable (Either e) 
Instance details

Defined in Data.Strict.Either

Methods

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

sequenceA :: Applicative f => Either e (f a) -> f (Either e a) #

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

sequence :: Monad m => Either e (m a) -> m (Either e a) #

Eq a => Eq1 (Either a) 
Instance details

Defined in Data.Strict.Either

Methods

liftEq :: (a0 -> b -> Bool) -> Either a a0 -> Either a b -> Bool #

Ord a => Ord1 (Either a) 
Instance details

Defined in Data.Strict.Either

Methods

liftCompare :: (a0 -> b -> Ordering) -> Either a a0 -> Either a b -> Ordering #

Read a => Read1 (Either a) 
Instance details

Defined in Data.Strict.Either

Methods

liftReadsPrec :: (Int -> ReadS a0) -> ReadS [a0] -> Int -> ReadS (Either a a0) #

liftReadList :: (Int -> ReadS a0) -> ReadS [a0] -> ReadS [Either a a0] #

liftReadPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec (Either a a0) #

liftReadListPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec [Either a a0] #

Show a => Show1 (Either a) 
Instance details

Defined in Data.Strict.Either

Methods

liftShowsPrec :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> Int -> Either a a0 -> ShowS #

liftShowList :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> [Either a a0] -> ShowS #

NFData a => NFData1 (Either a) 
Instance details

Defined in Data.Strict.Either

Methods

liftRnf :: (a0 -> ()) -> Either a a0 -> () #

Hashable a => Hashable1 (Either a) 
Instance details

Defined in Data.Strict.Either

Methods

liftHashWithSalt :: (Int -> a0 -> Int) -> Int -> Either a a0 -> Int #

Generic1 (Either a :: Type -> Type) 
Instance details

Defined in Data.Strict.Either

Associated Types

type Rep1 (Either a) :: k -> Type #

Methods

from1 :: Either a a0 -> Rep1 (Either a) a0 #

to1 :: Rep1 (Either a) a0 -> Either a a0 #

(Eq a, Eq b) => Eq (Either a b) 
Instance details

Defined in Data.Strict.Either

Methods

(==) :: Either a b -> Either a b -> Bool #

(/=) :: Either a b -> Either a b -> Bool #

(Data a, Data b) => Data (Either a b) 
Instance details

Defined in Data.Strict.Either

Methods

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

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

toConstr :: Either a b -> Constr #

dataTypeOf :: Either a b -> DataType #

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

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

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

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

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

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

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

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

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

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

(Ord a, Ord b) => Ord (Either a b) 
Instance details

Defined in Data.Strict.Either

Methods

compare :: Either a b -> Either a b -> Ordering #

(<) :: Either a b -> Either a b -> Bool #

(<=) :: Either a b -> Either a b -> Bool #

(>) :: Either a b -> Either a b -> Bool #

(>=) :: Either a b -> Either a b -> Bool #

max :: Either a b -> Either a b -> Either a b #

min :: Either a b -> Either a b -> Either a b #

(Read a, Read b) => Read (Either a b) 
Instance details

Defined in Data.Strict.Either

(Show a, Show b) => Show (Either a b) 
Instance details

Defined in Data.Strict.Either

Methods

showsPrec :: Int -> Either a b -> ShowS #

show :: Either a b -> String #

showList :: [Either a b] -> ShowS #

Generic (Either a b) 
Instance details

Defined in Data.Strict.Either

Associated Types

type Rep (Either a b) :: Type -> Type #

Methods

from :: Either a b -> Rep (Either a b) x #

to :: Rep (Either a b) x -> Either a b #

Semigroup (Either a b) 
Instance details

Defined in Data.Strict.Either

Methods

(<>) :: Either a b -> Either a b -> Either a b #

sconcat :: NonEmpty (Either a b) -> Either a b #

stimes :: Integral b0 => b0 -> Either a b -> Either a b #

(Hashable a, Hashable b) => Hashable (Either a b) 
Instance details

Defined in Data.Strict.Either

Methods

hashWithSalt :: Int -> Either a b -> Int #

hash :: Either a b -> Int #

(Binary a, Binary b) => Binary (Either a b) 
Instance details

Defined in Data.Strict.Either

Methods

put :: Either a b -> Put #

get :: Get (Either a b) #

putList :: [Either a b] -> Put #

(NFData a, NFData b) => NFData (Either a b) 
Instance details

Defined in Data.Strict.Either

Methods

rnf :: Either a b -> () #

type Rep1 (Either a :: Type -> Type) 
Instance details

Defined in Data.Strict.Either

type Rep1 (Either a :: Type -> Type) = D1 (MetaData "Either" "Data.Strict.Either" "strict-0.4-DcORXBfkCIx3v5lLd1UYRe" False) (C1 (MetaCons "Left" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 a)) :+: C1 (MetaCons "Right" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) Par1))
type Rep (Either a b) 
Instance details

Defined in Data.Strict.Either

type Rep (Either a b) = D1 (MetaData "Either" "Data.Strict.Either" "strict-0.4-DcORXBfkCIx3v5lLd1UYRe" False) (C1 (MetaCons "Left" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 a)) :+: C1 (MetaCons "Right" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 b)))

isRight :: Either a b -> Bool #

Yields True iff the argument is of the form Right _.

isLeft :: Either a b -> Bool #

Yields True iff the argument is of the form Left _.

either :: (a -> c) -> (b -> c) -> Either a b -> c #

Case analysis: if the value is Left a, apply the first function to a; if it is Right b, apply the second function to b.

lefts :: [Either a b] -> [a] #

Analogous to lefts in Data.Either.

rights :: [Either a b] -> [b] #

Analogous to rights in Data.Either.

partitionEithers :: [Either a b] -> ([a], [b]) #

Analogous to partitionEithers in Data.Either.

_Left :: Prism (Either a c) (Either b c) a b #

Analogous to _Left in Control.Lens.Prism.

_Right :: Prism (Either c a) (Either c b) a b #

Analogous to _Right in Control.Lens.Prism.