comptrans-0.1.0.6: Automatically converting ASTs into compositional data types
Copyright(c) 2013 James Koppel
LicenseBSD3
Safe HaskellNone
LanguageHaskell2010

Data.Comp.Trans

Description

Template Haskell to convert an ordinary mutually-recursive algebraic datatypes into a set of independent, unfixed, sorted signatures suitable for use with the compdata or cubix-compdata packages.

This package implements the algorithm described in Appendix A of "One Tool, Many Languages: Incremental Parametric Syntax for Multi-Language Transformation", OOPSLA 2018

GHC has a phase restriction which prevents code generated by Template Haskell being referred to by Template Haskell in the same file. Thus, when using this library, you will need to spread invocations out over several files.

We will refer to the following example in the documentation:

module Foo where
data Arith = Add Atom Atom
data Atom = Var String | Const Lit
data Lit = Lit Int
Synopsis

Run compdata, with potential configuration

data CompTrans a Source #

The central monad of comptrans, defined as the Q monad with additional configuration parameters

Instances

Instances details
Monad CompTrans Source # 
Instance details

Defined in Data.Comp.Trans.Util

Methods

(>>=) :: CompTrans a -> (a -> CompTrans b) -> CompTrans b #

(>>) :: CompTrans a -> CompTrans b -> CompTrans b #

return :: a -> CompTrans a #

Functor CompTrans Source # 
Instance details

Defined in Data.Comp.Trans.Util

Methods

fmap :: (a -> b) -> CompTrans a -> CompTrans b #

(<$) :: a -> CompTrans b -> CompTrans a #

MonadFail CompTrans Source # 
Instance details

Defined in Data.Comp.Trans.Util

Methods

fail :: String -> CompTrans a #

Applicative CompTrans Source # 
Instance details

Defined in Data.Comp.Trans.Util

Methods

pure :: a -> CompTrans a #

(<*>) :: CompTrans (a -> b) -> CompTrans a -> CompTrans b #

liftA2 :: (a -> b -> c) -> CompTrans a -> CompTrans b -> CompTrans c #

(*>) :: CompTrans a -> CompTrans b -> CompTrans b #

(<*) :: CompTrans a -> CompTrans b -> CompTrans a #

MonadIO CompTrans Source # 
Instance details

Defined in Data.Comp.Trans.Util

Methods

liftIO :: IO a -> CompTrans a #

runCompTrans :: CompTrans a -> Q a Source #

Runs a comptrans computation, resulting in a Template Haskell command which creates some number of declarations.

CompTrans values are created by deriveMulti, deriveTrans, and deriveUntrans, and may be configured using functions such as withSubstitutions

Substitutions

withSubstitutions :: Map Name Type -> CompTrans a -> CompTrans a Source #

Runs a comptrans declaration with a given set of type variable substitutions

getTypeParamVars :: [Name] -> CompTrans [Name] Source #

Retrieves the names of type parameters attached to a list of type declarations, referenced by name

Excluded types

withExcludedNames :: Set Name -> CompTrans a -> CompTrans a Source #

Runs a comptrans declaration with a given set of excluded namess

standardExcludedNames :: Set Name Source #

Names that should be excluded from an AST hierarchy. Includes base types, basic containers (Maybe, Either), and Text/ByteString.

Annotation propagation

withAnnotationProp Source #

Arguments

:: Type

annTyp, the annotation type being propagated

-> (Type -> Bool)

A test for whether a type is an annotation to propagate. Usually (== annType).

-> ([(Exp, Type)] -> Exp)

Annotation propogater. Usually constructed with defaultPropAnn. See AnnotationPropInfo.

-> (Exp -> Int -> [Exp])

Annotation unpropater. Usuallyl defaultUnpropAnn. See AnnotationPropInfo

-> CompTrans a

code generating comptrans declarations

-> CompTrans a 

defaultPropAnn Source #

Arguments

:: Exp

default annotation, to be used on terms that do not have an annotation

-> [(Exp, Type)] 
-> Exp 

A default annotation propagator: Assumes 0 or 1 annotations per constructor Returns the default annotation or copies the given annotation as appropriate.

