[Pkg-haskell-commits] [SCM] haskell-testpack branch, master, updated. debian/1.0.2-1-4-gb0d6b36

John Goerzen jgoerzen at complete.org
Fri Apr 23 15:21:01 UTC 2010


The following commit has been merged in the master branch:
commit 9ae5cc108d0feb0cb877c272bce23015a84f1f4c
Author: John Goerzen <jgoerzen at complete.org>
Date:   Thu Dec 7 23:11:09 2006 +0100

    Removed split-off ConfigFile

diff --git a/MissingH.cabal b/MissingH.cabal
index ae19798..91967a7 100644
--- a/MissingH.cabal
+++ b/MissingH.cabal
@@ -25,9 +25,6 @@ Exposed-Modules: Data.String, System.IO.Utils, System.IO.Binary, Data.List.Utils
   Network.SocketServer,
   Data.Either.Utils,
   Data.Maybe.Utils,
-  Data.ConfigFile,
-    Data.ConfigFile.Types,
-    Data.ConfigFile.Parser,
   Data.Bits.Utils,
   Data.Hash.CRC32.Posix, Data.Hash.CRC32.GZip,
    Data.Hash.MD5, Data.Hash.MD5.Zord64_HARD,
@@ -45,7 +42,6 @@ Exposed-Modules: Data.String, System.IO.Utils, System.IO.Binary, Data.List.Utils
     Database.AnyDBM.MapDBM,
     Database.AnyDBM.StringDBM,
   System.Console.GetOpt.Utils
-Other-Modules: Data.ConfigFile.Lexer
 Extensions: ExistentialQuantification, OverlappingInstances, 
    UndecidableInstances, CPP
 Build-Depends: network, parsec, base,
