| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Control.Applicative.Fail
Contents
- data Fail e a
- runFail :: Monoid e => Fail e a -> (e, Maybe a)
- runDLFail :: Fail (DList e) a -> ([e], Maybe a)
- afail :: Applicative f => e -> Fail (f e) a
- awarn :: Applicative f => e -> a -> Fail (f e) a
- fNull :: (Eq e, Monoid e) => Fail e a -> Bool
- 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
Intro
Assume you have some type
>>>:{data Animal = Animal { species :: String , weight :: Double , age :: Int } deriving (Show) :}
And you would like to produce this value from some data (e.g. query parameters). There can be some warnigns or value can not be produced at all. It would be great to have some simple tool to notify about warnings and/or fail computation.
Like that:
>>>let spc = "Parastratiosphecomyia stratiosphecomyioides">>>let w = 100>>>let a = 27234>>>:{let animal :: Fail [String] Animal animal = Animal <$> (if length spc > 20 then awarn "Name is too long" spc else if spc == "" then afail "Name can not be empty" else pure spc) <*> (if w < 0 then afail "Weight can not be negative" else pure w) <*> (if a < 0 then afail "Age can not be negative" else pure a) :}
>>>animalFail ["Name is too long"] (Just (Animal {species = "Parastratiosphecomyia stratiosphecomyioides", weight = 100.0, age = 27234}))
>>>getSucc animalJust (Animal {species = "Parastratiosphecomyia stratiosphecomyioides", weight = 100.0, age = 27234})
>>>getFail animalJust ["Name is too long"]
Now you can build your own parser-like things
Fail
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
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) | 
afail :: Applicative f => e -> Fail (f e) a Source
awarn :: Applicative f => e -> a -> Fail (f e) a Source
fNull :: (Eq e, Monoid e) => Fail e a -> Bool Source
Return True if pattern does not contain not success value nor fails, i.e. (Fail mempty Nothing)
Combinators
failEither :: Fail e a -> Either e a Source