alloy-1.2.2: Generic programming library

Safe HaskellSafe
LanguageHaskell98

Data.Generics.Alloy.Effect

Description

The module containing the AlloyA type-class for working with effectful functions (of the type a -> m a). This module is an analogue to Data.Generics.Alloy.Pure that supports functions that result in a monadic or applicative functor type.

All the functions in this module have versions for Applicative and for Monad. They have the same behaviour, and technically only the Applicative version is necessary, but since not all monads have Applicative instances, the Monad versions are provided for convenience.

Synopsis

Documentation

class AlloyA t o o' where Source

The Alloy type-class for effectful functions, to be used with sets of operations constructed from BaseOpA and :-*. You are unlikely to need to use transform directly; instead use 'makeRecurseA'\/'makeRecurseM' and 'makeDescendA'\/'makeDescendM'.

The first parameter to the type-class is the type currently being operated on, the second parameter is the set of operations to perform directly on the type, and the third parameter is the set of operations to perform on its children (if none of the second parameter operations can be applied).

Methods

transformM :: Monad m => o m -> o' m -> t -> m t Source

transformA :: Applicative f => o f -> o' f -> t -> f t Source

type RecurseA f opT = forall t. AlloyA t opT BaseOpA => t -> f t Source

A type representing a monadic/applicative functor modifier function that applies the given ops (opT) in the given monad/functor (f) directly to the given type (t).

makeRecurseA :: Applicative f => opT f -> RecurseA f opT Source

Given a set of operations (as described in the AlloyA type-class), makes a recursive modifier function that applies the operations directly to the given type, and then to its children, until it has been applied to all the largest instances of that type.

makeRecurseM :: Monad m => opT m -> RecurseA m opT Source

Useful equivalent of makeRecurseA.

type DescendA f opT = forall t. AlloyA t BaseOpA opT => t -> f t Source

A type representing a monadic/applicative functor modifier function that applies the given ops (opT) in the given monad/functor (f) to the children of the given type (t).

makeDescendA :: Applicative f => opT f -> DescendA f opT Source

Given a set of operations, makes a descent modifier function that applies the operation to the type's children, and further down, until it has been applied to all the largest instances of that type.

makeDescendM :: Monad m => opT m -> DescendA m opT Source

Useful equivalent of makeDescendA.

data BaseOpA m Source

The terminator for effectful opsets. Note that all effectful opsets are the same, and both can be used with the applicative functions or monad functions in this module. Whereas there is, for example, both makeRecurseA and makeRecurseM, there is only one terminator for the opsets, BaseOpA, which should be used regardless of whether you use makeRecurseA or makeRecurseM.

Constructors

BaseOpA 

baseOpA :: BaseOpA m Source

The function to give you an item of type BaseOpA.

data (t :-* opT) m infixr 7 Source

The type that extends an opset (opT) in the given monad/applicative-functor (m) to be applied to the given type (t). This is for use with the AlloyA class. A set of operations that operates on Foo, Bar and Baz in the IO monad can be constructed so:

ops :: (Foo :-* Bar :-* Baz :-* BaseOpA) IO
ops = doFoo :-* doBar :-* doBaz :-* baseOpA

doFoo :: Foo -> IO Foo
doBar :: Bar -> IO Bar
doBaz :: Baz -> IO Baz

The monad/functor parameter needs to be given when declaring an actual opset, but must be omitted when using the opset as part of a type-class constraint such as:

f :: AlloyA a (Foo :-* Bar :-* Baz :-* BaseOpA) BaseOpA => a -> IO a
f = makeRecurse ops

Constructors

(t -> m t) :-* (opT m) infixr 7 

type OneOpA t = t :-* BaseOpA Source

A handy synonym for a monadic/applicative opset with only one item, to use with AlloyA.

type TwoOpA s t = s :-* (t :-* BaseOpA) Source

A handy synonym for a monadic/applicative opset with only two items, to use with AlloyA.