~ubuntu-branches/ubuntu/maverick/haskell-configfile/maverick

« back to all changes in this revision

Viewing changes to src/Data/ConfigFile.hs

  • Committer: Bazaar Package Importer
  • Author(s): John Goerzen
  • Date: 2007-03-08 14:22:03 UTC
  • Revision ID: james.westby@ubuntu.com-20070308142203-j9niks7p5q8e9ycs
Tags: 1.0.1
Rebuild against newer MissingH.

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
{- arch-tag: ConfigParser main file
 
2
Copyright (C) 2004-2006 John Goerzen <jgoerzen@complete.org>
 
3
 
 
4
This program is free software; you can redistribute it and/or modify
 
5
it under the terms of the GNU Lesser General Public License as published by
 
6
the Free Software Foundation; either version 2.1 of the License, or
 
7
(at your option) any later version.
 
8
 
 
9
This program is distributed in the hope that it will be useful,
 
10
but WITHOUT ANY WARRANTY; without even the implied warranty of
 
11
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
 
12
GNU Lesser General Public License for more details.
 
13
 
 
14
You should have received a copy of the GNU Lesser General Public License
 
15
along with this program; if not, write to the Free Software
 
16
Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, MA  02110-1301  USA
 
17
-}
 
18
 
 
19
{- |
 
20
   Module     : Data.ConfigFile
 
21
   Copyright  : Copyright (C) 2004-2006 John Goerzen
 
22
   License    : GNU LGPL, version 2.1 or above
 
23
 
 
24
   Maintainer : John Goerzen <jgoerzen@complete.org> 
 
25
   Stability  : provisional
 
26
   Portability: portable
 
27
 
 
28
Configuration file parsing, generation, and manipulation
 
29
 
 
30
Copyright (c) 2004-2006 John Goerzen, jgoerzen\@complete.org
 
31
 
 
32
This module contains extensive documentation.  Please scroll down to the Introduction section to continue reading.
 
33
-}
 
34
module Data.ConfigFile
 
35
    (
 
36
     -- * Introduction
 
37
     -- $introduction
 
38
 
 
39
     -- ** Features
 
40
     -- $features
 
41
 
 
42
     -- ** History
 
43
     -- $history
 
44
 
 
45
     -- * Configuration File Format
 
46
     -- $format
 
47
 
 
48
     -- ** White Space
 
49
     -- $whitespace
 
50
 
 
51
     -- ** Comments
 
52
     -- $comments
 
53
 
 
54
     -- ** Case Sensitivity
 
55
     -- $casesens
 
56
 
 
57
     -- ** Interpolation
 
58
     -- $interpolation
 
59
 
 
60
     -- * Usage Examples
 
61
     -- $usage
 
62
 
 
63
     -- ** Non-Monadic Usage
 
64
     -- $usagenomonad
 
65
 
 
66
     -- ** Error Monad Usage
 
67
     -- $usageerrormonad
 
68
 
 
69
     -- ** Combined Error\/IO Monad Usage
 
70
     -- $usageerroriomonad
 
71
 
 
72
     -- * Types
 
73
     -- $types
 
74
     SectionSpec, OptionSpec, ConfigParser(..),
 
75
     CPErrorData(..), CPError,
 
76
     -- * Initialization
 
77
     -- $initialization
 
78
     emptyCP,
 
79
 
 
80
     -- * Configuring the ConfigParser
 
81
     -- $configuringcp
 
82
     
 
83
     -- ** Access Functions
 
84
     simpleAccess, interpolatingAccess,
 
85
 
 
86
     -- * Reading
 
87
     -- $reading
 
88
     readfile, readhandle, readstring,
 
89
 
 
90
     -- * Accessing Data
 
91
     Get_C(..),
 
92
     sections, has_section,
 
93
     options, has_option,
 
94
     items,
 
95
 
 
96
     -- * Modifying Data
 
97
     set, setshow, remove_option,
 
98
     add_section, remove_section,
 
99
     merge,
 
100
 
 
101
     -- * Output Data
 
102
     to_string
 
103
 
 
104
 
 
105
) where
 
106
import Data.ConfigFile.Types
 
107
import Data.ConfigFile.Parser
 
108
import Data.Map.Utils
 
109
import Data.Either.Utils
 
110
import Data.String
 
111
import qualified Data.Map as Map
 
112
import Data.List
 
113
import System.IO(Handle)
 
114
import Data.Char
 
115
import Control.Monad.Error
 
116
 
 
117
-- For interpolatingAccess
 
118
import Text.ParserCombinators.Parsec.Error(ParseError, messageString,
 
119
    errorMessages, Message(..))
 
120
import Text.ParserCombinators.Parsec(parse)
 
121
 
 
122
----------------------------------------------------------------------
 
123
-- Basic types / default values
 
