[Haskell-cafe] ANN: hflags-0.1, a command line flags library similar to Google's gflags

Gergely Risko gergely at risko.hu
Mon Apr 30 18:43:03 CEST 2012


Hello,

I would like to announce the release of HFlags, a command line flags
library that makes it very easy to define and use flags.

The API is similar to Google's gflags, here is a very simple example
program:

-=-
#!/usr/bin/env runhaskell

{-# LANGUAGE TemplateHaskell #-}

import HFlags

defineFlag "name" "Indiana Jones" "Who to greet."
defineFlag "r:repeat" (3 + 4 :: Int)
  "Number of times to repeat the message."

main = do remainingArgs <- $(initHFlags "Simple program v0.1")
          sequence_ $ replicate flags_repeat greet
  where
    greet = putStrLn $ "Hello "
                       ++ flags_name
                       ++ ", very nice to meet you!"
-=-

As you can see, we have TemplateHaskell functions to help with the
definition (and initialization) of the flags, and the values themselves
are pure, no need for being in the IO monad to use the value of the
flags.

Also, the initHFlags function automagically gathers all the flags
defined anywhere in the whole program, so if a library defines flags,
you don't have to mention it in the main, but the user will still be
able to set those flags too.

More details behind this design and more example can be found in the
following post: http://blog.risko.hu/2012/04/ann-hflags-0.html

Comments and criticism is welcome.

Code: http://github.com/errge/hflags
Examples: https://github.com/errge/hflags/tree/master/examples
Hackage: http://hackage.haskell.org/package/hflags

Best regards,
Gergely Risko




More information about the Haskell-Cafe mailing list