| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
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.logUsage 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]Documentation
Type contains config section and path from root.
This error can be raised if config has not target path.
load :: FilePath -> IO Config Source
Attempts to load a config from a given YAML file.
Fails with InvalidYaml if the file does not exist.
>>>config <- load "example.yaml"
keys :: Config -> [Key] Source
Returns all toplevel keys in a config.
>>>keys config["section1","section2"]
Narrows into a config section corresponding to a given key.
Fails with a KeyError if a key doesn't exist at the current level.
>>>:set -XOverloadedStrings>>>sub <- subconfig "section1" config
Returns a value for a given key.
Fails with a KeyError if the key doesn't exist.
>>>keys sub["field1","field2"]>>>putStrLn =<< lookup "field1" subvalue1