Copyright | 2019 Daniel YU |
---|---|
License | MIT |
Maintainer | leptonyu@gmail.com |
Stability | experimental |
Portability | portable |
Safe Haskell | None |
Language | Haskell2010 |
Configuration (re)Loader and Parser.
Synopsis
- runSalak :: (MonadCatch m, MonadIO m) => PropConfig -> RunSalakT m a -> m a
- runSalakWith :: (MonadCatch m, MonadIO m, HasLoad file) => String -> 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 {
- configKey :: !Text
- configName :: !String
- searchCurrent :: !Bool
- searchHome :: !Bool
- commandLine :: !ParseCommandLine
- loggerF :: !LFunc
- loadExt :: FilePath -> LoadSalak ()
- class Monad m => MonadSalak m where
- askSourcePack :: m SourcePack
- askReload :: m (IO ReloadResult)
- setLogF :: MonadIO m => (CallStack -> Text -> IO ()) -> m ()
- logSalak :: (HasCallStack, MonadIO m) => Text -> m ()
- require :: (MonadThrow m, MonadIO m, FromProp m a) => Text -> m a
- data RunSalakT m a
- type RunSalak = RunSalakT IO
- class PropOp f a where
- class FromProp m a where
- data Prop m a
- readPrimitive :: MonadIO m => (Value -> Either String a) -> Prop m a
- readEnum :: MonadIO m => (Text -> Either String a) -> Prop m a
- data SourcePack
- type Salak = SourcePack
- data SalakException
- data Writable a
- toWritable :: IO a -> IO (Writable a)
- getWritable :: Writable a -> IO a
- setWritable :: Maybe a -> Writable a -> IO ()
- data LoadSalakT m a
- type LoadSalak = LoadSalakT IO
- loadCommandLine :: (MonadThrow m, MonadIO m) => ParseCommandLine -> LoadSalakT m ()
- type ParseCommandLine = [String] -> IO [(Text, Text)]
- defaultParseCommandLine :: ParseCommandLine
- loadEnv :: (MonadThrow m, MonadIO m) => LoadSalakT m ()
- loadMock :: (MonadThrow m, MonadIO m) => [(Text, Text)] -> LoadSalakT m ()
- loadSalak :: (MonadThrow m, MonadIO m) => PropConfig -> LoadSalakT m ()
- loadSalakWith :: (MonadThrow m, MonadIO m, HasLoad file) => file -> String -> 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 {}
- 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 defines a universal procedure to load configurations and parse properties, also supports reload configurations.
We can load configurations from command lines, environment, configuration files such as yaml or toml etc., and we may want to have our own strategies to load configurations from multiply 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 `application.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.
After loading configurations, we can use require
to parse properties. 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"
Salak supports parse IO
values, which actually wrap a MVar
variable and can be reseted by reloading configurations.
Normal value will not be affected by reloading configurations.
GHCi play
>>>
:set -XFlexibleInstances -XMultiParamTypeClasses -XOverloadedStrings
>>>
import Salak
>>>
import Data.Default
>>>
import Data.Text(Text)
>>>
data Config = Config { name :: Text, dir :: Maybe Text, ext :: Int} deriving (Eq, Show)
>>>
instance 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) => String -> 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 MonadSalak
.
data PropConfig Source #
Prop load configuration
PropConfig | |
|
Instances
Default PropConfig Source # | |
Defined in Salak def :: PropConfig # |
Parsing Properties Function
class Monad m => MonadSalak m where Source #
Core type class of salak, which provide function to parse properties.
askSourcePack :: m SourcePack Source #
Monad has the ability to get a SourcePack instance.
askReload :: m (IO ReloadResult) Source #
Get reload action which used for reload profiles
setLogF :: MonadIO m => (CallStack -> Text -> IO ()) -> m () Source #
logSalak :: (HasCallStack, MonadIO m) => Text -> m () Source #
require :: (MonadThrow m, MonadIO m, 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"
require
supports parse IO
values, which actually wrap a MVar
variable and can be reseted by reloading configurations.
Normal value will not be affected by reloading configurations.
Instances
Standard MonadSalak
instance.
Instances
Operators
class PropOp f a where Source #
Prop operators.
Suppose we have the following definition:
data Config = Config { enabled :: Bool , level :: IO LogLevel }
(.?=) :: 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 default value 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" .?: level
class FromProp m a where Source #
Type class used to parse properties.
Nothing
fromProp :: MonadIO m => Prop m a Source #
Parse properties from Value
.
fromProp :: (Generic a, GFromProp m (Rep a), MonadIO m) => Prop m a Source #
Parse properties from Value
.
Instances
Property parser, used to parse property from Value
Instances
readPrimitive :: MonadIO m => (Value -> Either String a) -> Prop m a Source #
Parse primitive value from Value
data SourcePack Source #
Instances
Monad m => MonadReader SourcePack (Prop m) Source # | |
Defined in Salak.Internal.Prop 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 ask :: RunSalakT m SourcePack # local :: (SourcePack -> SourcePack) -> RunSalakT m a -> RunSalakT m a # reader :: (SourcePack -> a) -> RunSalakT m a # | |
Monad m => MonadSalak (ReaderT SourcePack m) Source # | |
Defined in Salak.Internal.Prop askSourcePack :: ReaderT SourcePack m SourcePack Source # askReload :: ReaderT SourcePack m (IO ReloadResult) Source # setLogF :: (CallStack -> Text -> IO ()) -> ReaderT SourcePack m () Source # logSalak :: Text -> ReaderT SourcePack m () Source # require :: (MonadThrow (ReaderT SourcePack m), MonadIO (ReaderT SourcePack m), FromProp (ReaderT SourcePack m) a) => Text -> ReaderT SourcePack m a Source # |
type Salak = SourcePack Source #
Type synonyms of SourcePack
data SalakException Source #
Exception
SalakException Keys String | Parse failed |
NullException Keys | Not found |
Instances
Show SalakException Source # | |
Defined in Salak.Internal.Prop showsPrec :: Int -> SalakException -> ShowS # show :: SalakException -> String # showList :: [SalakException] -> ShowS # | |
Exception SalakException Source # | |
Defined in Salak.Internal.Prop |
Writable Value
Writable data structure. Writable
is designed for working with IO
value pased by salak.
It provide a way to override IO
value provided by salak, can be used in the application which need to change
values of some configurations by overriding it directly. For example, logger function can use a log level property
to control which level of logs should be printed. By using Writeable
value, we can change the property
directly.
getWritable :: Writable a -> IO a Source #
Get value.
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 :: (MonadThrow m, MonadIO m) => ParseCommandLine -> LoadSalakT m () Source #
Default way to parse command line arguments
defaultParseCommandLine :: ParseCommandLine Source #
Default way to parse command line arguments
loadEnv :: (MonadThrow m, MonadIO m) => LoadSalakT m () Source #
Load environment variables into Source
loadMock :: (MonadThrow m, MonadIO m) => [(Text, Text)] -> LoadSalakT m () Source #
Load mock variables into Source
loadSalak :: (MonadThrow 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 :: (MonadThrow m, MonadIO m, HasLoad file) => file -> String -> 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.
Instances
Show ReloadResult Source # | |
Defined in Salak.Internal.Source showsPrec :: Int -> ReloadResult -> ShowS # show :: ReloadResult -> String # showList :: [ReloadResult] -> ShowS # |
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
.
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.
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: