perhaps-0: Perhaps, a monad

Copyright(c) Edward Kmett 2018
LicenseBSD3
Maintainerekmett@gmail.com
Stabilitystable
Portabilityportable
Safe HaskellSafe
LanguageHaskell2010

Data.Perhaps

Contents

Description

 
Synopsis

Maybe with an undisclosed error

data Perhaps a Source #

This monad occupies the middle ground between Maybe and Either in that you can get out an informative error but aren't able to care about its contents, except via bottoms.

Since bottoms are indistinguishable in pure code, one can view this as morally the same as Maybe, except when things go wrong, you can pass along a complaint, rather than take what you'd get from fromJust.

>>> import Control.Exception
>>> let x = excuse Overflow :: Perhaps ()

Attempting to Show a Perhaps value is hazardous, as it will contain an embedded exception.

>>> x
Can't *** Exception: arithmetic overflow

Recovery is possible as Can't isn't strict in its argument.

>>> x <|> Can ()
Can ()
>>> x `seq` ()
()

Constructors

Can a 
Can't Void 
Instances
Monad Perhaps Source # 
Instance details

Methods

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

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

return :: a -> Perhaps a #

fail :: String -> Perhaps a #

Functor Perhaps Source # 
Instance details

Methods

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

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

MonadFix Perhaps Source # 
Instance details

Methods

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

MonadFail Perhaps Source # 
Instance details

Methods

fail :: String -> Perhaps a #

Applicative Perhaps Source # 
Instance details

Methods

pure :: a -> Perhaps a #

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

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

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

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

Foldable Perhaps Source # 
Instance details

Methods

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

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

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

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

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

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

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

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

toList :: Perhaps a -> [a] #

null :: Perhaps a -> Bool #

length :: Perhaps a -> Int #

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

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

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

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

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

Traversable Perhaps Source # 
Instance details

Methods

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

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

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

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

MonadZip Perhaps Source # 
Instance details

Methods

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

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

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

Alternative Perhaps Source # 
Instance details

Methods

empty :: Perhaps a #

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

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

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

MonadPlus Perhaps Source # 
Instance details

Methods

mzero :: Perhaps a #

mplus :: Perhaps a -> Perhaps a -> Perhaps a #

MonadPerhaps Perhaps Source # 
Instance details

Methods

perhaps :: Perhaps a -> Perhaps a Source #

excuse :: Exception e => e -> Perhaps a Source #

Eq a => Eq (Perhaps a) Source # 
Instance details

Methods

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

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

Data a => Data (Perhaps a) Source # 
Instance details

Methods

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

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

toConstr :: Perhaps a -> Constr #

dataTypeOf :: Perhaps a -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord a => Ord (Perhaps a) Source # 
Instance details

Methods

compare :: Perhaps a -> Perhaps a -> Ordering #

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

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

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

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

max :: Perhaps a -> Perhaps a -> Perhaps a #

min :: Perhaps a -> Perhaps a -> Perhaps a #

Read a => Read (Perhaps a) Source # 
Instance details
Show a => Show (Perhaps a) Source # 
Instance details

Methods

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

show :: Perhaps a -> String #

showList :: [Perhaps a] -> ShowS #

Generic (Perhaps a) Source # 
Instance details

Associated Types

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

Methods

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

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

Semigroup a => Semigroup (Perhaps a) Source # 
Instance details

Methods

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

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

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

Semigroup a => Monoid (Perhaps a) Source # 
Instance details

Methods

mempty :: Perhaps a #

mappend :: Perhaps a -> Perhaps a -> Perhaps a #

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

Generic1 Perhaps Source # 
Instance details

Associated Types

type Rep1 Perhaps :: k -> * #

Methods

from1 :: Perhaps a -> Rep1 Perhaps a #

to1 :: Rep1 Perhaps a -> Perhaps a #

type Rep (Perhaps a) Source # 
Instance details
type Rep1 Perhaps Source # 
Instance details

believe :: Perhaps a -> a Source #

This partial function can be used like fromJust, but throws the user error.

excuse :: (MonadPerhaps m, Exception e) => e -> m a Source #

Fail with an exception as an excuse instead of just a string.