dyre-0.9.0: Dynamic reconfiguration in Haskell
Safe HaskellNone
LanguageHaskell2010

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.

Writing a program that uses Dyre

The following example program uses most of Dyre's major features:

-- DyreExample.hs --
module DyreExample
  ( Config(..)
  , defaultConfig
  , 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
    traverse 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.newParams "dyreExample" realMain showError

All of the program logic is contained in the DyreExample module. The module exports the Config data type, a defaultConfig, and the dyreExample function which, when applied to a Config, returns an (IO a) value to be used as main.

The Main module of the program is trivial. All that is required is to apply dyreExample to the default configuration:

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

Custom program configuration

Users can create a custom configuration file that overrides some or all of the default configuration:

-- ~/.config/dyreExample/dyreExample.hs --
import DyreExample
main = dyreExample $ defaultConfig { message = "Dyre Example v0.1 (Modified)" }

When a program that uses Dyre starts, Dyre checks to see if a custom configuration exists. If so, it runs a custom executable. Dyre (re)compiles and caches the custom executable the first time it sees the custom config or whenever the custom config has changed.

If a custom configuration grows large, you can extract parts of it into one or more files under lib/. For example:

-- ~/.config/dyreExample/dyreExample.hs --
import DyreExample
import Message
main = dyreExample $ defaultConfig { message = Message.msg }
-- ~/.config/dyreExample/lib/Message.hs --
module Message where
msg = "Dyre Example v0.1 (Modified)"

Working with the Cabal store

For a Dyre-enabled program to work when installed via cabal install, it needs to add its library directory as an extra include directory for compilation. The library package name must match the Dyre projectName for this to work. For example:

import Paths_dyreExample (getLibDir)

dyreExample cfg = do
  libdir <- getLibDir
  let params = (Dyre.newParams "dyreExample" realMain showError)
        { Dyre.includeDirs = [libdir] }
  Dyre.wrapMain params cfg

See also the Cabal Paths_pkgname feature documentation.

Specifying the compiler

If the compiler that Dyre should use is not available as ghc, set the HC environment variable when running the main program:

export HC=/opt/ghc/$GHC_VERSION/bin/ghc
dyreExample  # Dyre will use $HC for recompilation

Configuring Dyre

Program authors configure Dyre using the Params type. This type controls Dyre's behaviour, not the main program logic (the example uses the Config type for that).

Use newParams to construct a Params value. The three arguments are:

  • Application name (a String). This affects the names of files and directories that Dyre uses for config, cache and logging.
  • The real main function of the program, which has type (cfgType -> IO a). cfgType is the main program config type, and a is usually ().
  • The show error function, which has type (cfgType -> String -> cfgType). If compiling the custom program fails, Dyre uses this function to set the compiler output in the main program's configuration. The main program can then display the error string to the user, or handle it however the author sees fit.

The Params type has several other fields for modifying Dyre's behaviour. newParams uses reasonable defaults, but behaviours you can change include:

  • Where to look for custom configuration (configDir). By default Dyre will look for $XDG_CONFIG_HOME/<appName>/<appName>.hs,
  • Where to cache the custom executable and other files (cacheDir). By default Dyre will use $XDG_CACHE_HOME/<appName>/.
  • Extra options to pass to GHC when compiling the custom executable (ghcOpts). Default: none.

See Params for descriptions of all the fields.

Synopsis

Documentation

wrapMain :: Params cfgType a -> cfgType -> IO a Source #

wrapMain is how Dyre receives 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.

wrapMain returns whatever value is returned by the realMain function in the params (if it returns at all). In the common case this is () but you can use Dyre with any IO action.

data Params cfgType a 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 newParams, 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 a

    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.

  • includeDirs :: [FilePath]

    Optional extra include dirs to use during compilation. To support installation via cabal-install, include the path returned from Paths_<appName>.getLibDir.

  • 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.

  • rtsOptsHandling :: RTSOptionHandling

    Whether to append, or replace GHC runtime system options with others.

  • includeCurrentDirectory :: Bool

    Whether to add current directory to include list (set False to prevent name shadowing within project directory.) --

newParams Source #

Arguments

:: String

projectName

-> (cfg -> IO a)

realMain function

-> (cfg -> String -> cfg)

showError function

-> Params cfg a 

Construct a Params with the required values as given, and reasonable defaults for everything else.

defaultParams :: Params cfgType a Source #

Deprecated: Use newParams instead

A set of reasonable defaults for configuring Dyre. The fields that have to be filled are projectName, realMain, and showError (because their initial value is undefined).

Deprecated in favour of newParams which takes the required fields as arguments.