Paolo Capriotti's blog

Functional programming and more

Applicative option parser

There are quite a few option parsing libraries on Hackage already, but they either depend on Template Haskell, or require some boilerplate. Although I have nothing against the use of Template Haskell in general, I’ve always found its use in this case particularly unsatisfactory, and I’m convinced that a more idiomatic solution should exist.

In this post, I present a proof of concept implementation of a library that allows you to define type-safe option parsers in Applicative style.

The only extension that we actually need is GADT, since, as will be clear in a moment, our definition of Parser requires existential quantification.

> {-# LANGUAGE GADTs #-}
> import Control.Applicative

Let’s start by defining the Option type, corresponding to a concrete parser for a single option:

> data Option a = Option
>   { optName :: String
>   , optParser :: String -> Maybe a
>   }
> 
> instance Functor Option where
>   fmap f (Option name p) = Option name (fmap f . p)
> 
> optMatches :: Option a -> String -> Bool
> optMatches opt s = s == '-' : '-' : optName opt

For simplicity, we only support “long” options with exactly 1 argument. The optMatches function checks if an option matches a string given on the command line.

We can now define the main Parser type:

> data Parser a where
>   NilP :: a -> Parser a
>   ConsP :: Option (a -> b)
>         -> Parser a -> Parser b
> 
> instance Functor Parser where
>   fmap f (NilP x) = NilP (f x)
>   fmap f (ConsP opt rest) = ConsP (fmap (f.) opt) rest
> 
> instance Applicative Parser where
>   pure = NilP
>   NilP f <*> p = fmap f p
>   ConsP opt rest <*> p =
>     ConsP (fmap uncurry opt) ((,) <$> rest <*> p)

The Parser GADT resembles a heterogeneous list, with two constructors.

The NilP r constructor represents a “null” parser that doesn’t consume any arguments, and always returns r as a result.

The ConsP constructor is the combination of an Option returning a function, and an arbitrary parser returning an argument for that function. The combined parser applies the function to the argument and returns a result.

The definition of (<*>) probably needs some clarification. The variables involved have types:

opt :: Option (a -> b -> c)
rest :: Parser a
p :: Parser b

and we want to obtain a parser of type Parser c. So we uncurry the option, obtaining:

fmap uncurry opt :: Option ((a, b) -> c)

and compose it with a parser for the (a, b) pair, obtained by applying the (<*>) operator recursively:

(,) <$> rest <*> p :: Parser (a, b)

This is already enough to define some example parsers. Let’s first add a couple of convenience functions to help us create basic parsers:

> option :: String -> (String -> Maybe a) -> Parser a
> option name p = ConsP (fmap const (Option name p)) (NilP ())
> optionR :: Read a => String -> Parser a
> optionR name = option name p
>   where
>     p arg = case reads arg of
>       [(r, "")] -> Just r
>       _       -> Nothing

And a record to contain the result of our parser:

> data User = User
>   { userName :: String
>   , userId :: Integer
>   } deriving Show

A parser for User is easily defined in applicative style:

> parser :: Parser User
> parser = User <$> option "name" Just <*> optionR "id"

To be able to actually use this parser, we need a “run” function:

> runParser :: Parser a -> [String] -> Maybe (a, [String])
> runParser (NilP x) args = Just (x, args)
> runParser (ConsP _ _) [] = Nothing
> runParser p (arg : args) =
>   case stepParser p arg args of
>     Nothing -> Nothing
>     Just (p', args') -> runParser p' args'
> 
> stepParser :: Parser a -> String -> [String] -> Maybe (Parser a, [String])
> stepParser p arg args = case p of
>   NilP _ -> Nothing
>   ConsP opt rest
>     | optMatches opt arg -> case args of
>         [] -> Nothing
>         (value : args') -> do
>           f <- optParser opt value
>           return (fmap f rest, args')
>     | otherwise -> do
>         (rest', args') <- stepParser rest arg args
>         return (ConsP opt rest', args')

The idea is very simple: we take the first argument, and we go over each option of the parser, check if it matches, and if it does, we replace it with a NilP parser wrapping the result, consume the option and its argument from the argument list, then call runParser recursively.

Here is an example of runParser in action:

> ex1 :: Maybe User
> ex1 = fst <$> runParser parser ["--name", "fry", "--id", "1"]
> {- Just (User {userName = "fry", userId = 1}) -}

The order of arguments doesn’t matter:

> ex2 :: Maybe User
> ex2 = fst <$> runParser parser ["--id", "2", "--name", "bender"]
> {- Just (User {userName = "bender", userId = 2}) -}

Missing arguments will result in a parse error (i.e. Nothing). We don’t support default values but they are pretty easy to add.

> ex3 :: Maybe User
> ex3 = fst <$> runParser parser ["--name", "leela"]
> {- Nothing -}

I think the above Parser type represents a pretty clean and elegant solution to the option parsing problem. To make it actually usable, I would need to add a few more features (boolean flags, default values, a help generator) and improve error handling and performance (right now parsing a single option is quadratic in the size of the Parser), but it looks like a fun project.

Does anyone think it’s worth adding yet another option parser to Hackage?

Comments