strict-base-types-0.6.1: 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
LanguageHaskell98

Data.Either.Strict

Contents

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

Functor (Either a) 

Methods

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

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

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

Methods

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

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

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

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

Methods

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

show :: Either a b -> String #

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

type Rep (Either a b) # 
type Rep (Either a b) = D1 * (MetaData "Either" "Data.Strict.Either" "strict-0.3.2-1XGU2LPrqRE7Qw1PnSNhY5" 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))))

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] 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.

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

Analogous to _Left in Control.Lens.Prism.

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

Analogous to _Right in Control.Lens.Prism.

Orphan instances

Bitraversable Either Source # 

Methods

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

Bifoldable Either Source # 

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 #

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 #

Swapped Either Source # 

Methods

swapped :: (Profunctor p, Functor f) => p (Either b a) (f (Either d c)) -> p (Either a b) (f (Either c d)) #

Foldable (Either e) Source # 

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) Source # 

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) #

(Data a, Data b) => 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) #

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 #

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

Methods

arbitrary :: Gen (Either a b) #

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

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

Methods

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

hash :: Either a b -> Int #

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

Methods

toJSON :: Either a b -> Value #

toEncoding :: Either a b -> Encoding #

toJSONList :: [Either a b] -> Value #

toEncodingList :: [Either a b] -> Encoding #

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

Methods

parseJSON :: Value -> Parser (Either a b) #

parseJSONList :: Value -> Parser [Either a b] #

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

Methods

put :: Either a b -> Put #

get :: Get (Either a b) #

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

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

Methods

rnf :: Either a b -> () #

Strict (Either a b) (Either a b) Source # 

Methods

strict :: Iso' (Either a b) (Either a b) #