[Haskell] Re: High-level technique for program options handling
Ketil Malde
ketil+haskell at ii.uib.no
Wed Jan 28 15:22:59 EST 2004
(Reply-To: haskell-cafe)
Alastair Reid <alastair at reid-consulting-uk.ltd.uk> writes:
>> I have a question about error reporting. You use 'error' quite often. I
>> think that this can cause errors to pop up at strange moments during
>> program evaluation.
> You're right, it can lead to late error messages. For example, if
> two output files are specified then the program might read its
> input, spend some time processing and only report an error after
> some considerable time has passed. (I haven't actually seen this
> happen but I'm sure it would.)
I'm not sure this brings anything new on the table, but after this
thread I went back and reworked some of my option handling code.
Hopefully it will either be an inspirational example, or provide me
with feedback on my grave errors and mistakes :-) here it is:
------------------------------------------------------------
>-- Args is a record for the arguments, easily accessible by field
>-- in the program proper
>
>data Output = G | C | X deriving (Read,Eq)
>data Args = Args { kval :: Int,
> output :: Output,
> writer :: String -> IO (),
> parser :: Fasta.FHParser}
>
>-- usage prints using "error", this is perhaps Not Nice? (it
>-- makes it rather difficult to print usage and exit with success,
>-- should that happen to be important)...
>
>usage :: [String] -> a
>usage errs = error (usageInfo (concat errs ++
> "\nUsage: xegen -k <kval> [-u] -{G|C|X} [-o FILE] <filename>\n")
> options)
>
>-- ...but since usage has polymorphic type, I can use it to
>-- initialize required fields in the default argument struct:
>
>defaultArgs = Args
> { kval = usage ["You must specify a k value"]
> , output = usage ["Please specify -K, C, or X"]
> , writer = putStr, parser = bmfparser }
>
>-- mkK is used to parse the argument string for the -k option
>-- which needs to be an integer. This is IMHO superior to getting an
>-- anonymous "Prelude.read: no parse" message
>
>-- add a k value to p
>mkK :: Args -> String -> Args
>mkK p s = p {kval = if (and $ map isDigit s) then read s
> else usage ["The k value must be an integer"]}
>
>-- and here's the table of options
>
>options :: [OptDescr (Args -> Args)]
>options = [
> Option ['k'] ["word-size"] (ReqArg (\s p -> mkK p s) "INT")
> "Word size"
> ,Option ['G'] ["graph-output"] (NoArg (\p -> p { output = G }))
> "Output the graph in GraphViz format"
> ,Option ['C'] ["consensus-output"] (NoArg (\p -> p { output = C }))
> "Output assembled consensus sequences"
> ,Option ['X'] ["exons-output"] (NoArg (\p -> p { output = X }))
> "Output the (concatenated) exons"
> ,Option ['u'] ["input-upper"] (NoArg (\p -> p { parser = ugparser }))
> "accept only upper case characters"
> ,Option ['o'] ["output"] (ReqArg (\s p -> p { writer = writeFile s }) "FILE")
> "output file name (default is stdout)"
> ]
>
>-- comments are most welcome!
------------------------------------------------------------
> (Another issue with error reporting is that I should probably print the
> 'usage' message whenever flags are incorrectly omitted, duplicated, etc.
I think that's achieved in the above. And I think the late error
message problem can be solved by making sure the Args struct is
entirely evaluated before any "real code" is run.
-kzm
--
If I haven't seen further, it is by standing in the footprints of giants
More information about the Haskell
mailing list