| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Control.Monad.Fail
- newtype FailT e m a = FailT {}
- runFailC :: FailT e m a -> Compose m (Fail e) a
- runFailI :: FailT e Identity a -> Fail e a
- mapFailTBase :: (forall x. m x -> n x) -> FailT e m a -> FailT e n a
- mapFailTFail :: Functor m => (e -> e') -> FailT e m a -> FailT e' m a
- mfail :: (Applicative f, Applicative m) => e -> FailT (f e) m a
- mwarn :: (Applicative f, Applicative m) => e -> FailT (f e) m ()
Intro
Failing monad transformer, which behaves in general like
EitherT but it also supports warnings. In short, it behaves like
combination of EitherT and WriterT transformers and built on
Fail applicative functor.
>>>runFailT $ do {a <- return 10; b <- return 20; return (a, b)}Success (10,20)
>>>runFailT $ (,) <$> pure 10 <*> pure 20Success (10,20)
>>>fmap runDLFail $ runFailT $ do {a <- mfail 10 ; b <- mfail 20; return (a, b)}([10],Nothing)
>>>fmap runDLFail $ runFailT $ (,) <$> mfail 10 <*> mfail 20([10],Nothing)
Note, that Applicative instance behaves just like Monad: it fails
immediately. FailT also supports warning like Fail does:
>>>fmap runDLFail $ runFailT $ do {a <- mwarn 10 *> return 15; b <- return 20; return (a, b)}([10],Just (15,20))
>>>fmap runDLFail $ runFailT $ (,) <$> (mwarn 10 *> return 15) <*> return 20([10],Just (15,20))
You can also combine FailT with Fail using Compose like that:
>>>let check10 = do {liftBase $ print "checking 10"; return 10}>>>let check20 = do {liftBase $ print "checking 20"; mwarn "oups"; return 20}>>>fmap runDLFail $ getCompose $ (,) <$> runFailC check10 <*> runFailC check20"checking 10" "checking 20" (["oups"],Just (10,20))
Note how Compose functor is used here.
>>>let fail10 = do {liftBase $ print "failing 10"; mfail "10 is failed"}>>>fmap runDLFail $ getCompose $ (,) <$> runFailC fail10 <*> runFailC check20"failing 10" "checking 20" (["10 is failed","oups"],Nothing)
Note how second checker was runned even after first checker failed
(got "oups" message). This is because internal (monadic) checkers
unrolled back to IO (Fail e a) and wrapped to Compose so infered
type of runFailC fail10 is Compose IO (Fail (DList String)) a
Example from Control.Applicative.Fail can be also rewritten more convenient:
>>>:{data Animal = Animal { species :: String , weight :: Double , age :: Int } deriving (Show) :}
>>>let spc = "Parastratiosphecomyia stratiosphecomyioides">>>let w = 100>>>let a = 27234>>>:{let animal :: Fail [String] Animal animal = Animal <$> (runFailI $ do when (length spc > 20) $ mwarn "Name is too long" when (spc == "") $ mfail "Name can not be empty" return spc) <*> (runFailI $ do when (w < 0) $ mfail "Weight can not be negative" return w) <*> (runFailI $ do when (a < 0) $ mfail "Age can not be negative" return a) :}
>>>animalFail ["Name is too long"] (Just (Animal {species = "Parastratiosphecomyia stratiosphecomyioides", weight = 100.0, age = 27234}))
Monadic interface is much more comfortable here
Failing monad
Instances
| (Monad m, Monoid e) => MonadError e (FailT e m) | |
| (MonadReader r m, Monoid e) => MonadReader r (FailT e m) | |
| (MonadState s m, Monoid e) => MonadState s (FailT e m) | |
| (MonadWriter w m, Monoid e) => MonadWriter w (FailT e m) | |
| (Monoid e, MonadBase b m) => MonadBase b (FailT e m) | |
| MonadTrans (FailT e) | |
| (Monoid e, Monad m) => Monad (FailT e m) | |
| Functor m => Functor (FailT e m) | |
| (Monoid e, Functor m, Monad m) => Applicative (FailT e m) | NOTE: This instance behaves not like |
| Foldable m => Foldable (FailT e m) | |
| Traversable m => Traversable (FailT e m) | |
| Typeable (* -> (* -> *) -> * -> *) FailT | |
| Eq (m (Fail e a)) => Eq (FailT e m a) | |
| Ord (m (Fail e a)) => Ord (FailT e m a) | |
| Show (m (Fail e a)) => Show (FailT e m a) | |
| Generic (FailT e m a) | |
| (Applicative m, Monoid a, Monoid e) => Monoid (FailT e m a) | |
| type Rep (FailT e m a) |
mapFailTBase :: (forall x. m x -> n x) -> FailT e m a -> FailT e n a Source
mapFailTFail :: Functor m => (e -> e') -> FailT e m a -> FailT e' m a Source
Helper functions
mfail :: (Applicative f, Applicative m) => e -> FailT (f e) m a Source
mwarn :: (Applicative f, Applicative m) => e -> FailT (f e) m () Source