124
----------------------------------------------------------------------
 
125
 
 
126
{- | The default empty 'Data.ConfigFile' object.
 
127
 
 
128
The content contains only an empty mandatory @DEFAULT@ section.
 
129
 
 
130
'optionxform' is set to @map toLower@.
 
131
 
 
132
'usedefault' is set to @True@.
 
133
 
 
134
'accessfunc' is set to 'simpleAccess'.
 
135
-}
 
136
emptyCP :: ConfigParser
 
137
emptyCP = ConfigParser { content = fromAL [("DEFAULT", [])],
 
138
                       defaulthandler = defdefaulthandler,
 
139
                       optionxform = map toLower,
 
140
                       usedefault = True,
 
141
                       accessfunc = simpleAccess}
 
142
 
 
143
{- | Low-level tool to convert a parsed object into a 'CPData'
 
144
representation.  Performs no option conversions or special handling
 
145
of @DEFAULT@. -}
 
146
fromAL :: ParseOutput -> CPData
 
147
fromAL origal =
 
148
    let conv :: CPData -> (String, [(String, String)]) -> CPData
 
149
        conv fm sect = Map.insert (fst sect) (Map.fromList $ snd sect) fm
 
150
        in
 
151
        foldl conv Map.empty origal
 
152
 
 
153
{- | Default (non-interpolating) access function -}
 
154
simpleAccess ::  MonadError CPError m =>
 
155
                 ConfigParser -> SectionSpec -> OptionSpec -> m String
 
156
simpleAccess cp s o = defdefaulthandler cp s (optionxform cp $ o)
 
157
 
 
158
{- | Interpolating access function.  Please see the Interpolation section
 
159
above for a background on interpolation.
 
160
 
 
161
Although the format string looks similar to one used by "Text.Printf",
 
162
it is not the same.  In particular, only the %(...)s format is supported.
 
163
No width specifiers are supported and no conversions other than s are supported.
 
164
 
 
165
To use this function, you must specify a maximum recursion depth for
 
166
interpolation.  This is used to prevent a stack overflow in the event that
 
167
the configuration file contains an endless interpolation loop.  Values of 10
 
168
or so are usually more than enough, though you could probably go into the
 
169
hundreds or thousands before you have actual problems.
 
170
 
 
171
A value less than one will cause an instant error every time you attempt
 
172
a lookup.
 
173
 
 
174
This access method can cause 'get' and friends to return a new 'CPError':
 
175
'InterpolationError'.  This error would be returned when:
 
176
 
 
177
 * The configuration file makes a reference to an option that does
 
178
   not exist
 
179
 
 
180
 * The maximum interpolation depth is exceeded
 
181
 
 
182
 * There is a syntax error processing a %-directive in the configuration
 
183
   file
 
184
 
 
185
An interpolation lookup name specifies an option only.  There is no provision
 
186
to specify a section.  Interpolation variables are looked up in the current
 
187
section, and, if 'usedefault' is True, in @DEFAULT@ according to the normal
 
188
logic.
 
189
 
 
190
To use a literal percent sign, you must place @%%@ in the configuration
 
191
file when interpolation is used.
 
192
 
 
193
Here is how you might enable interpolation:
 
194
 
 
195
>let cp2 = cp {accessfunc = interpolatingAccess 10}
 
196
 
 
197
The @cp2@ object will now support interpolation with a maximum depth of 10.
 
198
 -}
 
199
interpolatingAccess :: MonadError CPError m =>
 
200
                       Int ->
 
201
                       ConfigParser -> SectionSpec -> OptionSpec
 
202
                       -> m String
 
203
 
 
204
interpolatingAccess maxdepth cp s o =
 
205
    if maxdepth < 1
 
206
       then interError "maximum interpolation depth exceeded"
 
207
       else do x <- simpleAccess cp s o
 
208
               case parse (interpmain $ lookupfunc) (s ++ "/" ++ o) x of
 
209
                 Left y -> case head (errorMessages y) of
 
210
                                Message z -> interError z
 
211
                                _ -> interError (show y)
 
212
                 Right y -> return y
 
213
    where
 
214
    lookupfunc = interpolatingAccess (maxdepth - 1) cp s
 
215
    interError x = throwError (InterpolationError x, "interpolatingAccess")
 
216
 
 
217
-- internal function: default handler
 
218
defdefaulthandler ::  MonadError CPError m =>
 
219
                      ConfigParser -> SectionSpec -> OptionSpec -> m String
 
220
 
 
221
defdefaulthandler cp sectn opt = 
 
222
    let fm = content cp
 
223
        lookup s o = do sect <- maybeToEither (NoSection s, 
 
224
                                               "get " ++ formatSO sectn opt) $ 
 
225
                                Map.lookup s fm
 
