provenience-0.1.1.0: Computations that automatically track data dependencies

Copyright(c) Olaf Klinke
LicenseGPL-3
Maintainerolaf.klinke@phymetric.de
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Control.Provenience

Contents

Description

The Provenience system lets you execute a function on particular input data while automatically recording the intermediate results together with a graph of the data flow. It is inspired by the Javelin software of the 80s which pre-dates Excel spreadsheets.

Intermediate results are stored in Variables, which decorate the data with a description. Instead of binding data to a Haskell identifier, you bind data to a Variable and provide a description of what the data is. Instead of applying a logical part to intermediate data, you apply the logical part to intermediate variables. So instead of writing code like

workflow x y z = let
    a = f x y
    b = g a z
    in h b

with Provenience you write

workflow x y z = do
    x' <- input x
    y' <- input y
    z' <- input z
    a <- var f <%> x' <%> y'
    b <- var g <%> a z'
    return (var h <%> b)

In addition to the above you should provide decoration for the variables which is used when rendering the data dependency graph. See <? and named. If and how the value of the variable is rendered is controlled with the render family functions and the DefaultRender class.

The ProvenienceT transformer has an additional type parameter for a machine-readable representation of a value. If you don't care about this, just use the unit type () here as in the Provenience type. Otherwise, all calls to render must be done on Variables of types which have a Representation in the chosen alternative type. After running the ProvenienceT computation you can extract the graph containing the alternative representations using graphAltReps. If the target representation is a spreadsheet, use renderSheet to obtain a spreadsheet where Variables are blocks of rows separated by blank rows.

Synopsis

Variables

data Variable a Source #

Every Variable has an identifier in the data flow graph.

Instances
Functor Variable Source # 
Instance details

Defined in Control.Provenience

Methods

fmap :: (a -> b) -> Variable a -> Variable b #

(<$) :: a -> Variable b -> Variable a #

Show a => Show (Variable a) Source # 
Instance details

Defined in Control.Provenience

Methods

showsPrec :: Int -> Variable a -> ShowS #

show :: Variable a -> String #

showList :: [Variable a] -> ShowS #

value :: Variable a -> a Source #

dereference

data VariableStore alt Source #

Variables are internally numbered by Node = Int and have an alternative value Representation alt. Further each variable has a Pandoc description (set by <?) and optionally a shortname set by named which is a String to be used in hyperlinks.

var :: Monad m => a -> ProvenienceT alt m a Source #

Register a new variable in the VariableStore. This variable has neither description, shortname nor valueRendering.

var = varM . pure 

varM :: Monad m => m a -> ProvenienceT alt m a Source #

Register a new variable with content from a monadic action in the VariableStore. This variable has neither description, shortname nor valueRendering.

input :: (Monad m, Representation a alt, DefaultRender a) => a -> ProvenienceT alt m a Source #

Register a static input variable which is immediately rendered.

inputM :: (Monad m, Representation a alt, DefaultRender a) => m a -> ProvenienceT alt m a Source #

Register a static input variable with content from a monad action which is immediately rendered.

func :: (Monad m, Default alt) => a -> Block -> ProvenienceT alt m a Source #

Combination of var and <? that can be used for immediate function application, e.g.

x  <- input 1
y  <- input 2
xy <- func (*) (renderDefault "*") <%> x <%> y

Modifiers

type StoreUpdate = forall m alt. Monad m => StateT (VariableStore alt) m () Source #

Action on the VariableStore

(<?) :: Variable a -> Block -> StoreUpdate infixl 3 Source #

The what is this?-operator. Changes the description of the computation's result.

>>> v <- var 99
>>> v <? renderDefault "bottles of beer on the wall"

named :: Variable a -> String -> StoreUpdate Source #

Provides a shortname symbol for the Variable, for use in hyperlinks and other references.

>>> v <- var 99
>>> v `named` "beer"

Rendering

linkto :: Monad m => Variable a -> StateT (VariableStore alt) m Inline Source #

Render a hyperlink to a Variable, to be used e.g. in descriptions of downstream variables. Make sure to provide a short name via named before calling linkto.

render :: (Representation a alt, Monad m, DefaultRender a) => Variable a -> StateT (VariableStore alt) m () Source #

render = renderWith renderDefault. You can use this function without providing a DefaultRender instance by using a conversion function to a type that is member of DefaultRender:

\f -> render . fmap f

renderWith :: (Representation a alt, Monad m) => (a -> Block) -> Variable a -> StateT (VariableStore alt) m () Source #

