gdritter repos config-ini / 295a994
Working bidir update function + some docs Getty Ritter 7 years ago
5 changed file(s) with 570 addition(s) and 204 deletion(s). Collapse all Expand all
11 {-# LANGUAGE OverloadedStrings #-}
2 {-# LANGUAGE OverloadedLists #-}
23 {-# LANGUAGE TemplateHaskell #-}
34
45 module Main where
1213 , _confPort :: Int
1314 , _confUseEncryption :: Bool
1415 , _confHostname :: Text
16 , _confConfigFile :: Maybe Text
1517 } deriving (Eq, Show)
1618
1719 makeLenses ''Config
2224 , _confPort = 8080
2325 , _confUseEncryption = True
2426 , _confHostname = "localhost"
27 , _confConfigFile = Nothing
2528 }
2629
27 parseConfig :: IniParser Config ()
30 parseConfig :: IniSpec Config ()
2831 parseConfig = section "NETWORK" $ do
29 confUsername .= fieldOf "user" text <?>
30 [ "your username" ]
31 confPort .= fieldOf "port" number <?>
32 [ "the port in question" ]
33 confUseEncryption .= flagDef "encryption" True <?>
34 [ "whether to use encryption (defaults to true)" ]
35 confHostname .=? field "hostname" <?>
36 [ "hostname to connect to (optional)" ]
32 confUsername .= field "user" text
33 & comment [ "your username" ]
34 confPort .= field "port" number
35 & comment [ "the port in question" ]
36 confUseEncryption .= flag "encryption"
37 & defaultValue True
38 & comment [ "whether to use encryption (defaults to true)" ]
39 confHostname .= field "hostname" text
40 & defaultValue "localhost"
41 & comment [ "hostname to connect to (optional)" ]
42 confConfigFile .=? field "config file" text
43 & placeholderValue "<file path>"
3744
3845 example :: Text
3946 example = "[NETWORK]\n\
40 \user = gdritter\n\
41 \port = 8888\n"
47 \# this contains a comment\n\
48 \; and a semicolon comment\n\
49 \user: gdritter\n\
50 \port: 8888\n"
4251
4352 main :: IO ()
4453 main = do
45 print (parseIniFile sampleConfig parseConfig example)
46 putStrLn (unpack (emitIniFile sampleConfig parseConfig))
54 let s = parseIniFile sampleConfig parseConfig example
55 print s
56 case s of
57 Left err -> putStrLn err
58 Right p -> do
59 putStrLn "------------------------"
60 putStrLn (unpack (emitIniFile sampleConfig parseConfig))
61 putStrLn "------------------------"
62 putStrLn "\n"
63 let p' = p { _confPort = 9191
64 , _confHostname = "argl"
65 }
66 let pol = defaultUpdatePolicy
67 { updateGeneratedCommentPolicy =
68 CommentPolicyAddDefaultComment
69 [ "value added by application" ]
70 , updateIgnoreExtraneousFields = False
71 }
72 let up = updateIniFile p' parseConfig example pol
73 case up of
74 Left err -> putStrLn err
75 Right up' -> do
76 putStrLn "------------------------"
77 putStrLn (unpack up')
78 putStrLn "------------------------"
1 {-# LANGUAGE CPP #-}
12 {-# LANGUAGE RankNTypes #-}
23 {-# LANGUAGE OverloadedStrings #-}
34 {-# LANGUAGE ScopedTypeVariables #-}
67
78 module Data.Ini.Config.Bidir
89 (
10 -- $main
11 -- * Parsing, Serializing, and Updating Files
912 parseIniFile
1013 , emitIniFile
14 , UpdatePolicy(..)
15 , UpdateCommentPolicy(..)
16 , defaultUpdatePolicy
17 , updateIniFile
1118 -- * Bidirectional Parser Types
12 , IniParser
13 , SectionParser
19 , IniSpec
20 , SectionSpec
1421 -- * Section-Level Parsing
1522 , section
1623 -- * Field-Level Parsing
1724 , (.=)
1825 , (.=?)
19 , (<?>)
2026 , field
21 , fieldOf
22 , fieldDef
23 , fieldDefOf
2427 , flag
25 , flagDef
28 , comment
29 , defaultValue
30 , placeholderValue
31 , skipIfMissing
2632 -- * FieldValues
2733 , FieldValue(..)
2834 , text
3036 , number
3137 , bool
3238 , readable
39 , listWithSeparator
40 -- * Miscellaneous Helpers
41 , (&)
42 , Lens
3343 ) where
3444
3545 import Control.Monad.Trans.State.Strict (State, runState, modify)
46 import qualified Data.Foldable as F
47 #if __GLASGOW_HASKELL__ >= 710
48 import Data.Function ((&))
49 #endif
3650 import Data.Monoid ((<>))
37 import Data.Sequence (Seq)
51 import Data.Sequence ((<|), Seq, ViewL(..))
3852 import qualified Data.Sequence as Seq
3953 import Data.Text (Text)
4054 import qualified Data.Text as T
55 import qualified Data.Traversable as F
4156 import Data.Typeable (Typeable, Proxy(..), typeRep)
57 import GHC.Exts (IsList(..))
4258 import Text.Read (readMaybe)
4359
4460 import Data.Ini.Config.Raw
4965 lkp :: Text -> Seq (Text, a) -> Maybe a
5066 lkp t = go . Seq.viewl
5167 where go ((t', x) Seq.:< rs)
52 | t == t' = Just x
68 | T.toLower t == T.toLower t' = Just x
5369 | otherwise = go (Seq.viewl rs)
5470 go Seq.EmptyL = Nothing
5571
72 rmv :: Text -> Seq (Field s) -> Seq (Field s)
73 rmv n = Seq.filter (\ f -> T.toLower (fieldName f) /= T.toLower n)
74
75 fieldName :: Field s -> Text
76 fieldName (Field _ FieldDescription { fdName = n }) = n
77 fieldName (FieldMb _ FieldDescription { fdName = n }) = n
78
79 fieldComment :: Field s -> Seq Text
80 fieldComment (Field _ FieldDescription { fdComment = n }) = n
81 fieldComment (FieldMb _ FieldDescription { fdComment = n }) = n
82
83 #if __GLASGOW_HASKELL__ < 710
84 {- | '&' is a reverse application operator. This provides notational
85 convenience. Its precedence is one higher than that of the
86 forward application operator '$', which allows '&' to be nested
87 in '$'. -}
88 (&) :: a -> (a -> b) -> b
89 a & f = f a
90 infixl 1 &
91 #endif
92
93 -- | A value of type "FieldValue" packages up a parser and emitter
94 -- function into a single value. These are used for bidirectional
95 -- parsing and emitting of the value of a field.
5696 data FieldValue a = FieldValue
5797 { fvParse :: Text -> Either String a
98 -- ^ The function to use when parsing the value of a field; if
99 -- the parser fails, then the string will be shown as an error
100 -- message to the user.
58101 , fvEmit :: a -> Text
102 -- ^ The serializer to use when serializing a value into an INI file.
59103 }
60104
61 data OutputOptions = OutputOptions
62 { outputOrdering :: OutputOrdering
63 } deriving (Eq, Show)
64
65 data OutputOrdering
66 = SameAsSpecification
67 | SameAsInputFile
68 deriving (Eq, Show)
69
105 -- This is actually being used as a writer monad, but using a state
106 -- monad lets us avoid the space leaks. Not that those are likely to
107 -- be a problem in this application, but it's not like it cost us
108 -- none.
70109 type BidirM s a = State (Seq s) a
71110
72111 runBidirM :: BidirM s a -> Seq s
73112 runBidirM = snd . flip runState Seq.empty
74113
75 newtype IniParser s a = IniParser (BidirM (Text, Seq (Field s)) a)
114 -- | An 'IniSpec' value represents the structure of an entire
115 -- INI-format file in a declarative way. The @s@ parameter represents
116 -- the type of a Haskell structure which is being serialized to or
117 -- from.
118 newtype IniSpec s a = IniSpec (BidirM (Text, Seq (Field s)) a)
76119 deriving (Functor, Applicative, Monad)
77120
78 newtype SectionParser s a = SectionParser (BidirM (Field s) a)
121 -- | A 'SectionSpec' value represents the structure of a single
122 -- section of an INI-format file in a declarative way. The @s@
123 -- parameter represents the type of a Haskell structure which is being
124 -- serialized to or from.
125 newtype SectionSpec s a = SectionSpec (BidirM (Field s) a)
79126 deriving (Functor, Applicative, Monad)
80127
81 section :: Text -> SectionParser s () -> IniParser s ()
82 section name (SectionParser mote) = IniParser $ do
128 -- |
129 section :: Text -> SectionSpec s () -> IniSpec s ()
130 section name (SectionSpec mote) = IniSpec $ do
83131 let fields = runBidirM mote
84132 modify (Seq.|> (name, fields))
85133
86134 data Field s
87 = forall a. Field (Lens s s a a) (FieldDescription a) Bool
135 = forall a. Eq a => Field (Lens s s a a) (FieldDescription a)
136 | forall a. Eq a => FieldMb (Lens s s (Maybe a) (Maybe a)) (FieldDescription a)
88137
89138 data FieldDescription t = FieldDescription
90 { fdName :: Text
91 , fdValue :: FieldValue t
92 , fdDefault :: Maybe t
93 , fdComment :: Seq Text
139 { fdName :: Text
140 , fdValue :: FieldValue t
141 , fdDefault :: Maybe t
142 , fdComment :: Seq Text
143 , fdDummy :: Maybe Text
144 , fdSkipIfMissing :: Bool
94145 }
95146
96 (.=) :: Lens s s t t -> FieldDescription t -> SectionParser s ()
97 l .= f = SectionParser $ modify (Seq.|> fd)
98 where fd = Field l f False
99
100 (.=?) :: Lens s s t t -> FieldDescription t -> SectionParser s ()
101 l .=? f = SectionParser $ modify (Seq.|> fd)
102 where fd = Field l f True
103
104 (<?>) :: FieldDescription t -> [Text] -> FieldDescription t
105 fd <?> comment = fd { fdComment = Seq.fromList comment }
106
107 infixr 8 .=
108 infixr 8 .=?
109 infixr 9 <?>
110
111 field :: Text -> FieldDescription Text
112 field name = fieldOf name text
113
114 fieldOf :: Text -> FieldValue a -> FieldDescription a
115 fieldOf name value = FieldDescription
116 { fdName = name
117 , fdValue = value
118 , fdDefault = Nothing
119 , fdComment = Seq.empty
147 {- |
148 Associate a field description with a field. If this field
149 is not present when parsing, it will attempt to fall back
150 on a default, and if no default value is present, it will
151 fail to parse.
152
153 When serializing an INI file, this will produce all the
154 comments associated with the field description followed
155 by the value of the field in the.
156 -}
157 (.=) :: Eq t => Lens s s t t -> FieldDescription t -> SectionSpec s ()
158 l .= f = SectionSpec $ modify (Seq.|> fd)
159 where fd = Field l f
160
161 {- |
162 Associate a field description with a field of type "Maybe a".
163 When parsing, this field will be initialized to "Nothing" if
164 it is not found, and to a "Just" value if it is. When
165 serializing an INI file, this will try to serialize a value
166 -}
167 (.=?) :: Eq t => Lens s s (Maybe t) (Maybe t) -> FieldDescription t -> SectionSpec s ()
168 l .=? f = SectionSpec $ modify (Seq.|> fd)
169 where fd = FieldMb l f
170
171 {- |
172 Associate a multiline comment with a "FieldDescription". When
173 serializing a field that has a comment associated, the comment will
174 appear before the field.
175 -}
176 comment :: [Text] -> FieldDescription t -> FieldDescription t
177 comment cmt fd = fd { fdComment = Seq.fromList cmt }
178
179 {- |
180 Choose a default value to be used in case of a missing value. This will
181 only be used in the case of non-optional fields.
182 -}
183 defaultValue :: t -> FieldDescription t -> FieldDescription t
184 defaultValue def fd = fd { fdDefault = Just def }
185
186 -- | Choose a placeholder value to be displayed for optional fields.
187 -- This is used when serializing an optional Ini field: the
188 -- field will appear commented out in the output using the
189 -- placeholder text as a value, so a spec that includes
190 --
191 -- @
192 -- myLens .=? field "x" & placeholderValue "<val>"
193 -- @
194 --
195 -- will serialize into an INI file that contains the line
196 --
197 -- @
198 -- # x = <val>
199 -- @
200 --
201 -- A placeholder value will only appear in the serialized output
202 -- if the field is optional, but will be preferred over serializing
203 -- a "defaultValue". If a "placeholderValue" is not
204 placeholderValue :: Text -> FieldDescription t -> FieldDescription t
205 placeholderValue t fd = fd { fdDummy = Just t }
206
207 -- | If the field is not found in parsing, simply skip instead of
208 -- raising an error or setting anything.
209 skipIfMissing :: FieldDescription t -> FieldDescription t
210 skipIfMissing fd = fd { fdSkipIfMissing = True }
211
212 infixr 0 .=
213 infixr 0 .=?
214
215 -- | Create a description of a field by a combination of the name of
216 -- the field and a "FieldValue" describing how to parse and emit
217 -- the
218 field :: Text -> FieldValue a -> FieldDescription a
219 field name value = FieldDescription
220 { fdName = name
221 , fdValue = value
222 , fdDefault = Nothing
223 , fdComment = Seq.empty
224 , fdDummy = Nothing
225 , fdSkipIfMissing = False
120226 }
121227
122 fieldDef :: Text -> Text -> FieldDescription Text
123 fieldDef name def = fieldDefOf name def text
124
125 fieldDefOf :: Text -> a -> FieldValue a -> FieldDescription a
126 fieldDefOf name def value = FieldDescription
127 { fdName = name
128 , fdValue = value
129 , fdDefault = Just def
130 , fdComment = Seq.empty
131 }
132
133228 flag :: Text -> FieldDescription Bool
134 flag name = fieldOf name bool
135
136 flagDef :: Text -> Bool -> FieldDescription Bool
137 flagDef name def = fieldDefOf name def bool
138
139 sample :: SectionParser (Text, Int) ()
140 sample = do
141 _1 .= field "foo" <?> ["comment for foo"]
142 _2 .= fieldDefOf "bar" 0 number
143
229 flag name = field name bool
230
231 -- | A "FieldValue" implementation for parsing and reading
232 -- values according to the logic of the "Read" and "Show"
233 -- instances for that type, providing a convenient
234 -- human-readable error message if the parsing step fails.
144235 readable :: forall a. (Show a, Read a, Typeable a) => FieldValue a
145236 readable = FieldValue { fvParse = parse, fvEmit = emit }
146237 where emit = T.pack . show
152243 prx :: Proxy a
153244 prx = Proxy
154245
246 -- | A "FieldValue" implementation for parsing and reading numeric
247 -- values according to the logic of the "Read" and "Show"
248 -- instances for that type.
155249 number :: (Show a, Read a, Num a, Typeable a) => FieldValue a
156250 number = readable
157251
252 -- |
158253 text :: FieldValue Text
159254 text = FieldValue { fvParse = Right, fvEmit = id }
160255
176271 emit True = "true"
177272 emit False = "false"
178273
179 parseIniFile :: s -> IniParser s () -> Text -> Either String s
180 parseIniFile def (IniParser mote) t =
274 listWithSeparator :: IsList l => Text -> FieldValue (Item l) -> FieldValue l
275 listWithSeparator sep fv = FieldValue
276 { fvParse = fmap fromList . mapM (fvParse fv . T.strip) . T.splitOn sep
277 , fvEmit = T.intercalate sep . map (fvEmit fv) . toList
278 }
279
280 -- | Provided an initial value and an 'IniSpec' describing the
281 -- structure of an INI file, parse a 'Text' value as an INI file,
282 -- update the initial value corresponding to the fields in the INI
283 -- file, and then return the modified value.
284 parseIniFile :: s -> IniSpec s () -> Text -> Either String s
285 parseIniFile def (IniSpec mote) t =
181286 let spec = runBidirM mote
182287 in case parseIni t of
183288 Left err -> Left err
184289 Right (Ini ini) -> runSpec def (Seq.viewl spec) ini
185290
186 runSpec :: s -> Seq.ViewL (Text, Seq (Field s)) -> Seq (Text, IniSection) -> Either String s
291 -- Are you reading this source code? It's not even that gross
292 -- yet. Just you wait. This is just the regular part. 'runSpec' is
293 -- easy: we walk the spec, and for each section, find the
294 -- corresponding section in the INI file and call runFields.
295 runSpec :: s -> Seq.ViewL (Text, Seq (Field s)) -> Seq (Text, IniSection)
296 -> Either String s
187297 runSpec s Seq.EmptyL _ = Right s
188298 runSpec s ((name, fs) Seq.:< rest) ini
189299 | Just v <- lkp (T.toLower name) ini = do
191301 runSpec s' (Seq.viewl rest) ini
192302 | otherwise = Left ("Unable to find section " ++ show name)
193303
304 -- These are some inline reimplementations of "lens" operators. We
305 -- need the identity functor to implement 'set':
194306 newtype I a = I { fromI :: a }
195307 instance Functor I where fmap f (I x) = I (f x)
196308
197309 set :: Lens s t a b -> b -> s -> t
198310 set lns x a = fromI (lns (const (I x)) a)
199311
312 -- ... and we need the const functor to implement 'get':
200313 newtype C a b = C { fromC :: a }
201314 instance Functor (C a) where fmap _ (C x) = C x
202315
203316 get :: Lens s t a b -> s -> a
204317 get lns a = fromC (lns C a)
205318
319 -- Now that we've got 'set', we can walk the field descriptions and
320 -- find them. There's some fiddly logic, but the high-level idea is
321 -- that we try to look up a field, and if it exists, parse it using
322 -- the provided parser and use the provided lens to add it to the
323 -- value. We have to decide what to do if it's not there, which
324 -- depends on lens metadata and whether it's an optional field or not.
206325 runFields :: s -> Seq.ViewL (Field s) -> IniSection -> Either String s
207326 runFields s Seq.EmptyL _ = Right s
208 runFields s (Field l descr optional Seq.:< fs) sect
327 runFields s (Field l descr Seq.:< fs) sect
209328 | Just v <- lkp (fdName descr) (isVals sect) = do
210 value <- fvParse (fdValue descr) (vValue v)
329 value <- fvParse (fdValue descr) (T.strip (vValue v))
211330 runFields (set l value s) (Seq.viewl fs) sect
212331 | Just def <- fdDefault descr =
213332 runFields (set l def s) (Seq.viewl fs) sect
214 | optional =
215 runFields s (Seq.viewl fs) sect
216333 | otherwise = Left ("Unable to find field " ++ show (fdName descr))
217
218 emitIniFile :: s -> IniParser s () -> Text
219 emitIniFile s (IniParser mote) =
334 runFields s (FieldMb l descr Seq.:< fs) sect
335 | Just v <- lkp (fdName descr) (isVals sect) = do
336 value <- fvParse (fdValue descr) (T.strip (vValue v))
337 runFields (set l (Just value) s) (Seq.viewl fs) sect
338 | otherwise =
339 runFields (set l Nothing s) (Seq.viewl fs) sect
340
341 -- | Serialize a value as an INI file according to a provided
342 -- 'IniSpec'.
343 emitIniFile :: s -> IniSpec s () -> Text
344 emitIniFile s (IniSpec mote) =
220345 let spec = runBidirM mote in
221346 printIni $ Ini $ fmap (\ (name, fs) -> (name, toSection s name fs)) spec
347
348 mkComments :: Seq Text -> Seq BlankLine
349 mkComments comments =
350 fmap (\ ln -> CommentLine '#' (" " <> ln)) comments
222351
223352 toSection :: s -> Text -> Seq (Field s) -> IniSection
224353 toSection s name fs = IniSection
227356 , isStartLine = 0
228357 , isEndLine = 0
229358 , isComments = Seq.empty
230 } where toVal (Field l descr optional) =
359 } where mkIniValue val descr optional =
231360 ( fdName descr
232361 , IniValue
233 { vLineNo = 0
234 , vName = fdName descr
235 , vValue = fvEmit (fdValue descr) (get l s)
236 , vComments = BlankLine Seq.<|
237 fmap (\ ln -> CommentLine '#' (" " <> ln))
238 (fdComment descr)
362 { vLineNo = 0
363 , vName = fdName descr
364 , vValue = val
365 , vComments = BlankLine <| mkComments (fdComment descr)
239366 , vCommentedOut = optional
367 , vDelimiter = '='
240368 }
241369 )
370 toVal (Field l descr) =
371 mkIniValue (fvEmit (fdValue descr) (get l s)) descr False
372 toVal (FieldMb l descr) =
373 case get l s of
374 Nothing
375 | Just d <- fdDefault descr ->
376 mkIniValue (fvEmit (fdValue descr) d) descr True
377 | otherwise ->
378 mkIniValue "" descr True
379 Just v ->
380 mkIniValue (fvEmit (fdValue descr) v) descr True
381
382 -- | An 'UpdatePolicy' describes how to
383 data UpdatePolicy = UpdatePolicy
384 { updateAddOptionalFields :: Bool
385 -- ^ If 'True', then optional fields not included in the INI file
386 -- will be included in the updated INI file. Defaults to 'False'.
387 , updateIgnoreExtraneousFields :: Bool
388 -- ^ If 'True', then fields in the INI file that have no
389 -- corresponding description in the 'IniSpec' will be ignored; if
390 -- 'False', then those fields will return an error value. Defaults
391 -- to 'True'.
392 , updateGeneratedCommentPolicy :: UpdateCommentPolicy
393 -- ^ The policy for what to do to comments associated with
394 -- modified fields during an update. Defaults to
395 -- 'CommentPolicyNone'.
396 } deriving (Eq, Show)
397
398 -- | A set of sensible 'UpdatePolicy' defaults which keep the diffs
399 -- between file versions minimal.
400 defaultUpdatePolicy :: UpdatePolicy
401 defaultUpdatePolicy = UpdatePolicy
402 { updateAddOptionalFields = False
403 , updateIgnoreExtraneousFields = True
404 , updateGeneratedCommentPolicy = CommentPolicyNone
405 }
406
407 -- | An 'UpdateCommentPolicy' describes what comments should accompany
408 -- a field added to or modified in an existing INI file when using
409 -- 'updateIniFile'.
410 data UpdateCommentPolicy
411 = CommentPolicyNone
412 -- ^ Do not add comments to new fields
413 | CommentPolicyAddFieldComment
414 -- ^ Add the same comment which appears in the 'IniSpec' value for
415 -- the field we're adding or modifying.
416 | CommentPolicyAddDefaultComment (Seq Text)
417 -- ^ Add a consistent comment to all new fields added or modified
418 -- by an 'updateIniFile' call.
419 deriving (Eq, Show)
420
421 -- | Given a value, an 'IniSpec', and a 'Text' form of an INI file,
422 -- parse 'Text' as INI and then selectively modify the file whenever
423 -- the provided value differs from the file. This is designed to help
424 -- applications update a user's configuration automatically while
425 -- retaining the structure and comments of a user's application,
426 -- ideally in a way which produces as few changes as possible to the
427 -- resulting file (so that, for example, the diff between the two
428 -- should be as small as possible.)
429 --
430 -- A field is considered to have "changed" if the parsed
431 -- representation of the field as extracted from the textual INI file
432 -- is not equal to the corresponding value in the provided
433 -- structure. Changed fields will retain their place in the overall
434 -- file, while newly added fields (for example, fields which have
435 -- been changed from a default value) will be added to the end of the
436 -- section in which they appear.
437 updateIniFile :: s -> IniSpec s () -> Text -> UpdatePolicy -> Either String Text
438 updateIniFile s (IniSpec mote) t pol =
439 let spec = runBidirM mote
440 in case parseIni t of
441 Left err -> Left ("Error parsing existing INI file: " ++ err)
442 Right (Ini ini) -> do
443 ini' <- updateIniSections s ini spec pol
444 return (printIni (Ini ini'))
445
446 updateIniSections :: s -> Seq (Text, IniSection)
447 -> Seq (Text, Seq (Field s))
448 -> UpdatePolicy
449 -> Either String (Seq (Text, IniSection))
450 updateIniSections s sections fields pol =
451 F.for sections $ \ (name, sec) -> do
452 let err = (Left ("Unexpected top-level section: " ++ show name))
453 spec <- maybe err Right (lkp name fields)
454 newVals <- updateIniSection s (isVals sec) spec pol
455 return (name, sec { isVals = newVals })
456
457 updateIniSection :: s -> Seq (Text, IniValue) -> Seq (Field s)
458 -> UpdatePolicy -> Either String (Seq (Text, IniValue))
459 updateIniSection s values fields pol = go (Seq.viewl values) fields
460 where go ((t, val) :< vs) fs =
461 -- For each field, we need to fetch the description of the
462 -- field in the spec
463 case F.find (\ f -> fieldName f == t) fs of
464 Just f@(Field l descr) ->
465 -- if it does exist, then we need to find out whether
466 -- the field has changed at all. We can do this with the
467 -- provided lens, and check it against the INI file
468 -- we've got. There's a minor complication: there's
469 -- nothing that forces the user to provide the same INI
470 -- file we originally parsed! One side-effect means that
471 -- the parsed INI file might not actually have a valid
472 -- field according to the field parser the user
473 -- provides. In that case, we'll assume the field is
474 -- outdated, and update it with the value in the
475 -- provided structure.
476 if Right (get l s) == fvParse (fdValue descr) (T.strip (vValue val))
477 -- if the value in the INI file parses the same as
478 -- the one in the structure we were passed, then it
479 -- doesn't need any updating, and we keep going,
480 -- removing the field from our list
481 then ((t, val) <|) `fmap` go (Seq.viewl vs) (rmv t fs)
482 -- otherwise, we've got a new updated value! Let's
483 -- synthesize a new element, using our comment policy
484 -- to comment it accordingly. (This pattern is
485 -- partial, but we should never have a situation
486 -- where it returns Nothing, because we already know
487 -- that we've matched a Field!)
488 else let Just nv = mkValue t f (vDelimiter val)
489 in ((t, nv) <|) `fmap` go (Seq.viewl vs) (rmv t fs)
490 -- And we have to replicate the logic for the FieldMb
491 -- case, because (as an existential) it doesn't really
492 -- permit us usable abstractions here. See the previous
493 -- comments for descriptions of the cases.
494 Just f@(FieldMb l descr) ->
495 let parsed = fvParse (fdValue descr) (T.strip (vValue val))
496 in if Right (get l s) == fmap Just parsed
497 then ((t, val) <|) `fmap` go (Seq.viewl vs) (rmv t fs)
498 -- this is in the only case where the FieldMb case
499 -- differs: we might NOT have a value in the
500 -- structure. In that case, we remove the value
501 -- from the file, as well!
502 else case mkValue t f (vDelimiter val) of
503 Just nv -> ((t, nv) <|) `fmap` go (Seq.viewl vs) (rmv t fs)
504 Nothing -> go (Seq.viewl vs) (rmv t fs)
505 -- Finally, if we can't find any description of the field,
506 -- then we might skip it or throw an error, depending on
507 -- the policy the user wants.
508 Nothing
509 | updateIgnoreExtraneousFields pol ->
510 ((t, val) <|) `fmap` go (Seq.viewl vs) fs
511 | otherwise -> Left ("Unexpected field: " ++ show t)
512 -- Once we've gone through all the fields in the file, we need
513 -- to see if there's anything left over that should be in the
514 -- file. We might want to include dummy values for things that
515 -- were left out, but if we have any non-optional fields left
516 -- over, then we definitely need to include them.
517 go EmptyL fs = return (finish (Seq.viewl fs))
518 finish (f@(Field l descr) :< fs)
519 | or [ updateAddOptionalFields pol
520 , fdDefault descr /= Just (get l s)
521 ]
522 , Just val <- mkValue (fieldName f) f '=' =
523 (fieldName f, val) <| finish (Seq.viewl fs)
524 | otherwise = finish (Seq.viewl fs)
525 finish (f@(FieldMb _ descr) :< fs)
526 | not (fdSkipIfMissing descr) && fdDefault descr == Nothing
527 , Just val <- mkValue (fieldName f) f '=' =
528 (fieldName f, val) <| finish (Seq.viewl fs)
529 | updateAddOptionalFields pol
530 , Just val <- mkValue (fieldName f) f '=' =
531 (fieldName f, val) <| finish (Seq.viewl fs)
532 | otherwise = finish (Seq.viewl fs)
533 -- If there's nothing left, then we can return a final value!
534 finish EmptyL = Seq.empty
535 mkValue t fld delim =
536 let comments = case updateGeneratedCommentPolicy pol of
537 CommentPolicyNone -> Seq.empty
538 CommentPolicyAddFieldComment ->
539 mkComments (fieldComment fld)
540 CommentPolicyAddDefaultComment cs ->
541 mkComments cs
542 val = IniValue
543 { vLineNo = 0
544 , vName = t <> " "
545 , vValue = ""
546 , vComments = comments
547 , vCommentedOut = False
548 , vDelimiter = delim
549 }
550 in case fld of
551 Field l descr ->
552 Just (val { vValue = " " <> fvEmit (fdValue descr) (get l s) })
553 FieldMb l descr ->
554 case get l s of
555 Just v -> Just (val { vValue = " " <> fvEmit (fdValue descr) v })
556 Nothing -> Nothing
557
242558
243559 -- DELETE ME LATER
244560
252568 _2 = lens snd (\ b (a, _) -> (a, b))
253569
254570
255 -- $main
256 -- This module is an alternate API used for parsing INI files.
257 -- unlike the standard API, it is bidirectional: it can be
258 -- used to emit an INI or even produce a modified INI file
259 -- with minimal modification.
260 --
261 -- This module is designed to be used with lenses: instead of
262 -- generating a new value as a result of parsing, we start
263 -- with a fully constructed value and then associate each field
264 -- of the INI file with a lens into that structure. Among other
265 -- things, this introduces more flexibility in terms of how we
266 -- organize both the configuration file and the data type that
267 -- represents the configuration. Consider the same example code
268 -- that appears in the documentation for the "Data.Ini.Config"
269 -- module, which parses a configuration file like this:
270 --
271 -- > [NETWORK]
272 -- > host = example.com
273 -- > port = 7878
274 -- >
275 -- > [LOCAL]
276 -- > user = terry
277 --
278 -- In that example, we split the configuration into a @NetworkConfig@
279 -- and a @LocalConfig@ type to mirror the configuration file's use of
280 -- @[LOCAL]@ and @[NETWORK]@ sections, but we might want to keep the
281 -- configuration data type as a single flat record, in which case our
282 -- parsing code becomes more awkward:
283 --
284 -- > data Config = Config
285 -- > { _cfHost :: String
286 -- > , _cfPort :: Int
287 -- > , _cfUser :: Text
288 -- > } deriving (Eq, Show)
289 -- >
290 -- > -- this is not ideal
291 -- > configParser :: IniParser Config
292 -- > configParser = do
293 -- > (host, port) <- section "NETWORK" $ do
294 -- > host <- fieldOf "host" string
295 -- > port <- fieldOf "port" number
296 -- > return (host, port)
297 -- > user <- section "LOCAL" $ field "user"
298 -- > return (Config host port user)
299 --
300 -- We could also use repeated invocations of 'section', but this
301 -- also makes our parsing code a lot uglier and involves unnecessary
302 -- repetition of the @\"NETWORK\"@ literal:
303 --
304 -- > -- this is kind of ugly
305 -- > configParser :: IniParser Config
306 -- > configParser = do
307 -- > host <- section "NETWORK" $ fieldOf "host" string
308 -- > port <- section "NETWORK" $ fieldOf "port" number
309 -- > user <- section "LOCAL" $ field "user"
310 -- > return (Config host port user)
311 --
312 -- Assuming that we generate lenses for the @Config@ type above,
313 -- then we can use the lens-based combinators in this module to
314 -- write terser parsing code by providing which lens to update
315 -- along with each field:
316 --
317 -- > configSpec :: IniSpec Config ()
318 -- > configSpec = do
319 -- > sectionSt "NETWORK" $ do
320 -- > cfHost .= field "host" string
321 -- > cfPort .= fieldOf "port" number
322 -- > sectionSt "LOCAL" $ do
323 -- > cfUser .= field "user"
324 --
325 -- Additionally, given a value of type @Config@, we can use the
326 -- same specification to emit an INI file, which is useful for
327 -- generating a valid sample configuration. To help with this,
328 -- we can rewrite the spec to make use of the @<?>@ operator,
329 -- which associates the field with a comment block that will
330 -- be printed above the field in the generated INI file.
331 --
332 -- > configSpec :: IniSpec Config ()
333 -- > configSpec = do
334 -- > sectionSt "NETWORK" $ do
335 -- > cfHost .= field "host" string <?> [ "the host" ]
336 -- > cfPort .= fieldOf "port" number <?> [ "the port" ]
337 -- > sectionSt "LOCAL" $ do
338 -- > cfUser .= field "user" <?> [ "the username" ]
339 --
340 -- Using an existing @Config@ value here, we can produce a sample
341 -- configuration:
571 {- | $main
572 This module is an alternate API used for parsing INI files.
573 unlike the standard API, it is bidirectional: it can be also used
574 to emit an INI, or even to produce an updated INI file with minimal
575 modification to the textual file provided.
576
577 This module makes some extra assumptions about your configuration type
578 and the way you interact with it: in particular, it assumes that you
579 have lenses for all the fields you're parsing, and that you have some
580 kind of sensible default value of that configuration. Instead of
581 providing combinators which can extract and parse a field of an INI
582 file into a value, the bidirectional API has you declaratively
583 associate lenses into your structure with descriptions of their
584 corresponding fields in INI files.
585
586 Consider the following example INI file:
587
588 > [NETWORK]
589 > host = example.com
590 > port = 7878
591 >
592 > [LOCAL]
593 > user = terry
594
595 We'd like to parse this INI file into a @Config@ type which we've
596 defined like this, using whatever "lens"-like library we prefer:
597
598 > data Config = Config
599 > { _cfHost :: String
600 > , _cfPort :: Int
601 > , _cfUser :: Maybe Text
602 > } deriving (Eq, Show)
603 >
604 > ''makeLenses Config
605
606 We define a basic specification of type @IniSpec Config ()@ by using
607 the provided combinators to declare sections and then associate fields
608 in those sections with lenses into our @Config@ structure.
609
610 > configSpec :: IniSpec Config ()
611 > configSpec = do
612 > section "NETWORK" $ do
613 > cfHost .= field "host" string
614 > cfPost .= field "port" number
615 > section "LOCAL" $ do
616 > cfUser .=? field "user" text
617
618 The '.=' operator associates a field with a lens directly, and the
619 '.=?' operator associates a field with a lens to a 'Maybe' value,
620 setting that value to 'Nothing' if the field does not appear in the
621 configuration. Each 'field' invocation must include the name of the
622 field and a representation of the type of that field: 'string',
623 'number', and 'text' in the above snippet are all values of type
624 'FieldValue', which bundles together a parser and serializer for a
625 value.
626
627 We can also provide extra metadata about a field, allowing it to be
628 skipped in parsing, or to provide an explicit default value, or to
629 include an explanatory comment for that value to be used when we
630 serialize an INI file. These are conventionally applied to the field
631 using the '&' operator:
632
633 > configSpec :: IniSpec Config ()
634 > configSpec = do
635 > section "NETWORK" $ do
636 > cfHost .= field "host" string
637 > & comment ["A comment about the host"]
638 > cfPost .= field "port" number
639 > & defaultValue 9999
640 > section "LOCAL" $ do
641 > cfUser .=? field "user" text
642
643 In order to parse an INI file, we need to provide a default value of
644 our underlying @config@ type on which we can perform our 'Lens'-based
645 updates.
646 -}
4646 -- ^ Right now, this will never show up in a parsed INI file, but
4747 -- it's used when emitting a default INI file: it causes the
4848 -- key-value line to include a leading comment as well.
49 , vDelimiter :: Char
4950 } deriving (Eq, Show)
5051
5152 -- | We want to keep track of the whitespace/comments in between KV
99100 pPairs name start leading prevs comments pairs = newPair <|> finishedSection
100101 where
101102 newPair = do
102 pair <- pPair comments
103 (n, pair) <- pPair comments
103104 rs <- sBlanks
104 pPairs name start leading prevs rs (pairs Seq.|> (vName pair, pair))
105 pPairs name start leading prevs rs (pairs Seq.|> (n, pair))
105106 finishedSection = do
106107 end <- getCurrentLine
107108 let newSection = IniSection
113114 }
114115 pSections comments (prevs Seq.|> (T.toLower name, newSection))
115116
116 pPair :: Seq BlankLine -> Parser IniValue
117 pPair :: Seq BlankLine -> Parser (Text, IniValue)
117118 pPair leading = do
118119 pos <- getCurrentLine
119120 key <- T.pack `fmap` some (noneOf "[]=:")
120 void (oneOf ":=")
121 delim <- oneOf ":="
121122 val <- T.pack `fmap` manyTill anyChar eol
122 return IniValue
123 { vLineNo = pos
124 , vName = T.strip key
125 , vValue = T.strip val
126 , vComments = leading
127 , vCommentedOut = False
128 }
123 return ( T.strip key
124 , IniValue
125 { vLineNo = pos
126 , vName = key
127 , vValue = val
128 , vComments = leading
129 , vCommentedOut = False
130 , vDelimiter = delim
131 } )
129132
130133 getCurrentLine :: Parser Int
131134 getCurrentLine = (fromIntegral . unPos . sourceLine) `fmap` getPosition
147150 F.foldMap buildComment (vComments val) <>
148151 (if vCommentedOut val then Builder.fromString "# " else mempty) <>
149152 Builder.fromText (vName val) <>
150 Builder.fromString " = " <>
153 Builder.singleton (vDelimiter val) <>
151154 Builder.fromText (vValue val) <>
152155 Builder.singleton '\n'
55 module Data.Ini.Config
66 (
77 -- $main
8 -- * Running Parsers
8 -- * Parsing Files
99 parseIniFile
1010 -- * Parser Types
1111 , IniParser
2828 , number
2929 , string
3030 , flag
31 , listWithSeparator
3132 ) where
3233
3334 import Control.Applicative (Applicative(..), Alternative(..))
3940 import Data.Text (Text)
4041 import qualified Data.Text as T
4142 import Data.Typeable (Typeable, Proxy(..), typeRep)
43 import GHC.Exts (IsList(..))
4244 import Text.Read (readMaybe)
4345
4446 lkp :: Text -> Seq (Text, a) -> Maybe a
279281 number :: (Num a, Read a, Typeable a) => Text -> Either String a
280282 number = readable
281283
282 -- | Convert a textua value to the appropriate string type. This will
284 -- | Convert a textual value to the appropriate string type. This will
283285 -- never fail.
284286 --
285287 -- >>> string "foo" :: Either String String
315317 "n" -> Right False
316318 _ -> Left ("Unable to parse " ++ show s ++ " as a boolean")
317319
320 -- | Convert a reader for a value into a reader for a list of those
321 -- values, separated by a chosen separator. This will split apart
322 -- the string on that separator, get rid of leading and trailing
323 -- whitespace on the individual chunks, and then attempt to parse
324 -- each of them according to the function provided, turning the
325 -- result into a list.
326 --
327 -- This is overloaded with the "IsList" typeclass, so it can be
328 -- used transparently to parse other list-like types.
329 --
330 -- >>> listWithSeparator "," number "2, 3, 4" :: Either String [Int]
331 -- Right [2,3,4]
332 -- >>> listWithSeparator " " number "7 8 9" :: Either String [Int]
333 -- Right [7,8,9]
334 -- >>> listWithSeparator ":" string "/bin:/usr/bin" :: Either String [FilePath]
335 -- Right ["/bin","/usr/bin"]
336 -- >>> listWithSeparator "," number "7 8 9" :: Either String [Int]
337 -- Left "Unable to parse \"2 3 4\" as a value of type Int"
338 listWithSeparator :: (IsList l)
339 => Text
340 -> (Text -> Either String (Item l))
341 -> Text -> Either String l
342 listWithSeparator sep rd =
343 fmap fromList . mapM (rd . T.strip) . T.splitOn sep
318344
319345 -- $setup
320346 --
9696 name <- T.strip `fmap` str
9797 val <- str
9898 cs <- Seq.fromList `fmap` listOf comment
99 return (name, I2.IniValue 0 name val cs False)
99 return (name, I2.IniValue 0 name val cs False '=')
100100 comment = oneof [ return I2.BlankLine
101101 , do { c <- elements ";#"
102102 ; txt <- str