| Copyright | (c) 2018 Daniel YU |
|---|---|
| License | BSD3 |
| Maintainer | Daniel YU <leptonyu@gmail.com> |
| Stability | experimental |
| Portability | portable |
| Safe Haskell | None |
| Language | Haskell2010 |
Data.Salak
Contents
Description
Configuration Loader for Production in Haskell.
Synopsis
- type LoadProperties = StateT Properties
- runLoad :: Monad m => LoadProperties m a -> m Properties
- askProperties :: Monad m => LoadProperties m Properties
- setValue :: Monad m => Text -> Property -> LoadProperties m ()
- loadCommandLine :: MonadIO m => ParseCommandLine -> LoadProperties m ()
- loadEnvironment :: MonadIO m => LoadProperties m ()
- loadJSON :: MonadIO m => Value -> LoadProperties m ()
- loadYaml :: MonadIO m => FilePath -> LoadProperties m ()
- loadYamlIfExists :: MonadIO m => Maybe FilePath -> LoadProperties m ()
- defaultProperties :: IO Properties
- defaultProperties' :: ParseCommandLine -> IO Properties
- defaultPropertiesWithFile :: FileName -> IO Properties
- defaultPropertiesWithFile' :: FileName -> ParseCommandLine -> IO Properties
- empty :: Properties
- lookup :: FromProperties a => Text -> Properties -> Return a
- toKeys :: Text -> [Key]
- data Property
- data Properties = Properties [Property] [HashMap Key Properties]
- type Key = Text
- class FromProperties a where
- fromProperties :: Properties -> Return a
- type Return = Either ErrResult
- insert :: [Key] -> Property -> Properties -> Properties
- defaultParseCommandLine :: ParseCommandLine
- type ParseCommandLine = [String] -> IO [(String, Property)]
- type FileName = String
- (.?>) :: FromProperties a => Properties -> Text -> Return a
- (.|=) :: Return a -> a -> a
- (.?=) :: Return a -> a -> Return a
- (.>>) :: FromProperties a => Properties -> Text -> a
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" .?= 1main = do
p <- defaultPropertiesWithFile "salak.yml"
let config = p .>> "salak.config" :: Config
enabled = p .?> "salak.enabled" .|= True
print config
print enabledProperties 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 |
| -> 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 |
| -> 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
empty :: Properties Source #
The empty Properties
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
A Property value represented as a Haskell value.
data Properties Source #
A Property Container to hold all properties
Constructors
| Properties [Property] [HashMap Key Properties] |
Instances
| Eq Properties Source # | |
Defined in Data.Salak.Types | |
| Show Properties Source # | |
Defined in Data.Salak.Types Methods showsPrec :: Int -> Properties -> ShowS # show :: Properties -> String # showList :: [Properties] -> ShowS # | |
class FromProperties a where Source #
Convert Properties to Haskell value.
Methods
fromProperties :: Properties -> Return a Source #
Instances
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.
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
(.>>) :: 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