226
                        maybeToEither (NoOption o, 
 
227
                                       "get " ++ formatSO sectn opt) $ 
 
228
                                Map.lookup o sect
 
229
        trydefault e = if (usedefault cp)
 
230
                       then 
 
231
                            lookup "DEFAULT" opt 
 
232
                                       -- Use original error if it's not in DEFAULT either
 
233
                                       `catchError` (\_ -> throwError e)
 
234
                       else throwError e
 
235
        in 
 
236
        lookup sectn opt `catchError` trydefault
 
237
 
 
238
 
 
239
{- | Combines two 'ConfigParser's into one.
 
240
 
 
241
Any duplicate options are resolved to contain the value specified in
 
242
the second parser.
 
243
 
 
244
The 'ConfigParser' options in the resulting object will be set as they
 
245
are in the second one passed to this function. -}
 
246
merge :: ConfigParser -> ConfigParser -> ConfigParser
 
247
merge src dest = 
 
248
    let conv :: String -> String
 
249
        conv = optionxform dest
 
250
        convFM :: CPOptions -> CPOptions
 
251
        convFM = Map.fromList . map (\x -> (conv (fst x), snd x)) . Map.toList
 
252
        mergesects a b = Map.union a b
 
253
        in
 
254
        dest { content = Map.unionWith mergesects 
 
255
                         (content dest) (Map.map convFM (content src)) }
 
256
 
 
257
{- | Utility to do a special case merge. -}
 
258
readutil :: ConfigParser -> ParseOutput -> ConfigParser
 
259
readutil old new = merge old $ old { content = fromAL new }
 
260
 
 
261
{- | Loads data from the specified file.  It is then combined with the
 
262
given 'ConfigParser' using the semantics documented under 'merge' with the
 
263
new data taking precedence over the old.  However, unlike
 
264
'merge', all the options
 
265
as set in the old object are preserved since the on-disk representation
 
266
does not convey those options.
 
267
 
 
268
May return an error if there is a syntax error.  May raise an exception if the file could not be accessed.
 
269
-}
 
270
--readfile :: ConfigParser -> FilePath ->IO (CPResult ConfigParser)
 
271
readfile :: MonadError CPError m => ConfigParser -> FilePath -> IO (m ConfigParser)
 
272
{-
 
273
readfile cp fp = do n <- parse_file fp
 
274
                    return $ do y <- n
 
275
                                return $ readutil cp y
 
276
-}
 
277
readfile cp fp = do n <- parse_file fp
 
278
                    return $ n >>= (return . readutil cp)
 
279
 
 
280
{- | Like 'readfile', but uses an already-open handle.  You should
 
281
use 'readfile' instead of this if possible, since it will be able to
 
282
generate better error messages.
 
283
 
 
284
Errors would be returned on a syntax error.
 
285
-}
 
286
--readhandle :: ConfigParser -> Handle -> IO (CPResult ConfigParser)
 
287
readhandle :: MonadError CPError m => ConfigParser -> Handle -> IO (m ConfigParser)
 
288
readhandle cp h = do n <- parse_handle h
 
289
                     return $ n >>= (return . (readutil cp))
 
290
 
 
291
{- | Like 'readfile', but uses a string.  You should use 'readfile'
 
292
instead of this if you are processing a file, since it can generate
 
293
better error messages.
 
294
 
 
295
Errors would be returned on a syntax error.
 
296
-}
 
297
readstring ::  MonadError CPError m =>
 
298
               ConfigParser -> String -> m ConfigParser
 
299
readstring cp s = do
 
300
                  n <- parse_string s
 
301
                  return $ readutil cp n
 
302
 
 
303
{- | Returns a list of sections in your configuration file.  Never includes
 
304
the always-present section @DEFAULT@. -}
 
305
sections :: ConfigParser -> [SectionSpec]
 
306
sections = filter (/= "DEFAULT") . Map.keys . content
 
307
 
 
308
{- | Indicates whether the given section exists.
 
309
 
 
310
No special @DEFAULT@ processing is done. -}
 
311
has_section :: ConfigParser -> SectionSpec -> Bool
 
312
has_section cp x = Map.member x (content cp)
 
313
 
 
314
{- | Adds the specified section name.  Returns a
 
315
'SectionAlreadyExists' error if the
 
316
section was already present.  Otherwise, returns the new 
 
317
'ConfigParser' object.-}
 
318
add_section ::  MonadError CPError m =>
 
319
                ConfigParser -> SectionSpec -> m ConfigParser
 
320
add_section cp s =
 
321
    if has_section cp s
 
322
       then throwError $ (SectionAlreadyExists s, "add_section")
 
323
       else return $ cp {content = Map.insert s Map.empty (content cp)}
 
