salak-0.1.9: 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}

Source

data Selector Source #

Instances
Eq Selector Source # 
Instance details

Defined in Salak.Types

Show Selector Source # 
Instance details

Defined in Salak.Types

data SourcePack Source #

Instances
Show SourcePack Source # 
Instance details

Defined in Salak.Types

FromProp a => IsString (Prop a) Source # 
Instance details

Defined in Salak.Prop

Methods

fromString :: String -> Prop a #

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

Defined in Salak

data Reload Source #

Constructors

Reload 

Fields

Instances
Show Reload Source # 
Instance details

Defined in Salak.Types

load :: (Functor f, Foldable f) => Reload -> f a -> (Priority -> a -> (Text, Value)) -> SourcePack -> SourcePack Source #

Salak

loadSalak :: Monad m => ReaderT SourcePack m a -> SourcePackT m () -> m a Source #

data PropConfig Source #

Constructors

PropConfig 

Fields

Instances
Default PropConfig Source # 
Instance details

Defined in Salak

Methods

def :: PropConfig #

class Monad m => HasSourcePack m where Source #

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

Defined in Salak

Utilities

runReloadable :: MonadIO m => SourcePack -> ReloadableSourcePackT m a -> m (a, IO (Bool, [String])) 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

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 #

data PResult a Source #

Constructors

O [Selector] a 
N [Selector] 
F [Selector] String 
Instances
Monad PResult Source # 
Instance details

Defined in Salak.Prop

Methods

(>>=) :: PResult a -> (a -> PResult b) -> PResult b #

(>>) :: PResult a -> PResult b -> PResult b #

return :: a -> PResult a #

fail :: String -> PResult a #

Functor PResult Source # 
Instance details

Defined in Salak.Prop

Methods

fmap :: (a -> b) -> PResult a -> PResult b #

(<$) :: a -> PResult b -> PResult a #

Applicative PResult Source # 
Instance details

Defined in Salak.Prop

Methods

pure :: a -> PResult a #

(<*>) :: PResult (a -> b) -> PResult a -> PResult b #

liftA2 :: (a -> b -> c) -> PResult a -> PResult b -> PResult c #

(*>) :: PResult a -> PResult b -> PResult b #

(<*) :: PResult a -> PResult b -> PResult a #

Alternative PResult Source # 
Instance details

Defined in Salak.Prop

Methods

empty :: PResult a #

(<|>) :: PResult a -> PResult a -> PResult a #

some :: PResult a -> PResult [a] #

many :: PResult a -> PResult [a] #

Eq a => Eq (PResult a) Source # 
Instance details

Defined in Salak.Prop

Methods

(==) :: PResult a -> PResult a -> Bool #

(/=) :: PResult a -> PResult a -> Bool #

Show a => Show (PResult a) Source # 
Instance details

Defined in Salak.Prop

Methods

showsPrec :: Int -> PResult a -> ShowS #

show :: PResult a -> String #

showList :: [PResult a] -> ShowS #

FromProp a => IsString (Prop a) Source # 
Instance details

Defined in Salak.Prop

Methods

fromString :: String -> Prop a #

readPrimitive :: ([Selector] -> Value -> PResult a) -> Prop a Source #

ReadPrimitive value

readSelect :: FromProp a => Text -> Prop a Source #

Parse value