| Portability | portable | 
|---|---|
| Stability | experimental | 
| Maintainer | Leon P Smith <[email protected]> | 
| Safe Haskell | None | 
Data.Configurator.Parser
Contents
Description
A set of combinators for high-level configuration parsing.
- class Applicative m => ConfigParser m
- runParser :: ConfigParser m => m a -> Config -> (Maybe a, [ConfigError])
- data ConfigParserA a
- runParserA :: ConfigParserA a -> Config -> (Maybe a, [ConfigError])
- parserA :: ConfigParser m => ConfigParserA a -> m a
- unsafeBind :: ConfigParserA a -> (a -> ConfigParserA b) -> ConfigParserA b
- data ConfigParserM a
- runParserM :: ConfigParserM a -> Config -> (Maybe a, [ConfigError])
- parserM :: ConfigParser m => ConfigParserM a -> m a
- recover :: ConfigParser m => m a -> m (Maybe a)
- key :: (ConfigParser m, FromMaybeValue a) => Name -> m a
- keyWith :: ConfigParser m => Name -> MaybeParser a -> m a
- subgroups :: ConfigParser m => Name -> m [Name]
- subassocs :: ConfigParser m => Name -> m [(Name, Value)]
- subassocs' :: ConfigParser m => Name -> m [(Name, Value)]
- data Config
- data ConfigTransform
- localConfig :: ConfigParser m => ConfigTransform -> m a -> m a
- union :: ConfigTransform -> ConfigTransform -> ConfigTransform
- subconfig :: Text -> ConfigTransform -> ConfigTransform
- superconfig :: Text -> ConfigTransform -> ConfigTransform
- data ConfigError = ConfigError {}
- data  ConfigErrorLocation - = KeyMissing [Name]
- | Key FilePath Name
 
- data ConversionError = ConversionError {}
- data  ConversionErrorWhy - = MissingValue
- | ExtraValues
- | ExhaustedValues
- | TypeError
- | ValueError
- | MonadFail
- | OtherError
 
High level parsing computations
class Applicative m => ConfigParser m Source
A ConfigParser computation produces a value of type Maybe aConfig,  in addition to a list of diagnostic messages,
   which may be interpreted as warnings or errors as deemed appropriate.
   The type class abstracts over ConfigParserM and ConfigParserA
   variants,  which are isomorphic but have different Applicative and
   Monad instances.  This is intended to be a closed typeclass, without
   any additional instances.
runParser :: ConfigParser m => m a -> Config -> (Maybe a, [ConfigError])Source
data ConfigParserA a Source
After executing a subcomputation that returns a Nothing value,
   computations of type ConfigParserA will continue to run in order to
   produce more error messages.  For this reason,  ConfigParserA does
   not have a proper Monad instance.  (But see unsafeBind)
runParserA :: ConfigParserA a -> Config -> (Maybe a, [ConfigError])Source
Exactly the same as runParser,  except less polymorphic
parserA :: ConfigParser m => ConfigParserA a -> m aSource
Lift a ConfigParserA action into a generic ConfigParser
    action.  Note that this does not change the semantics of the
    argument,  it just allows a ConfigParserA computation to be
    embedded in another ConfigParser computation of either variant.
unsafeBind :: ConfigParserA a -> (a -> ConfigParserA b) -> ConfigParserA bSource
The purpose of this function is to make it convenient to use do-notation
    with ConfigParserA,  either by defining a Monad instance or locally
    rebinding >>=.    Be warned that this is an abuse,  and incorrect
    usage can result in exceptions.   A safe way to use this function
    would be to treat is as applicative-do notation.  A safer alternative
    would be to use the ApplicativeDo language extension available in
    GHC 8.0 and not use this function at all.
data ConfigParserM a Source
runParserM :: ConfigParserM a -> Config -> (Maybe a, [ConfigError])Source
Exactly the same as runParser,  except less polymorphic
parserM :: ConfigParser m => ConfigParserM a -> m aSource
Lift a ConfigParserM action into a generic ConfigParser
    action.  Note that this does not change the semantics of the
    argument,  it just allows a ConfigParserM computation to be
    embedded in another ConfigParser computation of either variant.
