[Haskell-cafe] List-based ini parser?

S. Doaitse Swierstra doaitse at swierstra.net
Sat Jul 4 07:37:50 UTC 2015


Maybe you can get some inspiration form the uu-options package. It uses the  interleaved parsers from uu-parsinglib/uu-interleaved and easily handles options which are “distributed” over a several individual entries. It is directed towards command line options, but changing it so it works for similar formats should not be a problem.

The included Demo file shows its capabilities, and the error messages you get in case the input is incorrect. Note how the various integers are collected automatically, and how the order of the fileds in the input does not matter either,

 Doaitse



data Prefers  =  Agda | Haskell deriving Show
 <> <>data Address  =  Address  {  city_ :: String
 <>                          ,  street_ :: String} 
 <>                 deriving Show
 <> <>data Name     =  Name  {  name_:: String 
 <>                       ,  prefers_:: Prefers
 <>                       ,  ints_ :: [Int]
 <>                       ,  address_ :: Address} 
 <>                 deriving Show
 <>
 <>$(deriveLenses ''Name)
 <>$(deriveLenses ''Address)
 <>
 <> <>instance ShowParserType Prefers where
 <>   showType p = " <Agda | Haskell> "
 <>
 <> <>-- The next thing to do is to specify a initial record containing the default values:
 <>defaults = Name  "Atze" Haskell [] 
 <>                 (Address  "Utrecht" 
 <>                           "Princetonplein")
 <>
 <>-- Next we define the parser for the options, by specifying for each field what may be specified:
 <>
 <> <>oName =
 <>                 name     `option`   ("name",       pString,      "Name")
 <>            <>   ints     `options`  ("ints",       pNaturalRaw,  "A couple of numbers") 
 <>            <>   prefers  `choose`   [("agda",      Agda,         "in case you prefer Agda")
 <>                                     ,("haskell",   Haskell,      "in case you prefer Haskell")
 <>                                     ] 
 <>            <>   address  `field`
 <>                           (   city     `option`  ("city",   pString, "Home city")  
 <>                           <>  street   `option`  ("street" ,pString, "Home Street" )
 <>                           )
 <>{-
 <>-- | The function `main` may serve as a template for your own option handling. You can also use this module to see what  the effectis  of the various ways of passing options
 <>-- >>> ./Demo -i1 --ints 2 --street=Zandlust -a -nDoaitse -i3 --ints=4 --city=Tynaarlo
 <>--     Name {name_ = "Doaitse", prefers_ = Agda, ints_ = [1,2,3,4], address_ = Address {city_ = "Tynaarlo", street_ = "Zandlust"}}
 <>--
 <>-- >>> ./Demo -i1 --ints 2 --street=Zandlust --name Doaitse -i3 --ints=4 --city=Tynaarlo
 <>--     --name           [Char]         optional  Name
 <>--     --ints           Int            recurring A couple of numbers
 <>--     Choose at least one from(
 <>--     --agda                          required  In case you prefer Agda
 <>--     --haskell                       required  In case you prefer Haskell
 <>--     )
 <>--     --city           [Char]         optional  Home city
 <>--     --street         [Char]         optional  Home Street
 <>--     --
 <>--     --  Correcting steps:
 <>--     --    Inserted  "-a" at position 70 expecting one of ["--agda", "--agda=", "--haskell", "--haskell=", "--ints=", "--ints", "-i", "-h", "-a"]
 <>--     --    Inserted  "\EOT" at position 70 expecting "\EOT"
 <>
 <>
 <>main  ::IO ()
 <>main = do args  <- getArgs
 <>          case run  defaults oName  (concat (map  (++ "\EOT") args)) of
 <>            Left a        -> case a of
 <>                                   Succes v -> print v
 <>                                   Help   t -> putStrLn t
 <>            Right errors  -> putStrLn errors
 <>
 <>-- | The function `demo` can be used from within ghci:
 <>-}
 <>
 <>-- >>> demo ["-i2", "--street=Zandlust", "--ints=5", "-nAtze", "--city=Houten", "--agda", "-i3"]
 <>--     Name {name_ = "Atze", prefers_ = Agda, ints_ = [2,5,3], address_ = Address {city_ = "Houten", street_ = "Zandlust"}}
 <> 
 <> <>demo :: [[Char]] -> IO ()
 <>demo args =  case run  defaults oName  (concat (map  (++ "\EOT") args)) of
 <>                  Left a        -> case a of
 <>                                   Succes v -> print v
 <>                                   Help   t -> putStrLn t
 <>                  Right errors  -> putStr errors


> On 04 Jul 2015, at 1:26 , Mike Meyer <mwm at mired.org> wrote:
> 
> Ok,I've looked at the packages google and hackage found (ini, hsini & ConfigFile), and can't use any of them for dealing with the ini files I'm being handed.
> 
> The problem is they all parse the config file into Maps, and that doesn't seem to be an option. I need lists, because I have multiple sections with the same name that turn into a list of objects, as well as sections that can have multiple options with the same name that turn into multiple objects.
> 
> Any chance I overlooked a parser? Or maybe some parsing options in ConfigFile?
> 
> Any other advice on a library to do this?
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe

-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20150704/08488d23/attachment-0001.html>


More information about the Haskell-Cafe mailing list