Difference between revisions of "GetOpt"

From HaskellWiki
Jump to navigation Jump to search
(→‎See also: Command line option parsers)
m
 
(One intermediate revision by one other user not shown)
Line 1: Line 1:
[[Category:Idioms]]
+
[[Category:Idioms]][[Category: Pages under construction]]
   
 
I have noticed a lot of ways of dealing with GetOpt flags in Haskell
 
I have noticed a lot of ways of dealing with GetOpt flags in Haskell
Line 9: Line 9:
 
Note that I use each one of these approaches in different programs. I get the impression that how you use GetOpt really depends on what your particular needs are.
 
Note that I use each one of these approaches in different programs. I get the impression that how you use GetOpt really depends on what your particular needs are.
   
'''Out of date! 2010-08-27''' ''The last major edit was around 2007: could somebody refresh this, preferably cataloguing the new wrappers like cmdargs, cmdlib, parseargs, and maybe simpleargs (which maybe doesn't count). It could also be good to rename this page to something about command line options''
+
'''Out of date! 2012-11-07''' ''The last major edit was around 2007: could somebody refresh this. It could also be good to rename this page to something about command line options. The is now also a list of [[command line option parsers]].''
   
 
== Ginormous record ==
 
== Ginormous record ==

Latest revision as of 05:40, 8 June 2023


I have noticed a lot of ways of dealing with GetOpt flags in Haskell programs and thought it might be useful to catalogue them. A lot of this could be wrong btw, for example, advantages/disadvantages. But I think the general idea might be useful, so please add to this if you see other solutions.

Note that I use each one of these approaches in different programs. I get the impression that how you use GetOpt really depends on what your particular needs are.

Out of date! 2012-11-07 The last major edit was around 2007: could somebody refresh this. It could also be good to rename this page to something about command line options. The is now also a list of command line option parsers.

Ginormous record

Do you happen to have some giant recordful of command line parameters? Something like

 data Settings = Settings { filter     :: Maybe String
                          , dateFormat :: Maybe String
                          , blahBlah   :: Maybe Blah
                          ...
                          , thisIsGetting :: RatherLargeIsntIt
                          }

 emptySettings :: Settings
 emptySettings = Settings { filter = Nothing
                          , dateFormat = Nothing
                          }

 toSettings :: [Flag] -> Settings
 toSettings fs = toSettingsH fs emptySettings

 toSettingsH :: [Flag] -> Settings -> Settings
 toSettingsH (Filter s:fs)     i = toSettingsH fs (i { filter = s })
 toSettingsH (DateFormat s:fs) i = toSettingsH fs (i { dateFormat = i= })

Note: You can make this a little less painful by factoring out the recursion (took me a while to realise this!).

toSettings fs = foldr ($) emptySettings (map processFlag fs)

processFlag :: Flag -> Settings -> Settings
processFlag (Filter s) i = i { filter = Just s }
processFlag (DateFormat s) i = i { dateFormat = s }
...

Advantages:

  • simple, easy to look up settings

Disadvantages:

  • boring; have to write
    1. Flag type
    2. Settings record type
    3. default Settings
    4. processFlag entry
    5. GetOpt entry
  • record gets really really huge if you have a lot of flags

List of flags (darcs)

Don't bother keeping any records around, just pass around a big list of flags to functions that depend on settings.

if the flag has any parameters, you can't just write ( DateFormat `elem` fs); you'll have to write some boilerplate along the lines of

hasDateFormat :: [Flag] -> Bool
hasDateFormat (DateFormat s:fs) = True
hasDateFormat (_:fs) = hasDateFormat fs
hasDateFormat []     = False

getDateFormat :: [Flag] -> Maybe String
getDateFormat (DateFormat s:fs) = Just s
getDateFormat (_:fs) = getDateFormat fs
getDateFormat []     = Nothing

...which again can be factored out...

fromDateFormat :: Flag -> Maybe String
fromDateFormat (DateFormat x) = Just x
fromDateFormat _ = Nothing

hasDateFormat fs = any (isJust.fromDateFormat) fs
getDateFormat fs = listToMaybe $ mapMaybe fromDateFormat fs

Still, this is more pay-as-you-go in the sense that not all flags need to be accessed, so maybe you end up writing less boilerplate overall

Advantages:

  • simple
  • very convenient to add flags (as a minimum, you have to write
    1. flag type
    2. GetOpt entry
    3. lookup code (but pay-as-you-go)
    4. can support using a flag multiple times (-v -v -v)

Disadvantages:

  • still a bit boilerplatey

No lists, just records (lhs2TeX)

This one is due to Andres Löh (maybe), I think although my rendition of it may not be as nice as his.

Ever considered that your Settings record could almost be your Flag type? The trick here is recognising that constructors are functions too and what GetOpt really wants is just a function, not necessarily a constructor.

type Flag a = (a -> Settings -> Settings)

options :: [OptDescr Flag]
options =
  [ Option "f" ["filter"]
      (ReqArg (\x s -> s { filter = Just x }) "TYPE")
      "blahblah"
  , Option "d" ["date-format"]
      (ReqArg (\x s -> s { dateFormat = Just x }) "TYPE")
      "blahblah"

  ]

Advantages:

  • very convenient/compact; have to write
    1. Flag type
    2. Settings record type/GetOpt in one go
    3. default Settings
  • easy to lookup flags

Disadvantages:

  • Not as flexible
    • can't group flags into blocks and have different programs that use different subsets of flags (without sharing the same Setting type)
    • everything must go into Settings
    • seems harder to say stuff like 'if flag X is set and flag Y are in the list of Flags, then parameterise flag Z this way' or 'flags X and Y are mutually exclusive'

List of flags + existential types (GenI)

See attached code. Basically motivated by your idea that we should be able to pass constructors around like arguments. Note: attached code is written by very non-expert Eric. So be ready to consider it wrong and horrible in more ways than one can imagine.

Using it looks like this:

*Main> hasFlag LogFileFlag [ tf ]
False
*Main> hasFlag LogFileFlag [ lf, tf ]
True

*Main> [lf, tf]
[Flag LogFileFlag "hi",Flag TimeoutFlag 3]
*Main> setFlag LogFileFlag "bar" [ lf, tf ]
[Flag LogFileFlag "bar",Flag TimeoutFlag 3]
*Main> getFlag LogFileFlag [lf,tf]
Just "bar"

Advantages:

  • no more boilerplate only have to define
    1. flag type, although ugly
    2. getopt stuff
  • extensible (as any list of flags approach)
  • mix-n-matchable (cf #3; different programs can share subset of flags)
  • can really just say 'getFlag FooFlag'
  • setFlag / deleteFlag

(I'm not claiming there are more advantages; it's just that I wrote this and can remember why)

Disadavantages:

  • can't enforce that some flags are always set (cf #1 and #4)
  • making things too complicated! Existential types seems like overkill for GetOpt (well, I mostly did this to learn what they were)
  • ugly cpp macro or repetitive
         data FilterFlag = FilterFlag String deriving (Eq, Show, Typeable)
         data TimeoutFlag = TimeoutFlag Int  deriving (Eq, Show, Typeable)
    
  • ugly GetOpt wrappers
reqArg :: forall f x . (Eq f, Show f, Typeable f, Eq x, Show x, Typeable x)
       => (x -> f)      -- ^ flag
       -> (String -> x) -- ^ string reader for flag (probably |id| if already a String)
       -> String        -- ^ description
       -> ArgDescr Flag
reqArg s fn desc = ReqArg (\x -> Flag s (fn x)) desc

Flag code

This code is in the public domain.  Do whatever you want with it.
Eric Kow 2006-08-16

This is a library for dealing with optional command line arguments.

Note: you probably want to have a cpp macro that looks a little like this:
 #define FLAG(x,y) data x = x y deriving (Eq, Show, Typeable)

Some examples:

------------8<-----------------------------------------------------------
{-# OPTIONS_GHC -fglasgow-exts #-}

import Data.Typeable
import FlagsAndSwitches

data LogFileFlag = LogFileFlag String deriving (Eq, Show, Typeable)
data TimeoutFlag = TimeoutFlag Int    deriving (Eq, Show, Typeable)

lf = Flag LogFileFlag "hi"
tf = Flag TimeoutFlag 3
------------8<-----------------------------------------------------------

*Main> hasFlag LogFileFlag [ tf ]
False
*Main> hasFlag LogFileFlag [ lf, tf ]
True

*Main> [lf, tf]
[Flag LogFileFlag "hi",Flag TimeoutFlag 3]
*Main> setFlag LogFileFlag "bar" [ lf, tf ]
[Flag LogFileFlag "bar",Flag TimeoutFlag 3]
*Main> getFlag LogFileFlag [lf,tf]
Just "bar"

> {-# OPTIONS_GHC -fglasgow-exts #-}
> module FlagsAndSwitches where
>
> import Data.List (find)
> import Data.Typeable (Typeable, cast, typeOf)
>
> data Flag = forall f x . (Show f, Show x, Typeable f, Typeable x) => Flag (x -> f) x deriving Typeable
>
> instance Show Flag where
>   show (Flag f x) = "Flag " ++ show (f x)

> isFlag     :: (Typeable f, Typeable x) => (x -> f) -> Flag -> Bool
> hasFlag    :: (Typeable f, Typeable x) => (x -> f) -> [Flag] -> Bool
> deleteFlag :: (Typeable f, Typeable x) => (x -> f) -> [Flag] -> [Flag]
> setFlag    :: (Show f, Show x, Typeable f, Typeable x) => (x -> f) -> x -> [Flag] -> [Flag]
> getFlag    :: (Show f, Show x, Typeable f, Typeable x) => (x -> f) -> [Flag] -> Maybe x
>
> isFlag f1 (Flag f2 _) = typeOf f1 == typeOf f2
> hasFlag f      = any (isFlag f)
> deleteFlag f   = filter (not.isFlag f)
> setFlag f v fs = (Flag f v) : tl where tl = deleteFlag f fs
> getFlag f fs   = find (isFlag f) fs >>= cast

Association Lists

One can simplify the interface provided by System.Console.GetOpt, by treating options as association lists. One works with pairs of the form

(a,String)

where a is an enumeration type of option keys. One then passes a list of the type

[OptDescr (a,String)]

to getOpt.

This requires some project-independent code, but the per-project boilerplate is kept to a minimum. To declare the options for a particular project, one can write

data Flag
    = Filter
    | CodeDir
    | DateFormat
    | Help
    deriving (Eq)

defaults :: OptionList Flag
defaults =
    [ (Filter,     "Markdown.pl")
    , (DateFormat, "%B %e, %Y %H:%M:%S")
    ]

flags :: OptionSpecs Flag
flags = makeOptions
    [ (Filter,     'm', "markup", reqArg, "path",   "Path to Markdown.pl")
    , (CodeDir,    'c', "code",   reqArg, "path",   "Path to code directory")
    , (DateFormat, 'd', "date",   reqArg, "format", "Date format")
    , (Help,       'h', "help",   noArg,  [],       "This help message")
    ]

and the project-independent code can process options based on this information.

With different code, one could combine defaults and flags into one list, but this would come at the expense of readability; individual entries would no longer fit on one portable line.

An example function that accesses options of this form is

getOptionOr :: Eq a => a -> OptionList a -> String -> String
getOptionOr options assoc def = case lookup options assoc of
    Nothing -> def
    Just "" -> def
    Just s  -> s

which one would call using

getOptionOr CodeDir options "src"

to supply a context dependent default, rather than relying on a global default.

A worked example of this technique is given by Annote:GetOpt.

See also