GTALib-0.0.6: A library for GTA programming

Safe HaskellNone

GTA.Util.GenericSemiringStructureTemplate

Description

This module provides a mechanism for automatic generation of data-structure-dependent definitions necessary for the GTA framework (namely, an instance of GenericSemiringStructure as well as definitions of algebras and structures for map functions).

Synopsis

Documentation

genAlgebraDecl :: Name -> Q [Dec]Source

This function generates a definition of the algebra of a given data structure. For example, given a data structure defined below,

 data BinTree n l = BinNode n (BinTree n l) (BinTree n l)
                  | BinLeaf l

the following definition of the algebra is generated by genAlgebraDecl ''BinTree.

 data BinTreeAlgebra n l a = BinTreeAlgebra {
       binNode :: n -> a -> a -> a,
       binLeaf :: l -> a
     }

genMapFunctionsDecl :: Name -> Q [Dec]Source

This function generates a definition of a record holding functions to be mapped to values in a given data structure. For example, given a data structure defined below,

 data BinTree n l = BinNode n (BinTree n l) (BinTree n l)
                  | BinLeaf l

the following record is generated by genMapFunctionsDecl ''BinTree.

 data BinTreeMapFs n l b' = BinTreeMapFs {
       binNodeF :: n -> b',
       binLeafF :: l -> b'
     }

genInstanceDecl :: Name -> Q [Dec]Source

This function generates an instance of GenericSemiringStructure for a given data structure. For example, given a data structure defined below,

 data BinTree n l = BinNode n (BinTree n l) (BinTree n l)
                  | BinLeaf l

the following record is generated by genInstanceDecl''BinTree.

 instance GenericSemiringStructure (BinTreeAlgebra n l) (BinTree n l) (BinTreeMapFs n l) where
   freeAlgebra = BinTreeAlgebra {..} where
       binNode = BinNode
       binLeaf = BinLeaf
   pairAlgebra lvta1 lvta2 = BinTreeAlgebra {..} where
       binNode a (l1, l2) (r1, r2) = (binNode1 a l1 r1, binNode2 a l2 r2)
       binLeaf a                   = (binLeaf1 a, binLeaf2 a)
       (binNode1, binLeaf1) = let BinTreeAlgebra {..} = lvta1 in (binNode, binLeaf)
       (binNode2, binLeaf2) = let BinTreeAlgebra {..} = lvta2 in (binNode, binLeaf)
   makeAlgebra (CommutativeMonoid {..}) lvta frec fsingle = BinTreeAlgebra {..} where  
       binNode a l r = foldr oplus identity [fsingle (binNode' a l' r') | l' <- frec l, r' <- frec r]
       binLeaf a     = fsingle (binLeaf' a)
       (binNode', binLeaf') = let BinTreeAlgebra {..} = lvta in (binNode, binLeaf)
   foldingAlgebra op iop (BinTreeMapFs {..}) = BinTreeAlgebra {..} where
       binNode a l r = binNodeF a `op` l `op` r
       binLeaf a     = binLeafF a
   hom (BinTreeAlgebra {..}) = h where
       h (BinNode a l r) = binNode a (h l) (h r)
       h (BinLeaf a)     = binLeaf a
 

genAllDecl :: Name -> Q [Dec]Source

Given a data structure, this function generates a definition of its algebra (by genAlgebraDecl), a record of map functions (by genMapFunctionsDecl), and an instance of GenericSemiringStructure (by genInstanceDecl). Usage: genAllDecl ''BinTree.