Handling errors in Haskell

From HaskellWiki
Revision as of 15:30, 2 August 2017 by Jacco (talk | contribs) (Change Reddit type to IO to avoid confusion with try which only works in IO, added info on catching errors from pure code)
Jump to navigation Jump to search

These are the four types of error handling that are standard and widely used in the Haskell world, as of 2014.

There exist some other libraries like attempt (like Either, but where you don't care or know the type of the exception) and control-monad-exception which implements a checked exception monad, etc. but the following ones are the standard ones seen in the wild.

Exception

An unexpected code path, one that rarely but can happen and can be handled if needs be. Typically caused by IO going wrong in some way, like the machine running out of swap and your program terminating, a file not existing, etc. The most basic functions are:

  • throw :: Exception e => e -> a
  • try :: Exception e => IO a -> IO (Either e a)

from Control.Exception.

Say you were writing a library to do things on reddit, you would define an exception type in your API:

data RedditException
  = Couldn'tUpvote
  | CommentFailed
  | LoginFailed !Text
  | ConnectFailure !HttpError
  deriving (Show,Typeable)

instance Exception RedditException

login :: Details -> IO ()
login details = do
  code <- tryLogin details
  case code of
    (200,val) -> setLoginContext val
    (_,err)   -> throw (LoginFailed err)

Then later you might write try (login ) or catch (login ) (\(e :: RedditException) -> ) to handle the exception, if needed. Another exception might be a connection failure.

See Control.Exception for more detail and related functions.

Error (pure code)

Some pure functions contain calls to error, causing the evaluation to stop and crash:

head :: [a] -> a
head (x:_) = x
head []    = error "empty list"

Now suppose someone writes head ages and unexpectedly, ages is an empty list. If you are trying to take the head of an empty list your program logic is simply broken.

A solution here is to avoid the head function and use listToMaybe from Data.Maybe.

case listToMaybe ages of
  Nothing -> defaultAge
  Just first -> first

Alternatively, these errors can be caught from IO monad by using evaluate and try from Control.Exception. Ideally you should avoid partial functions like <head>head</head>, but sometimes this is not an option (e.g. when using an external library)

Error using the Either type

An expected return value: Either SomeError a The type indicates that an error is common, but doesn't mean your program is broke. Rather that some input value wasn't right. Typically used by parsers, consumers, that are pure and often error out.

data ParseError = ParseError !Pos !Text

So this type describes exactly what is going on:

runParser :: Parser a -> Text -> Either ParseError a

Take a parser of a, some text to parse, and return either a parser error or a parsed a. Typical usage would be:

main = do
  line <- getLine
  case runParser emailParser line of
    Right (user,domain) -> print ("The email is OK.",user,domain)
    Left (pos,err) -> putStrLn ("Parse error on " <> pos <> ": " <> err)

Or depending on the code one might opt instead to use a deconstructing function:

main = do
  line <- getLine
  either (putStrLn . ("Parse error: " <>) . show)
         (print . ("The email is OK.",))
         (runParser emailParser line)

No value using the Maybe type

There is simply no value there. This isn't a problem in the system. It means you don't care why there isn't a value, or you already know. Maybe a

Typical example:

lookup :: Eq a => a -> [(a,b)] -> Maybe b

That is, take some key a that can be compared for equality, and a list of pairs where the first is the same type of the key a and maybe return the b of the pair, or nothing.

So one might pattern match on this:

case lookup name person of
  Nothing -> "no name specified"
  Just name -> "Name: " <> name

Or use a deconstructing function:

maybe "no name specified"
      ("Name: " <>)
      (lookup name person)

Again, depends on the code and the person writing it whether an explicit case is used. Often monads like Maybe are composed to make a chain of possibly-nothing values:

lookup "height" profile >>=
parseInt >>=
flip lookup recommendedSizes


So lookup a height from a person's profile (might not exist), parse it as integer (might not parse), then use that as a key to lookup from a mapping list of age to clothes size: [(Int,Text)]