patch applied (cabal): #223 part 1: Extend Distribution.Command.Simple.Option

Duncan Coutts duncan.coutts at worc.ox.ac.uk
Wed Mar 19 18:23:36 EDT 2008


Mon Mar 17 13:30:15 PDT 2008  Pepe Iborra <mnislaih at gmail.com>
  * #223 part 1: Extend Distribution.Command.Simple.Option
       so that it really represents an option and not just a flag.
       It's been renamed to OptionField as it models a field in a flags-like data structure. 
       
          data OptionField a = OptionField {
            optionName        :: Name,
            optionDescr       :: [OptDescr a] }
        
          data OptDescr a  = ReqArg Description OptFlags ArgDescr (ReadE (a->a))         (a -> [String])
                           | OptArg Description OptFlags ArgDescr (ReadE (a->a)) (a->a)  (a -> [Maybe String])
                           | ChoiceOpt [(Description, OptFlags, a->a, a -> Bool)]
  			 | BoolOpt Description OptFlags{-True-} OptFlags{-False-} (Bool -> a -> a) (a -> Bool)
        
        An option field can expand to several command line options, which are all defined together.
        For example, the compiler flag is defined as follows.
        
              option [] ["compiler"] "compiler"
                 configHcFlavor (\v flags -> flags { configHcFlavor = v })
                 (choiceOpt [ (Flag GHC, ("g", ["ghc"]), "compile with GHC")
                            , (Flag NHC, ([] , ["nhc98"]), "compile with NHC")
                            , (Flag JHC, ([] , ["jhc"]), "compile with JHC")
                            , (Flag Hugs,([] , ["hugs"]), "compile with Hugs")])
        
        We can need to use several kinds of OptDescr for the same option, as in the 
        optimization Option (really a extreme case):
        
              ,multiOption "optimization"
                 configOptimization (\v flags -> flags { configOptimization = v })
                 [optArg' "n" (Flag . flagToOptimisationLevel)
                  ....
                  ....
                          "Build with optimization (n is 0--2, default is 1)",
                  noArg (Flag NoOptimisation) []
  

    M ./Cabal.cabal +1
    M ./Distribution/ParseUtils.hs -1 +8
    A ./Distribution/ReadE.hs
    M ./Distribution/Simple/Command.hs -54 +244
    M ./Distribution/Simple/Compiler.hs -2 +2
    M ./Distribution/Simple/Setup.hs -149 +117
    M ./Distribution/Simple/SetupWrapper.hs -1 +3
    M ./Distribution/Verbosity.hs -9 +9

View patch online:

  http://darcs.haskell.org/cabal/_darcs/patches/20080317203015-ddd76-c874c23f444b4b7d6877f9b4c1adc5e956fd9e85.gz



More information about the cabal-devel mailing list