salak-0.2.7: 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 define a universal procedure to load configurations and parse properties, also supports reload configuration files.

We can load configurations from command line, environment, configuration files such as yaml or toml etc, and we may want to have our own strategies to load configurations from multi sources and overwrite properties by orders of these sources.

PropConfig defines a common loading strategy:

1. loadCommandLine
2. loadEnvironment
3. loadConfFiles
4. load file from folder `salak.conf.dir` if defined
5. load file from current folder if enabled
6. load file from home folder if enabled
7. file extension matching, support yaml or toml or any other loader.

Load earlier has higher priority, priorities cannot be changed.

Usage:

Environment:

export TEST_CONFIG_NAME=daniel

Current Directory: salak.yaml

test.config:
  name: noop
  dir: ls

Current Directory: salak.toml

[test.config]
ext=2
data Config = Config
  { name :: Text
  , dir  :: Maybe Text
  , ext  :: Int
  } deriving (Eq, Show)

instance FromProp Config where
  fromProp = Config
    <$> "user" ? pattern "[a-z]{5,16}"
    <*> "pwd"
    <*> "ext" .?= 1

main = runSalak def { configName = Just "salak", loadExt = loadByExt $ YAML :|: TOML } $ do
  c :: Config <- require "test.config"
  lift $ print c

GHCi play

λ> import Salak
λ> import Salak.Load.YAML
λ> import Salak.Load.TOML
λ> :set -XTypeApplications
λ> instance FromProp Config where fromProp = Config <$> "user" <*> "dir" <*> "ext" .?= 1
λ> f = runSalak def { configName = Just "salak", loadExt = loadByExt $ YAML :|: TOML }
λ> f (require "") >>= print @Config
Config {name = "daniel", dir = Just "ls", ext = 2}

Salak

loadAndRunSalak Source #

Arguments

:: Monad m 
=> SourcePackT m ()

Load properties monad.

-> ReaderT SourcePack m a

Fetch properties monad.

-> m a 

Load and run salak SourcePack and fetch properties.

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

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

1. loadCommandLine
2. loadEnvironment
3. loadConfFiles
4. load file from folder `salak.conf.dir` if defined
5. load file from current folder if enabled
6. load file from home folder if enabled
7. file extension matching, support yaml or toml or any other loader.

data PropConfig Source #

Prop load configuration

Constructors

PropConfig 

Fields

Instances
Default PropConfig Source # 
Instance details

Defined in Salak

Methods

def :: PropConfig #

Static Get Properties

class Monad m => HasSourcePack m where Source #

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

Defined in Salak

Monad m => HasSourcePack (StateT 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 Get Properties

data ReloadableSourcePack Source #

Reloadable SourcePack

data ReloadResult Source #

Constructors

ReloadResult 

Fields

Instances
Eq ReloadResult Source # 
Instance details

Defined in Salak.Load.Dynamic

Show ReloadResult Source # 
Instance details

Defined in Salak.Load.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 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 Scientific 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 (ReaderT SourcePack m) Source # 
Instance details

Defined in Salak

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

Defined in Salak

Load configurations

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

Load By Extension

type ExtLoad = (String, FilePath -> SourcePackT IO ()) Source #

Load file by extension

class HasLoad a where Source #

Methods

loaders :: a -> [ExtLoad] Source #

Instances
(HasLoad a, HasLoad b) => HasLoad (a :|: b) Source # 
Instance details

Defined in Salak

Methods

loaders :: (a :|: b) -> [ExtLoad] Source #

data a :|: b infixr 3 Source #

Constructors

a :|: b infixr 3 
Instances
(HasLoad a, HasLoad b) => HasLoad (a :|: b) Source # 
Instance details

Defined in Salak

Methods

loaders :: (a :|: b) -> [ExtLoad] Source #

Other

data Value Source #

Instances
Eq Value Source # 
Instance details

Defined in Salak.Types.Value

Methods

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

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

Ord Value Source # 
Instance details

Defined in Salak.Types.Value

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.Value

Methods

showsPrec :: Int -> Value -> ShowS #

show :: Value -> String #

showList :: [Value] -> ShowS #

Show Source Source # 
Instance details

Defined in Salak.Types.Source

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

Deprecated: use runSalak instead