compdata-0.6.1.4: Compositional Data Types

Portabilitynon-portable (GHC Extensions)
Stabilityexperimental
MaintainerPatrick Bahr <paba@diku.dk>
Safe HaskellNone

Data.Comp.Param.Thunk

Description

This modules defines terms & contexts with thunks, with deferred monadic computations.

Synopsis

Documentation

type TermT m f = Term (Thunk m :+: f)Source

This type represents terms with thunks.

type TrmT m f a = Trm (Thunk m :+: f) aSource

This type represents terms with thunks.

type CxtT h m f a = Cxt h (Thunk m :+: f) aSource

This type represents contexts with thunks.

data Thunk m a b Source

thunk :: Thunk m :<: f => m (Cxt h f a b) -> Cxt h f a bSource

This function turns a monadic computation into a thunk.

whnf :: Monad m => TrmT m f a -> m (Either a (f a (TrmT m f a)))Source

This function evaluates all thunks until a non-thunk node is found.

whnf' :: Monad m => TrmT m f a -> m (TrmT m f a)Source

whnfPr :: (Monad m, g :<: f) => TrmT m f a -> m (g a (TrmT m f a))Source

This function first evaluates the argument term into whnf via whnf and then projects the top-level signature to the desired subsignature. Failure to do the projection is signalled as a failure in the monad.

nf :: (Monad m, Ditraversable f) => TrmT m f a -> m (Trm f a)Source

This function evaluates all thunks.

nfT :: (ParamFunctor m, Monad m, Ditraversable f) => TermT m f -> m (Term f)Source

This function evaluates all thunks.

nfPr :: (Monad m, Ditraversable g, g :<: f) => TrmT m f a -> m (Trm g a)Source

This function evaluates all thunks while simultaneously projecting the term to a smaller signature. Failure to do the projection is signalled as a failure in the monad as in whnfPr.

nfTPr :: (ParamFunctor m, Monad m, Ditraversable g, g :<: f) => TermT m f -> m (Term g)Source

This function evaluates all thunks while simultaneously projecting the term to a smaller signature. Failure to do the projection is signalled as a failure in the monad as in whnfPr.

evalStrict :: (Ditraversable g, Monad m, g :<: f) => (g (TrmT m f a) (f a (TrmT m f a)) -> TrmT m f a) -> g (TrmT m f a) (TrmT m f a) -> TrmT m f aSource

type AlgT m f g = Alg f (TermT m g)Source

This type represents algebras which have terms with thunks as carrier.

strict :: (f :<: g, Ditraversable f, Monad m) => f a (TrmT m g a) -> TrmT m g aSource

This combinator makes the evaluation of the given functor application strict by evaluating all thunks of immediate subterms.

strict' :: (f :<: g, Ditraversable f, Monad m) => f (TrmT m g a) (TrmT m g a) -> TrmT m g aSource

This combinator makes the evaluation of the given functor application strict by evaluating all thunks of immediate subterms.