| Copyright | (c) The University of Glasgow 2001 | 
|---|---|
| License | BSD-style (see the file libraries/base/LICENSE) | 
| Maintainer | libraries@haskell.org | 
| Stability | stable | 
| Portability | portable | 
| Safe Haskell | Trustworthy | 
| Language | Haskell2010 | 
Data.Maybe
Description
The Maybe type, and associated operations.
Synopsis
- data Maybe a
- maybe :: b -> (a -> b) -> Maybe a -> b
- isJust :: Maybe a -> Bool
- isNothing :: Maybe a -> Bool
- fromJust :: HasCallStack => Maybe a -> a
- fromMaybe :: a -> Maybe a -> a
- listToMaybe :: [a] -> Maybe a
- maybeToList :: Maybe a -> [a]
- catMaybes :: [Maybe a] -> [a]
- mapMaybe :: (a -> Maybe b) -> [a] -> [b]
Documentation
The Maybe type encapsulates an optional value.  A value of type
 Maybe aa (represented as Just aNothing).  Using Maybe is a good way to
 deal with errors or exceptional cases without resorting to drastic
 measures such as error.
The Maybe type is also a monad.  It is a simple kind of error
 monad, where all errors are represented by Nothing.  A richer
 error monad can be built using the Either type.
Instances
| MonadFail Maybe Source # | Since: base-4.9.0.0 | ||||
| MonadFix Maybe Source # | Since: base-2.1 | ||||
| MonadZip Maybe Source # | Since: base-4.8.0.0 | ||||
| Foldable Maybe Source # | Since: base-2.1 | ||||
| Defined in Data.Foldable Methods fold :: Monoid m => Maybe m -> m Source # foldMap :: Monoid m => (a -> m) -> Maybe a -> m Source # foldMap' :: Monoid m => (a -> m) -> Maybe a -> m Source # foldr :: (a -> b -> b) -> b -> Maybe a -> b Source # foldr' :: (a -> b -> b) -> b -> Maybe a -> b Source # foldl :: (b -> a -> b) -> b -> Maybe a -> b Source # foldl' :: (b -> a -> b) -> b -> Maybe a -> b Source # foldr1 :: (a -> a -> a) -> Maybe a -> a Source # foldl1 :: (a -> a -> a) -> Maybe a -> a Source # toList :: Maybe a -> [a] Source # null :: Maybe a -> Bool Source # length :: Maybe a -> Int Source # elem :: Eq a => a -> Maybe a -> Bool Source # maximum :: Ord a => Maybe a -> a Source # minimum :: Ord a => Maybe a -> a Source # | |||||
| Eq1 Maybe Source # | Since: base-4.9.0.0 | ||||
| Ord1 Maybe Source # | Since: base-4.9.0.0 | ||||
| Defined in Data.Functor.Classes | |||||
| Read1 Maybe Source # | Since: base-4.9.0.0 | ||||
| Defined in Data.Functor.Classes Methods liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Maybe a) Source # liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Maybe a] Source # liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Maybe a) Source # liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Maybe a] Source # | |||||
| Show1 Maybe Source # | Since: base-4.9.0.0 | ||||
| Traversable Maybe Source # | Since: base-2.1 | ||||
| Alternative Maybe Source # | Picks the leftmost  Since: base-2.1 | ||||
| Applicative Maybe Source # | Since: base-2.1 | ||||
| Functor Maybe Source # | Since: base-2.1 | ||||
| Monad Maybe Source # | Since: base-2.1 | ||||
| MonadPlus Maybe Source # | Picks the leftmost  Since: base-2.1 | ||||
| Generic1 Maybe Source # | |||||
| Defined in GHC.Generics | |||||
| Data a => Data (Maybe a) Source # | Since: base-4.0.0.0 | ||||
| Defined in Data.Data Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Maybe a -> c (Maybe a) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Maybe a) Source # toConstr :: Maybe a -> Constr Source # dataTypeOf :: Maybe a -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Maybe a)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Maybe a)) Source # gmapT :: (forall b. Data b => b -> b) -> Maybe a -> Maybe a Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Maybe a -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Maybe a -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Maybe a -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Maybe a -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Maybe a -> m (Maybe a) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Maybe a -> m (Maybe a) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Maybe a -> m (Maybe a) Source # | |||||
| Semigroup a => Monoid (Maybe a) Source # | Lift a semigroup into  Since 4.11.0: constraint on inner  Since: base-2.1 | ||||
| Semigroup a => Semigroup (Maybe a) Source # | Since: base-4.9.0.0 | ||||
| Generic (Maybe a) Source # | |||||
| Defined in GHC.Generics Associated Types 
 | |||||
