Fixed the remaining missing functions to get the Schemes compiling

This commit is contained in:
Neil Brown 2008-12-02 13:13:54 +00:00
parent 77251b842c
commit 82cae7691a
2 changed files with 31 additions and 16 deletions

View File

@ -28,8 +28,8 @@ with this program. If not, see <http://www.gnu.org/licenses/>.
-- advised. Instead, you should use functions in the "GenPolyplate" module to automatically -- advised. Instead, you should use functions in the "GenPolyplate" module to automatically
-- generate source files with the appropriate instances. -- generate source files with the appropriate instances.
module Data.Generics.Polyplate (PolyplateM(..), Polyplate(..), module Data.Generics.Polyplate (PolyplateM(..), Polyplate(..),
makeRecurseM, RecurseM, makeRecurseM, RecurseM, makeRecurse, Recurse,
makeDescendM, DescendM, makeDescendM, DescendM, makeDescend, Descend,
BaseOp, baseOp, BaseOp, baseOp,
ExtOpM, extOpM, ExtOp, extOp, OneOpM, OneOp, TwoOpM, TwoOp) where ExtOpM, extOpM, ExtOp, extOp, OneOpM, OneOp, TwoOpM, TwoOp) where
@ -94,8 +94,8 @@ class Polyplate t o o' where
instance (PolyplateM t mo mo' Identity, ConvertOpsToIdentity o mo, ConvertOpsToIdentity o' mo') => Polyplate t o o' where instance (PolyplateM t mo mo' Identity, ConvertOpsToIdentity o mo, ConvertOpsToIdentity o' mo') => Polyplate t o o' where
transform o o' t = runIdentity (transformM (convertOpsToIdentity o) (convertOpsToIdentity o') t) transform o o' t = runIdentity (transformM (convertOpsToIdentity o) (convertOpsToIdentity o') t)
-- | A type representing a recursive monadic modifier function that applies the given ops -- | A type representing a monadic modifier function that applies the given ops
-- (in the given monad) directly to the given type. -- (opT) in the given monad (m) directly to the given type (t).
type RecurseM m opT = forall t. PolyplateM t opT () m => t -> m t type RecurseM m opT = forall t. PolyplateM t opT () m => t -> m t
-- | Given a set of operations (as described in the 'PolyplateM' type-class), -- | Given a set of operations (as described in the 'PolyplateM' type-class),
@ -103,11 +103,34 @@ type RecurseM m opT = forall t. PolyplateM t opT () m => t -> m t
makeRecurseM :: Monad m => opT -> RecurseM m opT makeRecurseM :: Monad m => opT -> RecurseM m opT
makeRecurseM ops = transformM ops () makeRecurseM ops = transformM ops ()
-- | A type representing a monadic modifier function that applies the given ops
-- (opT) in the given monad (m) to the children of the given type (t).
type DescendM m opT = forall t. PolyplateM t () opT m => t -> m t type DescendM m opT = forall t. PolyplateM t () opT m => t -> m t
-- | Given a set of operations (as described in the 'PolyplateM' type-class),
-- makes a descent modifier function that applies the operation to the type's children.
makeDescendM :: Monad m => opT -> DescendM m opT makeDescendM :: Monad m => opT -> DescendM m opT
makeDescendM ops = transformM () ops makeDescendM ops = transformM () ops
-- | A type representing a modifier function that applies the given ops
-- (opT) directly to the given type (t).
type Recurse opT = forall t. Polyplate t opT () => t -> t
-- | Given a set of operations (as described in the 'Polyplate' type-class),
-- makes a modifier function that applies the operations directly.
makeRecurse :: opT -> Recurse opT
makeRecurse ops = transform ops ()
-- | A type representing a modifier function that applies the given ops
-- (opT) to the children of the given type (t).
type Descend opT = forall t. Polyplate t () opT => t -> t
-- | Given a set of operations (as described in the 'PolyplateM' type-class),
-- makes a descent modifier function that applies the operation to the type's children.
makeDescend :: opT -> Descend opT
makeDescend ops = transform () ops
-- | The type of the empty set of operations -- | The type of the empty set of operations
type BaseOp = () type BaseOp = ()

View File

@ -26,36 +26,28 @@ import Data.Generics.Polyplate
-- This can be used to perform a bottom-up depth-first traversal of a structure -- This can be used to perform a bottom-up depth-first traversal of a structure
-- (see 'applyBottomUpM'). -- (see 'applyBottomUpM').
makeBottomUpM :: PolyplateM t () opT m => opT -> (t -> m t) -> t -> m t makeBottomUpM :: PolyplateM t () opT m => opT -> (t -> m t) -> t -> m t
makeBottomUpM ops f v = descend v >>= f makeBottomUpM ops f v = makeDescendM ops v >>= f
where
descend = makeDescendM ops
-- | Given a list of operations and a modifier function, augments that modifier -- | Given a list of operations and a modifier function, augments that modifier
-- function to first apply the modifier function before then descending into the value. -- function to first apply the modifier function before then descending into the value.
-- This can be used to perform a top-down depth-first traversal of a structure -- This can be used to perform a top-down depth-first traversal of a structure
-- (see 'applyTopDownM'). -- (see 'applyTopDownM').
makeTopDownM :: PolyplateM t () opT m => opT -> (t -> m t) -> t -> m t makeTopDownM :: PolyplateM t () opT m => opT -> (t -> m t) -> t -> m t
makeTopDownM ops f v = f v >>= descend makeTopDownM ops f v = f v >>= makeDescendM ops
where
descend = makeDescendM ops
-- | Given a list of operations and a modifier function, augments that modifier -- | Given a list of operations and a modifier function, augments that modifier
-- function to first descend into the value before then applying the modifier function. -- function to first descend into the value before then applying the modifier function.
-- This can be used to perform a bottom-up depth-first traversal of a structure -- This can be used to perform a bottom-up depth-first traversal of a structure
-- (see 'applyBottomUp'). -- (see 'applyBottomUp').
makeBottomUp :: Polyplate t () opT => opT -> (t -> t) -> t -> t makeBottomUp :: Polyplate t () opT => opT -> (t -> t) -> t -> t
makeBottomUp ops f v = f (descend v) makeBottomUp ops f v = f (makeDescend ops v)
where
descend = makeDescend ops
-- | Given a list of operations and a modifier function, augments that modifier -- | Given a list of operations and a modifier function, augments that modifier
-- function to first apply the modifier function before then descending into the value. -- function to first apply the modifier function before then descending into the value.
-- This can be used to perform a top-down depth-first traversal of a structure -- This can be used to perform a top-down depth-first traversal of a structure
-- (see 'applyTopDown'). -- (see 'applyTopDown').
makeTopDown :: Polyplate t () opT => opT -> (t -> t) -> t -> t makeTopDown :: Polyplate t () opT => opT -> (t -> t) -> t -> t
makeTopDown ops f v = descend (f v) makeTopDown ops f v = makeDescend ops (f v)
where
descend = makeDescend ops
{- TODO {- TODO