nri-prelude-0.6.0.5: A Prelude inspired by the Elm programming language
Safe HaskellNone
LanguageHaskell2010

Result

Description

A Result is the result of a computation that may fail. This is a great way to manage errors in Elm, but we when using this package in Haskell we tend to rely on Task a lot too for error handling.

Synopsis

Type and Constructors

data Result error value Source #

A Result is either Ok meaning the computation succeeded, or it is an Err meaning that there was some failure.

Constructors

Ok value 
Err error 

Instances

Instances details
Monad (Result error) Source # 
Instance details

Defined in Result

Methods

(>>=) :: Result error a -> (a -> Result error b) -> Result error b #

(>>) :: Result error a -> Result error b -> Result error b #

return :: a -> Result error a #

Functor (Result error) Source # 
Instance details

Defined in Result

Methods

fmap :: (a -> b) -> Result error a -> Result error b #

(<$) :: a -> Result error b -> Result error a #

Applicative (Result error) Source # 
Instance details

Defined in Result

Methods

pure :: a -> Result error a #

(<*>) :: Result error (a -> b) -> Result error a -> Result error b #

liftA2 :: (a -> b -> c) -> Result error a -> Result error b -> Result error c #

(*>) :: Result error a -> Result error b -> Result error b #

(<*) :: Result error a -> Result error b -> Result error a #

(Eq value, Eq error) => Eq (Result error value) Source # 
Instance details

Defined in Result

Methods

(==) :: Result error value -> Result error value -> Bool #

(/=) :: Result error value -> Result error value -> Bool #

(Show value, Show error) => Show (Result error value) Source # 
Instance details

Defined in Result

Methods

showsPrec :: Int -> Result error value -> ShowS #

show :: Result error value -> String #

showList :: [Result error value] -> ShowS #

Mapping

map :: (a -> value) -> Result x a -> Result x value Source #

Apply a function to a result. If the result is Ok, it will be converted. If the result is an Err, the same error value will propagate through.

map sqrt (Ok 4.0)          == Ok 2.0
map sqrt (Err "bad input") == Err "bad input"

map2 :: (a -> b -> value) -> Result x a -> Result x b -> Result x value Source #

Apply a function if both results are Ok. If not, the first Err will propagate through.

map2 max (Ok 42) (Ok 13) == Ok 42 map2 max (Err "x") (Ok 13) == Err "x" map2 max (Ok 42) (Err "y") == Err "y" map2 max (Err "x") (Err "y") == Err "x"

This can be useful if you have two computations that may fail, and you want to put them together quickly.

map3 :: (a -> b -> c -> value) -> Result x a -> Result x b -> Result x c -> Result x value Source #

 

map4 :: (a -> b -> c -> d -> value) -> Result x a -> Result x b -> Result x c -> Result x d -> Result x value Source #

 

map5 :: (a -> b -> c -> d -> e -> value) -> Result x a -> Result x b -> Result x c -> Result x d -> Result x e -> Result x value Source #

 

Chaining

andThen :: (a -> Result c b) -> Result c a -> Result c b Source #

Chain together a sequence of computations that may fail. It is helpful to see its definition:

andThen : (a -> Result e b) -> Result e a -> Result e b
andThen callback result =
    case result of
      Ok value -> callback value
      Err msg -> Err msg

This means we only continue with the callback if things are going well. For example, say you need to use (toInt : String -> Result String Int) to parse a month and make sure it is between 1 and 12:

toValidMonth : Int -> Result String Int
toValidMonth month =
    if month >= 1 && month <= 12
        then Ok month
        else Err "months must be between 1 and 12"
toMonth : String -> Result String Int
toMonth rawString =
    toInt rawString
      |> andThen toValidMonth
-- toMonth "4" == Ok 4
-- toMonth "9" == Ok 9
-- toMonth "a" == Err "cannot parse to an Int"
-- toMonth "0" == Err "months must be between 1 and 12"

This allows us to come out of a chain of operations with quite a specific error message. It is often best to create a custom type that explicitly represents the exact ways your computation may fail. This way it is easy to handle in your code.

Handling Errors

withDefault :: a -> Result b a -> a Source #

If the result is Ok return the value, but if the result is an Err then return a given default value. The following examples try to parse integers.

Result.withDefault 0 (Ok 123)   == 123
Result.withDefault 0 (Err "no") == 0

toMaybe :: Result a b -> Maybe b Source #

Convert to a simpler Maybe if the actual error message is not needed or you need to interact with some code that primarily uses maybes.

parseInt : String -> Result ParseError Int

maybeParseInt : String -> Maybe Int
maybeParseInt string =
    toMaybe (parseInt string)

fromMaybe :: a -> Maybe b -> Result a b Source #

Convert from a simple Maybe to interact with some code that primarily uses Results.

parseInt : String -> Maybe Int

resultParseInt : String -> Result String Int
resultParseInt string =
    fromMaybe ("error parsing string: " ++ toString string) (parseInt string)

mapError :: (a -> b) -> Result a c -> Result b c Source #

Transform an Err value. For example, say the errors we get have too much information:

parseInt : String -> Result ParseError Int

type alias ParseError =
    { message : String
    , code : Int
    , position : (Int,Int)
    }

mapError .message (parseInt "123") == Ok 123
mapError .message (parseInt "abc") == Err "char 'a' is not a number"