yaml-config-0.2.0: Configuration management

Safe HaskellNone

Data.Yaml.Config

Description

Library for read config files in YAML format.

example.yaml:

 server:
     port: 8080
     logs:
         access: /var/log/server/access.log
         error:  /var/log/server/error.log

Usage example:

 module Main where
 import Prelude hiding (lookup)
 import Data.Word (Word16)
 import Data.Yaml.Config (load, subconfig, lookupDefault, lookup)

 main :: IO ()
 main = do
     config <- load "./example.yaml"

     serverConfig <- subconfig "server" config
     let interface = lookupDefault "interface" "127.0.0.1" serverConfig
         port :: Word16 = lookupDefault "port" 80 serverConfig

     logConfig <- subconfig "logs" serverConfig
     accessLog <- lookup "access" logConfig
     errorLog <- lookup "error" logConfig

     mapM_ putStrLn [interface, (show port), errorLog, accessLog]

Synopsis

Documentation

data Config Source

Type contains config section and path from root.

type Key = TextSource

Config or field name

newtype KeyError Source

This error can be raised if config has not target path.

Constructors

KeyError Key 

load :: FilePath -> IO ConfigSource

Find file in filesystem and try to load it as YAML config. May fail with InvalidYaml if file not found.

>>> config <- load "example.yaml"

keys :: Config -> [Key]Source

Show all first level config field's.

>>> keys config
["section1","section2"]

subconfigSource

Arguments

:: Failure KeyError m 
=> Key

Subconfig name

-> Config

(Sub)Config for find

-> m Config

Founded Subconfig

Get subconfig by name. May fail with KeyError if target key doesn't exist at current level.

>>> :set -XOverloadedStrings
>>> sub <- subconfig "section1" config

lookupSource

Arguments

:: (Failure KeyError m, FromJSON a) 
=> Key

Field name

-> Config

Config for find

-> m a

Field value

Get value for given key. May fail with KeyError if key doesn't exist.

>>> keys sub
["field1","field2"]
>>> putStrLn =<< lookup "field1" sub
value1

lookupDefaultSource

Arguments

:: FromJSON a 
=> Key

Field name

-> a

Default value

-> Config

Config for find

-> a

Founded or default value

Find value in config and return it or return default value.

>>> lookupDefault "field3" "def" sub
"def"