| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Control.Applicative.Fail
Contents
- data Fail e a
- ffail :: e -> Fail [e] a
- fwarn :: e -> a -> Fail [e] a
- fsucc :: a -> Fail e a
- getFail :: Fail e a -> Maybe e
- getSucc :: Fail e a -> Maybe a
- failEither :: Fail e a -> Either e a
- joinFail :: Monoid e => Fail e (Fail e a) -> Fail e a
- bindFail :: Monoid e => Fail e a -> (a -> Fail e b) -> Fail e b
- composeFail :: Monoid e => (a -> Fail e b) -> (b -> Fail e c) -> a -> Fail e c
Documentation
Applicative functor which collects all the fails instead of
immediate returning first fail like Either. It can not be a monad
because of differenct logic in Applicative. Applicative instance of
Fail continue to fold fails even when 'Fail e Nothing' pattern is
met. Monad instance can not behave like that, so Fail have no Monad
instance
Example usage:
>>>(,,) <$> Fail [10] (Just 10) <*> Success 10 <*> Success 20Fail [10] (Just (10,10,20))>>>(,) <$> Fail [1] Nothing <*> Success 10Fail [1] Nothing>>>(,) <$> Fail [1] (Just 10) <*> Fail [2] (Just 20)Fail [1,2] (Just (10,20))
or like that:
>>>(,) <$> ffail "oups" <*> fsucc 10Fail ["oups"] Nothing>>>(,,) <$> fwarn "oups" 10 <*> fwarn "meh" 20 <*> fsucc 30Fail ["oups","meh"] (Just (10,20,30))>>>(,,) <$> ffail "oups" <*> ffail "meh" <*> fsucc 30Fail ["oups","meh"] Nothing
This type is usefull for form parsing and returning your own type of errors
Instances
| Bifunctor Fail | |
| Functor (Fail e) | |
| Monoid e => Applicative (Fail e) | |
| Foldable (Fail e) | |
| Traversable (Fail e) | |
| (Eq e, Eq a) => Eq (Fail e a) | |
| (Ord e, Ord a) => Ord (Fail e a) | |
| (Read e, Read a) => Read (Fail e a) | |
| (Show e, Show a) => Show (Fail e a) | |
| Generic (Fail e a) | |
| (Monoid e, Monoid a) => Monoid (Fail e a) | |
| Typeable (* -> * -> *) Fail | |
| type Rep (Fail e a) |
Combinators
failEither :: Fail e a -> Either e a Source