| Safe Haskell | None |
|---|
HFlags
Description
The HFlags library supports easy definition of command line flags,
reimplementing the ideas from Google's gflags
(http://code.google.com/p/gflags).
Command line flags can be declared in any file at the toplevel,
using defineFlag. At runtime, the actual values are assigned to
the toplevel flags_name constants. Those can be used purely
throughout the program.
At the beginning of the main function, $(initHFlags program
description) has to be called to initialize the flags. All flags
will be initialized that are transitively reachable via imports
from main. This means, that any Haskell package can easily
define command line flags with HFlags. This feature is
demonstrated by
http://github.com/errge/hflags/blob/master/examples/ImportExample.hs.
A simple example (more in the http://github.com/errge/hflags/tree/master/examples directory):
#!/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 s <- $(initHFlags "Simple program v0.1")
sequence_ $ replicate flags_repeat greet
where
greet = putStrLn $ "Hello " ++ flags_name ++ ", very nice to meet you!"
At initHFlags time, the library also tries to gather flags out of
environment variables. HFLAGS_verbose=True is equivalent to
specify --verbose=True. This environment feature only works with
long options and the user has to specify a value even for Bools.
Definition of flags
defineCustomFlag :: String -> ExpQ -> String -> ExpQ -> ExpQ -> String -> Q [Dec]Source
The most flexible way of defining a flag. For an example see
http://github.com/errge/hflags/blob/master/examples/ComplexExample.hs.
For most things defineFlag should be enough instead.
The parameters:
- name of the flag (
l:longsyntax if you want to have the short optionlfor this flag), - quasiquoted and type signed default value,
- help string for the argument,
- read function, quasiquoted,
- show function, quasiquoted,
- help string for the flag.
defineQQFlag :: String -> ExpQ -> String -> String -> Q [Dec]Source
This just forwards to defineCustomFlag with [| read |] and
[| show |]. Useful for flags where the type is not an instance
of FlagType. For examples, see
http://github.com/errge/hflags/blob/master/examples/ComplexExample.hs.
The parameters:
- name of the flag (
l:longsyntax if you want to have the short optionlfor this flag),, - quasiquoted and type signed default value,
- help string for the argument,
- help string for the flag.
Class of types for which the easy defineFlag syntax is supported.
Initialization of flags at runtime
initHFlags :: String -> ExpQSource
Has to be called from the main before doing anything else:
main = do args <- $(initHFlags Simple program v0.1) ...
Internally, it uses Template Haskell trickery to gather all the
instances of the Flag class and then generates a call to
initFlags with the appropriate data gathered together from those
instances to a list.
Type after splicing is IO [String].