strict-base-types-0.5.0: 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.Maybe.Strict

Contents

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 

Methods

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

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

Eq a => Eq (Maybe a) 

Methods

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

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

Ord a => Ord (Maybe a) 

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) 
Show a => Show (Maybe a) 

Methods

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

show :: Maybe a -> String #

showList :: [Maybe a] -> ShowS #

type Rep (Maybe a) 
type Rep (Maybe a) = D1 (MetaData "Maybe" "Data.Strict.Maybe" "strict-0.3.2-HHI2FPLqQto28EK1aExOvf" False) ((:+:) (C1 (MetaCons "Nothing" PrefixI False) U1) (C1 (MetaCons "Just" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceLazy DecidedStrict) (Rec0 a))))

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

Analogous to listToMaybe in Data.Maybe.

maybeToList :: Maybe a -> [a] Source #

Analogous to maybeToList in Data.Maybe.

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

Analogous to catMaybes in Data.Maybe.

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

Analogous to mapMaybe in Data.Maybe.

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

Analogous to _Just in Control.Lens.Prism

Orphan instances

Foldable Maybe Source # 

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

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

Data a => Data (Maybe a) Source # 

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)) -> Maybe (c (Maybe a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (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) #

Generic (Maybe a) Source # 

Associated Types

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

Methods

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

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

Monoid a => Monoid (Maybe a) Source # 

Methods

mempty :: Maybe a #

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

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

Arbitrary a => Arbitrary (Maybe a) Source # 

Methods

arbitrary :: Gen (Maybe a) #

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

Hashable a => Hashable (Maybe a) Source # 

Methods

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

hash :: Maybe a -> Int #

ToJSON a => ToJSON (Maybe a) Source # 
FromJSON a => FromJSON (Maybe a) Source # 
Binary a => Binary (Maybe a) Source # 

Methods

put :: Maybe a -> Put #

get :: Get (Maybe a) #

putList :: [Maybe a] -> Put #

NFData a => NFData (Maybe a) Source # 

Methods

rnf :: Maybe a -> () #

Strict (Maybe a) (Maybe a) Source # 

Methods

strict :: Iso' (Maybe a) (Maybe a) #