diff --git a/src/Data/ConfigFile.hs b/src/Data/ConfigFile.hs
deleted file mode 100644
index 0149d9b..0000000
--- a/src/Data/ConfigFile.hs
+++ /dev/null
@@ -1,881 +0,0 @@
-{- arch-tag: ConfigParser main file
-Copyright (C) 2004-2006 John Goerzen <jgoerzen at complete.org>
-
-This program is free software; you can redistribute it and/or modify
-it under the terms of the GNU General Public License as published by
-the Free Software Foundation; either version 2 of the License, or
-(at your option) any later version.
-
-This program is distributed in the hope that it will be useful,
-but WITHOUT ANY WARRANTY; without even the implied warranty of
-MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
-GNU General Public License for more details.
-
-You should have received a copy of the GNU General Public License
-along with this program; if not, write to the Free Software
-Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA
--}
-
-{- |
-   Module     : Data.ConfigFile
-   Copyright  : Copyright (C) 2004-2006 John Goerzen
-   License    : GNU GPL, version 2 or above
-
-   Maintainer : John Goerzen <jgoerzen at complete.org> 
-   Stability  : provisional
-   Portability: portable
-
-Configuration file parsing, generation, and manipulation
-
-Copyright (c) 2004-2006 John Goerzen, jgoerzen\@complete.org
-
-This module contains extensive documentation.  Please scroll down to the Introduction section to continue reading.
--}
-module Data.ConfigFile
-    (
-     -- * Introduction
-     -- $introduction
-
-     -- ** Features
-     -- $features
-
-     -- ** History
-     -- $history
-
-     -- * Configuration File Format
-     -- $format
-
-     -- ** White Space
-     -- $whitespace
-
-     -- ** Comments
-     -- $comments
-
-     -- ** Case Sensitivity
-     -- $casesens
-
-     -- ** Interpolation
-     -- $interpolation
-
-     -- * Usage Examples
-     -- $usage
-
-     -- ** Non-Monadic Usage
-     -- $usagenomonad
-
-     -- ** Error Monad Usage
-     -- $usageerrormonad
-
-     -- ** Combined Error\/IO Monad Usage
-     -- $usageerroriomonad
-
-     -- * Types
-     -- $types
-     SectionSpec, OptionSpec, ConfigParser(..),
-     CPErrorData(..), CPError,
-     -- * Initialization
-     -- $initialization
-     emptyCP,
-
-     -- * Configuring the ConfigParser
-     -- $configuringcp
-     
-     -- ** Access Functions
-     simpleAccess, interpolatingAccess,
-
-     -- * Reading
-     -- $reading
-     readfile, readhandle, readstring,
-
-     -- * Accessing Data
-     Get_C(..),
-     sections, has_section,
-     options, has_option,
-     items,
-
-     -- * Modifying Data
-     set, setshow, remove_option,
-     add_section, remove_section,
-     merge,
-
-     -- * Output Data
-     to_string
-
-
-) where
-import Data.ConfigFile.Types
-import Data.ConfigFile.Parser
-import Data.Map.Utils
-import Data.Either.Utils
-import Data.String
-import qualified Data.Map as Map
-import Data.List
-import System.IO(Handle)
-import Data.Char
-import Control.Monad.Error
-
--- For interpolatingAccess
-import Text.ParserCombinators.Parsec.Error(ParseError, messageString,
-    errorMessages, Message(..))
-import Text.ParserCombinators.Parsec(parse)
-
-----------------------------------------------------------------------
--- Basic types / default values
-----------------------------------------------------------------------
-
-{- | The default empty 'Data.ConfigFile' object.
-
-The content contains only an empty mandatory @DEFAULT@ section.
-
-'optionxform' is set to @map toLower at .
-
-'usedefault' is set to @True at .
-
-'accessfunc' is set to 'simpleAccess'.
--}
-emptyCP :: ConfigParser
-emptyCP = ConfigParser { content = fromAL [("DEFAULT", [])],
-                       defaulthandler = defdefaulthandler,
-                       optionxform = map toLower,
-                       usedefault = True,
-                       accessfunc = simpleAccess}
-
-{- | Low-level tool to convert a parsed object into a 'CPData'
-representation.  Performs no option conversions or special handling
-of @DEFAULT at . -}
-fromAL :: ParseOutput -> CPData
-fromAL origal =
-    let conv :: CPData -> (String, [(String, String)]) -> CPData
-        conv fm sect = Map.insert (fst sect) (Map.fromList $ snd sect) fm
-        in
-        foldl conv Map.empty origal
-
-{- | Default (non-interpolating) access function -}
-simpleAccess ::  MonadError CPError m =>
-                 ConfigParser -> SectionSpec -> OptionSpec -> m String
-simpleAccess cp s o = defdefaulthandler cp s (optionxform cp $ o)
-
-{- | Interpolating access function.  Please see the Interpolation section
-above for a background on interpolation.
-
-Although the format string looks similar to one used by "Text.Printf",
-it is not the same.  In particular, only the %(...)s format is supported.
-No width specifiers are supported and no conversions other than s are supported.
-
-To use this function, you must specify a maximum recursion depth for
-interpolation.  This is used to prevent a stack overflow in the event that
-the configuration file contains an endless interpolation loop.  Values of 10
-or so are usually more than enough, though you could probably go into the
-hundreds or thousands before you have actual problems.
-
-A value less than one will cause an instant error every time you attempt
-a lookup.
-
-This access method can cause 'get' and friends to return a new 'CPError':
-'InterpolationError'.  This error would be returned when:
-
- * The configuration file makes a reference to an option that does
-   not exist
-
- * The maximum interpolation depth is exceeded
-
- * There is a syntax error processing a %-directive in the configuration
-   file
-
-An interpolation lookup name specifies an option only.  There is no provision
-to specify a section.  Interpolation variables are looked up in the current
-section, and, if 'usedefault' is True, in @DEFAULT@ according to the normal
-logic.
-
-To use a literal percent sign, you must place @%%@ in the configuration
-file when interpolation is used.
-
-Here is how you might enable interpolation:
-
->let cp2 = cp {accessfunc = interpolatingAccess 10}
-
-The @cp2@ object will now support interpolation with a maximum depth of 10.
- -}
-interpolatingAccess :: MonadError CPError m =>
-                       Int ->
-                       ConfigParser -> SectionSpec -> OptionSpec
-                       -> m String
-
-interpolatingAccess maxdepth cp s o =
-    if maxdepth < 1
-       then interError "maximum interpolation depth exceeded"
-       else do x <- simpleAccess cp s o
-               case parse (interpmain $ lookupfunc) (s ++ "/" ++ o) x of
-                 Left y -> case head (errorMessages y) of
-                                Message z -> interError z
-                                _ -> interError (show y)
-                 Right y -> return y
-    where
-    lookupfunc = interpolatingAccess (maxdepth - 1) cp s
-    interError x = throwError (InterpolationError x, "interpolatingAccess")
-
--- internal function: default handler
-defdefaulthandler ::  MonadError CPError m =>
-                      ConfigParser -> SectionSpec -> OptionSpec -> m String
-
-defdefaulthandler cp sectn opt = 
-    let fm = content cp
-        lookup s o = do sect <- maybeToEither (NoSection s, 
-                                               "get " ++ formatSO sectn opt) $ 
-                                Map.lookup s fm
-                        maybeToEither (NoOption o, 
-                                       "get " ++ formatSO sectn opt) $ 
-                                Map.lookup o sect
-        trydefault e = if (usedefault cp)
-                       then 
-                            lookup "DEFAULT" opt 
-                                       -- Use original error if it's not in DEFAULT either
-                                       `catchError` (\_ -> throwError e)
-                       else throwError e
-        in 
-        lookup sectn opt `catchError` trydefault
-
-
-{- | Combines two 'ConfigParser's into one.
-
-Any duplicate options are resolved to contain the value specified in
-the second parser.
-
-The 'ConfigParser' options in the resulting object will be set as they
-are in the second one passed to this function. -}
-merge :: ConfigParser -> ConfigParser -> ConfigParser
-merge src dest = 
-    let conv :: String -> String
-        conv = optionxform dest
-        convFM :: CPOptions -> CPOptions
-        convFM = Map.fromList . map (\x -> (conv (fst x), snd x)) . Map.toList
-        mergesects a b = Map.union a b
-        in
-	dest { content = Map.unionWith mergesects 
-                         (content dest) (Map.map convFM (content src)) }
-
-{- | Utility to do a special case merge. -}
-readutil :: ConfigParser -> ParseOutput -> ConfigParser
-readutil old new = merge old $ old { content = fromAL new }
-
-{- | Loads data from the specified file.  It is then combined with the
-given 'ConfigParser' using the semantics documented under 'merge' with the
-new data taking precedence over the old.  However, unlike
-'merge', all the options
-as set in the old object are preserved since the on-disk representation
-does not convey those options.
-
-May return an error if there is a syntax error.  May raise an exception if the file could not be accessed.
--}
---readfile :: ConfigParser -> FilePath ->IO (CPResult ConfigParser)
-readfile :: MonadError CPError m => ConfigParser -> FilePath -> IO (m ConfigParser)
-{-
-readfile cp fp = do n <- parse_file fp
-                    return $ do y <- n
-                                return $ readutil cp y
--}
-readfile cp fp = do n <- parse_file fp
-                    return $ n >>= (return . readutil cp)
-
-{- | Like 'readfile', but uses an already-open handle.  You should
-use 'readfile' instead of this if possible, since it will be able to
-generate better error messages.
-
-Errors would be returned on a syntax error.
--}
---readhandle :: ConfigParser -> Handle -> IO (CPResult ConfigParser)
-readhandle :: MonadError CPError m => ConfigParser -> Handle -> IO (m ConfigParser)
-readhandle cp h = do n <- parse_handle h
-                     return $ n >>= (return . (readutil cp))
-
-{- | Like 'readfile', but uses a string.  You should use 'readfile'
-instead of this if you are processing a file, since it can generate
-better error messages.
-
-Errors would be returned on a syntax error.
--}
-readstring ::  MonadError CPError m =>
-               ConfigParser -> String -> m ConfigParser
-readstring cp s = do
-                  n <- parse_string s
-                  return $ readutil cp n
-
-{- | Returns a list of sections in your configuration file.  Never includes
-the always-present section @DEFAULT at . -}
-sections :: ConfigParser -> [SectionSpec]
-sections = filter (/= "DEFAULT") . Map.keys . content
-
-{- | Indicates whether the given section exists.
-
-No special @DEFAULT@ processing is done. -}
-has_section :: ConfigParser -> SectionSpec -> Bool
-has_section cp x = Map.member x (content cp)
-
-{- | Adds the specified section name.  Returns a
-'SectionAlreadyExists' error if the
-section was already present.  Otherwise, returns the new 
-'ConfigParser' object.-}
-add_section ::  MonadError CPError m =>
-                ConfigParser -> SectionSpec -> m ConfigParser
-add_section cp s =
-    if has_section cp s
-       then throwError $ (SectionAlreadyExists s, "add_section")
-       else return $ cp {content = Map.insert s Map.empty (content cp)}
-
-{- | Removes the specified section.  Returns a 'NoSection' error if
-the section does not exist; otherwise, returns the new 'ConfigParser'
-object.
-
-This call may not be used to remove the @DEFAULT@ section.  Attempting to do
-so will always cause a 'NoSection' error.
- -}
-remove_section ::  MonadError CPError m =>
-                   ConfigParser -> SectionSpec -> m ConfigParser
-remove_section _ "DEFAULT" = throwError $ (NoSection "DEFAULT", "remove_section")
-remove_section cp s = 
-    if has_section cp s
-       then return $ cp {content = Map.delete s (content cp)}
-       else throwError $ (NoSection s, "remove_section")
-
-{- | Removes the specified option.  Returns a 'NoSection' error if the
-section does not exist and a 'NoOption' error if the option does not
-exist.  Otherwise, returns the new 'ConfigParser' object.
--}
-remove_option ::  MonadError CPError m =>
-                  ConfigParser -> SectionSpec -> OptionSpec -> m ConfigParser
-remove_option cp s passedo =
-    do sectmap <- maybeToEither (NoSection s, 
-                                 "remove_option " ++ formatSO s passedo) $ 
-                  Map.lookup s (content cp)
-       let o = (optionxform cp) passedo
-       let newsect = Map.delete o sectmap
-       let newmap = Map.insert s newsect (content cp)
-       if Map.member o sectmap
-          then return $ cp {content = newmap}
-          else throwError $ (NoOption o, 
-                             "remove_option " ++ formatSO s passedo)
-
-{- | Returns a list of the names of all the options present in the
-given section.
-
-Returns an error if the given section does not exist.
--}
-options ::  MonadError CPError m =>
-            ConfigParser -> SectionSpec -> m [OptionSpec]
-options cp x = maybeToEither (NoSection x, "options") $ 
-               do
-               o <- Map.lookup x (content cp)
-               return $ Map.keys o
-
-{- | Indicates whether the given option is present.  Returns True
-only if the given section is present AND the given option is present
-in that section.  No special @DEFAULT@ processing is done.  No
-exception could be raised or error returned.
--}
-has_option :: ConfigParser -> SectionSpec -> OptionSpec -> Bool
-has_option cp s o = 
-    let c = content cp
-        v = do secthash <- Map.lookup s c
-               return $ Map.member (optionxform cp $ o) secthash
-        in maybe False id v
-
-{- | The class representing the data types that can be returned by "get".
--}
-class Get_C a where 
-    {- | Retrieves a string from the configuration file.
-
-When used in a context where a String is expected, returns that string verbatim.
-
-When used in a context where a Bool is expected, parses the string to
-a Boolean value (see logic below).
-
-When used in a context where anything that is an instance of Read is expected,
-calls read to parse the item.
-
-An error will be returned of no such option could be found or if it could
-not be parsed as a boolean (when returning a Bool).
-
-When parsing to a Bool, strings are case-insentively converted as follows:
-
-The following will produce a True value:
-
- * 1
-
- * yes
-
- * on
-
- * enabled
-
- * true
-
-The following will produce a False value:
-
- * 0
-
- * no
-
- * off
-
- * disabled
-
- * false -}
-    get :: MonadError CPError m => ConfigParser -> SectionSpec -> OptionSpec -> m a
-                           
-instance Get_C String where
-    get cp s o = eitherToMonadError $ (accessfunc cp) cp s o
-
-instance Get_C Bool where
-    get = getbool
-
-instance (Num t, Read t) => Get_C t where
-    get = genericget
-
-genericget cp s o = get cp s o >>= return . read
-
-getbool ::  MonadError CPError m =>
-            ConfigParser -> SectionSpec -> OptionSpec -> m Bool
-getbool cp s o = 
-    do val <- get cp s o
-       case map toLower . strip $ val of
-                  "1" -> return True
-                  "yes" -> return True
-                  "on" -> return True
-                  "enabled" -> return True
-                  "true" -> return True
-                  "0" -> return False
-                  "no" -> return False
-                  "off" -> return False
-                  "disabled" -> return False
-                  "false" -> return False
-                  _ -> throwError (ParseError $ "couldn't parse bool " ++
-                                   val ++ " from " ++ formatSO s o, "getbool")
-
-formatSO s o =
-    "(" ++ s ++ "/" ++ o ++ ")"
-
-
-{- | Returns a list of @(optionname, value)@ pairs representing the content
-of the given section.  Returns an error the section is invalid. -}
-items ::  MonadError CPError m =>
-          ConfigParser -> SectionSpec -> m [(OptionSpec, String)]
-items cp s = do fm <- maybeToEither (NoSection s, "items") $ 
-                      Map.lookup s (content cp)
-                return $ Map.toList fm
-
-{- | Sets the option to a new value, replacing an existing one if it exists.
-
-Returns an error if the section does not exist. -}
-set ::  MonadError CPError m =>
-        ConfigParser -> SectionSpec -> OptionSpec -> String -> m ConfigParser
-set cp s passedo val = 
-    do sectmap <- maybeToEither (NoSection s, "set " ++ formatSO s passedo) $ 
-                  Map.lookup s (content cp)
-       let o = (optionxform cp) passedo
-       let newsect = Map.insert o val sectmap
-       let newmap = Map.insert s newsect (content cp)
-       return $ cp { content = newmap}
-
-{- | Sets the option to a new value, replacing an existing one if it exists.
-It requires only a showable value as its parameter.
-This can be used with bool values, as well as numeric ones.
-
-Returns an error if the section does not exist. -}
-setshow :: (Show a, MonadError CPError m) => 
-           ConfigParser -> SectionSpec -> OptionSpec -> a -> m ConfigParser
-setshow cp s o val = set cp s o (show val)
-
-{- | Converts the 'ConfigParser' to a string representation that could be
-later re-parsed by this module or modified by a human.
-
-Note that this does not necessarily re-create a file that was originally
-loaded.  Things may occur in a different order, comments will be removed,
-etc.  The conversion makes an effort to make the result human-editable,
-but it does not make an effort to make the result identical to the original
-input.
-
-The result is, however, guaranteed to parse the same as the original input.
- -}
-to_string :: ConfigParser -> String
-to_string cp = 
-    let gen_option (key, value) = 
-            key ++ ": " ++ (replace "\n" "\n    " value) ++ "\n"
-        gen_section (sect, valfm) = -- gen a section, but omit DEFAULT if empty
-            if (sect /= "DEFAULT") || (Map.size valfm > 0)
-               then "[" ++ sect ++ "]\n" ++
-                        (concat $ map gen_option (Map.toList valfm)) ++ "\n"
-               else ""
-        in
-        concat $ map gen_section (Map.toList (content cp))
-
-----------------------------------------------------------------------
--- Docs
-----------------------------------------------------------------------
-
-{- $introduction
-
-Many programs need configuration files. These configuration files are
-typically used to configure certain runtime behaviors that need to be
-saved across sessions. Various different configuration file formats
-exist.
-
-The ConfigParser module attempts to define a standard format that is
-easy for the user to edit, easy for the programmer to work with, yet
-remains powerful and flexible.
--}
-
-{- $features
-
-For the programmer, this module provides:
-
- * Simple calls to both read /and write/ configuration files
-
- * Call that can generate a string version of a file that is
-   re-parsable by this module (useful for, for instance, sending the
-   file down a network)
-
- * Segmented configuration files that let you separate configuration
-   into distinct sections, each with its own namespace. This can be
-   used to configure multiple modules in one file, to configure
-   multiple instances of a single object, etc.
-
- * On-the-fly parsing of integer, boolean, float, multi-line string values,
-   and anything else Haskell's read can deal with
-
- * It is possible to make a configuration file parsable by this
-   module, the Unix shell, and\/or Unix make, though some feautres are,
-   of course, not compatible with these other tools.
-
- * Syntax checking with error reporting including line numbers
-
- * Implemented in pure Haskell.  No dependencies on modules outside
-   the standard library distributed with Haskell compilers or interpreters.
-   All calls except those that read directly from a handle are pure calls
-   and can be used outside the IO monad.
-
- * Comprehensive documentation
-
- * Extensible API
-
- * Complete compatibility with Python's ConfigParser module, or my
-   ConfigParser module for OCaml, part of my MissingLib package.
-
-For the user, this module provides:
-
- * Easily human-editable configuration files with a clear, concise,
-   and consistent format
-
- * Configuration file format consistent with other familiar formats
-   (\/etc\/passwd is a valid ConfigParser file)
-
- * No need to understand semantics of markup languages like XML
--}
-
-{- $history
-
-This module is based on Python's ConfigParser module at
-<http://www.python.org/doc/current/lib/module-ConfigParser.html>.  I had
-earlier developed an OCaml implementation as part of my MissingLib library
-at <gopher://gopher.quux.org/devel/missinglib>.
-
-While the API of these three modules is similar, and the aim is to preserve all
-useful features of the original Python module, there are some differences
-in the implementation details.  This module is a complete, clean re-implementation
-in Haskell, not a Haskell translation of a Python program.  As such, the feature
-set is slightly different.
--}
-
-{- $format
-
-The basic configuration file format resembles that of an old-style
-Windows .INI file. Here are two samples:
-
->debug = yes
->inputfile = /etc/passwd
->names = Peter, Paul, Mary, George, Abrahaham, John, Bill, Gerald, Richard,
->        Franklin, Woodrow
->color = red 
-
-This defines a file without any explicit section, so all items will
-occur within the default section @DEFAULT at . The @debug@ option can be read
-as a boolean or a string. The remaining items can be read as a string
-only. The @names@ entry spans two lines -- any line starting with
-whitespace, and containing something other than whitespace or
-comments, is taken as a continuation of the previous line.
-
-Here's another example: 
-
-># Default options
->[DEFAULT]
->hostname: localhost 
-># Options for the first file
->[file1]
->location: /usr/local
->user: Fred
->uid: 1000
->optionaltext: Hello, this  entire string is included 
->[file2]
->location: /opt
->user: Fred
->uid: 1001 
-
-This file defines three sections. The @DEFAULT@ section specifies an
-entry @hostname at . If you attempt to read the hostname option in any
-section, and that section doesn't define @hostname@, you will get the
-value from @DEFAULT@ instead. This is a nice time-saver. You can also
-note that you can use colons instead of the = character to separate
-option names from option entries.
--}
-
-{- $whitespace
-
-Whitespace (spaces, tabs, etc) is automatically stripped from the
-beginning and end of all strings. Thus, users can insert whitespace
-before\/after the colon or equal sign if they like, and it will be
-automatically stripped.
-
-Blank lines or lines consisting solely of whitespace are ignored. 
-
-A line giving an option or a section name may not begin with white space.
-This requirement is necessary so there is no ambiguity between such lines
-and continuation lines for multi-line options.
-
--}
-
-{- $comments
-
-Comments are introduced with the pound sign @#@ or the semicolon @;@. They
-cause the parser to ignore everything from that character to the end
-of the line.
-
-Comments /may not/ occur within the definitions of options; that is, you
-may not place a comment in the middle of a line such as @user: Fred at . 
-That is because the parser considers the comment characters part
-of the string; otherwise, you'd be unable to use those characters in
-your strings. You can, however, \"comment out\" options by putting the
-comment character at the start of the line.
-
--}
-
-{- $casesens
-
-By default, section names are case-sensitive but option names are
-not. The latter can be adjusted by adjusting 'optionxform'.  -}
-
-{- $interpolation
-
-Interpolation is an optional feature, disabled by default.  If you replace
-the default 'accessfunc' ('simpleAccess') with 'interpolatingAccess',
-then you get interpolation support with 'get' and the other 'get'-based functions.
-
-As an example, consider the following file:
-
->arch = i386
->project = test
->filename = test_%(arch)s.c
->dir = /usr/src/%(filename)s 
->percent = 5%% 
-
-With interpolation, you would get these results:
-
->get cp "DEFAULT" "filename" -> "test_i386.c"
->get cp "DEFAULT" "dir" -> "/usr/src/test_i386.c"
->get cp "DEFAULT" "percent" -> "5%"
-
-For more details on interpolation, please see the documentation for the
-'interpolatingAccess' function.
--}
-
-{- $usage
-
-The basic theory of working with ConfigParser is this:
-
- 1. Parse or build a 'ConfigParser' object
- 
- 2. Work with it in one of several ways
-
- 3. To make changes, you discard the original object and use a new one.
-    Changes can be "chained" through one of several monads.
-
-The default 'ConfigParser' object that you always start with is 'emptyCP'.
-From here, you load data into it (merging data into the empty object),
-set up structures yourself, or adjust options.
-
-Let's take a look at some basic use cases.
-
--}
-
-{- $usagenomonad
-You'll notice that many functions in this module return a 
- at MonadError 'CPError'@ over some
-type.  Although its definition is not this simple, you can consider this to be
-the same as returning @Either CPError a at .
-
-That is, these functions will return @Left error@ if there's a problem
-or @Right result@ if things are fine.  The documentation for individual
-functions describes the specific circumstances in which an error may occur in
-more detail.
-
-Some people find it annoying to have to deal with errors manually.
-You can transform errors into exceptions in your code by using 
-'Data.Either.Utils.forceEither'.  Here's an example of this style of programming:
-
-> import Data.Either.Utils
-> do
->    val <- readfile emptyCP "/etc/foo.cfg"
->    let cp = forceEither val
->    putStrLn "Your setting is:"
->    putStrLn $ forceEither $ get cp "sect1" "opt1"
-
-In short, you can just put @forceEither $@ in front of every call that returns
-something that is a MonadError.
-This is still a pure functional call, so it can be used outside
-of the IO monads.  The exception, however, can only be caught in the IO
-monad.
-
-If you don't want to bother with 'forceEither', you can use the error monad.  It's simple and better... read on.
--}
-
-{- $usageerrormonad
-
-The return type is actually defined in terms of the Error monad, which is
-itself based on the Either data type.
-
-Here's a neat example of chaining together calls to build up a 'ConfigParser'
-object:
-
->do let cp = emptyCP
->   cp <- add_section cp "sect1"
->   cp <- set cp "sect1" "opt1" "foo"
->   cp <- set cp "sect1" "opt2" "bar"
->   options cp "sect1"
-
-The return value of this little snippet is @Right [\"opt1\", \"opt2\"]@.
-(Note to beginners: unlike the IO monad, you /can/ escape from the Error
-monad.)
-
-Although it's not obvious, there actually was error checking there.  If
-any of those calls would have generated an error, processing would have
-stopped immediately and a @Left@ value would have been returned.  Consider
-this example:
-
->do let cp = emptyCP
->   cp <- add_section cp "sect1"
->   cp <- set cp "sect1" "opt1" "foo"
->   cp <- set cp "sect2" "opt2" "bar"
->   options cp "sect1"
-
-The return value from this is @Left ('NoSection' \"sect2\", \"set\")@.  The
-second call to 'set' failed, so the final call was skipped, and the result
-of the entire computation was considered to be an error.
-
-You can combine this with the non-monadic style to get a final, pure value
-out of it:
-
->forceEither $ do let cp = emptyCP
->                 cp <- add_section cp "sect1"
->                 cp <- set cp "sect1" "opt1" "foo"
->                 cp <- set cp "sect1" "opt2" "bar"
->                 options cp "sect1"
-
-This returns @[\"opt1\", \"opt2\"]@.  A quite normal value.
-
--}
-
-{- $usageerroriomonad
-
-You've seen a nice way to use this module in the Error monad and get an Either
-value out.  But that's the Error monad, so IO is not permitted.  
-Using Haskell's monad transformers, you can run it in the combined
-Error\/IO monad.  That is, you will get an IO result back.  Here is a full
-standalone example of doing that:
-
->import Data.ConfigFile
->import Control.Monad.Error
->
->main = do
->          rv <- runErrorT $
->              do
->              cp <- join $ liftIO $ readfile empty "/etc/passwd"
->              let x = cp
->              liftIO $ putStrLn "In the test"
->              nb <- get x "DEFAULT" "nobody"
->              liftIO $ putStrLn nb
->              foo <- get x "DEFAULT" "foo"
->              liftIO $ putStrLn foo
->              return "done"
->          print rv
-
-On my system, this prints:
-
->In the test
->x:65534:65534:nobody:/nonexistent:/bin/sh
->Left (NoOption "foo","get")
-
-That is, my @\/etc\/passwd@ file contains a @nobody@ user but not a @foo@ user.
-
-Let's look at how that works.
-
-First, @main@ always runs in the IO monad only, so we take the result from
-the later calls and put it in @rv at .  Note that the combined block
-is started with @runErrorT $ do@ instead of just @do at .
-
-To get something out of the call to 'readfile', we use
- at join $ liftIO $ readfile at .  This will bring the result out of the IO monad
-into the combined monad and process it like usual.  From here on,
-everything looks normal, except for IO calls.  They are all executed under
- at liftIO@ so that the result value is properly brought into the combined
-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
-monad, this is wrapped in IO.  So the final return type after applying
- at runErrorT@ is @IO (Either CPError String)@.
-
-In this case, there was an error, and processing stopped at that point just
-like the example of the pure Error monad.  We print out the return value,
-so you see the error displayed as a @Left@ value.
-
-It all works quite easily.
-
--}
-
-{- $configuringcp
-
-You may notice that the 'ConfigParser' object has some configurable parameters,
-such as 'usedefault'.  In case you're not familiar with the Haskell syntax
-for working with these, you can use syntax like this to set these options:
-
->let cp2 = cp { usedefault = False }
-
-This will create a new 'ConfigParser' that is the same as @cp@ except for
-the 'usedefault' field, which is now always False.  The new object will be
-called @cp2@ in this example.
--}
-
-{- $reading
-
-You can use these functions to read data from a file.
-
-A common idiom for loading a new object from stratch is:
-
- at cp <- 'readfile' 'emptyCP' \"\/etc\/foo.cfg\"@
-
-Note the use of 'emptyCP'; this will essentially cause the file's data
-to be merged with the empty 'ConfigParser'.
--}
-
-{- $types
-
-The code used to say this:
-
->type CPResult a = MonadError CPError m => m a
->simpleAccess :: ConfigParser -> SectionSpec -> OptionSpec -> CPResult String
-
-But Hugs did not support that type declaration.  Therefore, types are now
-given like this:
-
->simpleAccess :: MonadError CPError m =>
->                ConfigParser -> SectionSpec -> OptionSpec -> m String
-
-Although it looks more confusing than before, it still means the same.
-The return value can still be treated as @Either CPError String@ if you so
-desire.
--}
diff --git a/src/Data/ConfigFile/Lexer.hs b/src/Data/ConfigFile/Lexer.hs
deleted file mode 100644
index 863dafa..0000000
--- a/src/Data/ConfigFile/Lexer.hs
+++ /dev/null
@@ -1,104 +0,0 @@
-{- arch-tag: ConfigParser lexer support
-Copyright (C) 2004 John Goerzen <jgoerzen at complete.org>
-
-This program is free software; you can redistribute it and/or modify
-it under the terms of the GNU General Public License as published by
-the Free Software Foundation; either version 2 of the License, or
-(at your option) any later version.
-
-This program is distributed in the hope that it will be useful,
-but WITHOUT ANY WARRANTY; without even the implied warranty of
-MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
-GNU General Public License for more details.
-
-You should have received a copy of the GNU General Public License
-along with this program; if not, write to the Free Software
-Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA
--}
-
-{- |
-   Module     : Data.ConfigFile.Lexer
-   Copyright  : Copyright (C) 2004 John Goerzen
-   License    : GNU GPL, version 2 or above
-
-   Maintainer : John Goerzen <jgoerzen at complete.org> 
-   Stability  : provisional
-   Portability: portable
-
-Lexer support for "Data.ConfigFile".  This module is not intended to be
-used directly by your programs.
-
-Copyright (c) 2004 John Goerzen, jgoerzen\@complete.org
--}
-module Data.ConfigFile.Lexer 
-(
-       -- -- * Temporary for testing
-       --comment_chars, eol, optionsep, whitespace_chars, comment_line,
-       --empty_line, sectheader_chars, sectheader, oname_chars, value_chars,
-       --extension_line, optionkey, optionvalue, optionpair
-       loken,
-       CPTok(..)
-) where
-
-import Text.ParserCombinators.Parsec
-import Text.ParserCombinators.Parsec.Utils
-
-data CPTok = IGNOREDATA
-           | NEWSECTION String
-           | NEWSECTION_EOF String
-           | EXTENSIONLINE String
-           | NEWOPTION (String, String)
-             deriving (Eq, Show, Ord)
-
-comment_chars = oneOf "#;"
-eol = string "\n" <|> string "\r\n" <|> string "\r" <?> "End of line"
-eoleof = eof <|> do {eol; return ()}
-optionsep = oneOf ":=" <?> "option separator"
-whitespace_chars = oneOf " \t" <?> "whitespace"
-comment_line = do skipMany whitespace_chars
-                  comment_chars             <?> "start of comment"
-                  (many $ noneOf "\r\n")   <?> "content of comment"
-                  eoleof
-eolstuff = (try comment_line) <|> (try empty_line)
-empty_line = do many whitespace_chars
-                eoleof
-             <?> "empty line"
-sectheader_chars = noneOf "]\r\n"
-sectheader = do char '['
-                sname <- many1 $ sectheader_chars
-                char ']'
-                eolstuff
-                return sname
-             <?> "start of section"
-oname_chars = noneOf ":=\r\n"
-value_chars = noneOf "\r\n"
-extension_line = do many1 whitespace_chars
-                    c1 <- noneOf "\r\n#;"
-                    remainder <- many value_chars
-                    eolstuff
-                    return (c1 : remainder)
-
-optionkey = many1 oname_chars
-optionvalue = many value_chars
-optionpair = do key <- optionkey
-                optionsep
-                value <- optionvalue
-                eolstuff
-                return (key, value)
-             <?> "key/value option"
-
-iloken :: Parser (GeneralizedToken CPTok)
-iloken =
-    -- Ignore these things
-    try (do {comment_line; togtok $ IGNOREDATA})
-    <|> try (do {empty_line; togtok $ IGNOREDATA})
-    
-    -- Real stuff
-    <|> (do {sname <- sectheader; togtok $ NEWSECTION sname})
-    <|> try (do {extension <- extension_line; togtok $ EXTENSIONLINE extension})
-    <|> try (do {pair <- optionpair; togtok $ NEWOPTION pair})
---    <?> "Invalid syntax in configuration file"
-        
-loken :: Parser [GeneralizedToken CPTok]
-loken = do x <- manyTill iloken eof
-           return $ filter (\y -> snd y /= IGNOREDATA) x
diff --git a/src/Data/ConfigFile/Parser.hs b/src/Data/ConfigFile/Parser.hs
deleted file mode 100644
index 4d7bebc..0000000
--- a/src/Data/ConfigFile/Parser.hs
+++ /dev/null
@@ -1,164 +0,0 @@
-{- arch-tag: ConfigParser parser support
-Copyright (C) 2004 John Goerzen <jgoerzen at complete.org>
-
-This program is free software; you can redistribute it and/or modify
-it under the terms of the GNU General Public License as published by
-the Free Software Foundation; either version 2 of the License, or
-(at your option) any later version.
-
-This program is distributed in the hope that it will be useful,
-but WITHOUT ANY WARRANTY; without even the implied warranty of
-MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
-GNU General Public License for more details.
-
-You should have received a copy of the GNU General Public License
-along with this program; if not, write to the Free Software
-Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA
--}
-
-{- |
-   Module     : Data.ConfigFile.Parser
-   Copyright  : Copyright (C) 2004 John Goerzen
-   License    : GNU GPL, version 2 or above
-
-   Maintainer : John Goerzen <jgoerzen at complete.org> 
-   Stability  : provisional
-   Portability: portable
-
-Parser support for "Data.ConfigFile".  This module is not intended to be
-used directly by your programs.
-
-Copyright (c) 2004 John Goerzen, jgoerzen\@complete.org
--}
-module Data.ConfigFile.Parser
-(
- parse_string, parse_file, parse_handle, interpmain, ParseOutput
-       --satisfyG,
-       --main
-) where
-import Text.ParserCombinators.Parsec
-import Control.Monad.Error(throwError, MonadError)
-import Data.String
-import Data.ConfigFile.Lexer
-import System.IO(Handle, hGetContents)
-import Text.ParserCombinators.Parsec.Utils
-import Data.ConfigFile.Types
-
-----------------------------------------------------------------------
--- Exported funcs
-----------------------------------------------------------------------
-
-parse_string :: MonadError CPError m =>
-                String -> m ParseOutput
-parse_string s = 
-    detokenize "(string)" $ parse loken "(string)" s
-
---parse_file :: FilePath -> IO (CPResult ParseOutput)
-parse_file :: MonadError CPError m => FilePath -> IO (m ParseOutput)
-parse_file f =
-    do o <- parseFromFile loken f
-       return $ detokenize f o
-
---parse_handle :: Handle -> IO (CPResult ParseOutput)
-parse_handle :: MonadError CPError m => Handle -> IO (m ParseOutput)
-parse_handle h =
-    do s <- hGetContents h
-       let o = parse loken (show h) s
-       return $ detokenize (show h) o
-
-----------------------------------------------------------------------
--- Private funcs
-----------------------------------------------------------------------
-detokenize fp l =
-    let conv msg (Left err) = throwError $ (ParseError (show err), msg)
-        conv msg (Right val) = return val
-        in do r <- conv "lexer" l
-              conv "parser" $ runParser main () fp r
-
-main :: GeneralizedTokenParser CPTok () ParseOutput
-main =
-    do {s <- sectionlist; return s}
-    <|> try (do 
-             o <- optionlist
-             s <- sectionlist
-             return $ ("DEFAULT", o) : s
-            )
-    <|> do {o <- optionlist; return $ [("DEFAULT", o)] }
-    <?> "Error parsing config file tokens"
-        
-sectionlist :: GeneralizedTokenParser CPTok () ParseOutput
-sectionlist = do {eof; return []}
-              <|> try (do 
-                       s <- sectionhead
-                       eof
-                       return [(s, [])]
-                      )
-              <|> do
-                  s <- section
-                  sl <- sectionlist
-                  return (s : sl)
-
-section :: GeneralizedTokenParser CPTok () (String, [(String, String)])
-section = do {sh <- sectionhead; ol <- optionlist; return (sh, ol)}
-
-sectionhead :: GeneralizedTokenParser CPTok () String
-sectionhead = 
-    let wf (NEWSECTION x) = Just x
-        wf _ = Nothing
-        in
-        do {s <- tokeng wf; return $ strip s}
-
-optionlist :: GeneralizedTokenParser CPTok () [(String, String)]
-optionlist = many1 coption
-
-coption :: GeneralizedTokenParser CPTok () (String, String)
-coption =
-    let wf (NEWOPTION x) = Just x
-        wf _ = Nothing
-        wfx (EXTENSIONLINE x) = Just x
-        wfx _ = Nothing
-        in
-        do o <- tokeng wf
-           l <- many $ tokeng wfx
-           return (strip (fst o), valmerge ((snd o) : l))
-
-valmerge :: [String] -> String
-valmerge vallist =
-    let vl2 = map strip vallist
-        in join "\n" vl2
-
-----------------------------------------------------------------------
--- Interpolation
-----------------------------------------------------------------------
-
-interpval :: Parser String
-interpval  = do
-            string "%("
-            s <- (many1 $ noneOf ")") <?> "interpolation name"
-            string ")s"               <?> "end of interpolation name"
-            return s
-
-percentval :: Parser String
-percentval = do
-             string "%%"
-             return "%"
-
-interpother :: Parser String
-interpother = do
-              c <- noneOf "%"
-              return [c]
-
-interptok :: (String -> Either CPError String) -> Parser String
-interptok lookupfunc = (try percentval)
-                       <|> interpother
-                       <|> do s <- interpval
-                              case lookupfunc s of
-                                 Left (InterpolationError x, _) -> fail x
-                                 Left _ -> fail $ "unresolvable interpolation reference to \"" ++ s ++ "\""
-                                 Right x -> return x
-
-
-interpmain :: (String -> Either CPError String) -> Parser String
-interpmain lookupfunc =
-    do r <- manyTill (interptok lookupfunc) eof
-       return $ concat r
diff --git a/src/Data/ConfigFile/Types.hs b/src/Data/ConfigFile/Types.hs
deleted file mode 100644
index b789607..0000000
--- a/src/Data/ConfigFile/Types.hs
+++ /dev/null
@@ -1,113 +0,0 @@
-{- arch-tag: ConfigParser types
-Copyright (C) 2004-2005 John Goerzen <jgoerzen at complete.org>
-
-This program is free software; you can redistribute it and/or modify
-it under the terms of the GNU General Public License as published by
-the Free Software Foundation; either version 2 of the License, or
-(at your option) any later version.
-
-This program is distributed in the hope that it will be useful,
-but WITHOUT ANY WARRANTY; without even the implied warranty of
-MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
-GNU General Public License for more details.
-
-You should have received a copy of the GNU General Public License
-along with this program; if not, write to the Free Software
-Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA
--}
-
-{- |
-   Module     : Data.ConfigFile.Types
-   Copyright  : Copyright (C) 2004-2005 John Goerzen
-   License    : GNU GPL, version 2 or above
-
-   Maintainer : John Goerzen <jgoerzen at complete.org> 
-   Stability  : provisional
-   Portability: portable
-
-Internal types for "Data.ConfigFile".  This module is not intended to be
-used directly by your programs.
-
-Copyright (c) 2004 John Goerzen, jgoerzen\@complete.org
--}
-
-module Data.ConfigFile.Types (
-                                    CPOptions, CPData, 
-                                    CPErrorData(..), CPError, {-CPResult,-}
-                                    ConfigParser(..),
-                                    SectionSpec,
-                                    OptionSpec,
-                                    ParseOutput
-                                   ) where
-import qualified Data.Map as Map
-import Data.Char
-import Control.Monad.Error
-
-{- | Internal output from parser -}
-type ParseOutput = [(String, [(String, String)])]
-
-{- | Names of sections -}
-type SectionSpec = String
-
-{- | Names of options -}
-type OptionSpec = String
-
-{- | Storage of options. -}
-type CPOptions = Map.Map OptionSpec String
-
-{- | The main data storage type (storage of sections).
-
-PLEASE NOTE: This type is exported only for use by other modules under
-Data.ConfigFile.  You should NEVER access the FiniteMap in a ConfigParser
-directly.  This type may change in future releases of MissingH, which could
-break your programs.  Please retrict yourself to the interface in
-'Data.ConfigFile'.
- -}
-type CPData = Map.Map SectionSpec CPOptions
-
-{- | Possible ConfigParser errors. -}
-data CPErrorData = ParseError String        -- ^ Parse error
-                 | SectionAlreadyExists SectionSpec -- ^ Attempt to create an already-existing ection
-                 | NoSection SectionSpec    -- ^ The section does not exist
-                 | NoOption OptionSpec      -- ^ The option does not exist
-                 | OtherProblem String      -- ^ Miscellaneous error
-                 | InterpolationError String -- ^ Raised by 'Data.ConfigFile.interpolatingAccess' if a request was made for a non-existant option
-                   deriving (Eq, Ord, Show)
-
-{- | Indicates an error occurred.  The String is an explanation of the location
-of the error. -}
-type CPError = (CPErrorData, String)
-
-instance Error CPError where
-    noMsg = (OtherProblem "", "")
-    strMsg x = (OtherProblem x, "")
-
-{- Removed due to Hugs incompatibility.
-
-| Basic ConfigParser error handling.  The Left value indicates
-an error, while a Right value indicates success.
-type CPResult a = MonadError CPError m => m a
--}
-
-{- | This is the main record that is used by 'Data.ConfigFile'.
--}
-data ConfigParser = ConfigParser 
-    { -- | The data itself
-      content :: CPData,
-      -- | How to transform an option into a standard representation
-      optionxform :: (OptionSpec -> OptionSpec),
-      -- | Function to look up an option, considering a default value
-      -- if 'usedefault' is True; or ignoring a default value otherwise.
-      -- The option specification is assumed to be already transformed.
-      defaulthandler :: ConfigParser -> SectionSpec -> OptionSpec -> Either CPError String,
-      -- | Whether or not to seek out a default action when no match
-      -- is found.
-      usedefault :: Bool,
-      -- | Function that is used to perform lookups, do optional
-      -- interpolation, etc.  It is assumed that accessfunc
-      -- will internally call defaulthandler to do the underlying lookup.
-      -- The option value is not assumed to be transformed.
-      accessfunc :: (ConfigParser -> SectionSpec -> OptionSpec -> Either CPError String)
-    }
-
-

-- 
haskell-testpack



More information about the Pkg-haskell-commits mailing list