324
 
 
325
{- | Removes the specified section.  Returns a 'NoSection' error if
 
326
the section does not exist; otherwise, returns the new 'ConfigParser'
 
327
object.
 
328
 
 
329
This call may not be used to remove the @DEFAULT@ section.  Attempting to do
 
330
so will always cause a 'NoSection' error.
 
331
 -}
 
332
remove_section ::  MonadError CPError m =>
 
333
                   ConfigParser -> SectionSpec -> m ConfigParser
 
334
remove_section _ "DEFAULT" = throwError $ (NoSection "DEFAULT", "remove_section")
 
335
remove_section cp s = 
 
336
    if has_section cp s
 
337
       then return $ cp {content = Map.delete s (content cp)}
 
338
       else throwError $ (NoSection s, "remove_section")
 
339
 
 
340
{- | Removes the specified option.  Returns a 'NoSection' error if the
 
341
section does not exist and a 'NoOption' error if the option does not
 
342
exist.  Otherwise, returns the new 'ConfigParser' object.
 
343
-}
 
344
remove_option ::  MonadError CPError m =>
 
345
                  ConfigParser -> SectionSpec -> OptionSpec -> m ConfigParser
 
346
remove_option cp s passedo =
 
347
    do sectmap <- maybeToEither (NoSection s, 
 
348
                                 "remove_option " ++ formatSO s passedo) $ 
 
349
                  Map.lookup s (content cp)
 
350
       let o = (optionxform cp) passedo
 
351
       let newsect = Map.delete o sectmap
 
352
       let newmap = Map.insert s newsect (content cp)
 
353
       if Map.member o sectmap
 
354
          then return $ cp {content = newmap}
 
355
          else throwError $ (NoOption o, 
 
356
                             "remove_option " ++ formatSO s passedo)
 
357
 
 
358
{- | Returns a list of the names of all the options present in the
 
359
given section.
 
360
 
 
361
Returns an error if the given section does not exist.
 
362
-}
 
363
options ::  MonadError CPError m =>
 
364
            ConfigParser -> SectionSpec -> m [OptionSpec]
 
365
options cp x = maybeToEither (NoSection x, "options") $ 
 
366
               do
 
367
               o <- Map.lookup x (content cp)
 
368
               return $ Map.keys o
 
369
 
 
370
{- | Indicates whether the given option is present.  Returns True
 
371
only if the given section is present AND the given option is present
 
372
in that section.  No special @DEFAULT@ processing is done.  No
 
373
exception could be raised or error returned.
 
374
-}
 
375
has_option :: ConfigParser -> SectionSpec -> OptionSpec -> Bool
 
376
has_option cp s o = 
 
377
    let c = content cp
 
378
        v = do secthash <- Map.lookup s c
 
379
               return $ Map.member (optionxform cp $ o) secthash
 
380
        in maybe False id v
 
381
 
 
382
{- | The class representing the data types that can be returned by "get".
 
383
-}
 
384
class Get_C a where 
 
385
    {- | Retrieves a string from the configuration file.
 
386
 
 
387
When used in a context where a String is expected, returns that string verbatim.
 
388
 
 
389
When used in a context where a Bool is expected, parses the string to
 
390
a Boolean value (see logic below).
 
391
 
 
392
When used in a context where anything that is an instance of Read is expected,
 
393
calls read to parse the item.
 
394
 
 
395
An error will be returned of no such option could be found or if it could
 
396
not be parsed as a boolean (when returning a Bool).
 
397
 
 
398
When parsing to a Bool, strings are case-insentively converted as follows:
 
399
 
 
400
The following will produce a True value:
 
401
 
 
402
 * 1
 
403
 
 
404
 * yes
 
405
 
 
406
 * on
 
407
 
 
408
 * enabled
 
409
 
 
410
 * true
 
411
 
 
412
The following will produce a False value:
 
413
 
 
414
 * 0
 
415
 
 
416
 * no
 
417
 
 
418
 * off
 
419
 
 
420
 * disabled
 
421
 
 
422
 * false -}
 
423
    get :: MonadError CPError m => ConfigParser -> SectionSpec -> OptionSpec -> m a
 
424
                           
 
425
instance Get_C String where
 
426
    get cp s o = eitherToMonadError $ (accessfunc cp) cp s o
 
427
 
 
428
instance Get_C Bool where
 
429
    get = getbool
 
430
 
 
431
instance (Num t, Read t) => Get_C t where
 
432
    get = genericget
 
433
 
 
434
genericget cp s o = get cp s o >>= return . read
 
435
 
 
436
getbool ::  MonadError CPError m =>
 
437
            ConfigParser -> SectionSpec -> OptionSpec -> m Bool
 
438
getbool cp s o = 
 
439
    do val <- get cp s o
 
440
       case map toLower . strip $ val of
 
441
                  "1" -> return True
 
442
                  "yes" -> return True
 