recover :: ConfigParser m => m a -> m (Maybe a)Source
Looking up values by name
key :: (ConfigParser m, FromMaybeValue a) => Name -> m aSource
Look up a given value in the current configuration context,  and convert
 the value using the fromMaybeValue method.
keyWith :: ConfigParser m => Name -> MaybeParser a -> m aSource
Look up a given value in the current configuration context,  and convert
 the value using the MaybeParser argument.
Discovering names
subgroups :: ConfigParser m => Name -> m [Name]Source
Returns all the non-empty value groupings that is directly under the argument grouping in the current configuration context. For example, given the following context:
foo { }
bar {
  a {
    x = 1
  }
  b {
    c {
      y = 2
    }
  }
}
default
  a {
    x = 3
  }
}
Then the following arguments to subgroups would return the following lists:
subgroups "" ==> [ "bar", "default" ] subgroups "bar" ==> [ "bar.a", "bar.b" ] subgroups "bar.b" ==> [ "bar.b.c" ] subgroups "default" ==> [ "default.a" ]
All other arguments to subgroups would return [] in the given context.
subassocs :: ConfigParser m => Name -> m [(Name, Value)]Source
Returns all the value bindings from the current configuration context that is contained within the given subgroup, in lexicographic order. For example, given the following context:
x = 1
foo {
  x = 2
  bar {
    y = on
  }
}
foo = "Hello"
Then the following arguments to subassocs would return the following lists:
subassocs ""         ==>  [("foo",String "Hello"),("x",Number 1)]
subassocs "foo"      ==>  [("foo.x",Number 2)]
subassocs "foo.bar"  ==>  [("foo.bar.x",Bool True)]
All other arguments to subassocs would return [] in the given context.
subassocs' :: ConfigParser m => Name -> m [(Name, Value)]Source
Returns all the value bindings from the current configuration context that is contained within the given subgroup and all of it's subgroups in lexicographic order. For example, given the following context:
x = 1
foo {
  x = 2
  bar {
    y = on
  }
}
foo = "Hello"
Then the following arguments to 'subassocs\'' would return the following lists:
subassocs' ""         ==>  [ ("foo"       , String "Hello")
                           , ("foo.bar.y" , Bool True     )
                           , ("foo.x"     , Number 2      )
                           , ("x"         , Number 1      )
                           ]
subassocs' "foo"      ==>  [ ("foo.bar.y" , Bool True     )
                           , ("foo.x"     , Number 2      )
                           ]
subassocs' "foo.bar"  ==>  [ ("foo.bar.y" , Bool True     )
                           ]
All other arguments to subassocs' would return [] in the given context.
Modifying the configuration context
data ConfigTransform Source
Conceptually, a ConfigTransform is a function Config -> Config.
   It's a restricted subset of such functions as to preserve the possibility
   of reliable dependency tracking in later versions of configurator-ng.
Instances
| Monoid ConfigTransform | 
 | 
localConfig :: ConfigParser m => ConfigTransform -> m a -> m aSource
subconfig :: Text -> ConfigTransform -> ConfigTransformSource
subconfig groupgroup (either directly,  or contained within a
 descendant value grouping),  and removes the group prefix from all
 of the keys in the map.  It's analogous to the cd (change directory)
 command on common operating systems,  except that subconfig can only
 descend down the directory tree,  and cannot ascend into a parent
 directory.
superconfig :: Text -> ConfigTransform -> ConfigTransformSource
superconfig groupgroup prefix to all keys in the map.
 It is vaguely analogous to the mount command on unix operating systems.
Error / warning messages
data ConfigError Source
An error (or warning) from a higher-level parser of a configuration file.
Constructors
| ConfigError | |
data ConfigErrorLocation Source
Constructors
| KeyMissing [Name] | |
| Key FilePath Name | 
data ConversionError Source
Constructors
| ConversionError | |
| Fields 
 | |