Copyright | (c) Sebastian Fischer 2006 Björn Peemöller 2011 |
---|---|
License | BSD-3-clause |
Maintainer | bjp@informatik.uni-kiel.de |
Stability | experimental |
Portability | portable |
Safe Haskell | Safe |
Language | Haskell2010 |
This library provides selector functions, test and update operations as well as some useful auxiliary functions for FlatCurry data terms. Most of the provided functions are based on general transformation functions that replace constructors with user-defined functions. For recursive datatypes the transformations are defined inductively over the term structure. This is quite usual for transformations on FlatCurry terms, so the provided functions can be used to implement specific transformations without having to explicitly state the recursion. Essentially, the tedious part of such transformations - descend in fairly complex term structures - is abstracted away, which hopefully makes the code more clear and brief.
Synopsis
- type Update a b = (b -> b) -> a -> a
- trProg :: (String -> [String] -> [TypeDecl] -> [FuncDecl] -> [OpDecl] -> a) -> Prog -> a
- progName :: Prog -> String
- progImports :: Prog -> [String]
- progTypes :: Prog -> [TypeDecl]
- progFuncs :: Prog -> [FuncDecl]
- progOps :: Prog -> [OpDecl]
- updProg :: (String -> String) -> ([String] -> [String]) -> ([TypeDecl] -> [TypeDecl]) -> ([FuncDecl] -> [FuncDecl]) -> ([OpDecl] -> [OpDecl]) -> Prog -> Prog
- updProgName :: Update Prog String
- updProgImports :: Update Prog [String]
- updProgTypes :: Update Prog [TypeDecl]
- updProgFuncs :: Update Prog [FuncDecl]
- updProgOps :: Update Prog [OpDecl]
- allVarsInProg :: Prog -> [VarIndex]
- updProgExps :: Update Prog Expr
- rnmAllVarsInProg :: Update Prog VarIndex
- updQNamesInProg :: Update Prog QName
- rnmProg :: String -> Prog -> Prog
- trType :: (QName -> Visibility -> [TVarIndex] -> [ConsDecl] -> a) -> (QName -> Visibility -> [TVarIndex] -> TypeExpr -> a) -> TypeDecl -> a
- typeName :: TypeDecl -> QName
- typeVisibility :: TypeDecl -> Visibility
- typeParams :: TypeDecl -> [TVarIndex]
- typeConsDecls :: TypeDecl -> [ConsDecl]
- typeSyn :: TypeDecl -> TypeExpr
- isTypeSyn :: TypeDecl -> Bool
- isDataTypeDecl :: TypeDecl -> Bool
- isExternalType :: TypeDecl -> Bool
- isPublicType :: TypeDecl -> Bool
- updType :: (QName -> QName) -> (Visibility -> Visibility) -> ([TVarIndex] -> [TVarIndex]) -> ([ConsDecl] -> [ConsDecl]) -> (TypeExpr -> TypeExpr) -> TypeDecl -> TypeDecl
- updTypeName :: Update TypeDecl QName
- updTypeVisibility :: Update TypeDecl Visibility
- updTypeParams :: Update TypeDecl [TVarIndex]
- updTypeConsDecls :: Update TypeDecl [ConsDecl]
- updTypeSynonym :: Update TypeDecl TypeExpr
- updQNamesInType :: Update TypeDecl QName
- trCons :: (QName -> Int -> Visibility -> [TypeExpr] -> a) -> ConsDecl -> a
- consName :: ConsDecl -> QName
- consArity :: ConsDecl -> Int
- consVisibility :: ConsDecl -> Visibility
- isPublicCons :: ConsDecl -> Bool
- consArgs :: ConsDecl -> [TypeExpr]
- updCons :: (QName -> QName) -> (Int -> Int) -> (Visibility -> Visibility) -> ([TypeExpr] -> [TypeExpr]) -> ConsDecl -> ConsDecl
- updConsName :: Update ConsDecl QName
- updConsArity :: Update ConsDecl Int
- updConsVisibility :: Update ConsDecl Visibility
- updConsArgs :: Update ConsDecl [TypeExpr]
- updQNamesInConsDecl :: Update ConsDecl QName
- tVarIndex :: TypeExpr -> TVarIndex
- domain :: TypeExpr -> TypeExpr
- range :: TypeExpr -> TypeExpr
- tConsName :: TypeExpr -> QName
- tConsArgs :: TypeExpr -> [TypeExpr]
- trTypeExpr :: (TVarIndex -> a) -> (QName -> [a] -> a) -> (a -> a -> a) -> ([TVarIndex] -> a -> a) -> TypeExpr -> a
- isTVar :: TypeExpr -> Bool
- isTCons :: TypeExpr -> Bool
- isFuncType :: TypeExpr -> Bool
- isForallType :: TypeExpr -> Bool
- updTVars :: (TVarIndex -> TypeExpr) -> TypeExpr -> TypeExpr
- updTCons :: (QName -> [TypeExpr] -> TypeExpr) -> TypeExpr -> TypeExpr
- updFuncTypes :: (TypeExpr -> TypeExpr -> TypeExpr) -> TypeExpr -> TypeExpr
- updForallTypes :: ([TVarIndex] -> TypeExpr -> TypeExpr) -> TypeExpr -> TypeExpr
- argTypes :: TypeExpr -> [TypeExpr]
- typeArity :: TypeExpr -> Int
- resultType :: TypeExpr -> TypeExpr
- allVarsInTypeExpr :: TypeExpr -> [TVarIndex]
- allTypeCons :: TypeExpr -> [QName]
- rnmAllVarsInTypeExpr :: (TVarIndex -> TVarIndex) -> TypeExpr -> TypeExpr
- updQNamesInTypeExpr :: (QName -> QName) -> TypeExpr -> TypeExpr
- trOp :: (QName -> Fixity -> Integer -> a) -> OpDecl -> a
- opName :: OpDecl -> QName
- opFixity :: OpDecl -> Fixity
- opPrecedence :: OpDecl -> Integer
- updOp :: (QName -> QName) -> (Fixity -> Fixity) -> (Integer -> Integer) -> OpDecl -> OpDecl
- updOpName :: Update OpDecl QName
- updOpFixity :: Update OpDecl Fixity
- updOpPrecedence :: Update OpDecl Integer
- trFunc :: (QName -> Int -> Visibility -> TypeExpr -> Rule -> a) -> FuncDecl -> a
- funcName :: FuncDecl -> QName
- funcArity :: FuncDecl -> Int
- funcVisibility :: FuncDecl -> Visibility
- funcType :: FuncDecl -> TypeExpr
- funcRule :: FuncDecl -> Rule
- updFunc :: (QName -> QName) -> (Int -> Int) -> (Visibility -> Visibility) -> (TypeExpr -> TypeExpr) -> (Rule -> Rule) -> FuncDecl -> FuncDecl
- updFuncName :: Update FuncDecl QName
- updFuncArity :: Update FuncDecl Int
- updFuncVisibility :: Update FuncDecl Visibility
- updFuncType :: Update FuncDecl TypeExpr
- updFuncRule :: Update FuncDecl Rule
- isPublicFunc :: FuncDecl -> Bool
- isExternal :: FuncDecl -> Bool
- allVarsInFunc :: FuncDecl -> [VarIndex]
- funcArgs :: FuncDecl -> [VarIndex]
- funcBody :: FuncDecl -> Expr
- funcRHS :: FuncDecl -> [Expr]
- rnmAllVarsInFunc :: Update FuncDecl VarIndex
- updQNamesInFunc :: Update FuncDecl QName
- updFuncArgs :: Update FuncDecl [VarIndex]
- updFuncBody :: Update FuncDecl Expr
- trRule :: ([VarIndex] -> Expr -> a) -> (String -> a) -> Rule -> a
- ruleArgs :: Rule -> [VarIndex]
- ruleBody :: Rule -> Expr
- ruleExtDecl :: Rule -> String
- isRuleExternal :: Rule -> Bool
- updRule :: ([VarIndex] -> [VarIndex]) -> (Expr -> Expr) -> (String -> String) -> Rule -> Rule
- updRuleArgs :: Update Rule [VarIndex]
- updRuleBody :: Update Rule Expr
- updRuleExtDecl :: Update Rule String
- allVarsInRule :: Rule -> [VarIndex]
- rnmAllVarsInRule :: Update Rule VarIndex
- updQNamesInRule :: Update Rule QName
- trCombType :: a -> (Int -> a) -> a -> (Int -> a) -> CombType -> a
- isCombTypeFuncCall :: CombType -> Bool
- isCombTypeFuncPartCall :: CombType -> Bool
- isCombTypeConsCall :: CombType -> Bool
- isCombTypeConsPartCall :: CombType -> Bool
- varNr :: Expr -> VarIndex
- literal :: Expr -> Literal
- combType :: Expr -> CombType
- combName :: Expr -> QName
- combArgs :: Expr -> [Expr]
- missingCombArgs :: Expr -> Int
- letBinds :: Expr -> [(VarIndex, Expr)]
- letBody :: Expr -> Expr
- freeVars :: Expr -> [VarIndex]
- freeExpr :: Expr -> Expr
- orExps :: Expr -> [Expr]
- caseType :: Expr -> CaseType
- caseExpr :: Expr -> Expr
- caseBranches :: Expr -> [BranchExpr]
- isVar :: Expr -> Bool
- isLit :: Expr -> Bool
- isComb :: Expr -> Bool
- isLet :: Expr -> Bool
- isFree :: Expr -> Bool
- isOr :: Expr -> Bool
- isCase :: Expr -> Bool
- trExpr :: (VarIndex -> a) -> (Literal -> a) -> (CombType -> QName -> [a] -> a) -> ([(VarIndex, a)] -> a -> a) -> ([VarIndex] -> a -> a) -> (a -> a -> a) -> (CaseType -> a -> [b] -> a) -> (Pattern -> a -> b) -> (a -> TypeExpr -> a) -> Expr -> a
- updVars :: (VarIndex -> Expr) -> Expr -> Expr
- updLiterals :: (Literal -> Expr) -> Expr -> Expr
- updCombs :: (CombType -> QName -> [Expr] -> Expr) -> Expr -> Expr
- updLets :: ([(VarIndex, Expr)] -> Expr -> Expr) -> Expr -> Expr
- updFrees :: ([VarIndex] -> Expr -> Expr) -> Expr -> Expr
- updOrs :: (Expr -> Expr -> Expr) -> Expr -> Expr
- updCases :: (CaseType -> Expr -> [BranchExpr] -> Expr) -> Expr -> Expr
- updBranches :: (Pattern -> Expr -> BranchExpr) -> Expr -> Expr
- updTypeds :: (Expr -> TypeExpr -> Expr) -> Expr -> Expr
- isFuncCall :: Expr -> Bool
- isFuncPartCall :: Expr -> Bool
- isConsCall :: Expr -> Bool
- isConsPartCall :: Expr -> Bool
- isGround :: Expr -> Bool
- allVars :: Expr -> [VarIndex]
- rnmAllVars :: Update Expr VarIndex
- updQNames :: Update Expr QName
- trBranch :: (Pattern -> Expr -> a) -> BranchExpr -> a
- branchPattern :: BranchExpr -> Pattern
- branchExpr :: BranchExpr -> Expr
- updBranch :: (Pattern -> Pattern) -> (Expr -> Expr) -> BranchExpr -> BranchExpr
- updBranchPattern :: Update BranchExpr Pattern
- updBranchExpr :: Update BranchExpr Expr
- trPattern :: (QName -> [VarIndex] -> a) -> (Literal -> a) -> Pattern -> a
- patCons :: Pattern -> QName
- patArgs :: Pattern -> [VarIndex]
- patLiteral :: Pattern -> Literal
- isConsPattern :: Pattern -> Bool
- updPattern :: (QName -> QName) -> ([VarIndex] -> [VarIndex]) -> (Literal -> Literal) -> Pattern -> Pattern
- updPatCons :: (QName -> QName) -> Pattern -> Pattern
- updPatArgs :: ([VarIndex] -> [VarIndex]) -> Pattern -> Pattern
- updPatLiteral :: (Literal -> Literal) -> Pattern -> Pattern
- patExpr :: Pattern -> Expr
- isPublic :: Visibility -> Bool
Documentation
trProg :: (String -> [String] -> [TypeDecl] -> [FuncDecl] -> [OpDecl] -> a) -> Prog -> a Source #
transform program
progImports :: Prog -> [String] Source #
get imports from program
updProg :: (String -> String) -> ([String] -> [String]) -> ([TypeDecl] -> [TypeDecl]) -> ([FuncDecl] -> [FuncDecl]) -> ([OpDecl] -> [OpDecl]) -> Prog -> Prog Source #
update program
allVarsInProg :: Prog -> [VarIndex] Source #
get all program variables (also from patterns)
rnmProg :: String -> Prog -> Prog Source #
rename program (update name of and all qualified names in program)
trType :: (QName -> Visibility -> [TVarIndex] -> [ConsDecl] -> a) -> (QName -> Visibility -> [TVarIndex] -> TypeExpr -> a) -> TypeDecl -> a Source #
transform type declaration
typeVisibility :: TypeDecl -> Visibility Source #
get visibility of type declaration
typeParams :: TypeDecl -> [TVarIndex] Source #
get type parameters of type declaration
typeConsDecls :: TypeDecl -> [ConsDecl] Source #
get constructor declarations from type declaration
isDataTypeDecl :: TypeDecl -> Bool Source #
is type declaration declaring a regular type?
isExternalType :: TypeDecl -> Bool Source #
is type declaration declaring an external type?
updType :: (QName -> QName) -> (Visibility -> Visibility) -> ([TVarIndex] -> [TVarIndex]) -> ([ConsDecl] -> [ConsDecl]) -> (TypeExpr -> TypeExpr) -> TypeDecl -> TypeDecl Source #
update type declaration
updTypeVisibility :: Update TypeDecl Visibility Source #
update visibility of type declaration
updTypeConsDecls :: Update TypeDecl [ConsDecl] Source #
update constructor declarations of type declaration
trCons :: (QName -> Int -> Visibility -> [TypeExpr] -> a) -> ConsDecl -> a Source #
transform constructor declaration
consVisibility :: ConsDecl -> Visibility Source #
get visibility of constructor declaration
isPublicCons :: ConsDecl -> Bool Source #
Is the constructor declaration public?
updCons :: (QName -> QName) -> (Int -> Int) -> (Visibility -> Visibility) -> ([TypeExpr] -> [TypeExpr]) -> ConsDecl -> ConsDecl Source #
update constructor declaration
updConsVisibility :: Update ConsDecl Visibility Source #
update visibility of constructor declaration
updQNamesInConsDecl :: Update ConsDecl QName Source #
update all qualified names in constructor declaration
trTypeExpr :: (TVarIndex -> a) -> (QName -> [a] -> a) -> (a -> a -> a) -> ([TVarIndex] -> a -> a) -> TypeExpr -> a Source #
transform type expression
isFuncType :: TypeExpr -> Bool Source #
is type declaration a functional type?
isForallType :: TypeExpr -> Bool Source #
is type declaration a forall type?
updTCons :: (QName -> [TypeExpr] -> TypeExpr) -> TypeExpr -> TypeExpr Source #
update all type constructors
updFuncTypes :: (TypeExpr -> TypeExpr -> TypeExpr) -> TypeExpr -> TypeExpr Source #
update all functional types
updForallTypes :: ([TVarIndex] -> TypeExpr -> TypeExpr) -> TypeExpr -> TypeExpr Source #
update all forall types
resultType :: TypeExpr -> TypeExpr Source #
get result type from (nested) functional type
allVarsInTypeExpr :: TypeExpr -> [TVarIndex] Source #
get indexes of all type variables
allTypeCons :: TypeExpr -> [QName] Source #
yield the list of all contained type constructors
rnmAllVarsInTypeExpr :: (TVarIndex -> TVarIndex) -> TypeExpr -> TypeExpr Source #
rename variables in type expression
updQNamesInTypeExpr :: (QName -> QName) -> TypeExpr -> TypeExpr Source #
update all qualified names in type expression
opPrecedence :: OpDecl -> Integer Source #
get precedence of operator declaration
updOp :: (QName -> QName) -> (Fixity -> Fixity) -> (Integer -> Integer) -> OpDecl -> OpDecl Source #
update operator declaration
trFunc :: (QName -> Int -> Visibility -> TypeExpr -> Rule -> a) -> FuncDecl -> a Source #
transform function
funcVisibility :: FuncDecl -> Visibility Source #
get visibility of function
updFunc :: (QName -> QName) -> (Int -> Int) -> (Visibility -> Visibility) -> (TypeExpr -> TypeExpr) -> (Rule -> Rule) -> FuncDecl -> FuncDecl Source #
update function
updFuncVisibility :: Update FuncDecl Visibility Source #
update visibility of function
isPublicFunc :: FuncDecl -> Bool Source #
is function public?
isExternal :: FuncDecl -> Bool Source #
is function externally defined?
allVarsInFunc :: FuncDecl -> [VarIndex] Source #
get variable names in a function declaration
updFuncArgs :: Update FuncDecl [VarIndex] Source #
update arguments of function, if not externally defined
ruleExtDecl :: Rule -> String Source #
get rules external declaration
isRuleExternal :: Rule -> Bool Source #
is rule external?
updRule :: ([VarIndex] -> [VarIndex]) -> (Expr -> Expr) -> (String -> String) -> Rule -> Rule Source #
update rule
allVarsInRule :: Rule -> [VarIndex] Source #
get variable names in a functions rule
trCombType :: a -> (Int -> a) -> a -> (Int -> a) -> CombType -> a Source #
transform combination type
isCombTypeFuncCall :: CombType -> Bool Source #
is type of combination FuncCall?
isCombTypeFuncPartCall :: CombType -> Bool Source #
is type of combination FuncPartCall?
isCombTypeConsCall :: CombType -> Bool Source #
is type of combination ConsCall?
isCombTypeConsPartCall :: CombType -> Bool Source #
is type of combination ConsPartCall?
missingCombArgs :: Expr -> Int Source #
get number of missing arguments if expression is combined
caseBranches :: Expr -> [BranchExpr] Source #
get branch expressions from case expression
trExpr :: (VarIndex -> a) -> (Literal -> a) -> (CombType -> QName -> [a] -> a) -> ([(VarIndex, a)] -> a -> a) -> ([VarIndex] -> a -> a) -> (a -> a -> a) -> (CaseType -> a -> [b] -> a) -> (Pattern -> a -> b) -> (a -> TypeExpr -> a) -> Expr -> a Source #
transform expression
updCombs :: (CombType -> QName -> [Expr] -> Expr) -> Expr -> Expr Source #
update all combined expressions in given expression
updLets :: ([(VarIndex, Expr)] -> Expr -> Expr) -> Expr -> Expr Source #
update all let expressions in given expression
updFrees :: ([VarIndex] -> Expr -> Expr) -> Expr -> Expr Source #
update all free declarations in given expression
updOrs :: (Expr -> Expr -> Expr) -> Expr -> Expr Source #
update all or expressions in given expression
updCases :: (CaseType -> Expr -> [BranchExpr] -> Expr) -> Expr -> Expr Source #
update all case expressions in given expression
updBranches :: (Pattern -> Expr -> BranchExpr) -> Expr -> Expr Source #
update all case branches in given expression
updTypeds :: (Expr -> TypeExpr -> Expr) -> Expr -> Expr Source #
update all typed expressions in given expression
isFuncCall :: Expr -> Bool Source #
is expression a call of a function where all arguments are provided?
isFuncPartCall :: Expr -> Bool Source #
is expression a partial function call?
isConsCall :: Expr -> Bool Source #
is expression a call of a constructor?
isConsPartCall :: Expr -> Bool Source #
is expression a partial constructor call?
branchPattern :: BranchExpr -> Pattern Source #
get pattern from branch expression
branchExpr :: BranchExpr -> Expr Source #
get expression from branch expression
updBranch :: (Pattern -> Pattern) -> (Expr -> Expr) -> BranchExpr -> BranchExpr Source #
update branch expression
updBranchPattern :: Update BranchExpr Pattern Source #
update pattern of branch expression
updBranchExpr :: Update BranchExpr Expr Source #
update expression of branch expression
patLiteral :: Pattern -> Literal Source #
get literal from literal pattern
isConsPattern :: Pattern -> Bool Source #
is pattern a constructor pattern?
updPattern :: (QName -> QName) -> ([VarIndex] -> [VarIndex]) -> (Literal -> Literal) -> Pattern -> Pattern Source #
update pattern
updPatArgs :: ([VarIndex] -> [VarIndex]) -> Pattern -> Pattern Source #
update arguments of constructor pattern
isPublic :: Visibility -> Bool Source #
Is this a public Visibility
?