443
                  "on" -> return True
 
444
                  "enabled" -> return True
 
445
                  "true" -> return True
 
446
                  "0" -> return False
 
447
                  "no" -> return False
 
448
                  "off" -> return False
 
449
                  "disabled" -> return False
 
450
                  "false" -> return False
 
451
                  _ -> throwError (ParseError $ "couldn't parse bool " ++
 
452
                                   val ++ " from " ++ formatSO s o, "getbool")
 
453
 
 
454
formatSO s o =
 
455
    "(" ++ s ++ "/" ++ o ++ ")"
 
456
 
 
457
 
 
458
{- | Returns a list of @(optionname, value)@ pairs representing the content
 
459
of the given section.  Returns an error the section is invalid. -}
 
460
items ::  MonadError CPError m =>
 
461
          ConfigParser -> SectionSpec -> m [(OptionSpec, String)]
 
462
items cp s = do fm <- maybeToEither (NoSection s, "items") $ 
 
463
                      Map.lookup s (content cp)
 
464
                return $ Map.toList fm
 
465
 
 
466
{- | Sets the option to a new value, replacing an existing one if it exists.
 
467
 
 
468
Returns an error if the section does not exist. -}
 
469
set ::  MonadError CPError m =>
 
470
        ConfigParser -> SectionSpec -> OptionSpec -> String -> m ConfigParser
 
471
set cp s passedo val = 
 
472
    do sectmap <- maybeToEither (NoSection s, "set " ++ formatSO s passedo) $ 
 
473
                  Map.lookup s (content cp)
 
474
       let o = (optionxform cp) passedo
 
475
       let newsect = Map.insert o val sectmap
 
476
       let newmap = Map.insert s newsect (content cp)
 
477
       return $ cp { content = newmap}
 
478
 
 
479
{- | Sets the option to a new value, replacing an existing one if it exists.
 
480
It requires only a showable value as its parameter.
 
481
This can be used with bool values, as well as numeric ones.
 
482
 
 
483
Returns an error if the section does not exist. -}
 
484
setshow :: (Show a, MonadError CPError m) => 
 
485
           ConfigParser -> SectionSpec -> OptionSpec -> a -> m ConfigParser
 
486
setshow cp s o val = set cp s o (show val)
 
487
 
 
488
{- | Converts the 'ConfigParser' to a string representation that could be
 
489
later re-parsed by this module or modified by a human.
 
490
 
 
491
Note that this does not necessarily re-create a file that was originally
 
492
loaded.  Things may occur in a different order, comments will be removed,
 
493
etc.  The conversion makes an effort to make the result human-editable,
 
494
but it does not make an effort to make the result identical to the original
 
495
input.
 
496
 
 
497
The result is, however, guaranteed to parse the same as the original input.
 
498
 -}
 
499
to_string :: ConfigParser -> String
 
500
to_string cp = 
 
501
    let gen_option (key, value) = 
 
502
            key ++ ": " ++ (replace "\n" "\n    " value) ++ "\n"
 
503
        gen_section (sect, valfm) = -- gen a section, but omit DEFAULT if empty
 
504
            if (sect /= "DEFAULT") || (Map.size valfm > 0)
 
505
               then "[" ++ sect ++ "]\n" ++
 
506
                        (concat $ map gen_option (Map.toList valfm)) ++ "\n"
 
507
               else ""
 
508
        in
 
509
        concat $ map gen_section (Map.toList (content cp))
 
510
 
 
511
----------------------------------------------------------------------
 
512
-- Docs
 
513
----------------------------------------------------------------------
 
514
 
 
515
{- $introduction
 
516
 
 
517
Many programs need configuration files. These configuration files are
 
518
typically used to configure certain runtime behaviors that need to be
 
519
saved across sessions. Various different configuration file formats
 
520
exist.
 
521
 
 
522
The ConfigParser module attempts to define a standard format that is
 
523
easy for the user to edit, easy for the programmer to work with, yet
 
524
remains powerful and flexible.
 
525
-}
 
