applicative-fail-1.1.1: Applicative functor and monad which collects all your fails

Safe HaskellNone
LanguageHaskell2010

Control.Applicative.Fail

Contents

Synopsis

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)
:}
>>> animal
Fail ["Name is too long"] (Just (Animal {species = "Parastratiosphecomyia stratiosphecomyioides", weight = 100.0, age = 27234}))
>>> getSucc animal
Just (Animal {species = "Parastratiosphecomyia stratiosphecomyioides", weight = 100.0, age = 27234})
>>> getFail animal
Just ["Name is too long"]

Now you can build your own parser-like things

Fail

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

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) 

runFail :: Monoid e => Fail e a -> (e, Maybe a) Source

Unwraps Fail to tuple of error and value. If pattern is Success then return mempty in error part.

runDLFail :: Fail (DList e) a -> ([e], Maybe a) Source

Unwraps Fail and constrain error container to DList for type inference

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)

getFail :: Fail e a -> Maybe e Source

Return fail part if exists

getSucc :: Fail e a -> Maybe a Source

Return success part if exists

Combinators

failEither :: Fail e a -> Either e a Source

Return Right if there is value (including pattern '(Fail e (Just a))'). If there is no value return Left

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

Join two fails like monad does. This function still match to Applicative