salak-0.1.11: Configuration Loader

Copyright(c) 2019 Daniel YU
LicenseBSD3
Maintainerleptonyu@gmail.com
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

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 SourcePack. 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 FromProp Config where
  fromProp = Config
    <$> "user"
    <*> "pwd"
    <*> "ext" .?= 1
main = do
  c :: Config <- defaultLoadSalak def $ require ""
  print c
λ> c
Config {name = "daniel", dir = Nothing, ext = 1}

Salak

defaultLoadSalak :: MonadIO m => PropConfig -> ReaderT SourcePack m a -> m a Source #

Default load salak. All these configuration sources has orders, from highest order to lowest order:

1. CommandLine
2. Environment
3. Specified Yaml file(file in `configDirKey`)
4. Yaml file in current directory
5. Yaml file in home directory

loadSalak Source #

Arguments

:: Monad m 
=> ReaderT SourcePack m a

Fetch properties monad.

-> SourcePackT m ()

Load properties monad.

-> m a 

Load salak SourcePack and fetch properties.

data PropConfig Source #

Prop load configuration

Constructors

PropConfig 

Fields

Instances
Default PropConfig Source # 
Instance details

Defined in Salak

Methods

def :: PropConfig #

Static Load

class Monad m => HasSourcePack m where Source #

Instances
Monad m => HasSourcePack (StateT SourcePack m) Source # 
Instance details

Defined in Salak

Monad m => HasSourcePack (ReaderT SourcePack m) Source # 
Instance details

Defined in Salak

fetch Source #

Arguments

:: (HasSourcePack m, FromProp a) 
=> Text

Properties key

-> m (Either String a) 

Try fetch properties from SourcePack

require Source #

Arguments

:: (HasSourcePack m, FromProp a) 
=> Text

Properties key

-> m a 

Fetch properties from SourcePack, or throw fail

Dynamic Load

data ReloadableSourcePack Source #

Reloadable SourcePack

data ReloadResult Source #

Constructors

ReloadResult 

Fields

Instances
Eq ReloadResult Source # 
Instance details

Defined in Salak.Dynamic

Show ReloadResult Source # 
Instance details

Defined in Salak.Dynamic

reloadable :: (MonadIO m, HasSourcePack m) => ReloadableSourcePackT m a -> m a Source #

Lift to reloadable environment for dynamic properties.

fetchD Source #

Arguments

:: (MonadIO m, FromProp a) 
=> Text

Properties key

-> ReloadableSourcePackT m (Either String (IO a)) 

Try fetch dynamic properties from SourcePack

requireD Source #

Arguments

:: (MonadIO m, FromProp a) 
=> Text

Properties key

-> ReloadableSourcePackT m (IO a) 

Fetch dynamic properties from SourcePack, or throw fail

Prop Parser

type Prop = PropT PResult Source #

class FromProp a where Source #

Minimal complete definition

Nothing

Methods

fromProp :: Prop a Source #

fromProp :: (Generic a, GFromProp (Rep a)) => Prop a Source #

Instances
FromProp Bool Source # 
Instance details

Defined in Salak.Prop

FromProp Double Source # 
Instance details

Defined in Salak.Prop

FromProp Float Source # 
Instance details

Defined in Salak.Prop

FromProp Int Source # 
Instance details

Defined in Salak.Prop

FromProp Int8 Source # 
Instance details

Defined in Salak.Prop

FromProp Int16 Source # 
Instance details

Defined in Salak.Prop

FromProp Int32 Source # 
Instance details

Defined in Salak.Prop

FromProp Int64 Source # 
Instance details

Defined in Salak.Prop

FromProp Word Source # 
Instance details

Defined in Salak.Prop

FromProp Word8 Source # 
Instance details

Defined in Salak.Prop

FromProp Word16 Source # 
Instance details

Defined in Salak.Prop

FromProp Word32 Source # 
Instance details

Defined in Salak.Prop

FromProp Word64 Source # 
Instance details

Defined in Salak.Prop

FromEnumProp a => FromProp a Source # 
Instance details

Defined in Salak.Prop

Methods

fromProp :: Prop a Source #

FromProp Scientific Source # 
Instance details

Defined in Salak.Prop

FromProp Text Source # 
Instance details

Defined in Salak.Prop

FromProp Text Source # 
Instance details

Defined in Salak.Prop

FromProp String Source # 
Instance details

Defined in Salak.Prop

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

Defined in Salak.Prop

Methods

fromProp :: Prop [a] Source #

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

Defined in Salak.Prop

Methods

fromProp :: Prop (Maybe a) Source #

class FromEnumProp a where Source #

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

Optional value.

(.?:) :: (Alternative f, Default b) => f a -> (b -> a) -> f a infixl 5 Source #

Default value.

SourcePack

data SourcePack Source #

Instances
Show SourcePack Source # 
Instance details

Defined in Salak.Types

MonadReader SourcePack Prop Source # 
Instance details

Defined in Salak.Prop

Methods

ask :: Prop SourcePack #

local :: (SourcePack -> SourcePack) -> Prop a -> Prop a #

reader :: (SourcePack -> a) -> Prop a #

Monad m => HasSourcePack (StateT SourcePack m) Source # 
Instance details

Defined in Salak

Monad m => HasSourcePack (ReaderT SourcePack m) Source # 
Instance details

Defined in Salak

loadMock :: Monad m => [(Text, Text)] -> SourcePackT m () Source #

data Value Source #

Instances
Eq Value Source # 
Instance details

Defined in Salak.Types

Methods

(==) :: Value -> Value -> Bool #

(/=) :: Value -> Value -> Bool #

Ord Value Source # 
Instance details

Defined in Salak.Types

Methods

compare :: Value -> Value -> Ordering #

(<) :: Value -> Value -> Bool #

(<=) :: Value -> Value -> Bool #

(>) :: Value -> Value -> Bool #

(>=) :: Value -> Value -> Bool #

max :: Value -> Value -> Value #

min :: Value -> Value -> Value #

Show Value Source # 
Instance details

Defined in Salak.Types

Methods

showsPrec :: Int -> Value -> ShowS #

show :: Value -> String #

showList :: [Value] -> ShowS #