Avoiding boilerplate retrieving GetOpt cmd line args

Ok, I'm writing a command line tool, using System.Console.GetOpt to handle command line arguments. My Flags structure so far is
data Flag = Filter String | DateFormat String | DocStart String | DocEnd String ...
and I want to write accessor functions that return the strings if specified, otherwise returning a default. The best I've been able to do is this:
getFilter = getString f "Markdown.pl" where f (Filter s) = Just s f _ = Nothing
getDateFormat = getString f "%B %e, %Y" where f (DateFormat s) = Just s f _ = Nothing
getDocStart = getString f "^{-$" where f (DocStart s) = Just s f _ = Nothing
getDocEnd = getString f "^-}$" where f (DocEnd s) = Just s f _ = Nothing
using a generic accessor function `getString`. There are eight (and growing) needless lines here, where what I really want to do is to pass the constructors `Filter`, `DateFormat`, `DocStart`, or `DocEnd` to the function `getString`. ghci types each of these as `String -> Flag`, so one at least knows how to type such a `getString`, but using a constructor-passed-as-an-argument in a pattern match is of course a "Parse error in pattern". (I expected as much, but I had to try... `String -> Flag` is not enough information to make it clear we're passing a constructor, rather than some hairy arbitrary function, so such a pattern match would be undecidable in general.) So what's the right idiom for avoiding this boilerplate? Thanks, Dave

Hi, Not sure if this will help avoid the boilerplate, but I've always liked the approach at http://leiffrenzel.de/papers/commandline-options-in-haskell.html (particularly the section "Towards a higher level") for being able to specify defaults. It's the best resource I've found on command line options in Haskell so far. Levi
Ok, I'm writing a command line tool, using System.Console.GetOpt to handle command line arguments. My Flags structure so far is
data Flag = Filter String | DateFormat String | DocStart String | DocEnd String ...
and I want to write accessor functions that return the strings if specified, otherwise returning a default. The best I've been able to do is this:
getFilter = getString f "Markdown.pl" where f (Filter s) = Just s f _ = Nothing
getDateFormat = getString f "%B %e, %Y" where f (DateFormat s) = Just s f _ = Nothing
getDocStart = getString f "^{-$" where f (DocStart s) = Just s f _ = Nothing
getDocEnd = getString f "^-}$" where f (DocEnd s) = Just s f _ = Nothing
using a generic accessor function `getString`.
There are eight (and growing) needless lines here, where what I really want to do is to pass the constructors `Filter`, `DateFormat`, `DocStart`, or `DocEnd` to the function `getString`. ghci types each of these as `String -> Flag`, so one at least knows how to type such a `getString`, but using a constructor-passed-as-an-argument in a pattern match is of course a "Parse error in pattern". (I expected as much, but I had to try... `String -> Flag` is not enough information to make it clear we're passing a constructor, rather than some hairy arbitrary function, so such a pattern match would be undecidable in general.)
So what's the right idiom for avoiding this boilerplate?
Thanks, Dave
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Thu, Jul 26, 2007 at 10:25:06PM -0700, Dave Bayer wrote:
Ok, I'm writing a command line tool, using System.Console.GetOpt to handle command line arguments. My Flags structure so far is
data Flag = Filter String | DateFormat String | DocStart String | DocEnd String ...
and I want to write accessor functions that return the strings if specified, otherwise returning a default. The best I've been able to do is
I don't know if my reply is going to be helpful to you. This is what I would suggest: why don't you create a data type with label records, and than you store that data type in a IORef and update the IORef. At the end you just read the IORef with your updated data: data Config = { filter :: String , dateFormat :: String , etc ... } Then you create a new IOref with config, and, with getOpt, you update the IOref with modifyIORef. At the very end you read the modified IOref. This way you can have default options to be modified with command line options. I don't know if it is clear, but I adopted this approach in a program I'm writing. A program with 14 command line options. Have a look at this part here (starting from data Opts=): http://gorgias.mine.nu/repos/xmobar/Main.hs This way I can load a configuration file and change some of the options, configured in that file, with the given command line options. I hope this is going to help you. Andrea

Hi, Here is a possible two part response. Not literate code, just using > to distinguish code from everything else. A short answer ==============
getFilter = getString f "Markdown.pl" where f (Filter s) = Just s f _ = Nothing
getDateFormat = getString f "%B %e, %Y" where f (DateFormat s) = Just s f _ = Nothing
For starters, you could squish these down into something like
flagToString :: Flag -> Maybe String flagToString (Filter s) = Just s flagToString (DateFormat s) = Just s ... flagToString _ = Nothing
Then you would have
getFilter = getString flagToString "Markdown.pl" getDateFormat = getString flagToString "%B %e, %Y"
A long answer ============= I have noticed a lot of ways of dealing with GetOpt flags in Hakell 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. Solution #1 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 (i) Flag type (ii) Settings record type (iii) default Settings (iv) processFlag entry (v) GetOpt entry record gets really really huge if you have a lot of flags Solution #2 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 (i) flag type (ii) GetOpt entry (iii) lookup code (but pay-as-you-go) Disadvantages: still a bit boilerplatey Solution #3 No lists, just records (lhs2TeX) ---------------------------------- This one is due to Andres Löh, 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 (i) Flag type (ii) Settings record type/GetOpt in one go (iii) 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' Solution #4 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 (i) flag type, although ugly (ii) 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 ata 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 -- Eric Kow http://www.loria.fr/~kow PGP Key ID: 08AC04F9 Merci de corriger mon français.

On 7/27/07, Eric Y. Kow
Solution #3 No lists, just records (lhs2TeX) ----------------------------------
Advantages: very convenient/compact; have to write (i) Flag type (ii) Settings record type/GetOpt in one go (iii) 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'
This is what I'm using for my current project. Most of the disadvantages don't apply in my case, because all my flags are largely-independent simulation parameters. The one thing I find annoying, though, is that for each option I add, I need to make changes in three places: 1) The definition of my options record 2) My default options value 3) My list of GetOpt.OptDescr What I'd really like to be able to do is specify the field name, field type, and GetOpt info in a single place, without any redundancy. This is obviously impossible in vanilla Haskell, so some kind of fancy preprocessing or templating would be necessary. (Sadly, I'm not in a position to pull this off right now.) Stuart

