| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Data.Maybe.Unpacked
Description
This module is intended to be a drop-in replacement
for base's Maybe. To shave off pointer chasing, it
uses '-XUnboxedSums' to represent the type
as two machine words that are contiguous in memory, without
loss of expressiveness that base's MaybeMaybe provides.
This library provides pattern synonyms and Just
that allow users to pattern match on an unpacked Maybe
in a familiar way.Nothing
Functions are also provided for converting an unpacked Maybe to the base library's Maybe, and vice versa.
This library is in alpha, and the internals are likely to change.
- data Maybe a where
- nothing :: Maybe a
- just :: a -> Maybe a
- maybe :: b -> (a -> b) -> Maybe a -> b
- isJust :: Maybe a -> Bool
- isNothing :: Maybe a -> Bool
- fromJust :: 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]
- fromBaseMaybe :: Maybe a -> Maybe a
- toBaseMaybe :: Maybe a -> Maybe a
Documentation
The Maybe type encapsulates an optional value. A value of type
either contains a value of type Maybe aa (represented as ),
or it is empty (represented as Just a). Using NothingMaybe 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 . A richer
error monad can be built using the NothingEither type.
Constructors
| Maybe (#(##) | a#) |
Bundled Patterns
| pattern Just :: a -> Maybe a | The |
| pattern Nothing :: Maybe a | The |
Instances
| Monad Maybe Source # | |
| Functor Maybe Source # | |
| MonadFix Maybe Source # | |
| MonadFail Maybe Source # | |
| Applicative Maybe Source # | |
| Foldable Maybe Source # | |
| Traversable Maybe Source # | |
| Eq1 Maybe Source # | |
| Ord1 Maybe Source # | |
| Read1 Maybe Source # | |
| Show1 Maybe Source # | |
| MonadZip Maybe Source # | |
| Alternative Maybe Source # | |
| MonadPlus Maybe Source # | |
| Eq a => Eq (Maybe a) Source # | |
| Data a => Data (Maybe a) Source # | |
| Ord a => Ord (Maybe a) Source # | |
| Read a => Read (Maybe a) Source # | |
| Show a => Show (Maybe a) Source # | |
| Semigroup a => Semigroup (Maybe a) Source # | |
| Semigroup a => Monoid (Maybe a) Source # | |
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:
>>>maybe 0 (*2) (fromBaseMaybe $ readMaybe "5")10>>>maybe 0 (*2) (fromBaseMaybe $ readMaybe "")0
Apply show to a Maybe Int. If we have , we want to show
the underlying just nInt n. But if we have nothing, we return the
empty string instead of (for example) "Nothing":
>>>maybe "" show (just 5)"5">>>maybe "" show nothing""
fromMaybe :: a -> Maybe a -> a Source #
The fromMaybe function takes a default value and and Maybe
value. If the Maybe is nothing, it returns the default values;
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 )>>>let parse = fromBaseMaybe . readMaybe :: String -> Maybe Int>>>fromMaybe 0 (parse "5")5>>>fromMaybe 0 (parse "")0
listToMaybe :: [a] -> Maybe a Source #
The listToMaybe function returns Nothing on an empty list
or where 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 not given nothing.
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 )>>>let parse = fromBaseMaybe . readMaybe :: String -> Maybe Int>>>sum $ maybeToList (parse "3")3>>>sum $ maybeToList (parse "")0
This being said Maybe is an instance of the Foldable typeclass
so the example above could also be written as:
>>>import Text.Read ( readMaybe )>>>let parse = fromBaseMaybe . readMaybe :: String -> Maybe Int>>>sum $ parse "3"3>>>sum $ parse ""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 )>>>let parse = fromBaseMaybe . readMaybe :: String -> Maybe Int>>>[ parse x | x <- ["1", "Foo", "3"] ][Just 1,Nothing,Just 3]>>>catMaybes $ [ parse x | 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 . If this is Maybe bNothing, no element
is added on to the result list. If it is , then Just bb is
included in the result list.
Examples
Using is a shortcut for mapMaybe f x
in most cases:catMaybes $ map f x
>>>import Text.Read ( readMaybe )>>>let parse = fromBaseMaybe . readMaybe :: String -> Maybe Int>>>mapMaybe parse ["1", "Foo", "3"][1,3]>>>catMaybes $ map parse ["1", "Foo", "3"][1,3]
If we map the just function, the entire list should be returned:
>>>mapMaybe just [1,2,3][1,2,3]
fromBaseMaybe :: Maybe a -> Maybe a Source #
The fromBaseMaybe function converts base's Maybe to a
Maybe. This function is good for using existing
functions that return Maybe maybes.
Examples
Basic usage:
>>>import Text.Read ( readMaybe )>>>let parse = fromBaseMaybe . readMaybe :: String -> Maybe Int>>>parse "3"Just 3>>>parse ""Nothing
toBaseMaybe :: Maybe a -> Maybe a Source #
The toBaseMaybe function converts a Maybe value to a
value of base's Maybe type.
This function is provided for testing and convenience
but it is not an idiomatic use of this library. It ruins the speed and space gains from
unpacking the Maybe. I implore you to destruct the Maybe with maybe instead.
Examples
Basic usage:
>>>import Data.List (unfoldr)>>>let ana n = if n == 5 then nothing else just (n+1,n+1)>>>unfoldr (toBaseMaybe . ana) 0[1,2,3,4,5]