526
 
 
527
{- $features
 
528
 
 
529
For the programmer, this module provides:
 
530
 
 
531
 * Simple calls to both read /and write/ configuration files
 
532
 
 
533
 * Call that can generate a string version of a file that is
 
534
   re-parsable by this module (useful for, for instance, sending the
 
535
   file down a network)
 
536
 
 
537
 * Segmented configuration files that let you separate configuration
 
538
   into distinct sections, each with its own namespace. This can be
 
539
   used to configure multiple modules in one file, to configure
 
540
   multiple instances of a single object, etc.
 
541
 
 
542
 * On-the-fly parsing of integer, boolean, float, multi-line string values,
 
543
   and anything else Haskell's read can deal with
 
544
 
 
545
 * It is possible to make a configuration file parsable by this
 
546
   module, the Unix shell, and\/or Unix make, though some feautres are,
 
547
   of course, not compatible with these other tools.
 
548
 
 
549
 * Syntax checking with error reporting including line numbers
 
550
 
 
551
 * Implemented in pure Haskell.  No dependencies on modules outside
 
552
   the standard library distributed with Haskell compilers or interpreters.
 
553
   All calls except those that read directly from a handle are pure calls
 
554
   and can be used outside the IO monad.
 
555
 
 
556
 * Comprehensive documentation
 
557
 
 
558
 * Extensible API
 
559
 
 
560
 * Complete compatibility with Python's ConfigParser module, or my
 
561
   ConfigParser module for OCaml, part of my MissingLib package.
 
562
 
 
563
For the user, this module provides:
 
564
 
 
565
 * Easily human-editable configuration files with a clear, concise,
 
566
   and consistent format
 
567
 
 
568
 * Configuration file format consistent with other familiar formats
 
569
   (\/etc\/passwd is a valid ConfigParser file)
 
570
 
 
571
 * No need to understand semantics of markup languages like XML
 
572
-}
 
573
 
 
574
{- $history
 
575
 
 
576
This module is based on Python's ConfigParser module at
 
577
<http://www.python.org/doc/current/lib/module-ConfigParser.html>.  I had
 
578
earlier developed an OCaml implementation as part of my MissingLib library
 
579
at <gopher://gopher.quux.org/devel/missinglib>.
 
580
 
 
581
While the API of these three modules is similar, and the aim is to preserve all
 
582
useful features of the original Python module, there are some differences
 
583
in the implementation details.  This module is a complete, clean re-implementation
 
584
in Haskell, not a Haskell translation of a Python program.  As such, the feature
 
585
set is slightly different.
 
586
-}
 
587
 
 
588
{- $format
 
589
 
 
590
The basic configuration file format resembles that of an old-style
 
591
Windows .INI file. Here are two samples:
 
592
 
 
593
>debug = yes
 
594
>inputfile = /etc/passwd
 
595
>names = Peter, Paul, Mary, George, Abrahaham, John, Bill, Gerald, Richard,
 
596
>        Franklin, Woodrow
 
597
>color = red 
 
598
 
 
599
This defines a file without any explicit section, so all items will
 
600
occur within the default section @DEFAULT@. The @debug@ option can be read
 
601
as a boolean or a string. The remaining items can be read as a string
 
602
only. The @names@ entry spans two lines -- any line starting with
 
603
whitespace, and containing something other than whitespace or
 
604
comments, is taken as a continuation of the previous line.
 
605
 
 
606
Here's another example: 
 
607
 
 
608
># Default options
 
609
>[DEFAULT]
 
610
>hostname: localhost 
 
611
># Options for the first file
 
612
>[file1]
 
613
>location: /usr/local
 
614
>user: Fred
 
615
>uid: 1000
 
616
>optionaltext: Hello, this  entire string is included 
 
617
>[file2]
 
618
>location: /opt
 
619
>user: Fred
 
620
>uid: 1001 
 
621
 
 
622
This file defines three sections. The @DEFAULT@ section specifies an
 
623
entry @hostname@. If you attempt to read the hostname option in any
 
624
section, and that section doesn't define @hostname@, you will get the
 
625
value from @DEFAULT@ instead. This is a nice time-saver. You can also
 
626
note that you can use colons instead of the = character to separate
 
627
option names from option entries.
 
628
-}
 
629
 
 
630
{- $whitespace
 
631
 
 
632
Whitespace (spaces, tabs, etc) is automatically stripped from the
 
633
beginning and end of all strings. Thus, users can insert whitespace
 
634
before\/after the colon or equal sign if they like, and it will be
 
635
automatically stripped.
 
636
 
 
637
Blank lines or lines consisting solely of whitespace are ignored. 
 
638
 
 
639
A line giving an option or a section name may not begin with white space.
 
640
This requirement is necessary so there is no ambiguity between such lines
 
641
and continuation lines for multi-line options.
 
642
 
 
643
-}
 
644
 
 
645
{- $comments
 
646
 
 
647
Comments are introduced with the pound sign @#@ or the semicolon @;@. They
 
648
cause the parser to ignore everything from that character to the end
 
649
of the line.
 
650
 
 
651
Comments /may not/ occur within the definitions of options; that is, you
 
652
may not place a comment in the middle of a line such as @user: Fred@. 
 
653
That is because the parser considers the comment characters part
 
654
of the string; otherwise, you'd be unable to use those characters in
 
655
your strings. You can, however, \"comment out\" options by putting the
 
656
comment character at the start of the line.
 
657
 
 
658
-}
 
