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.Maybe.Strict

Description

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

Note that in contrast to the standard lazy Maybe type, the strict Maybe type is not an applicative functor, and therefore also not a monad. The problem is the homomorphism law, which states that

pure f <*> pure x = pure (f x)  -- must hold for all f

This law does not hold for the expected applicative functor instance of Maybe, as this instance does not satisfy pure f <*> pure _|_ = pure (f _|_) for f = const.

Synopsis

Documentation

data Maybe a #

The type of strict optional values.

Constructors

Nothing 
Just !a 
Instances
Functor Maybe 
Instance details

Defined in Data.Strict.Maybe

Methods

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

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

Foldable Maybe 
Instance details

Defined in Data.Strict.Maybe

Methods

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

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

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

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

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

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

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

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

toList :: Maybe a -> [a] #

null :: Maybe a -> Bool #

length :: Maybe a -> Int #

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

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

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

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

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

Traversable Maybe 
Instance details

Defined in Data.Strict.Maybe

Methods

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

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

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

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

Eq1 Maybe 
Instance details

Defined in Data.Strict.Maybe

Methods

liftEq :: (a -> b -> Bool) -> Maybe a -> Maybe b -> Bool #

Ord1 Maybe 
Instance details

Defined in Data.Strict.Maybe

Methods

liftCompare :: (a -> b -> Ordering) -> Maybe a -> Maybe b -> Ordering #

Read1 Maybe 
Instance details

Defined in Data.Strict.Maybe

Methods

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

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

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Maybe a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Maybe a] #

Show1 Maybe 
Instance details

Defined in Data.Strict.Maybe

Methods

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

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

NFData1 Maybe 
Instance details

Defined in Data.Strict.Maybe

Methods

liftRnf :: (a -> ()) -> Maybe a -> () #

Hashable1 Maybe 
Instance details

Defined in Data.Strict.Maybe

Methods

liftHashWithSalt :: (Int -> a -> Int) -> Int -> Maybe a -> Int #

Eq a => Eq (Maybe a) 
Instance details

Defined in Data.Strict.Maybe

Methods

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

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

Data a => Data (Maybe a) 
Instance details

Defined in Data.Strict.Maybe

Methods

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

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

toConstr :: Maybe a -> Constr #

dataTypeOf :: Maybe a -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord a => Ord (Maybe a) 
Instance details

Defined in Data.Strict.Maybe

Methods

compare :: Maybe a -> Maybe a -> Ordering #

(<) :: Maybe a -> Maybe a -> Bool #

(<=) :: Maybe a -> Maybe a -> Bool #

(>) :: Maybe a -> Maybe a -> Bool #

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

max :: Maybe a -> Maybe a -> Maybe a #

min :: Maybe a -> Maybe a -> Maybe a #

Read a => Read (Maybe a) 
Instance details

Defined in Data.Strict.Maybe

Show a => Show (Maybe a) 
Instance details

Defined in Data.Strict.Maybe

Methods

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

show :: Maybe a -> String #

showList :: [Maybe a] -> ShowS #

Generic (Maybe a) 
Instance details

Defined in Data.Strict.Maybe

Associated Types

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

Methods

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

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

Semigroup a => Semigroup (Maybe a) 
Instance details

Defined in Data.Strict.Maybe

Methods

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

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

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

Semigroup a => Monoid (Maybe a) 
Instance details

Defined in Data.Strict.Maybe

Methods

mempty :: Maybe a #

mappend :: Maybe a -> Maybe a -> Maybe a #

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

Hashable a => Hashable (Maybe a) 
Instance details

Defined in Data.Strict.Maybe

Methods

hashWithSalt :: Int -> Maybe a -> Int #

hash :: Maybe a -> Int #

Binary a => Binary (Maybe a) 
Instance details

Defined in Data.Strict.Maybe

Methods

put :: Maybe a -> Put #

get :: Get (Maybe a) #

putList :: [Maybe a] -> Put #

NFData a => NFData (Maybe a) 
Instance details

Defined in Data.Strict.Maybe

Methods

rnf :: Maybe a -> () #

Generic1 Maybe 
Instance details

Defined in Data.Strict.Maybe

Associated Types

type Rep1 Maybe :: k -> Type #

Methods

from1 :: Maybe a -> Rep1 Maybe a #

to1 :: Rep1 Maybe a -> Maybe a #

type Rep (Maybe a) 
Instance details

Defined in Data.Strict.Maybe

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

Defined in Data.Strict.Maybe

type Rep1 Maybe = D1 (MetaData "Maybe" "Data.Strict.Maybe" "strict-0.4-DcORXBfkCIx3v5lLd1UYRe" False) (C1 (MetaCons "Nothing" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Just" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) Par1))

maybe :: b -> (a -> b) -> Maybe a -> b #

Given a default value, a function and a Maybe value, yields the default value if the Maybe value is Nothing and applies the function to the value stored in the Just otherwise.

isJust :: Maybe a -> Bool #

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

isNothing :: Maybe a -> Bool #

Yields True iff the argument is Nothing.

fromJust :: Maybe a -> a #

Extracts the element out of a Just and throws an error if the argument is Nothing.

fromMaybe :: a -> Maybe a -> a #

Given a default value and a Maybe, yield the default value if the Maybe argument is Nothing and extract the value out of the Just otherwise.

listToMaybe :: [a] -> Maybe a #

Analogous to listToMaybe in Data.Maybe.

maybeToList :: Maybe a -> [a] #

Analogous to maybeToList in Data.Maybe.

catMaybes :: [Maybe a] -> [a] #

Analogous to catMaybes in Data.Maybe.

mapMaybe :: (a -> Maybe b) -> [a] -> [b] #

Analogous to mapMaybe in Data.Maybe.

_Just :: Prism (Maybe a) (Maybe b) a b #

Analogous to _Just in Control.Lens.Prism