applicative-fail-0.0.2: Applicative functor which collects all your fails

Safe HaskellSafe-Inferred
LanguageHaskell2010

Control.Applicative.Fail

Contents

Synopsis

Documentation

data Fail e a Source

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 20
Fail [10] (Just (10,10,20))
>>> (,) <$> Fail [1] Nothing <*> Success 10
Fail [1] Nothing
>>> (,) <$> Fail [1] (Just 10) <*> Fail [2] (Just 20)
Fail [1,2] (Just (10,20))

or like that:

>>> (,) <$> ffail "oups" <*> fsucc 10
Fail ["oups"] Nothing
>>> (,,) <$> fwarn "oups" 10 <*> fwarn "meh" 20 <*> fsucc 30
Fail ["oups","meh"] (Just (10,20,30))
>>> (,,) <$> ffail "oups" <*> ffail "meh" <*> fsucc 30
Fail ["oups","meh"] Nothing

This type is usefull for form parsing and returning your own type of errors

Constructors

Fail e (Maybe a)

(Just a) when checking may proceed in Applicative

Success a 

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) 

ffail :: e -> Fail [e] a Source

fwarn :: e -> a -> Fail [e] a Source

fsucc :: a -> Fail e a Source

getFail :: Fail e a -> Maybe e Source

getSucc :: Fail e a -> Maybe a Source

Combinators

joinFail :: Monoid e => Fail e (Fail e a) -> Fail e a Source

Join two fails like monad does

bindFail :: Monoid e => Fail e a -> (a -> Fail e b) -> Fail e b infixl 1 Source

This is a monadic-like bind. It breaks computation like Maybe and does not correspond to Applicative instance behaviour. So, instead of implementing Monad instance we just implement separate bind operator

composeFail :: Monoid e => (a -> Fail e b) -> (b -> Fail e c) -> a -> Fail e c infixl 1 Source