659
 
 
660
{- $casesens
 
661
 
 
662
By default, section names are case-sensitive but option names are
 
663
not. The latter can be adjusted by adjusting 'optionxform'.  -}
 
664
 
 
665
{- $interpolation
 
666
 
 
667
Interpolation is an optional feature, disabled by default.  If you replace
 
668
the default 'accessfunc' ('simpleAccess') with 'interpolatingAccess',
 
669
then you get interpolation support with 'get' and the other 'get'-based functions.
 
670
 
 
671
As an example, consider the following file:
 
672
 
 
673
>arch = i386
 
674
>project = test
 
675
>filename = test_%(arch)s.c
 
676
>dir = /usr/src/%(filename)s 
 
677
>percent = 5%% 
 
678
 
 
679
With interpolation, you would get these results:
 
680
 
 
681
>get cp "DEFAULT" "filename" -> "test_i386.c"
 
682
>get cp "DEFAULT" "dir" -> "/usr/src/test_i386.c"
 
683
>get cp "DEFAULT" "percent" -> "5%"
 
684
 
 
685
For more details on interpolation, please see the documentation for the
 
686
'interpolatingAccess' function.
 
687
-}
 
688
 
 
689
{- $usage
 
690
 
 
691
The basic theory of working with ConfigParser is this:
 
692
 
 
693
 1. Parse or build a 'ConfigParser' object
 
694
 
 
695
 2. Work with it in one of several ways
 
696
 
 
697
 3. To make changes, you discard the original object and use a new one.
 
698
    Changes can be "chained" through one of several monads.
 
699
 
 
700
The default 'ConfigParser' object that you always start with is 'emptyCP'.
 
701
From here, you load data into it (merging data into the empty object),
 
702
set up structures yourself, or adjust options.
 
703
 
 
704
Let's take a look at some basic use cases.
 
705
 
 
706
-}
 
707
 
 
708
{- $usagenomonad
 
709
You'll notice that many functions in this module return a 
 
710
@MonadError 'CPError'@ over some
 
711
type.  Although its definition is not this simple, you can consider this to be
 
712
the same as returning @Either CPError a@.
 
713
 
 
714
That is, these functions will return @Left error@ if there's a problem
 
715
or @Right result@ if things are fine.  The documentation for individual
 
716
functions describes the specific circumstances in which an error may occur in
 
717
more detail.
 
718
 
 
719
Some people find it annoying to have to deal with errors manually.
 
720
You can transform errors into exceptions in your code by using 
 
721
'Data.Either.Utils.forceEither'.  Here's an example of this style of programming:
 
722
 
 
723
> import Data.Either.Utils
 
724
> do
 
725
>    val <- readfile emptyCP "/etc/foo.cfg"
 
726
>    let cp = forceEither val
 
727
>    putStrLn "Your setting is:"
 
728
>    putStrLn $ forceEither $ get cp "sect1" "opt1"
 
729
 
 
730
In short, you can just put @forceEither $@ in front of every call that returns
 
731
something that is a MonadError.
 
732
This is still a pure functional call, so it can be used outside
 
733
of the IO monads.  The exception, however, can only be caught in the IO
 
734
monad.
 
735
 
 
736
If you don't want to bother with 'forceEither', you can use the error monad.  It's simple and better... read on.
 
737
-}
 