On Friday 27 July 2007, Dave Bayer wrote:
Ok, I'm writing a command line tool, using System.Console.GetOpt to handle command line arguments. My Flags structure so far is
data Flag = Filter String
| DateFormat String | DocStart String | DocEnd String
...
and I want to write accessor functions that return the strings if specified, otherwise returning a default. The best I've been able to
do is this:
getFilter = getString f "Markdown.pl" where f (Filter s) = Just s f _ = Nothing
getDateFormat = getString f "%B %e, %Y" where f (DateFormat s) = Just s f _ = Nothing
getDocStart = getString f "^{-$" where f (DocStart s) = Just s f _ = Nothing
getDocEnd = getString f "^-}$" where f (DocEnd s) = Just s f _ = Nothing
using a generic accessor function `getString`.
There are eight (and growing) needless lines here, where what I really want to do is to pass the constructors `Filter`, `DateFormat`, `DocStart`, or `DocEnd` to the function `getString`. ghci types each of these as `String -> Flag`, so one at least knows how to type such a `getString`, but using a constructor-passed-as-an-argument in a pattern match is of course a "Parse error in pattern". (I expected as much, but I had to try... `String -> Flag` is not enough information to make it clear we're passing a constructor, rather than some hairy arbitrary function, so such a pattern match would be undecidable in general.)
So what's the right idiom for avoiding this boilerplate?
What you want can (almost) be done as follows: {-# OPTIONS_GHC -fglasgow-exts #-} import Data.Generics import Data.Typeable data Flag = Filter String | DateFormat String | DocStart String | DocEnd String deriving (Typeable, Data) getString :: Flag -> String -> Flag -> String getString c df f | toConstr c /= toConstr f = df getString c df (Filter s) = s getString c df (DateFormat s) = s getString c df (DocStart s) = s getString c df (DocEnd s) = s This version uses overlapping patterns, of course; it should be evident how to change that if you want. Call it as getString Filter{} "Markdown.pl" flag Jonathan Cast http://sourceforge.net/projects/fid-core http://sourceforge.net/projects/fid-emacs

Hi Why not:
data Flag = Filter String | DateFormat String | DocStart String | DocEnd String
Becomes: data Flag = Flag Key String data Key = Filter | DateFormat | DocStart | DocEnd getString :: Flag -> Key -> String getString (Flag x y) key = if key == x then y else "" You can easily extend this to defaults: defaults = [(DocStart,"1")] then lookup, instead of just "" as the else clause. If you have to use Data/Typeable you will no longer be writing portable Haskell, and while they are great, they aren't the thing to use here. Thanks Neil

Neil Mitchell
then lookup, instead of just "" as the else clause.
Thanks, all. After digesting what was on this thread as I woke up this morning, I ended up writing something rather close to this. I have a reusable wrapper around System.Console.GetOpt that adds
type Opt a = (a,String)
noArg :: a -> ArgDescr (Opt a) noArg x = NoArg (x,"")
reqArg :: a -> String -> ArgDescr (Opt a) reqArg x s = ReqArg f s where f y = (x,y)
optArg :: a -> String -> ArgDescr (Opt a) optArg x s = OptArg f s where f (Just y) = (x,y) f Nothing = (x,"")
isOption :: Eq a => a -> [Opt a] -> Bool isOption opt assoc = case lookup opt assoc of Nothing -> False Just _ -> True
getOption :: Eq a => a -> [Opt a] -> String getOption opt assoc = case lookup opt assoc of Nothing -> "" Just s -> s
Then in a project-specific module I write
data Flag = Filter | DateFormat | DocStart | DocEnd | ForceStyle | Help deriving (Eq)
defaults :: [Opt Flag] defaults = [ (Filter, "Markdown.pl") , (DateFormat, "%B %e, %Y") , (DocStart, "^\\s*{-\\s*$") , (DocEnd, "^\\s*-}\\s*$") ]
flags :: [OptDescr (Opt Flag)] flags = [ Option ['s'] ["style"] (noArg ForceStyle) "Overwrite existing style.css" , Option ['m'] ["markup"] (reqArg Filter "path") "Path to Markdown-style markup filter" , Option ['d'] ["date"] (reqArg DateFormat "format") "Unix-style modification date format" , Option ['a'] ["start"] (reqArg DocStart "string") "Documentation start string" , Option ['b'] ["end"] (reqArg DocEnd "string") "Documentation end string" , Option ['h'] ["help"] (noArg Help) "Print this help message" ]
which looks "almost" like the sample code I started with. Reading quickly, one might miss the case change from `NoArg` to `noArg`, etc. This is simple, and it works, with less option-specific boilerplate. One could imagine generating `flags` automatically from an extension of `defaults`, but I'm content to move on. The relevant code is at http://www.math.columbia.edu/~bayer/Haskell/Annote/GetOpt.html http://www.math.columbia.edu/~bayer/Haskell/Annote/Flags.html http://www.math.columbia.edu/~bayer/Haskell/Annote/Main.html

To anyone who followed up on this thread (hi!). I have posted the GetOpt-summary part of my message on the wiki: http://www.haskell.org/haskellwiki/GetOpt Please update it with the relevant parts of your followups, and correct any silliness. Haven't had the time to look, but I'm particularly interested in what Johnathan suggested because (at a glance), it seems far less clumsy than my solution #4. As usual, don't hesitate to remove things from this page, rename it, etc. -- Eric Kow http://www.loria.fr/~kow PGP Key ID: 08AC04F9 Merci de corriger mon français.
participants (8)
-
Andrea Rossato
-
Dave Bayer
-
Dave Bayer
-
Eric Y. Kow
-
Jonathan Cast
-
Levi Stephen
-
Neil Mitchell
-
Stuart Cook