| Safe Haskell | None |
|---|
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 config server
let interface = lookupDefault serverConfig interface 127.0.0.1
port :: Word16 = lookupDefault serverConfig port 80
logConfig <- subconfig serverConfig logs
accessLog <- lookup logConfig access
errorLog <- lookup logConfig error
mapM_ putStrLn [interface, (show port), errorLog, accessLog]
Documentation
Type contains config section and path from root.
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"
Show all first level config field's.
>>>keys config["section1","section2"]
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
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" subvalue1