| Read a => Read (Maybe a) Source # | Since: base-2.1 | ||||
| Show a => Show (Maybe a) Source # | Since: base-2.1 | ||||
| Eq a => Eq (Maybe a) Source # | Since: base-2.1 | ||||
| Ord a => Ord (Maybe a) Source # | Since: base-2.1 | ||||
| type Rep1 Maybe Source # | Since: base-4.6.0.0 | ||||
| type Rep (Maybe a) Source # | Since: base-4.6.0.0 | ||||
| Defined in GHC.Generics | |||||
maybe :: b -> (a -> b) -> Maybe a -> b Source #
The maybe function takes a default value, a function, and a Maybe
 value.  If the Maybe value is Nothing, the function returns the
 default value.  Otherwise, it applies the function to the value inside
 the Just and returns the result.
Examples
Basic usage:
>>>maybe False odd (Just 3)True
>>>maybe False odd NothingFalse
Read an integer from a string using readMaybe. If we succeed,
 return twice the integer; that is, apply (*2) to it. If instead
 we fail to parse an integer, return 0 by default:
>>>import Text.Read ( readMaybe )>>>maybe 0 (*2) (readMaybe "5")10>>>maybe 0 (*2) (readMaybe "")0
Apply show to a Maybe Int. If we have Just n, we want to show
 the underlying Int n. But if we have Nothing, we return the
 empty string instead of (for example) "Nothing":
>>>maybe "" show (Just 5)"5">>>maybe "" show Nothing""
fromJust :: HasCallStack => Maybe a -> a Source #
The fromJust function extracts the element out of a Just and
 throws an error if its argument is Nothing.
Examples
Basic usage:
>>>fromJust (Just 1)1
>>>2 * (fromJust (Just 10))20
>>>2 * (fromJust Nothing)*** Exception: Maybe.fromJust: Nothing ...
WARNING: This function is partial. You can use case-matching instead.
fromMaybe :: a -> Maybe a -> a Source #
The fromMaybe function takes a default value and a Maybe
 value.  If the Maybe is Nothing, it returns the default value;
 otherwise, it returns the value contained in the Maybe.
Examples
Basic usage:
>>>fromMaybe "" (Just "Hello, World!")"Hello, World!"
>>>fromMaybe "" Nothing""
Read an integer from a string using readMaybe. If we fail to
 parse an integer, we want to return 0 by default:
>>>import Text.Read ( readMaybe )>>>fromMaybe 0 (readMaybe "5")5>>>fromMaybe 0 (readMaybe "")0
listToMaybe :: [a] -> Maybe a Source #
The listToMaybe function returns Nothing on an empty list
 or Just aa is the first element of the list.
Examples
Basic usage:
>>>listToMaybe []Nothing
>>>listToMaybe [9]Just 9
>>>listToMaybe [1,2,3]Just 1
Composing maybeToList with listToMaybe should be the identity
 on singleton/empty lists:
>>>maybeToList $ listToMaybe [5][5]>>>maybeToList $ listToMaybe [][]
But not on lists with more than one element:
>>>maybeToList $ listToMaybe [1,2,3][1]
maybeToList :: Maybe a -> [a] Source #
The maybeToList function returns an empty list when given
 Nothing or a singleton list when given Just.
Examples
Basic usage:
>>>maybeToList (Just 7)[7]
>>>maybeToList Nothing[]
One can use maybeToList to avoid pattern matching when combined
 with a function that (safely) works on lists:
>>>import Text.Read ( readMaybe )>>>sum $ maybeToList (readMaybe "3")3>>>sum $ maybeToList (readMaybe "")0
catMaybes :: [Maybe a] -> [a] Source #
The catMaybes function takes a list of Maybes and returns
 a list of all the Just values.
Examples
Basic usage:
>>>catMaybes [Just 1, Nothing, Just 3][1,3]
When constructing a list of Maybe values, catMaybes can be used
 to return all of the "success" results (if the list is the result
 of a map, then mapMaybe would be more appropriate):
>>>import Text.Read ( readMaybe )>>>[readMaybe x :: Maybe Int | x <- ["1", "Foo", "3"] ][Just 1,Nothing,Just 3]>>>catMaybes $ [readMaybe x :: Maybe Int | x <- ["1", "Foo", "3"] ][1,3]
mapMaybe :: (a -> Maybe b) -> [a] -> [b] Source #
The mapMaybe function is a version of map which can throw
 out elements.  In particular, the functional argument returns
 something of type Maybe bNothing, no element
 is added on to the result list.  If it is Just bb is
 included in the result list.
Examples
Using mapMaybe f xcatMaybes $ map f x
>>>import Text.Read ( readMaybe )>>>let readMaybeInt = readMaybe :: String -> Maybe Int>>>mapMaybe readMaybeInt ["1", "Foo", "3"][1,3]>>>catMaybes $ map readMaybeInt ["1", "Foo", "3"][1,3]
If we map the Just constructor, the entire list should be returned:
>>>mapMaybe Just [1,2,3][1,2,3]