strict-base-0.4.0.0: Strict versions of base data types.

Copyright(c) 2017 Daniel Mendler 2006-2007 Roman Leshchinskiy
LicenseBSD-style (see the file LICENSE)
MaintainerDaniel Mendler <mail@daniel-mendler.de>
Stabilityexperimental
Portabilityportable
Safe HaskellSafe
LanguageHaskell2010

Data.Strict.Either

Contents

Description

Strict Either.

Same as the standard Haskell Either, but Left _|_ = Right _|_ = _|_

Synopsis

Documentation

data Either a b Source #

The strict choice type.

Constructors

Left !a 
Right !b 

Instances

Bifunctor Either Source # 

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 #

Functor (Either a) Source # 

Methods

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

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

Foldable (Either a) Source # 

Methods

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

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

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

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

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

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

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

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

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

null :: Either a a -> Bool #

length :: Either a a -> Int #

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

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

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

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

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

Traversable (Either a) Source # 

Methods

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

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

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

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

Generic1 (Either a) Source # 

Associated Types

type Rep1 (Either a :: * -> *) :: * -> * #

Methods

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

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

(Eq b, Eq a) => Eq (Either a b) Source # 

Methods

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

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

(Data b, Data a) => Data (Either a b) Source # 

Methods

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

gunfold :: (forall c r. Data c => c (c -> 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 c. Data c => c -> c) -> 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 b, Ord a) => Ord (Either a b) Source # 

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 b, Read a) => Read (Either a b) Source # 
(Show b, Show a) => Show (Either a b) Source # 

Methods

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

show :: Either a b -> String #

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

Generic (Either a b) Source # 

Associated Types

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

Methods

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

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

type Rep1 (Either a) Source # 
type Rep1 (Either a) = D1 (MetaData "Either" "Data.Strict.Either" "strict-base-0.4.0.0-1k3wDu59CS22iu6yIZo2Dn" False) ((:+:) (C1 (MetaCons "Left" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 a))) (C1 (MetaCons "Right" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) Par1)))
type Rep (Either a b) Source # 
type Rep (Either a b) = D1 (MetaData "Either" "Data.Strict.Either" "strict-base-0.4.0.0-1k3wDu59CS22iu6yIZo2Dn" False) ((:+:) (C1 (MetaCons "Left" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 a))) (C1 (MetaCons "Right" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 b))))

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

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.

isLeft :: Either a b -> Bool Source #

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

isRight :: Either a b -> Bool Source #

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

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

Analogous to lefts in Data.Either.

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

Analogous to rights in Data.Either.

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

Analogous to partitionEithers in Data.Either.

Orphan instances

IsStrict (Either a b) (Either a b) Source # 

Methods

fromStrict :: Either a b -> Either a b Source #

toStrict :: Either a b -> Either a b Source #