gdritter repos config-ini / 85ac32c
Lots of documentation fixes + optional sections Getty Ritter 6 years ago
3 changed file(s) with 170 addition(s) and 66 deletion(s). Collapse all Expand all
1414 , _confUseEncryption :: Bool
1515 , _confHostname :: Text
1616 , _confConfigFile :: Maybe Text
17 , _confPath :: [Text]
1718 } deriving (Eq, Show)
1819
1920 makeLenses ''Config
2526 , _confUseEncryption = True
2627 , _confHostname = "localhost"
2728 , _confConfigFile = Nothing
29 , _confPath = ["/bin"]
2830 }
2931
3032 configSpec :: IniSpec Config ()
4143 & comment [ "hostname to connect to (optional)" ]
4244 confConfigFile .=? field "config file" text
4345 & placeholderValue "<file path>"
46 confPath .= field "path" (listWithSeparator ":" text)
47 & skipIfMissing
48 & comment [ "a colon-separated path list" ]
4449
4550 example :: Text
4651 example = "[NETWORK]\n\
4752 \# this contains a comment\n\
4853 \; and a semicolon comment\n\
4954 \user: gdritter\n\
50 \port: 8888\n"
55 \port: 8888\n\
56 \path= /bin:/usr/bin\n"
5157
5258 main :: IO ()
5359 main = do
6268 putStrLn "\n"
6369 let p' = p { _confPort = 9191
6470 , _confHostname = "argl"
71 , _confPath = "/usr/sbin" : _confPath p
6572 }
6673 let pol = defaultUpdatePolicy
6774 { updateGeneratedCommentPolicy =
99 (
1010 -- $main
1111 -- * Parsing, Serializing, and Updating Files
12 -- $using
1213 parseIniFile
1314 , emitIniFile
1415 , UpdatePolicy(..)
1617 , defaultUpdatePolicy
1718 , updateIniFile
1819 -- * Bidirectional Parser Types
20 -- $types
1921 , IniSpec
2022 , SectionSpec
2123 -- * Section-Level Parsing
24 -- $sections
2225 , section
26 , sectionOpt
2327 -- * Field-Level Parsing
28 -- $fields
29 , FieldDescription
2430 , (.=)
2531 , (.=?)
2632 , field
3036 , placeholderValue
3137 , skipIfMissing
3238 -- * FieldValues
39 -- $fieldvalues
3340 , FieldValue(..)
3441 , text
3542 , string
3744 , bool
3845 , readable
3946 , listWithSeparator
47 , pairWithSeparator
4048 -- * Miscellaneous Helpers
49 -- $misc
4150 , (&)
4251 , Lens
4352 ) where
115124 -- INI-format file in a declarative way. The @s@ parameter represents
116125 -- the type of a Haskell structure which is being serialized to or
117126 -- from.
118 newtype IniSpec s a = IniSpec (BidirM (Text, Seq (Field s)) a)
127 newtype IniSpec s a = IniSpec (BidirM (Section s) a)
119128 deriving (Functor, Applicative, Monad)
120129
121130 -- | A 'SectionSpec' value represents the structure of a single
125134 newtype SectionSpec s a = SectionSpec (BidirM (Field s) a)
126135 deriving (Functor, Applicative, Monad)
127136
128 -- |
137 -- | Define the specification of a top-level INI section.
129138 section :: Text -> SectionSpec s () -> IniSpec s ()
130139 section name (SectionSpec mote) = IniSpec $ do
131140 let fields = runBidirM mote
132 modify (Seq.|> (name, fields))
133
141 modify (Seq.|> Section name fields False)
142
143 -- | Define the specification of an optional top-level INI section. If
144 -- this section does not appear in a parsed INI file, then it will be
145 -- skipped.
146 sectionOpt :: Text -> SectionSpec s () -> IniSpec s ()
147 sectionOpt name (SectionSpec mote) = IniSpec $ do
148 let fields = runBidirM mote
149 modify (Seq.|> Section name fields True)
150
151 data Section s = Section Text (Seq (Field s)) Bool
152
153 -- | A "Field" is a description of
134154 data Field s
135155 = forall a. Eq a => Field (Lens s s a a) (FieldDescription a)
136156 | forall a. Eq a => FieldMb (Lens s s (Maybe a) (Maybe a)) (FieldDescription a)
137157
158 -- | A 'FieldDescription' is a declarative representation of the
159 -- structure of a field. This includes the name of the field and the
160 -- 'FieldValue' used to parse and serialize values of that field, as
161 -- well as other metadata that might be needed in the course of
162 -- parsing or serializing a structure.
138163 data FieldDescription t = FieldDescription
139164 { fdName :: Text
140165 , fdValue :: FieldValue t
214239
215240 -- | Create a description of a field by a combination of the name of
216241 -- the field and a "FieldValue" describing how to parse and emit
217 -- the
242 -- values associated with that field.
218243 field :: Text -> FieldValue a -> FieldDescription a
219244 field name value = FieldDescription
220245 { fdName = name
225250 , fdSkipIfMissing = False
226251 }
227252
253 -- | Create a description of a 'Bool'-valued field.
228254 flag :: Text -> FieldDescription Bool
229255 flag name = field name bool
230256
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.
257 -- | A "FieldValue" for parsing and serializing values according to
258 -- the logic of the "Read" and "Show" instances for that type,
259 -- providing a convenient human-readable error message if the
260 -- parsing step fails.
235261 readable :: forall a. (Show a, Read a, Typeable a) => FieldValue a
236262 readable = FieldValue { fvParse = parse, fvEmit = emit }
237263 where emit = T.pack . show
243269 prx :: Proxy a
244270 prx = Proxy
245271
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.
272 -- | Represents a numeric field whose value is parsed according to the
273 -- 'Read' implementation for that type, and is serialized according to
274 -- the 'Show' implementation for that type.
249275 number :: (Show a, Read a, Num a, Typeable a) => FieldValue a
250276 number = readable
251277
252 -- |
278 -- | Represents a field whose value is a 'Text' value
253279 text :: FieldValue Text
254280 text = FieldValue { fvParse = Right, fvEmit = id }
255281
282 -- | Represents a field whose value is a 'String' value
256283 string :: FieldValue String
257284 string = FieldValue { fvParse = Right . T.unpack, fvEmit = T.pack }
258285
286 -- | Represents a field whose value is a 'Bool' value. This parser is
287 -- case-insensitive, and matches the words @true@, @false@, @yes@, and
288 -- @no@, as well as single-letter abbreviations for all of the
289 -- above. This will serialize as @true@ for 'True' and @false@ for
290 -- 'False'.
259291 bool :: FieldValue Bool
260292 bool = FieldValue { fvParse = parse, fvEmit = emit }
261293 where parse s = case T.toLower s of
271303 emit True = "true"
272304 emit False = "false"
273305
306 -- | Represents a field whose value is a sequence of other values
307 -- which are delimited by a given string, and whose individual values
308 -- are described by another 'FieldValue' value. This uses GHC's
309 -- `IsList` typeclass to convert back and forth between sequence
310 -- types.
274311 listWithSeparator :: IsList l => Text -> FieldValue (Item l) -> FieldValue l
275312 listWithSeparator sep fv = FieldValue
276313 { fvParse = fmap fromList . mapM (fvParse fv . T.strip) . T.splitOn sep
277314 , fvEmit = T.intercalate sep . map (fvEmit fv) . toList
315 }
316
317 -- | Represents a field whose value is a pair of two other values
318 -- separated by a given string, whose individual values are described
319 -- by two different 'FieldValue' values.
320 pairWithSeparator :: FieldValue l -> Text -> FieldValue r -> FieldValue (l, r)
321 pairWithSeparator left sep right = FieldValue
322 { fvParse = \ t ->
323 let (leftChunk, rightChunk) = T.breakOn sep t
324 in do
325 x <- fvParse left leftChunk
326 y <- fvParse right rightChunk
327 return (x, y)
328 , fvEmit = \ (x, y) -> fvEmit left x <> sep <> fvEmit right y
278329 }
279330
280331 -- | Provided an initial value and an 'IniSpec' describing the
292343 -- yet. Just you wait. This is just the regular part. 'runSpec' is
293344 -- easy: we walk the spec, and for each section, find the
294345 -- corresponding section in the INI file and call runFields.
295 runSpec :: s -> Seq.ViewL (Text, Seq (Field s)) -> Seq (Text, IniSection)
346 runSpec :: s -> Seq.ViewL (Section s) -> Seq (Text, IniSection)
296347 -> Either String s
297348 runSpec s Seq.EmptyL _ = Right s
298 runSpec s ((name, fs) Seq.:< rest) ini
349 runSpec s (Section name fs opt Seq.:< rest) ini
299350 | Just v <- lkp (T.toLower name) ini = do
300351 s' <- runFields s (Seq.viewl fs) v
301352 runSpec s' (Seq.viewl rest) ini
353 | opt = runSpec s (Seq.viewl rest) ini
302354 | otherwise = Left ("Unable to find section " ++ show name)
303355
304356 -- These are some inline reimplementations of "lens" operators. We
328380 | Just v <- lkp (fdName descr) (isVals sect) = do
329381 value <- fvParse (fdValue descr) (T.strip (vValue v))
330382 runFields (set l value s) (Seq.viewl fs) sect
383 | fdSkipIfMissing descr =
384 runFields s (Seq.viewl fs) sect
331385 | Just def <- fdDefault descr =
332386 runFields (set l def s) (Seq.viewl fs) sect
333387 | otherwise = Left ("Unable to find field " ++ show (fdName descr))
343397 emitIniFile :: s -> IniSpec s () -> Text
344398 emitIniFile s (IniSpec mote) =
345399 let spec = runBidirM mote in
346 printIni $ Ini $ fmap (\ (name, fs) -> (name, toSection s name fs)) spec
400 printIni $ Ini $ fmap (\ (Section name fs _) -> (name, toSection s name fs)) spec
347401
348402 mkComments :: Seq Text -> Seq BlankLine
349403 mkComments comments =
444498 return (printIni (Ini ini'))
445499
446500 updateIniSections :: s -> Seq (Text, IniSection)
447 -> Seq (Text, Seq (Field s))
501 -> Seq (Section s)
448502 -> UpdatePolicy
449503 -> Either String (Seq (Text, IniSection))
450504 updateIniSections s sections fields pol =
451505 F.for sections $ \ (name, sec) -> do
452506 let err = (Left ("Unexpected top-level section: " ++ show name))
453 spec <- maybe err Right (lkp name fields)
507 Section _ spec _ <- maybe err Right
508 (F.find (\ (Section n _ _) -> n == name) fields)
454509 newVals <- updateIniSection s (isVals sec) spec pol
455510 return (name, sec { isVals = newVals })
456511
569624
570625
571626
572 {- $main This module is an alternate API used for parsing INI files.
573 Unlike the standard API, it is bidirectional: the same declarative
574 structure can be also used to emit an INI file, or even to produce an
575 updated INI file with minimal modification to the textual file
576 provided.
577
578 This module makes some extra assumptions about your configuration type
579 and the way you interact with it: in particular, it assumes that you
580 have lenses for all the fields you're parsing, and that you have some
581 kind of sensible default value of that configuration. Instead of
582 providing combinators which can extract and parse a field of an INI
583 file into a value, the bidirectional API allows you to declaratively
584 map lenses into your structure to descriptions of corresponding fields
585 in INI files.
627 {- $main
628
629 This module presents an alternate API for parsing INI files. Unlike
630 the standard API, it is bidirectional: the same declarative structure
631 can be used to parse an INI file to a value, serialize an INI file
632 from a value, or even /update/ an INI file by comparing it against a
633 value and serializing in a way that minimizes the differences between
634 revisions of the file.
635
636 This API does make some extra assumptions about your configuration
637 type and the way you interact with it: in particular, it assumes that
638 you have lenses for all the fields you're parsing, and that you have
639 some kind of sensible default value of that configuration
640 type. Instead of providing combinators which can extract and parse a
641 field of an INI file into a value, the bidirectional API allows you to
642 declaratively associate a lens into your structure with a field of the
643 INI file.
586644
587645 Consider the following example INI file:
588646
605663 >
606664 > ''makeLenses Config
607665
608 We can now define a basic specification of the type @IniSpec Config
666 We can now define a basic specification of the type @'IniSpec' Config
609667 ()@ by using the provided operations to declare our top-level
610668 sections, and then within those sections associate fields with lenses
611669 into our @Config@ structure.
612670
613 > configSpec :: IniSpec Config ()
614 > configSpec = do
615 > section "NETWORK" $ do
616 > cfHost .= field "host" string
617 > cfPost .= field "port" number
618 > section "LOCAL" $ do
619 > cfUser .=? field "user" text
620
621 The '.=' operator associates a field with a lens directly, and the
622 '.=?' operator associates a field with a lens to a 'Maybe' value,
623 setting that value to 'Nothing' if the field does not appear in the
624 configuration. Each 'field' invocation must include the name of the
625 field and a representation of the type of that field: 'string',
626 'number', and 'text' in the above snippet are all values of type
627 'FieldValue', which bundle together a parser and serializer so that
628 they can be used bidirectionally.
671 @
672 'configSpec' :: 'IniSpec' Config ()
673 'configSpec' = do
674 'section' \"NETWORK\" $ do
675 cfHost '.=' 'field' \"host\" 'string'
676 cfPost '.=' 'field' \"port\" 'number'
677 'section' \"LOCAL\" $ do
678 cfUser '.=?' 'field' \"user\" 'text'
679 @
680
681 There are two operators used to associate lenses with fields:
682
683 ['.='] Associates a lens of type @Lens' s a@ with a field description
684 of type @FieldDescription a@
685
686 ['.=?'] Associates a lens of type @Lens' s (Maybe a)@ with a field
687 description of type @FieldDescription a@. If the value does
688 not appear in an INI file, then the lens will be set to
689 'Nothing'; similarly, if the value is 'Nothing', then the
690 field will not be serialized in the file.
691
692 Each field must include the field's name as well as a 'FieldValue',
693 which describes how to both parse and serialize a value of a given
694 type. Several built-in 'FieldValue' descriptions are provided, but you
695 can always build your own by providing parsing and serialization
696 functions for individual fields.
629697
630698 We can also provide extra metadata about a field, allowing it to be
631699 skipped in parsing, or to provide an explicit default value, or to
633701 serialize an INI file. These are conventionally applied to the field
634702 using the '&' operator:
635703
636 > configSpec :: IniSpec Config ()
637 > configSpec = do
638 > section "NETWORK" $ do
639 > cfHost .= field "host" string
640 > & comment ["The desired hostname (optional)"]
641 > & skipIfMissing
642 > cfPost .= field "port" number
643 > & comment ["The port number"]
644 > & defaultValue 9999
645 > section "LOCAL" $ do
646 > cfUser .=? field "user" text
704 @
705 configSpec :: 'IniSpec' Config ()
706 configSpec = do
707 'section' \"NETWORK\" $ do
708 cfHost '.=' 'field' \"host\" 'string'
709 & 'comment' [\"The desired hostname (optional)\"]
710 & 'skipIfMissing'
711 cfPost '.=' 'field' \"port\" 'number'
712 & 'comment' [\"The port number\"]
713 & 'defaultValue' 9999
714 'section' \"LOCAL\" $ do
715 cfUser '.=?' 'field' \"user\" 'text'
716 @
647717
648718 In order to parse an INI file, we need to provide a default value of
649719 our underlying @Config@ type on which we can perform our 'Lens'-based
658728 spacing and comments.
659729
660730 -}
731
732 -- $using
733 -- Functions for parsing, serializing, and updating INI files.
734
735 -- $types
736 -- Types which represent declarative specifications for INI
737 -- file structure.
738
739 -- $sections
740 -- Declaring sections of an INI file specification
741
742 -- $fields
743 -- Declaring individual fields of an INI file specification.
744
745 -- $fieldvalues
746 -- Values of type 'FieldValue' represent both a parser and a
747 -- serializer for a value of a given type. It's possible to manually
748 -- create 'FieldValue' descriptions, but for simple configurations,
749 -- but for the sake of convenience, several commonly-needed
750 -- varieties of 'FieldValue' are defined here.
751
752 -- $misc
753 -- These values and types are exported for compatibility.
11 module Data.Ini.Config.Raw
22 ( -- $main
3
34 -- * INI types
45 Ini(..)
56 , IniSection(..)
3233
3334 -- | An 'IniSection' consists of a name, a mapping of key-value pairs,
3435 -- and metadata about where the section starts and ends in the
35 -- file. The section names found in 'isName' are *not* normalized to
36 -- lower-case or stripped of whitespace, and thus should appear
36 -- file. The section names found in 'isName' are __not__ normalized
37 -- to lower-case or stripped of whitespace, and thus should appear
3738 -- exactly as they appear in the original source file.
3839 data IniSection = IniSection
3940 { isName :: Text
193194 Builder.fromText (vValue val) <>
194195 Builder.singleton '\n'
195196
196 -- | $main
197 -- This module is subject to change in the future, and therefore
198 -- should not be relied upon to have a consistent API.
197 {- $main
198
199 __Warning!__ This module is subject to change in the future, and therefore should
200 not be relied upon to have a consistent API.
201
202 -}