Portability | portable |
---|---|
Stability | experimental |
Maintainer | Joachim Breitner <mail@joachim-breitner.de> |
Language.Haskell.SealModule
Contents
Description
This provides a Template Haskell function to convert a set of function declarations which use global constants into function declarations that take these constants as parameters.
The goal is to make it more convenient to write pure, non-monadic code that deep in the call stack requires some configuration data without having to pass these paramters around explicitly.
- sealedParam :: a
- sealModule :: Q [Dec] -> Q [Dec]
Example
Consider the following minimal example:
{-# LANGUAGE TemplateHaskell #-}
module Example1 where import Language.Haskell.SealModule import Control.Monad sealModule [d| verbose :: Bool verbose = sealedParam worker :: Int -> IO Int worker n = do when verbose $ putStrLn $ "Got " ++ show n return $ Suc n |]
The function verbose
will be removed from the module, and the function
worker
will be equivalent to
worker :: Bool -> Int -> IO Int worker verbose n = do when verbose $ putStrLn $ "Got " ++ show n return $ Suc n
This also works if worker
had called foo
, foo
had called bar
and only
bar
would use the configuration parameter verbose
.
Record Wildcards
sealModule
supports more than one sealedParam
, they are added to the
paramter list in the order in which they appear in the declaration list. But if
you want to be able to conveniently add further parameters without changing the
functions' signature, you can use record wildcards:
{-# LANGUAGE TemplateHaskell, RecordWildCards #-}
module Example2 where import Language.Haskell.SealModule import Control.Monad data Config = Config { verbose :: Bool, increment :: Int } sealModule [d| config :: Config config = sealedParam Config{..} = config worker :: Int -> IO Int worker n = do when verbose $ putStrLn $ "Got " ++ show n return $ n + increment |]
This way, the fields of the Config
record appear as top-level declarations
inside the sealed module. Each function is exposed with one additional
parameter of type Config
. If you later need an additional configuration value
anywhere in the module, all you have to do is add it to the Config
record
data type. No function signatures change this way.
API
sealedParam :: aSource
sealedParam
turns a toplevel declaration into a sealed parameter. It
must only be used inside a call to sealModule
and there only in the form
of a top level declaration of the form
name = sealedParam
A type signature for name
may be given, and is a prerequisite for the
generated functions having type signatures.
sealModule :: Q [Dec] -> Q [Dec]Source
sealModule
modifies the passed top level declarations to have additional
parameters for each declaration bound to sealedParam
, in the order of
their appearance. The parameter declarations and their type signature, if
present, are removed from the list of declarations.
The generated functions will have a type signature if and only they have a type signature and all parameters have type signatures.
Problems
- The code passed to
sealModule
has to be indented. - Although the modified functions will apear in haddock documentation if they
and all parameters have type signatures, Haddock annotations inside
sealModule
are lost. A work around is the approach shown in the following listing. It is important that no type signature is given inside thesealModule
, otherwise the compiler will complain about duplicate type signatures, and that the signatures are given aftersealModule
.
{-# LANGUAGE TemplateHaskell #-}
module Example1 where import Language.Haskell.SealModule import Control.Monad sealModule [d| verbose :: Bool verbose = sealedParam worker n = do when verbose $ putStrLn $ "Got " ++ show n return $ Suc n |] -- | This is the documentation for 'worker'. worker :: Bool -> Int -> IO Int