rec-def-0.1: Recusively defined values
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Recursive.R.Internal

Description

This module provides the R data type, which wraps an imperative propagator (e.g. Data.Recursive.Propagator.Naive) in a pure and (if done right) safe data structure.

The result of getR is always a solution of the given equations, but for it to be deterministic (and hence for this API to be safe), the following should hold:

  • The a in R a should be partially orderd (POrder)
  • That partial order must respect equality on a
  • It must have a bottom element bottom (Bottom).
  • The function passed to defR1, defR2 etc. must be a monotonic function between these partial orders.

If this does not hold, then the result of getR may not be deterministic.

Termination depends on whether a soluiton can be found iteratively. This is guaranteed if all partial orders involved satisfy the Ascending Chain Condition.

Synopsis

Documentation

data R a Source #

A value of type R a is a a, but defined using only specific operations (which you will find in the corresponding module, e.g. Data.Recursive.Bool), which allow recursive definitions.

You can use getR to extract the value.

Do not use the extracted value in the definition of that value, this will loop just like a recursive definition with plain values would.

getR :: HasPropagator a => R a -> a Source #

Extract the value from a R a. This must not be used when _defining_ that value.

getRDual :: HasPropagator (Dual a) => R (Dual a) -> a Source #

Convenience variant of getR to also remove the Dual newtype wrapper, mostly for use with Data.Recursive.DualBool.

mkR :: HasPropagator a => a -> R a Source #

Any value of type a is also a value of type r a.

defR1 :: (HasPropagator a, HasPropagator b) => (Prop a -> Prop b -> IO ()) -> R a -> R b Source #

Defines a value of type R b to be a function of the values of R a.

The action passed it should declare that relation to the underlying propagator.

The Prop a propagator must only be used for reading values _from_.

defR2 :: (HasPropagator a, HasPropagator b, HasPropagator c) => (Prop a -> Prop b -> Prop c -> IO ()) -> R a -> R b -> R c Source #

Defines a value of type R c to be a function of the values of R a and R b.

The action passed it should declare that relation to the underlying propagator.

The Prop a and Prop b propagators must only be used for reading values _from_.

defRList :: (HasPropagator a, HasPropagator b) => ([Prop a] -> Prop b -> IO ()) -> [R a] -> R b Source #

Defines a value of type R b to be a function of the values of a list of R a values.

The action passed it should declare that relation to the underlying propagator.

The Prop a propagators must only be used for reading values _from_.