Bulat Ziganshin wrote:
Hello Tomasz,
[snip]
ultimately, the main problem of all options-parsing stuff i ever seen,
is requirement to repeat option definition many times. if i have, say,
40 options, then i need to maintain 3 to 5 program fragments that deal
with each option. something like this:

data Options = Options { r :: Bool,
                        x :: Int
                        ....
                      }

options = { "r", "description"
           ....
         }

main = do list <- getOpts options cmdline
         let options = Options { r = findBoolOption list "r",
                                 x = findIntOption list "x",
                                 ....
                               }


If it is not necessary to specify a specific command letter for each option, then perhaps options could be composed by something like (following code untested):

class OptionClass a where
     setOption :: a -> String -> IO ()
     getOptionDescription :: a -> String -> String

data Option = forall a. OptionClass a => Option a
instance OptionClass Option where
     setOption (Option a) = setOption a
     getOptionDescription (Option a ) opt = getOptionDescription a opt

data ComposedOption = ComposedOption _ [Option]
instance OptionClass ComposedOption where
setOption (ComposedOption _ os) (c:cs) = setOption (os !! (fromEnum c - fromEnum 'a')) cs
     getOptionDescription (ComposedOption description os) (c:cs)=
description ++ "." ++ getOptionDescription (os !! (fromEnum x - fromEnum 'a')) cs

Then each element in a module that needs an option makes its own instance of the existential eg

data ModOption1 = ModOption1
data ModOption2 = ModOption2

instance OptionClass ModOption1 where
    setOption ModOption1 s = case s of
[] -> do -- set default value s -> do -- parse s and set accordingly

    getOptionDescription ModOption1 optvalue =
-- description of this option, possibly clarified to the specific example of optvalue -- "would read from the file 'foo.txt'" if optvalue == " foo.txt"

moduleOptions = ComposedOption "My module" [ModOption1, ModOption2]

Then in main, do:

allOptions = ComposedOption "Name of program" [Module1.moduleOptions, Module2.moduleOptions, ...]

A disadvantage would be that the options would involve multiple letters in general eg -aaaab -aba etc when there is a lot of nesting, but an advantage is that it allows libraries requiring options and code using such libraries to be written in a modular way.

Best regards, Brian.
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to