{-# LANGUAGE PatternGuards #-} module Control.Applicative.Error where import Control.Applicative -- |An error idiom. Rather like the error monad, but collect all -- |errors together data Failing a = Success a | Failure [ErrorMsg] deriving Show type ErrorMsg = String instance Functor Failing where fmap f (Failure fs) = Failure fs fmap f (Success a) = Success (f a) instance Applicative Failing where pure = Success Failure msgs <*> Failure msgs' = Failure (msgs ++ msgs') Success _ <*> Failure msgs' = Failure msgs' Failure msgs' <*> Success _ = Failure msgs' Success f <*> Success x = Success (f x) -- | Tries to read a value maybeRead :: Read a => String -- | The value -> String -- | The error message -> Failing a maybeRead s msg | [(i, _)] <- readsPrec 0 s = Success i | otherwise = Failure [msg] -- | Tries to read an Integer asInteger :: String -> Failing Integer asInteger s = maybeRead s (s ++ " is not a valid integer")