Supply the valueRendering and altRep for the variable.

renderShow :: Show a => a -> Block Source #

Use the show method to render a value as Plain text.

class DefaultRender a where Source #

Class of types with a default rendering method. For the basic types renderDefault equals renderShow.

Methods

renderDefault :: a -> Block Source #

Instances
DefaultRender Char Source # 
Instance details

Defined in Control.Provenience

DefaultRender Double Source # 
Instance details

Defined in Control.Provenience

DefaultRender Int Source # 
Instance details

Defined in Control.Provenience

DefaultRender Integer Source # 
Instance details

Defined in Control.Provenience

DefaultRender String Source #

render Strings as plain text.

Instance details

Defined in Control.Provenience

DefaultRender Text Source # 
Instance details

Defined in Control.Provenience

DefaultRender Block Source # 
Instance details

Defined in Control.Provenience

DefaultRender (Ratio Integer) Source # 
Instance details

Defined in Control.Provenience

data Proveniencei18n Source #

Internationalization of the keywords used in renderStore.

Constructors

Proveniencei18n 

Fields

renderStore :: Proveniencei18n -> VariableStore alt -> Block Source #

Render the store with Pandoc. For each Variable the following data is written:

  1. The variable name given with named,
  2. The variables linking to this one (if any),
  3. The edge labels linking to this variable,
  4. The variables depending on this one (if any),
  5. The description provided with <?,
  6. A rendering of the value as provided by one of the render family functions.

renderSheet :: forall row sheet. (ToSheet row sheet, ToRow StaticCellValue row) => Proveniencei18n -> VariableStore (Seq row) -> sheet Source #

When the alternative representation is in terms of spreadsheet rows, we can assemble the VariableStore into a spreadheet. This is analogous to renderStore but only places the data underneath the shortname, thus omitting any formatted descriptions.

graphAltReps :: VariableStore alt -> Gr alt Block Source #

Obtain a graph of all the Variables alternative representations

graphShortnames :: VariableStore alt -> Gr String Block Source #

Obtain a graph of all the Variables short names

The Provenience monad

type ProvenienceT alt m a = StateT (VariableStore alt) m (Variable a) Source #

A Monad transformer that keeps track of data dependencies

(<%>) :: Monad m => ProvenienceT alt m (a -> b) -> Variable a -> ProvenienceT alt m b infixl 4 Source #

Applicative-style application operator. Replaces the function Variable with its (partial) application and creates an edge from the argument to the result Variable that is labeled with the function description.

f <- func succ (renderDefault "successor")
x <- input (5 :: Int)
y <- pure f <%> x
x <? renderDefault "input data"
y <? renderDefault "The successor of 5"
render y

The above creates the following graph.

"input data"  "successor"  "The successor of 5"
     5        ----------->        6

If you want to re-use a function in several applications then bind f to the Provenience action rather the Variable like below.

let f = func succ (renderDefault "successor")
x <- input (5 :: Int)
y <- f <%> x
z <- f <%> y

(<%?>) :: Monad m => ProvenienceT alt m (a -> b) -> Either a (Variable a) -> ProvenienceT alt m b infixl 4 Source #

Conditional use of a Variable. The Left a could be a default parameter to the function which is not worth registering a Variable for.

(<%%>) :: Monad m => ProvenienceT alt m (a -> m b) -> Variable a -> ProvenienceT alt m b infixl 4 Source #

Like above but permit side-effects in the base monad.

runProvenienceT :: Monad m => ProvenienceT alt m a -> Node -> m ((a, VariableStore alt), Node) Source #

Run the Provenience monad and return the value of the result variable together with the VariableStore and its next unused Node. Initialize the VariableStore with an empty graph and start with the given Node identifier.

execProvenienceT :: Monad m => ProvenienceT alt m a -> Node -> m (VariableStore alt, Node) Source #

run the Provenience monad and return the data dependency graph

execProvenience :: Provenience a -> Node -> (VariableStore (), Node) Source #

run the Provenience monad and return the data dependency graph

evalProvenienceT :: Monad m => ProvenienceT alt m a -> m a Source #

run the Provenience monad and return the resulting value.

evalProvenience :: Provenience a -> a Source #

run the Provenience monad and return the resulting value.

sequenceProvenienceT :: (Traversable t, Monad m) => t (ProvenienceT alt m a) -> m (t (a, VariableStore alt)) Source #

Run multiple ProvenienceT actions using the same pool of Nodes but returning seperate VariableStores. This is useful when several data flow graphs get embedded into the same document, where hyperlink targets must be unique.