738
 
 
739
{- $usageerrormonad
 
740
 
 
741
The return type is actually defined in terms of the Error monad, which is
 
742
itself based on the Either data type.
 
743
 
 
744
Here's a neat example of chaining together calls to build up a 'ConfigParser'
 
745
object:
 
746
 
 
747
>do let cp = emptyCP
 
748
>   cp <- add_section cp "sect1"
 
749
>   cp <- set cp "sect1" "opt1" "foo"
 
750
>   cp <- set cp "sect1" "opt2" "bar"
 
751
>   options cp "sect1"
 
752
 
 
753
The return value of this little snippet is @Right [\"opt1\", \"opt2\"]@.
 
754
(Note to beginners: unlike the IO monad, you /can/ escape from the Error
 
755
monad.)
 
756
 
 
757
Although it's not obvious, there actually was error checking there.  If
 
758
any of those calls would have generated an error, processing would have
 
759
stopped immediately and a @Left@ value would have been returned.  Consider
 
760
this example:
 
761
 
 
762
>do let cp = emptyCP
 
763
>   cp <- add_section cp "sect1"
 
764
>   cp <- set cp "sect1" "opt1" "foo"
 
765
>   cp <- set cp "sect2" "opt2" "bar"
 
766
>   options cp "sect1"
 
767
 
 
768
The return value from this is @Left ('NoSection' \"sect2\", \"set\")@.  The
 
769
second call to 'set' failed, so the final call was skipped, and the result
 
770
of the entire computation was considered to be an error.
 
771
 
 
772
You can combine this with the non-monadic style to get a final, pure value
 
773
out of it:
 
774
 
 
775
>forceEither $ do let cp = emptyCP
 
776
>                 cp <- add_section cp "sect1"
 
777
>                 cp <- set cp "sect1" "opt1" "foo"
 
778
>                 cp <- set cp "sect1" "opt2" "bar"
 
779
>                 options cp "sect1"
 
780
 
 
781
This returns @[\"opt1\", \"opt2\"]@.  A quite normal value.
 
782
 
 
783
-}
 
784
 
 
785
{- $usageerroriomonad
 
786
 
 
787
You've seen a nice way to use this module in the Error monad and get an Either
 
788
value out.  But that's the Error monad, so IO is not permitted.  
 
789
Using Haskell's monad transformers, you can run it in the combined
 
790
Error\/IO monad.  That is, you will get an IO result back.  Here is a full
 
791
standalone example of doing that:
 
792
 
 
793
>import Data.ConfigFile
 
794
>import Control.Monad.Error
 
795
>
 
796
>main = do
 
797
>          rv <- runErrorT $
 
798
>              do
 
799
>              cp <- join $ liftIO $ readfile empty "/etc/passwd"
 
800
>              let x = cp
 
801
>              liftIO $ putStrLn "In the test"
 
802
>              nb <- get x "DEFAULT" "nobody"
 
803
>              liftIO $ putStrLn nb
 
804
>              foo <- get x "DEFAULT" "foo"
 
805
>              liftIO $ putStrLn foo
 
806
>              return "done"
 
807
>          print rv
 
808
 
 
809
On my system, this prints:
 
810
 
 
811
>In the test
 
812
>x:65534:65534:nobody:/nonexistent:/bin/sh
 
813
>Left (NoOption "foo","get")
 
814
 
 
815
That is, my @\/etc\/passwd@ file contains a @nobody@ user but not a @foo@ user.
 
816
 
 
817
Let's look at how that works.
 
818
 
 
819
First, @main@ always runs in the IO monad only, so we take the result from
 
820
the later calls and put it in @rv@.  Note that the combined block
 
821
is started with @runErrorT $ do@ instead of just @do@.
 
822
 
 
823
To get something out of the call to 'readfile', we use
 
824
@join $ liftIO $ readfile@.  This will bring the result out of the IO monad
 
825
into the combined monad and process it like usual.  From here on,
 
826
everything looks normal, except for IO calls.  They are all executed under
 
827
@liftIO@ so that the result value is properly brought into the combined
 
828
monad.  This finally returns @\"done\"@.  Since we are in the Error monad, that means that the literal value is @Right \"done\"@.  Since we are also in the IO
 
829
monad, this is wrapped in IO.  So the final return type after applying
 
830
@runErrorT@ is @IO (Either CPError String)@.
 
831
 
 
832
In this case, there was an error, and processing stopped at that point just
 
833
like the example of the pure Error monad.  We print out the return value,
 
834
so you see the error displayed as a @Left@ value.
 
835
 
 
836
It all works quite easily.
 
837
 
 
838
-}
 
839
 
 
840
{- $configuringcp
 
841
 
 
842
You may notice that the 'ConfigParser' object has some configurable parameters,
 
843
such as 'usedefault'.  In case you're not familiar with the Haskell syntax
 
844
for working with these, you can use syntax like this to set these options:
 
845
 
 
846
>let cp2 = cp { usedefault = False }
 
847
 
 
848
This will create a new 'ConfigParser' that is the same as @cp@ except for
 
849
the 'usedefault' field, which is now always False.  The new object will be
 
850
called @cp2@ in this example.
 
851
-}
 
852
 
 
853
{- $reading
 
854
 
 
855
You can use these functions to read data from a file.
 
856
 
 
857
A common idiom for loading a new object from stratch is:
 
858
 
 
859
@cp <- 'readfile' 'emptyCP' \"\/etc\/foo.cfg\"@
 
860
 
 
861
Note the use of 'emptyCP'; this will essentially cause the file's data
 
862
to be merged with the empty 'ConfigParser'.
 
863
-}
 
864
 
 
865
{- $types
 
866
 
 
867
The code used to say this:
 
868
 
 
869
>type CPResult a = MonadError CPError m => m a
 
870
>simpleAccess :: ConfigParser -> SectionSpec -> OptionSpec -> CPResult String
 
871
 
 
872
But Hugs did not support that type declaration.  Therefore, types are now
 
873
given like this:
 
874
 
 
875
>simpleAccess :: MonadError CPError m =>
 
876
>                ConfigParser -> SectionSpec -> OptionSpec -> m String
 
877
 
 
878
Although it looks more confusing than before, it still means the same.
 
879
The return value can still be treated as @Either CPError String@ if you so
 
880
desire.
 
881
-}