unpacked-maybe-0.1.0.0: An unpacked maybe data type

Safe HaskellNone
LanguageHaskell2010

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 Maybe type as two machine words that are contiguous in memory, without loss of expressiveness that base's Maybe provides.

This library provides pattern synonyms Just and Nothing that allow users to pattern match on an unpacked Maybe in a familiar way.

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.

Synopsis

Documentation

data Maybe a Source #

The Maybe type encapsulates an optional value. A value of type Maybe a either contains a value of type a (represented as Just a), or it is empty (represented as Nothing). 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.

Constructors

Maybe (#(##) | a#) 

Bundled Patterns

pattern Just :: a -> Maybe a

The Just pattern synonym mimics the functionality of the Just constructor from Data.Maybe.

pattern Nothing :: Maybe a

The Nothing pattern synonym mimics the functionality of the Nothing constructor from Data.Maybe.

Instances

Monad Maybe Source # 

Methods

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

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

return :: a -> Maybe a #

fail :: String -> Maybe a #

Functor Maybe Source # 

Methods

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

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

MonadFix Maybe Source # 

Methods

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

MonadFail Maybe Source # 

Methods

fail :: String -> Maybe a #

Applicative Maybe Source # 

Methods

pure :: a -> Maybe a #

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

liftA2 :: (a -> b -> c) -> Maybe a -> Maybe b -> Maybe c #

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

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

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

Eq1 Maybe Source # 

Methods

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

Ord1 Maybe Source # 

Methods

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

Read1 Maybe Source # 

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

Methods

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

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

MonadZip Maybe Source # 

Methods

mzip :: Maybe a -> Maybe b -> Maybe (a, b) #

mzipWith :: (a -> b -> c) -> Maybe a -> Maybe b -> Maybe c #

munzip :: Maybe (a, b) -> (Maybe a, Maybe b) #

Alternative Maybe Source # 

Methods

empty :: Maybe a #

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

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

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

MonadPlus Maybe Source # 

Methods

mzero :: Maybe a #

mplus :: Maybe a -> Maybe a -> Maybe a #

Eq a => Eq (Maybe a) Source # 

Methods

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

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

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

Ord a => Ord (Maybe a) Source # 

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

Methods

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

show :: Maybe a -> String #

showList :: [Maybe a] -> ShowS #

Semigroup a => Semigroup (Maybe a) Source # 

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

Methods

mempty :: Maybe a #

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

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

nothing :: Maybe a Source #

This is the same as Nothing.

just :: a -> Maybe a Source #

This is the same as Just.

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 nothing
False

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 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
""

isJust :: Maybe a -> Bool Source #

The isJust function returns True if its argument is of the form Just _.

Examples

Basic usage:

>>> isJust (just 3)
True
>>> isJust (just ())
True
>>> isJust nothing
False

Only the outer constructor is taken into consideration:

>>> isJust (just nothing)
True

isNothing :: Maybe a -> Bool Source #

The isNothing function returns True if its argument is nothing.

Examples

Basic usage:

>>> isNothing (just 3)
False
>>> isNothing (just ())
False
>>> isNothing nothing
True

Only the outer constructor is taken into consideration:

>>> isNothing (just nothing)
False

fromJust :: 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: Data.Maybe.Unpacked.fromJust: 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 Just a where a 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 Maybe b. If this is Nothing, no element is added on to the result list. If it is Just b, then b is included in the result list.

Examples

Using mapMaybe f x is a shortcut for catMaybes $ map f x in most cases:

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