| Copyright | (c) 2019 Daniel YU |
|---|---|
| License | BSD3 |
| Maintainer | leptonyu@gmail.com |
| Stability | experimental |
| Portability | portable |
| Safe Haskell | None |
| Language | Haskell2010 |
Salak
Contents
Description
Configuration Loader for Production in Haskell.
Synopsis
- runSalak :: (MonadCatch m, MonadIO m) => PropConfig -> RunSalakT m a -> m a
- runSalakWith :: (MonadCatch m, MonadIO m, HasLoad file) => FileName -> file -> RunSalakT m a -> m a
- loadAndRunSalak :: (MonadThrow m, MonadIO m) => LoadSalakT m () -> RunSalakT m a -> m a
- loadAndRunSalak' :: (MonadThrow m, MonadIO m) => LoadSalakT m () -> (SourcePack -> m a) -> m a
- data PropConfig = PropConfig {
- configName :: Maybe FileName
- configDirKey :: Text
- searchCurrent :: Bool
- searchHome :: Bool
- commandLine :: ParseCommandLine
- loadExt :: FilePath -> LoadSalak ()
- class HasSalak m where
- class Monad m => MonadSalak m where
- askSalak :: m SourcePack
- data RunSalakT m a
- type RunSalak = RunSalakT IO
- data LoadSalakT m a
- type LoadSalak = LoadSalakT IO
- loadCommandLine :: MonadIO m => ParseCommandLine -> LoadSalakT m ()
- type ParseCommandLine = [String] -> IO [(Text, Text)]
- defaultParseCommandLine :: ParseCommandLine
- loadEnv :: MonadIO m => LoadSalakT m ()
- loadMock :: MonadIO m => [(Text, Text)] -> LoadSalakT m ()
- loadSalak :: (MonadCatch m, MonadIO m) => PropConfig -> LoadSalakT m ()
- loadSalakWith :: (MonadCatch m, MonadIO m, HasLoad file) => file -> FileName -> LoadSalakT m ()
- type ExtLoad = (String, FilePath -> LoadSalak ())
- loadByExt :: HasLoad a => a -> FilePath -> LoadSalak ()
- class HasLoad a where
- data a :|: b = a :|: b
- data ReloadResult = ReloadResult {}
- askReload :: MonadSalak m => m (IO ReloadResult)
- class PropOp f a where
- class Monad m => FromProp m a where
- data Prop m a
- readPrimitive :: MonadThrow m => (Value -> Either String a) -> Prop m a
- readEnum :: MonadThrow m => (Text -> Either String a) -> Prop m a
- data SourcePack
- data PropException
- class MonadThrow m => MonadCatch (m :: Type -> Type)
- class Monad m => MonadThrow (m :: Type -> Type)
- class Monad m => MonadIO (m :: Type -> Type)
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 MonadCatch m => FromProp m Config where
fromProp = Config
<$> "user" ? pattern "[a-z]{5,16}"
<*> "pwd"
<*> "ext" .?= 1
main = runSalakWith "salak" (YAML :|: TOML) $ do
c :: Config <- require "test.config"
lift $ print cGHCi play
λ> :set -XFlexibleInstances -XMultiParamTypeClasses
λ> import Salak
λ> import Data.Default
λ> import Data.Text(Text)
λ> data Config = Config { name :: Text, dir :: Maybe Text, ext :: Int} deriving (Eq, Show)
λ> instance MonadCatch m => FromProp m Config where fromProp = Config <$> "user" <*> "dir" <*> "ext" .?= 1
λ> runSalak def (require "") :: IO Config
Config {name = "daniel", dir = Nothing, ext = 1}Salak Main Functions
runSalak :: (MonadCatch m, MonadIO m) => PropConfig -> RunSalakT m a -> m a Source #
Run salak, load strategy refer to loadSalak
runSalakWith :: (MonadCatch m, MonadIO m, HasLoad file) => FileName -> file -> RunSalakT m a -> m a Source #
Run salak, load strategy refer to loadSalakWith
loadAndRunSalak :: (MonadThrow m, MonadIO m) => LoadSalakT m () -> RunSalakT m a -> m a Source #
Standard salak functions, by load and run with RunSalakT.
loadAndRunSalak' :: (MonadThrow m, MonadIO m) => LoadSalakT m () -> (SourcePack -> m a) -> m a Source #
Standard salak functions, by load and with a SourcePack instance.
Users should use SourcePack to create custom MonadSalak instances, then you get will an instance of HasSalak.
data PropConfig Source #
Prop load configuration
Constructors
| PropConfig | |
Fields
| |
Instances
| Default PropConfig Source # | |
Defined in Salak Methods def :: PropConfig # | |
Run Functions
class HasSalak m where Source #
Core type class of salak, which provide function to parse properties.
Methods
require :: FromProp m a => Text -> m a Source #
Parse properties using FromProp. For example:
a :: Bool <- require "bool.key" b :: Maybe Int <- require "int.optional.key" c :: Either String Int <- require "int.error.key" d :: IO Int <- require "int.reloadable.key"
Instances
| (MonadThrow m, MonadSalak m) => HasSalak m Source # | |
class Monad m => MonadSalak m where Source #
Monad has the ability to get a SourcePack instance.
Methods
askSalak :: m SourcePack Source #
Instances
| (m' ~ t (RunSalakT m), MonadTrans t, Monad m, Monad m') => MonadSalak m' Source # | |
Defined in Salak.Internal Methods askSalak :: m' SourcePack Source # | |
| Monad m => MonadSalak (Prop m) Source # | |
Defined in Salak.Internal.Prop Methods askSalak :: Prop m SourcePack Source # | |
| Monad m => MonadSalak (RunSalakT m) Source # | |
Defined in Salak.Internal Methods askSalak :: RunSalakT m SourcePack Source # | |
| MonadIO m => MonadSalak (LoadSalakT m) Source # | |
Defined in Salak.Internal Methods askSalak :: LoadSalakT m SourcePack Source # | |
Standard HasSalak instance.
Instances
| MonadTrans RunSalakT Source # | |
Defined in Salak.Internal | |
| Monad m => MonadReader SourcePack (RunSalakT m) Source # | |
Defined in Salak.Internal Methods ask :: RunSalakT m SourcePack # local :: (SourcePack -> SourcePack) -> RunSalakT m a -> RunSalakT m a # reader :: (SourcePack -> a) -> RunSalakT m a # | |
| Monad m => Monad (RunSalakT m) Source # | |
| Functor m => Functor (RunSalakT m) Source # | |
| Applicative m => Applicative (RunSalakT m) Source # | |
Defined in Salak.Internal | |
| MonadIO m => MonadIO (RunSalakT m) Source # | |
Defined in Salak.Internal | |
| MonadThrow m => MonadThrow (RunSalakT m) Source # | |
Defined in Salak.Internal | |
| MonadCatch m => MonadCatch (RunSalakT m) Source # | |
| MonadUnliftIO m => MonadUnliftIO (RunSalakT m) Source # | |
Defined in Salak.Internal | |
| Monad m => MonadSalak (RunSalakT m) Source # | |
Defined in Salak.Internal Methods askSalak :: RunSalakT m SourcePack Source # | |
Load Functions
Monad for Loader
data LoadSalakT m a Source #
Configuration Loader Monad, used for load properties from sources. Custom loaders using loadTrie
Instances
type LoadSalak = LoadSalakT IO Source #
Simple IO Monad
Basic loaders
loadCommandLine :: MonadIO m => ParseCommandLine -> LoadSalakT m () Source #
Default way to parse command line arguments
defaultParseCommandLine :: ParseCommandLine Source #
Default way to parse command line arguments
loadSalak :: (MonadCatch m, MonadIO m) => PropConfig -> LoadSalakT m () 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.
loadSalakWith :: (MonadCatch m, MonadIO m, HasLoad file) => file -> FileName -> LoadSalakT m () Source #
File Loaders
loadByExt :: HasLoad a => a -> FilePath -> LoadSalak () Source #
Load files with specified format, yaml or toml, etc.
Reload Functions
data ReloadResult Source #
Reload result, show erros or changes.
Constructors
| ReloadResult | |
Instances
| Show ReloadResult Source # | |
Defined in Salak.Internal.Source Methods showsPrec :: Int -> ReloadResult -> ShowS # show :: ReloadResult -> String # showList :: [ReloadResult] -> ShowS # | |
askReload :: MonadSalak m => m (IO ReloadResult) Source #
Get reload action which used for reload profiles
Properties Parsers
class PropOp f a where Source #
Prop operators.
Suppose we have following definition:
data Config = Config
{ enabled :: Bool
, level :: IO LogLevel
}Minimal complete definition
Methods
(.?=) :: f a -> a -> f a infixl 5 Source #
Parse or default value
instance MonadThrow m => FromProp m Config where
fromProp = Config
<$> "enabled" .?= True
<*> "level" .?= (return LevelInfo)IO value will work right.
(.?:) :: Default b => f a -> (b -> a) -> f a infixl 5 Source #
Parse or auto extract from a Default value
instance Default Config where
def = Config True (return LevelInfo)
instance MonadThrow m => FromProp m Config where
fromProp = Config
<$> "enabled" .?: enabled
<$> "level" .?: levelInstances
| Alternative f => PropOp f a Source # | Support normal value |
| (Show a, MonadCatch m, MonadIO m, FromProp (Either SomeException) a) => PropOp (Prop m) (IO a) Source # | Support IO value |
class Monad m => FromProp m a where Source #
Minimal complete definition
Nothing
Instances
Instances
readPrimitive :: MonadThrow m => (Value -> Either String a) -> Prop m a Source #
Parse primitive value from Value
readEnum :: MonadThrow m => (Text -> Either String a) -> Prop m a Source #
Parse enum value from Text
data SourcePack Source #
Instances
| Monad m => MonadReader SourcePack (Prop m) Source # | |
Defined in Salak.Internal.Prop Methods ask :: Prop m SourcePack # local :: (SourcePack -> SourcePack) -> Prop m a -> Prop m a # reader :: (SourcePack -> a) -> Prop m a # | |
| Monad m => MonadReader SourcePack (RunSalakT m) Source # | |
Defined in Salak.Internal Methods ask :: RunSalakT m SourcePack # local :: (SourcePack -> SourcePack) -> RunSalakT m a -> RunSalakT m a # reader :: (SourcePack -> a) -> RunSalakT m a # | |
data PropException Source #
Constructors
| PropException String | Parse failed |
| NullException | Not found |
Instances
| Show PropException Source # | |
Defined in Salak.Internal.Prop Methods showsPrec :: Int -> PropException -> ShowS # show :: PropException -> String # showList :: [PropException] -> ShowS # | |
| Exception PropException Source # | |
Defined in Salak.Internal.Prop Methods toException :: PropException -> SomeException # fromException :: SomeException -> Maybe PropException # displayException :: PropException -> String # | |
Reexport
class MonadThrow m => MonadCatch (m :: Type -> Type) #
A class for monads which allow exceptions to be caught, in particular
exceptions which were thrown by throwM.
Instances should obey the following law:
catch (throwM e) f = f e
Note that the ability to catch an exception does not guarantee that we can
deal with all possible exit points from a computation. Some monads, such as
continuation-based stacks, allow for more than just a success/failure
strategy, and therefore catch cannot be used by those monads to properly
implement a function such as finally. For more information, see
MonadMask.
Minimal complete definition
Instances
class Monad m => MonadThrow (m :: Type -> Type) #
A class for monads in which exceptions may be thrown.
Instances should obey the following law:
throwM e >> x = throwM e
In other words, throwing an exception short-circuits the rest of the monadic computation.
Minimal complete definition
Instances
class Monad m => MonadIO (m :: Type -> Type) #
Monads in which IO computations may be embedded.
Any monad built by applying a sequence of monad transformers to the
IO monad will be an instance of this class.
Instances should satisfy the following laws, which state that liftIO
is a transformer of monads:
Minimal complete definition