minimal-configuration-0.1: Minimal ini like configuration library with a few extras

Portabilityportable
Stabilityunstable
Safe HaskellSafe-Inferred

System.Config.File

Contents

Description

IMPORTANT NOTE: this module works with the user's home directory, and that is the place where the configuration will be read from and persisted.

Synopsis

Basics

Types

data Configuration Source

While the internal representation is not exposed directly, an implementation of the Show instance is provided in order to dump the configuration when that may be aidful in debugging. However, you will only see the key values stored inside the Map

Instances

Managing

withConfigurationSource

Arguments

:: String

Configuration file name

-> (Configuration -> IO b) 
-> IO b 

However if you like to stack software ala withSocketsDo $ withX $ withY this might not be your preferred approach. You could go with the following approach, which was excluded for library portability:

 {-# LANGUAGE ImplicitParams, RankNTypes #-}
 import System.Config.File

 withConfigurationImplicit :: String -> ((?configuration :: Configuration) => IO b) -> IO b
 withConfigurationImplicit filename f = withConfiguration filename (\c -> let ?configuration = c in f)

 main = withConfigurationImplicit ".apprc" $ do
    print $ hasV "name" ?configuration
    print $ getV "name" ?configuration

loadConfigurationSource

Arguments

:: String

Configuration file name

-> IO Configuration 

saveConfiguration :: Configuration -> IO ()Source

The configuration will be saved into the same file it was read from, obviously

CRUD

Data "entry"

It proved useful that for a few small cases to also have a way to "build" the configuration interactively. When you consider easy to validate fields (that don't depend on other fields), it seems to be worth to have this functionality included.

Validation

type InteractiveValidator = Value -> IO (Either String Value)Source

Via the Left data constructor we are able to pass the message necessary to notify the user that the inputed data is not valid

Execution

fillInteractively :: Configuration -> [(Key, InteractiveValidator)] -> IO ConfigurationSource

Request user input for the set of (Key, InteractiveValidator). For keys that are already set in the Configuration, values will be overwritten

fillInteractivelyWhen :: (Configuration -> Bool) -> Configuration -> [(Key, InteractiveValidator)] -> IO ConfigurationSource

Execution dependent on a predicate

Predicates

newC :: Configuration -> BoolSource

Has this configuration just been created?

emptyC :: Configuration -> BoolSource

Configuration doesn't contain any values?