defaultUnpropAnn :: Exp -> Int -> [Exp] Source #

A default annotation unpropagator: Assumes 0 or 1 annotations per constructor. If 1 annotation given, copies it.

Derive multi-sorted compositional data types

deriveMultiComp :: Name -> CompTrans [Dec] Source #

Declares a multi-sorted compositional datatype isomorphic to the given ADT.

e.g.

import qualified Foo as F
runCompTrans $ deriveMultiComp ''F.Arith

will create

data ArithL
data AtomL
data LitL

data Arith e l where
  Add :: e AtomL -> e AtomL -> Arith e ArithL

data Atom e l where
  Var :: String -> Atom e AtomL
  Const :: e LitL -> Atom e AtomL

data Lit (e :: * -> *) l where
  Lit :: Int -> Lit e LitL

generateNameLists :: Name -> CompTrans [Dec] Source #

e.g.

runCompTrans $ generateNameLists ''Arith

will create

origASTTypes = [mkName Foo.Arith, mkName Foo.Atom, mkName Foo.Lit]
newASTTypes  = [mkName Arith, mkName Atom, mkName Lit]
newASTLabels = map ConT [mkName ArithL, mkName "AtomL', mkName LitL]

makeSumType :: String -> [Name] -> CompTrans [Dec] Source #

Creates a type-level list from a list of TH names.

Example:

-- In Names.hs
import qualified Foo as F
runCompTrans $ generateNameLists ''F.Arith -- Defines newASTTypes

-- In Types.hs
import qualified Foo as F
import Names
runCompTrans $ deriveMult ''F.arith
runCompTrans $ makeSumType "ArithSig" newASTTypes

will create

type ArithSig = '[Arith, Atom, Lit]

Derive translation functions

deriveTrans :: [Name] -> Type -> CompTrans [Dec] Source #

Creates a functions translating from an ADT to its isomorphic multi-sorted compositional data type

import qualified Foo as F
...
type ArithTerm = Term Arith
runCompTrans $ deriveTrans [''Arith, ''Atom, ''Lit] (TH.ConT ''ArithTerm)

will create,

class Trans a l where
  trans :: a -> ArithTerm l

instance Trans F.Arith ArithL where
  trans (F.Add x y) = iAdd (trans x) (trans y)

instance Trans F.Atom AtomL where
  trans (F.Var s)   = iVar s
  trans (F.Const x) = iConst (trans x)

instance Trans F.Lit LitL where
  trans (F.Lit n) = iLit n

With annotation propagation on, it will instead produce, e.g.: `trans :: F.Arith Ann -> Term (Arith :&: Ann) ArithL`

deriveUntrans :: [Name] -> Type -> CompTrans [Dec] Source #

Creates an untranslate function inverting the translate function created by deriveTrans.

import qualified Foo as F
type ArithTerm = Term (Sum '[Arith, Atom, Lit])
deriveUntrans [''F.Arith, ''F.Atom, ''F.Lit] (TH.ConT ''ArithTerm)

will create

type family Targ l
newtype T l = T {t :: Targ l}

class Untrans f where
  untrans :: Alg f t

untranslate :: ArithTerm l -> Targ l
untranslate = t . cata untrans

type instance Targ ArithL = F.Arith
instance Untrans Arith where
  untrans (Add x y) = T $ F.Add (t x) (t y)

type instance Targ AtomL = F.Atom
instance Untrans Atom where
  untrans (Var s)   = T $ F.Var s
  untrans (Const x) = T $ F.Const (t x)

type instance Targ LitL = F.Lit
instance Untrans Lit where
  untrans (Lit n) = T $ F.Lit n

With annotation propagations on, it will instead produce untranslate :: Term (Arith :&: Ann) l -> Targ l Ann

where Ann is the provided annotation type.

Note that you will need to manually provide an instance (All Untrans fs) => Untrans (Sum fs) due to phase issues. (Or (All Untrans (DistAnn fs a)) => Untrans (Sum fs :&: a), if you are propagating annotations.)

Uncategorized