Copyright | (c) Edward Kmett 2018 |
---|---|
License | BSD3 |
Maintainer | ekmett@gmail.com |
Stability | stable |
Portability | portable |
Safe Haskell | Safe |
Language | Haskell2010 |
Synopsis
- data Perhaps a
- believe :: Perhaps a -> a
- mayhap :: Perhaps a -> Maybe a
- newtype PerhapsT m a = PerhapsT {
- runPerhapsT :: m (Perhaps a)
- class MonadPlus m => MonadPerhaps m where
- mapPerhapsT :: (m (Perhaps a) -> n (Perhaps b)) -> PerhapsT m a -> PerhapsT n b
- liftCallCC :: CallCC m (Perhaps a) (Perhaps b) -> CallCC (PerhapsT m) a b
- liftCatch :: Catch e m (Perhaps a) -> Catch e (PerhapsT m) a
- liftListen :: Monad m => Listen w m (Perhaps a) -> Listen w (PerhapsT m) a
- liftPass :: Monad m => Pass w m (Perhaps a) -> Pass w (PerhapsT m) a
Maybe with an undisclosed error
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` ()
()
Instances
believe :: Perhaps a -> a Source #
This partial function can be used like fromJust
, but throws the user
error.
Transformer
PerhapsT | |
|
Instances
MonadTrans PerhapsT Source # | |
MonadWriter w m => MonadWriter w (PerhapsT m) Source # | |
MonadState s m => MonadState s (PerhapsT m) Source # | |
MonadReader r m => MonadReader r (PerhapsT m) Source # | |
Monad m => Monad (PerhapsT m) Source # | |
Functor m => Functor (PerhapsT m) Source # | |
MonadFix m => MonadFix (PerhapsT m) Source # | |
Monad m => MonadFail (PerhapsT m) Source # | |
Monad m => Applicative (PerhapsT m) Source # | |
Foldable m => Foldable (PerhapsT m) Source # | |
fold :: Monoid m0 => PerhapsT m m0 -> m0 # foldMap :: Monoid m0 => (a -> m0) -> PerhapsT m a -> m0 # foldr :: (a -> b -> b) -> b -> PerhapsT m a -> b # foldr' :: (a -> b -> b) -> b -> PerhapsT m a -> b # foldl :: (b -> a -> b) -> b -> PerhapsT m a -> b # foldl' :: (b -> a -> b) -> b -> PerhapsT m a -> b # foldr1 :: (a -> a -> a) -> PerhapsT m a -> a # foldl1 :: (a -> a -> a) -> PerhapsT m a -> a # toList :: PerhapsT m a -> [a] # null :: PerhapsT m a -> Bool # length :: PerhapsT m a -> Int # elem :: Eq a => a -> PerhapsT m a -> Bool # maximum :: Ord a => PerhapsT m a -> a # minimum :: Ord a => PerhapsT m a -> a # | |
Traversable m => Traversable (PerhapsT m) Source # | |
MonadZip m => MonadZip (PerhapsT m) Source # | |
MonadIO m => MonadIO (PerhapsT m) Source # | |
Monad m => Alternative (PerhapsT m) Source # | |
Monad m => MonadPlus (PerhapsT m) Source # | |
MonadCont m => MonadCont (PerhapsT m) Source # | |
Monad m => MonadPerhaps (PerhapsT m) Source # | |
Functor m => Generic1 (PerhapsT m :: * -> *) Source # | |
Eq (m (Perhaps a)) => Eq (PerhapsT m a) Source # | |
(Data (m (Perhaps a)), Typeable m, Typeable a) => Data (PerhapsT m a) Source # | |
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PerhapsT m a -> c (PerhapsT m a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (PerhapsT m a) # toConstr :: PerhapsT m a -> Constr # dataTypeOf :: PerhapsT m a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (PerhapsT m a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (PerhapsT m a)) # gmapT :: (forall b. Data b => b -> b) -> PerhapsT m a -> PerhapsT m a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PerhapsT m a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PerhapsT m a -> r # gmapQ :: (forall d. Data d => d -> u) -> PerhapsT m a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> PerhapsT m a -> u # gmapM :: Monad m0 => (forall d. Data d => d -> m0 d) -> PerhapsT m a -> m0 (PerhapsT m a) # gmapMp :: MonadPlus m0 => (forall d. Data d => d -> m0 d) -> PerhapsT m a -> m0 (PerhapsT m a) # gmapMo :: MonadPlus m0 => (forall d. Data d => d -> m0 d) -> PerhapsT m a -> m0 (PerhapsT m a) # | |
Ord (m (Perhaps a)) => Ord (PerhapsT m a) Source # | |
Read (m (Perhaps a)) => Read (PerhapsT m a) Source # | |
Show (m (Perhaps a)) => Show (PerhapsT m a) Source # | |
Generic (PerhapsT m a) Source # | |
type Rep1 (PerhapsT m :: * -> *) Source # | |
type Rep (PerhapsT m a) Source # | |
Class
class MonadPlus m => MonadPerhaps m where Source #
perhaps :: Perhaps a -> m a Source #
This is a monad homomorphism
perhaps :: (m ~ t n, MonadTrans t, MonadPerhaps n) => Perhaps a -> m a Source #
This is a monad homomorphism
excuse :: Exception e => e -> m a Source #
Fail with an exception as an excuse instead of just a string.
Instances
MonadPerhaps Perhaps Source # | |
Monad m => MonadPerhaps (PerhapsT m) Source # | |
MonadPerhaps m => MonadPerhaps (IdentityT m) Source # | |
MonadPerhaps m => MonadPerhaps (StateT s m) Source # | |
MonadPerhaps m => MonadPerhaps (StateT s m) Source # | |
(MonadPerhaps m, Monoid w) => MonadPerhaps (WriterT w m) Source # | |
(MonadPerhaps m, Monoid w) => MonadPerhaps (WriterT w m) Source # | |
MonadPerhaps m => MonadPerhaps (ReaderT r m) Source # | |
(MonadPerhaps m, Monoid w) => MonadPerhaps (RWST r w s m) Source # | |
(MonadPerhaps m, Monoid w) => MonadPerhaps (RWST r w s m) Source # | |
Combinators
mapPerhapsT :: (m (Perhaps a) -> n (Perhaps b)) -> PerhapsT m a -> PerhapsT n b Source #
Transform the computation inside a PerhapsT
.
runPerhapsT
(mapPerhapsT
f m) = f (runPerhapsT
m)
liftCallCC :: CallCC m (Perhaps a) (Perhaps b) -> CallCC (PerhapsT m) a b Source #
Lift a callCC
operation to the new monad.
liftCatch :: Catch e m (Perhaps a) -> Catch e (PerhapsT m) a Source #
Lift a catchE
operation to the new monad.