salak-0.2.2: Configuration Loader

Copyright(c) 2018 Daniel YU
LicenseBSD3
MaintainerDaniel YU <leptonyu@gmail.com>
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Data.Salak

Contents

Description

Configuration Loader for Production in Haskell.

Synopsis

How to use this library

| This library default a standard configuration load process. It can load properties from CommandLine, Environment, `JSON value` and Yaml files. They all load to the same format Properties. Earler property source has higher order to load property. For example:

CommandLine:  --package.a.enabled=true
Environment: PACKAGE_A_ENABLED: false
lookup "package.a.enabled" properties => Just True

CommandLine has higher order then Environment, for the former load properties earler then later.

Usage:

data Config = Config
  { name :: Text
  , dir  :: Maybe Text
  , ext  :: Int
  } deriving (Eq, Show)

instance FromProperties Config where
  fromProperties v = Config
        <$> v .?> "name"
        <*> v .?> "dir"
        <*> v .?> "ext" .?= 1
main = do
  p <- defaultPropertiesWithFile "salak.yml"
  let config  = p .>> "salak.config"  :: Config
      enabled = p .?> "salak.enabled" .|= True
  print config
  print enabled

Properties Loader

type LoadProperties = StateT Properties Source #

Monad to Load Properties

Since: 0.2.2

runLoad :: Monad m => LoadProperties m a -> m Properties Source #

Load Properties

Since: 0.2.2

askProperties :: Monad m => LoadProperties m Properties Source #

Get current Properties

Since: 0.2.2

setValue :: Monad m => Text -> Property -> LoadProperties m () Source #

Set value to current properties

Since: 0.2.2

loadCommandLine :: MonadIO m => ParseCommandLine -> LoadProperties m () Source #

Load Properties from CommandLine

Since: 0.2.2

loadEnvironment :: MonadIO m => LoadProperties m () Source #

Load Properties from CommandLine

Since: 0.2.2

loadJSON :: MonadIO m => Value -> LoadProperties m () Source #

Load Properties from JSON Value

Since: 0.2.2

loadYaml :: MonadIO m => FilePath -> LoadProperties m () Source #

Load Properties from Yaml

Since: 0.2.2

loadYamlIfExists :: MonadIO m => Maybe FilePath -> LoadProperties m () Source #

Load Properties from Yaml if exists

Since: 0.2.2

Predefined Loaders

defaultProperties :: IO Properties Source #

Initialize default properties from CommandLine and Environment. CommandLine use default parser.

defaultProperties' :: ParseCommandLine -> IO Properties Source #

Initialize default properties from CommandLine and Environment.

defaultPropertiesWithFile Source #

Arguments

:: FileName

specify default config file name, can reset by config "salak.config.name" from CommandLine or Environment.

-> IO Properties 

Initialize default properties from CommandLine, Environment and Yaml files. All these configuration sources has orders, from highest order to lowest order:

1. CommandLine
2. Environment
3. Specified Yaml file(file in "salak.config.dir")
4. Yaml file in current directory
5. Yaml file in home directory

defaultPropertiesWithFile' Source #

Arguments

:: FileName

specify default config file name, can reset by config "salak.config.name" from CommandLine or Environment.

-> ParseCommandLine

parser for command line

-> IO Properties 

Initialize default properties from CommandLine, Environment and Yaml files. All these configuration sources has orders, from highest order to lowest order:

1. CommandLine
2. Environment
3. Specified Yaml file(file in "salak.config.dir")
4. Yaml file in current directory
5. Yaml file in home directory

Lookup Properties

lookup :: FromProperties a => Text -> Properties -> Return a Source #

Find Properties by key and convert to specific Haskell value.

toKeys :: Text -> [Key] Source #

Split origin key by . to sub keys:

"salak.config.name" -> ["salak","config","name"]
"" -> []
"a..b" -> ["a","b"]

Types

data Property Source #

A Property value represented as a Haskell value.

Constructors

PNum !Scientific

Numeric Property

PStr !Text

String Property

PBool !Bool

Bool Property

Instances
Eq Property Source # 
Instance details

Defined in Data.Salak.Types

Show Property Source # 
Instance details

Defined in Data.Salak.Types

IsString Property Source # 
Instance details

Defined in Data.Salak.Types

FromProperties Property Source # 
Instance details

Defined in Data.Salak.Types

data Properties Source #

A Property Container to hold all properties

Instances
Eq Properties Source # 
Instance details

Defined in Data.Salak.Types

Show Properties Source # 
Instance details

Defined in Data.Salak.Types

type Key = Text Source #

Property key

class FromProperties a where Source #

Convert Properties to Haskell value.

Instances
FromProperties Bool Source # 
Instance details

Defined in Data.Salak.Types

FromProperties Char Source # 
Instance details

Defined in Data.Salak.Types

FromProperties Double Source # 
Instance details

Defined in Data.Salak.Types

FromProperties Float Source # 
Instance details

Defined in Data.Salak.Types

FromProperties Int Source # 
Instance details

Defined in Data.Salak.Types

FromProperties Int8 Source # 
Instance details

Defined in Data.Salak.Types

FromProperties Int16 Source # 
Instance details

Defined in Data.Salak.Types

FromProperties Int32 Source # 
Instance details

Defined in Data.Salak.Types

FromProperties Int64 Source # 
Instance details

Defined in Data.Salak.Types

FromProperties Word Source # 
Instance details

Defined in Data.Salak.Types

FromProperties Word8 Source # 
Instance details

Defined in Data.Salak.Types

FromProperties Word16 Source # 
Instance details

Defined in Data.Salak.Types

FromProperties Word32 Source # 
Instance details

Defined in Data.Salak.Types

FromProperties Word64 Source # 
Instance details

Defined in Data.Salak.Types

FromProperties Scientific Source # 
Instance details

Defined in Data.Salak.Types

FromProperties Text Source # 
Instance details

Defined in Data.Salak.Types

FromProperties String Source # 
Instance details

Defined in Data.Salak.Types

FromProperties Property Source # 
Instance details

Defined in Data.Salak.Types

FromProperties a => FromProperties [a] Source # 
Instance details

Defined in Data.Salak.Types

FromProperties a => FromProperties (Maybe a) Source # 
Instance details

Defined in Data.Salak.Types

type Return = Either ErrResult Source #

Return of FromProperties

Properties Loader Helper

insert :: [Key] -> Property -> Properties -> Properties Source #

Insert simple Property into Properties by Key. If the key already have values then the new property will discard.

defaultParseCommandLine :: ParseCommandLine Source #

Default command line parsers. Use format:

--KEY=VALUE

For example:

--salak.config.name=test.yml => ("salak.config.name", PStr "test.yml")

type ParseCommandLine = [String] -> IO [(String, Property)] Source #

CommandLine parser. Parse command line into property key values.

type FileName = String Source #

Yaml file name.

Operations

(.?>) :: FromProperties a => Properties -> Text -> Return a infixl 5 Source #

Find Properties by key and convert to specific Haskell value.

Since: 0.2.1

(.|=) :: Return a -> a -> a infixl 5 Source #

Get property or use default value if not found, but will throw exception if parse failed.

Since: 0.2.1

(.?=) :: Return a -> a -> Return a infixl 5 Source #

Use default value if Key not found

Since: 0.2.1

(.>>) :: FromProperties a => Properties -> Text -> a infixl 5 Source #

Find Properties by key and convert to specific Haskell value. Throw error if property not found or parse failed

Since: 0.2.1