dyre-0.8.0: Dynamic reconfiguration in Haskell

Config.Dyre

Description

Dyre is a library for configuring your Haskell programs. Like Xmonad, programs configured with Dyre will look for a configuration file written in Haskell, which essentially defines a custom program configured exactly as the user wishes it to be. And since the configuration is written in Haskell, the user is free to do anything they might wish in the context of configuring the program.

Dyre places emphasis on elegance of operation and ease of integration with existing applications. The wrapMain function is the sole entry point for Dyre. When partially applied with a parameter structure, it wraps around the realMain value from that structure, yielding an almost identical function which has been augmented with dynamic recompilation functionality.

The Config.Dyre.Relaunch module provides the ability to restart the program (recompiling if applicable), and persist state across restarts, but it has no impact whatsoever on the rest of the library whether it is used or not.

A full example of using most of Dyre's major features is as follows:

  • - DyreExample.hs -- module DyreExample where

import qualified Config.Dyre as Dyre import Config.Dyre.Relaunch

import System.IO

data Config = Config { message :: String, errorMsg :: Maybe String } data State = State { bufferLines :: [String] } deriving (Read, Show)

defaultConfig :: Config defaultConfig = Config Dyre Example v0.1 Nothing

showError :: Config -> String -> Config showError cfg msg = cfg { errorMsg = Just msg }

realMain Config{message = message, errorMsg = errorMsg } = do (State buffer) <- restoreTextState $ State [] case errorMsg of Nothing -> return () Just em -> putStrLn $ Error: ++ em putStrLn message mapM putStrLn . reverse $ buffer putStr > >> hFlush stdout input <- getLine case input of exit -> return () quit -> return () other -> relaunchWithTextState (State $ other:buffer) Nothing

dyreExample = Dyre.wrapMain $ Dyre.defaultParams { Dyre.projectName = dyreExample , Dyre.realMain = realMain , Dyre.showError = showError }

Notice that all of the program logic is contained in the DyreExample module. The main module of the program is absolutely trivial, being essentially just the default configuration for the program:

  • - Main.hs -- import DyreExample main = dyreExample defaultConfig

When reading the above program, notice that the majority of the code is simply *program logic*. Dyre is designed to intelligently handle recompilation with a minimum of programmer work.

Some mention should be made of Dyre's defaults. The defaultParams structure used in the example defines reasonable default values for most configuration items. The three elements defined above are the only elements that must be overridden. For documentation of the parameters, consult the Config.Dyre.Params module.

In the absence of any customization, Dyre will search for configuration files in '$XDG_CONFIG_HOME/<appName>/<appName>.hs', and will store cache files in '$XDG_CACHE_HOME/<appName>/' directory. The module System.Environment.XDG is used for this purpose, which also provides analogous behaviour on Windows.

Synopsis

Documentation

wrapMain :: Params cfgType -> cfgType -> IO ()Source

wrapMain is how Dyre recieves control of the program. It is expected that it will be partially applied with its parameters to yield a main entry point, which will then be called by the main function, as well as by any custom configurations.

data Params cfgType Source

This structure is how all kinds of useful data is fed into Dyre. Of course, only the projectName, realMain, and showError fields are really necessary. By using the set of default values provided as Config.Dyre.defaultParams, you can get all the benefits of using Dyre to configure your program in only five or six lines of code.

Constructors

Params 

Fields

projectName :: String

The name of the project. This needs to also be the name of the executable, and the name of the configuration file.

configCheck :: Bool

Should Dyre look for and attempt to compile custom configurations? Useful for creating program entry points that bypass Dyre's recompilation, for testing purposes.

configDir :: Maybe (IO FilePath)

The directory to look for a configuration file in.

cacheDir :: Maybe (IO FilePath)

The directory to store build files in, including the final generated executable.

realMain :: cfgType -> IO ()

The main function of the program. When Dyre has completed all of its recompilation, it passes the configuration data to this function and gets out of the way.

showError :: cfgType -> String -> cfgType

This function is used to display error messages that occur during recompilation, by allowing the program to modify its initial configuration.

hidePackages :: [String]

Packages that need to be hidden during compilation

ghcOpts :: [String]

Miscellaneous GHC compilation settings go here

forceRecomp :: Bool

Should GHC be given the -fforce-recomp flag?

statusOut :: String -> IO ()

A status output function. Will be called with messages when Dyre recompiles or launches anything. A good value is 'hPutStrLn stderr', assuming there is no pressing reason to not put messages on stderr.

defaultParams :: Params cfgTypeSource

A set of reasonable defaults for configuring Dyre. The fields that have to be filled are projectName, realMain, and showError.