Module FlatCurry.Goodies

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.

Author: Sebastian Fischer

Version: November 2020

Summary of exported operations:

trProg :: (String -> [String] -> [TypeDecl] -> [FuncDecl] -> [OpDecl] -> a) -> Prog -> a  Deterministic 
transform program
progName :: Prog -> String  Deterministic 
get name from program
progImports :: Prog -> [String]  Deterministic 
get imports from program
progTypes :: Prog -> [TypeDecl]  Deterministic 
get type declarations from program
progFuncs :: Prog -> [FuncDecl]  Deterministic 
get functions from program
progOps :: Prog -> [OpDecl]  Deterministic 
get infix operators from program
updProg :: (String -> String) -> ([String] -> [String]) -> ([TypeDecl] -> [TypeDecl]) -> ([FuncDecl] -> [FuncDecl]) -> ([OpDecl] -> [OpDecl]) -> Prog -> Prog  Deterministic 
update program
updProgName :: (String -> String) -> Prog -> Prog  Deterministic 
update name of program
updProgImports :: ([String] -> [String]) -> Prog -> Prog  Deterministic 
update imports of program
updProgTypes :: ([TypeDecl] -> [TypeDecl]) -> Prog -> Prog  Deterministic 
update type declarations of program
updProgFuncs :: ([FuncDecl] -> [FuncDecl]) -> Prog -> Prog  Deterministic 
update functions of program
updProgOps :: ([OpDecl] -> [OpDecl]) -> Prog -> Prog  Deterministic 
update infix operators of program
allVarsInProg :: Prog -> [Int]  Deterministic 
get all program variables (also from patterns)
updProgExps :: (Expr -> Expr) -> Prog -> Prog  Deterministic 
lift transformation on expressions to program
rnmAllVarsInProg :: (Int -> Int) -> Prog -> Prog  Deterministic 
rename programs variables
updQNamesInProg :: ((String,String) -> (String,String)) -> Prog -> Prog  Deterministic 
update all qualified names in program
rnmProg :: String -> Prog -> Prog  Deterministic 
rename program (update name of and all qualified names in program)
trType :: ((String,String) -> Visibility -> [(Int,Kind)] -> [ConsDecl] -> a) -> ((String,String) -> Visibility -> [(Int,Kind)] -> TypeExpr -> a) -> ((String,String) -> Visibility -> [(Int,Kind)] -> NewConsDecl -> a) -> TypeDecl -> a  Deterministic 
transform type declaration
typeName :: TypeDecl -> (String,String)  Deterministic 
get name of type declaration
typeVisibility :: TypeDecl -> Visibility  Deterministic 
get visibility of type declaration
typeParams :: TypeDecl -> [(Int,Kind)]  Deterministic 
get type parameters of type declaration
typeConsDecls :: TypeDecl -> [ConsDecl]  Deterministic 
get constructor declarations from type declaration
typeSyn :: TypeDecl -> TypeExpr  Deterministic 
get synonym of type declaration
isTypeData :: TypeDecl -> Bool  Deterministic 
is type declaration a basic data type?
isTypeSyn :: TypeDecl -> Bool  Deterministic 
is type declaration a type synonym?
isTypeNew :: TypeDecl -> Bool  Deterministic 
is type declaration a newtype?
updType :: ((String,String) -> (String,String)) -> (Visibility -> Visibility) -> ([(Int,Kind)] -> [(Int,Kind)]) -> ([ConsDecl] -> [ConsDecl]) -> (NewConsDecl -> NewConsDecl) -> (TypeExpr -> TypeExpr) -> TypeDecl -> TypeDecl  Deterministic 
update type declaration
updTypeName :: ((String,String) -> (String,String)) -> TypeDecl -> TypeDecl  Deterministic 
update name of type declaration
updTypeVisibility :: (Visibility -> Visibility) -> TypeDecl -> TypeDecl  Deterministic 
update visibility of type declaration
updTypeParams :: ([(Int,Kind)] -> [(Int,Kind)]) -> TypeDecl -> TypeDecl  Deterministic 
update type parameters of type declaration
updTypeConsDecls :: ([ConsDecl] -> [ConsDecl]) -> TypeDecl -> TypeDecl  Deterministic 
update constructor declarations of type declaration
updTypeNewConsDecl :: (NewConsDecl -> NewConsDecl) -> TypeDecl -> TypeDecl  Deterministic 
update newtype constructor declaration of type declaration
updTypeSynonym :: (TypeExpr -> TypeExpr) -> TypeDecl -> TypeDecl  Deterministic 
update synonym of type declaration
updQNamesInType :: ((String,String) -> (String,String)) -> TypeDecl -> TypeDecl  Deterministic 
update all qualified names in type declaration
trCons :: ((String,String) -> Int -> Visibility -> [TypeExpr] -> a) -> ConsDecl -> a  Deterministic 
transform constructor declaration
consName :: ConsDecl -> (String,String)  Deterministic 
get name of constructor declaration
consArity :: ConsDecl -> Int  Deterministic 
get arity of constructor declaration
consVisibility :: ConsDecl -> Visibility  Deterministic 
get visibility of constructor declaration
consArgs :: ConsDecl -> [TypeExpr]  Deterministic 
get arguments of constructor declaration
updCons :: ((String,String) -> (String,String)) -> (Int -> Int) -> (Visibility -> Visibility) -> ([TypeExpr] -> [TypeExpr]) -> ConsDecl -> ConsDecl  Deterministic 
update constructor declaration
updConsName :: ((String,String) -> (String,String)) -> ConsDecl -> ConsDecl  Deterministic 
update name of constructor declaration
updConsArity :: (Int -> Int) -> ConsDecl -> ConsDecl  Deterministic 
update arity of constructor declaration
updConsVisibility :: (Visibility -> Visibility) -> ConsDecl -> ConsDecl  Deterministic 
update visibility of constructor declaration
updConsArgs :: ([TypeExpr] -> [TypeExpr]) -> ConsDecl -> ConsDecl  Deterministic 
update arguments of constructor declaration
updQNamesInConsDecl :: ((String,String) -> (String,String)) -> ConsDecl -> ConsDecl  Deterministic 
update all qualified names in constructor declaration
trNewCons :: ((String,String) -> Visibility -> TypeExpr -> a) -> NewConsDecl -> a  Deterministic 
transform newtype constructor declaration
newConsArg :: NewConsDecl -> TypeExpr  Deterministic 
newConsName :: NewConsDecl -> (String,String)  Deterministic 
newConsVisibility :: NewConsDecl -> Visibility  Deterministic 
updNewCons :: ((String,String) -> (String,String)) -> (Visibility -> Visibility) -> (TypeExpr -> TypeExpr) -> NewConsDecl -> NewConsDecl  Deterministic 
update newtype constructor declaration
updNewConsName :: ((String,String) -> (String,String)) -> NewConsDecl -> NewConsDecl  Deterministic 
update name of newtype constructor declaration
updNewConsVisibility :: (Visibility -> Visibility) -> NewConsDecl -> NewConsDecl  Deterministic 
update visibility of newtype constructor declaration
updNewConsArg :: (TypeExpr -> TypeExpr) -> NewConsDecl -> NewConsDecl  Deterministic 
update argument of newtype constructor declaration
updQNamesInNewConsDecl :: ((String,String) -> (String,String)) -> NewConsDecl -> NewConsDecl  Deterministic 
tVarIndex :: TypeExpr -> Int  Deterministic 
get index from type variable
domain :: TypeExpr -> TypeExpr  Deterministic 
get domain from functional type
range :: TypeExpr -> TypeExpr  Deterministic 
get range from functional type
tConsName :: TypeExpr -> (String,String)  Deterministic 
get name from constructed type
tConsArgs :: TypeExpr -> [TypeExpr]  Deterministic 
get arguments from constructed type
trTypeExpr :: (Int -> a) -> ((String,String) -> [a] -> a) -> (a -> a -> a) -> ([(Int,Kind)] -> a -> a) -> TypeExpr -> a  Deterministic 
transform type expression
isTVar :: TypeExpr -> Bool  Deterministic 
is type expression a type variable?
isTCons :: TypeExpr -> Bool  Deterministic 
is type declaration a constructed type?
isFuncType :: TypeExpr -> Bool  Deterministic 
is type declaration a functional type?
isForallType :: TypeExpr -> Bool  Deterministic 
is type declaration a forall type?
updTVars :: (Int -> TypeExpr) -> TypeExpr -> TypeExpr  Deterministic 
update all type variables
updTCons :: ((String,String) -> [TypeExpr] -> TypeExpr) -> TypeExpr -> TypeExpr  Deterministic 
update all type constructors
updFuncTypes :: (TypeExpr -> TypeExpr -> TypeExpr) -> TypeExpr -> TypeExpr  Deterministic 
update all functional types
updForallTypes :: ([(Int,Kind)] -> TypeExpr -> TypeExpr) -> TypeExpr -> TypeExpr  Deterministic 
update all forall types
argTypes :: TypeExpr -> [TypeExpr]  Deterministic 
get argument types from functional type
resultType :: TypeExpr -> TypeExpr  Deterministic 
get result type from (nested) functional type
rnmAllVarsInTypeExpr :: (Int -> Int) -> TypeExpr -> TypeExpr  Deterministic 
rename variables in type expression
updQNamesInTypeExpr :: ((String,String) -> (String,String)) -> TypeExpr -> TypeExpr  Deterministic 
update all qualified names in type expression
trOp :: ((String,String) -> Fixity -> Int -> a) -> OpDecl -> a  Deterministic 
transform operator declaration
opName :: OpDecl -> (String,String)  Deterministic 
get name from operator declaration
opFixity :: OpDecl -> Fixity  Deterministic 
get fixity of operator declaration
opPrecedence :: OpDecl -> Int  Deterministic 
get precedence of operator declaration
updOp :: ((String,String) -> (String,String)) -> (Fixity -> Fixity) -> (Int -> Int) -> OpDecl -> OpDecl  Deterministic 
update operator declaration
updOpName :: ((String,String) -> (String,String)) -> OpDecl -> OpDecl  Deterministic 
update name of operator declaration
updOpFixity :: (Fixity -> Fixity) -> OpDecl -> OpDecl  Deterministic 
update fixity of operator declaration
updOpPrecedence :: (Int -> Int) -> OpDecl -> OpDecl  Deterministic 
update precedence of operator declaration
trFunc :: ((String,String) -> Int -> Visibility -> TypeExpr -> Rule -> a) -> FuncDecl -> a  Deterministic 
transform function
funcName :: FuncDecl -> (String,String)  Deterministic 
get name of function
funcArity :: FuncDecl -> Int  Deterministic 
get arity of function
funcVisibility :: FuncDecl -> Visibility  Deterministic 
get visibility of function
funcType :: FuncDecl -> TypeExpr  Deterministic 
get type of function
funcRule :: FuncDecl -> Rule  Deterministic 
get rule of function
updFunc :: ((String,String) -> (String,String)) -> (Int -> Int) -> (Visibility -> Visibility) -> (TypeExpr -> TypeExpr) -> (Rule -> Rule) -> FuncDecl -> FuncDecl  Deterministic 
update function
updFuncName :: ((String,String) -> (String,String)) -> FuncDecl -> FuncDecl  Deterministic 
update name of function
updFuncArity :: (Int -> Int) -> FuncDecl -> FuncDecl  Deterministic 
update arity of function
updFuncVisibility :: (Visibility -> Visibility) -> FuncDecl -> FuncDecl  Deterministic 
update visibility of function
updFuncType :: (TypeExpr -> TypeExpr) -> FuncDecl -> FuncDecl  Deterministic 
update type of function
updFuncRule :: (Rule -> Rule) -> FuncDecl -> FuncDecl  Deterministic 
update rule of function
isExternal :: FuncDecl -> Bool  Deterministic 
is function externally defined?
allVarsInFunc :: FuncDecl -> [Int]  Deterministic 
get variable names in a function declaration
funcArgs :: FuncDecl -> [Int]  Deterministic 
get arguments of function, if not externally defined
funcBody :: FuncDecl -> Expr  Deterministic 
get body of function, if not externally defined
funcRHS :: FuncDecl -> [Expr]  Deterministic 
rnmAllVarsInFunc :: (Int -> Int) -> FuncDecl -> FuncDecl  Deterministic 
rename all variables in function
updQNamesInFunc :: ((String,String) -> (String,String)) -> FuncDecl -> FuncDecl  Deterministic 
update all qualified names in function
updFuncArgs :: ([Int] -> [Int]) -> FuncDecl -> FuncDecl  Deterministic 
update arguments of function, if not externally defined
updFuncBody :: (Expr -> Expr) -> FuncDecl -> FuncDecl  Deterministic 
update body of function, if not externally defined
trRule :: ([Int] -> Expr -> a) -> (String -> a) -> Rule -> a  Deterministic 
transform rule
ruleArgs :: Rule -> [Int]  Deterministic 
get rules arguments if it's not external
ruleBody :: Rule -> Expr  Deterministic 
get rules body if it's not external
ruleExtDecl :: Rule -> String  Deterministic 
get rules external declaration
isRuleExternal :: Rule -> Bool  Deterministic 
is rule external?
updRule :: ([Int] -> [Int]) -> (Expr -> Expr) -> (String -> String) -> Rule -> Rule  Deterministic 
update rule
updRuleArgs :: ([Int] -> [Int]) -> Rule -> Rule  Deterministic 
update rules arguments
updRuleBody :: (Expr -> Expr) -> Rule -> Rule  Deterministic 
update rules body
updRuleExtDecl :: (String -> String) -> Rule -> Rule  Deterministic 
update rules external declaration
allVarsInRule :: Rule -> [Int]  Deterministic 
get variable names in a functions rule
rnmAllVarsInRule :: (Int -> Int) -> Rule -> Rule  Deterministic 
rename all variables in rule
updQNamesInRule :: ((String,String) -> (String,String)) -> Rule -> Rule  Deterministic 
update all qualified names in rule
trCombType :: a -> (Int -> a) -> a -> (Int -> a) -> CombType -> a  Deterministic 
transform combination type
isCombTypeFuncCall :: CombType -> Bool  Deterministic 
is type of combination FuncCall?
isCombTypeFuncPartCall :: CombType -> Bool  Deterministic 
is type of combination FuncPartCall?
isCombTypeConsCall :: CombType -> Bool  Deterministic 
is type of combination ConsCall?
isCombTypeConsPartCall :: CombType -> Bool  Deterministic 
is type of combination ConsPartCall?
missingArgs :: CombType -> Int  Deterministic 
varNr :: Expr -> Int  Deterministic 
get internal number of variable
literal :: Expr -> Literal  Deterministic 
get literal if expression is literal expression
combType :: Expr -> CombType  Deterministic 
get combination type of a combined expression
combName :: Expr -> (String,String)  Deterministic 
get name of a combined expression
combArgs :: Expr -> [Expr]  Deterministic 
get arguments of a combined expression
missingCombArgs :: Expr -> Int  Deterministic 
get number of missing arguments if expression is combined
letBinds :: Expr -> [(Int,Expr)]  Deterministic 
get indices of variables in let declaration
letBody :: Expr -> Expr  Deterministic 
get body of let declaration
freeVars :: Expr -> [Int]  Deterministic 
get variable indices from declaration of free variables
freeExpr :: Expr -> Expr  Deterministic 
get expression from declaration of free variables
orExps :: Expr -> [Expr]  Deterministic 
get expressions from or-expression
caseType :: Expr -> CaseType  Deterministic 
get case-type of case expression
caseExpr :: Expr -> Expr  Deterministic 
get scrutinee of case expression
caseBranches :: Expr -> [BranchExpr]  Deterministic 
get branch expressions from case expression
isVar :: Expr -> Bool  Deterministic 
is expression a variable?
isLit :: Expr -> Bool  Deterministic 
is expression a literal expression?
isComb :: Expr -> Bool  Deterministic 
is expression combined?
isLet :: Expr -> Bool  Deterministic 
is expression a let expression?
isFree :: Expr -> Bool  Deterministic 
is expression a declaration of free variables?
isOr :: Expr -> Bool  Deterministic 
is expression an or-expression?
isCase :: Expr -> Bool  Deterministic 
is expression a case expression?
trExpr :: (Int -> a) -> (Literal -> a) -> (CombType -> (String,String) -> [a] -> a) -> ([(Int,a)] -> a -> a) -> ([Int] -> a -> a) -> (a -> a -> a) -> (CaseType -> a -> [b] -> a) -> (Pattern -> a -> b) -> (a -> TypeExpr -> a) -> Expr -> a  Deterministic 
transform expression
updVars :: (Int -> Expr) -> Expr -> Expr  Deterministic 
update all variables in given expression
updLiterals :: (Literal -> Expr) -> Expr -> Expr  Deterministic 
update all literals in given expression
updCombs :: (CombType -> (String,String) -> [Expr] -> Expr) -> Expr -> Expr  Deterministic 
update all combined expressions in given expression
updLets :: ([(Int,Expr)] -> Expr -> Expr) -> Expr -> Expr  Deterministic 
update all let expressions in given expression
updFrees :: ([Int] -> Expr -> Expr) -> Expr -> Expr  Deterministic 
update all free declarations in given expression
updOrs :: (Expr -> Expr -> Expr) -> Expr -> Expr  Deterministic 
update all or expressions in given expression
updCases :: (CaseType -> Expr -> [BranchExpr] -> Expr) -> Expr -> Expr  Deterministic 
update all case expressions in given expression
updBranches :: (Pattern -> Expr -> BranchExpr) -> Expr -> Expr  Deterministic 
update all case branches in given expression
updTypeds :: (Expr -> TypeExpr -> Expr) -> Expr -> Expr  Deterministic 
update all typed expressions in given expression
isFuncCall :: Expr -> Bool  Deterministic 
is expression a call of a function where all arguments are provided?
isFuncPartCall :: Expr -> Bool  Deterministic 
is expression a partial function call?
isConsCall :: Expr -> Bool  Deterministic 
is expression a call of a constructor?
isConsPartCall :: Expr -> Bool  Deterministic 
is expression a partial constructor call?
isGround :: Expr -> Bool  Deterministic 
is expression fully evaluated?
allVars :: Expr -> [Int]  Deterministic 
get all variables (also pattern variables) in expression
rnmAllVars :: (Int -> Int) -> Expr -> Expr  Deterministic 
rename all variables (also in patterns) in expression
updQNames :: ((String,String) -> (String,String)) -> Expr -> Expr  Deterministic 
update all qualified names in expression
trBranch :: (Pattern -> Expr -> a) -> BranchExpr -> a  Deterministic 
transform branch expression
branchPattern :: BranchExpr -> Pattern  Deterministic 
get pattern from branch expression
branchExpr :: BranchExpr -> Expr  Deterministic 
get expression from branch expression
updBranch :: (Pattern -> Pattern) -> (Expr -> Expr) -> BranchExpr -> BranchExpr  Deterministic 
update branch expression
updBranchPattern :: (Pattern -> Pattern) -> BranchExpr -> BranchExpr  Deterministic 
update pattern of branch expression
updBranchExpr :: (Expr -> Expr) -> BranchExpr -> BranchExpr  Deterministic 
update expression of branch expression
trPattern :: ((String,String) -> [Int] -> a) -> (Literal -> a) -> Pattern -> a  Deterministic 
transform pattern
patCons :: Pattern -> (String,String)  Deterministic 
get name from constructor pattern
patArgs :: Pattern -> [Int]  Deterministic 
get arguments from constructor pattern
patLiteral :: Pattern -> Literal  Deterministic 
get literal from literal pattern
isConsPattern :: Pattern -> Bool  Deterministic 
is pattern a constructor pattern?
updPattern :: ((String,String) -> (String,String)) -> ([Int] -> [Int]) -> (Literal -> Literal) -> Pattern -> Pattern  Deterministic 
update pattern
updPatCons :: ((String,String) -> (String,String)) -> Pattern -> Pattern  Deterministic 
update constructors name of pattern
updPatArgs :: ([Int] -> [Int]) -> Pattern -> Pattern  Deterministic 
update arguments of constructor pattern
updPatLiteral :: (Literal -> Literal) -> Pattern -> Pattern  Deterministic 
update literal of pattern
patExpr :: Pattern -> Expr  Deterministic 
build expression from pattern

Exported datatypes:


Update

Type synonym: Update a b = (b -> b) -> a -> a


Exported operations:

trProg :: (String -> [String] -> [TypeDecl] -> [FuncDecl] -> [OpDecl] -> a) -> Prog -> a  Deterministic 

transform program

progName :: Prog -> String  Deterministic 

get name from program

progImports :: Prog -> [String]  Deterministic 

get imports from program

progTypes :: Prog -> [TypeDecl]  Deterministic 

get type declarations from program

progFuncs :: Prog -> [FuncDecl]  Deterministic 

get functions from program

progOps :: Prog -> [OpDecl]  Deterministic 

get infix operators from program

updProg :: (String -> String) -> ([String] -> [String]) -> ([TypeDecl] -> [TypeDecl]) -> ([FuncDecl] -> [FuncDecl]) -> ([OpDecl] -> [OpDecl]) -> Prog -> Prog  Deterministic 

update program

updProgName :: (String -> String) -> Prog -> Prog  Deterministic 

update name of program

updProgImports :: ([String] -> [String]) -> Prog -> Prog  Deterministic 

update imports of program

updProgTypes :: ([TypeDecl] -> [TypeDecl]) -> Prog -> Prog  Deterministic 

update type declarations of program

updProgFuncs :: ([FuncDecl] -> [FuncDecl]) -> Prog -> Prog  Deterministic 

update functions of program

updProgOps :: ([OpDecl] -> [OpDecl]) -> Prog -> Prog  Deterministic 

update infix operators of program

allVarsInProg :: Prog -> [Int]  Deterministic 

get all program variables (also from patterns)

updProgExps :: (Expr -> Expr) -> Prog -> Prog  Deterministic 

lift transformation on expressions to program

rnmAllVarsInProg :: (Int -> Int) -> Prog -> Prog  Deterministic 

rename programs variables

updQNamesInProg :: ((String,String) -> (String,String)) -> Prog -> Prog  Deterministic 

update all qualified names in program

rnmProg :: String -> Prog -> Prog  Deterministic 

rename program (update name of and all qualified names in program)

trType :: ((String,String) -> Visibility -> [(Int,Kind)] -> [ConsDecl] -> a) -> ((String,String) -> Visibility -> [(Int,Kind)] -> TypeExpr -> a) -> ((String,String) -> Visibility -> [(Int,Kind)] -> NewConsDecl -> a) -> TypeDecl -> a  Deterministic 

transform type declaration

typeName :: TypeDecl -> (String,String)  Deterministic 

get name of type declaration

typeVisibility :: TypeDecl -> Visibility  Deterministic 

get visibility of type declaration

typeParams :: TypeDecl -> [(Int,Kind)]  Deterministic 

get type parameters of type declaration

typeConsDecls :: TypeDecl -> [ConsDecl]  Deterministic 

get constructor declarations from type declaration

typeSyn :: TypeDecl -> TypeExpr  Deterministic 

get synonym of type declaration

isTypeData :: TypeDecl -> Bool  Deterministic 

is type declaration a basic data type?

isTypeSyn :: TypeDecl -> Bool  Deterministic 

is type declaration a type synonym?

isTypeNew :: TypeDecl -> Bool  Deterministic 

is type declaration a newtype?

updType :: ((String,String) -> (String,String)) -> (Visibility -> Visibility) -> ([(Int,Kind)] -> [(Int,Kind)]) -> ([ConsDecl] -> [ConsDecl]) -> (NewConsDecl -> NewConsDecl) -> (TypeExpr -> TypeExpr) -> TypeDecl -> TypeDecl  Deterministic 

update type declaration

updTypeName :: ((String,String) -> (String,String)) -> TypeDecl -> TypeDecl  Deterministic 

update name of type declaration

updTypeVisibility :: (Visibility -> Visibility) -> TypeDecl -> TypeDecl  Deterministic 

update visibility of type declaration

updTypeParams :: ([(Int,Kind)] -> [(Int,Kind)]) -> TypeDecl -> TypeDecl  Deterministic 

update type parameters of type declaration

updTypeConsDecls :: ([ConsDecl] -> [ConsDecl]) -> TypeDecl -> TypeDecl  Deterministic 

update constructor declarations of type declaration

updTypeNewConsDecl :: (NewConsDecl -> NewConsDecl) -> TypeDecl -> TypeDecl  Deterministic 

update newtype constructor declaration of type declaration

updTypeSynonym :: (TypeExpr -> TypeExpr) -> TypeDecl -> TypeDecl  Deterministic 

update synonym of type declaration

updQNamesInType :: ((String,String) -> (String,String)) -> TypeDecl -> TypeDecl  Deterministic 

update all qualified names in type declaration

trCons :: ((String,String) -> Int -> Visibility -> [TypeExpr] -> a) -> ConsDecl -> a  Deterministic 

transform constructor declaration

consName :: ConsDecl -> (String,String)  Deterministic 

get name of constructor declaration

consArity :: ConsDecl -> Int  Deterministic 

get arity of constructor declaration

consVisibility :: ConsDecl -> Visibility  Deterministic 

get visibility of constructor declaration

consArgs :: ConsDecl -> [TypeExpr]  Deterministic 

get arguments of constructor declaration

updCons :: ((String,String) -> (String,String)) -> (Int -> Int) -> (Visibility -> Visibility) -> ([TypeExpr] -> [TypeExpr]) -> ConsDecl -> ConsDecl  Deterministic 

update constructor declaration

updConsName :: ((String,String) -> (String,String)) -> ConsDecl -> ConsDecl  Deterministic 

update name of constructor declaration

updConsArity :: (Int -> Int) -> ConsDecl -> ConsDecl  Deterministic 

update arity of constructor declaration

updConsVisibility :: (Visibility -> Visibility) -> ConsDecl -> ConsDecl  Deterministic 

update visibility of constructor declaration

updConsArgs :: ([TypeExpr] -> [TypeExpr]) -> ConsDecl -> ConsDecl  Deterministic 

update arguments of constructor declaration

updQNamesInConsDecl :: ((String,String) -> (String,String)) -> ConsDecl -> ConsDecl  Deterministic 

update all qualified names in constructor declaration

trNewCons :: ((String,String) -> Visibility -> TypeExpr -> a) -> NewConsDecl -> a  Deterministic 

transform newtype constructor declaration

newConsName :: NewConsDecl -> (String,String)  Deterministic 

updNewCons :: ((String,String) -> (String,String)) -> (Visibility -> Visibility) -> (TypeExpr -> TypeExpr) -> NewConsDecl -> NewConsDecl  Deterministic 

update newtype constructor declaration

updNewConsName :: ((String,String) -> (String,String)) -> NewConsDecl -> NewConsDecl  Deterministic 

update name of newtype constructor declaration

updNewConsVisibility :: (Visibility -> Visibility) -> NewConsDecl -> NewConsDecl  Deterministic 

update visibility of newtype constructor declaration

updNewConsArg :: (TypeExpr -> TypeExpr) -> NewConsDecl -> NewConsDecl  Deterministic 

update argument of newtype constructor declaration

updQNamesInNewConsDecl :: ((String,String) -> (String,String)) -> NewConsDecl -> NewConsDecl  Deterministic 

tVarIndex :: TypeExpr -> Int  Deterministic 

get index from type variable

domain :: TypeExpr -> TypeExpr  Deterministic 

get domain from functional type

range :: TypeExpr -> TypeExpr  Deterministic 

get range from functional type

tConsName :: TypeExpr -> (String,String)  Deterministic 

get name from constructed type

tConsArgs :: TypeExpr -> [TypeExpr]  Deterministic 

get arguments from constructed type

trTypeExpr :: (Int -> a) -> ((String,String) -> [a] -> a) -> (a -> a -> a) -> ([(Int,Kind)] -> a -> a) -> TypeExpr -> a  Deterministic 

transform type expression

isTVar :: TypeExpr -> Bool  Deterministic 

is type expression a type variable?

isTCons :: TypeExpr -> Bool  Deterministic 

is type declaration a constructed type?

isFuncType :: TypeExpr -> Bool  Deterministic 

is type declaration a functional type?

isForallType :: TypeExpr -> Bool  Deterministic 

is type declaration a forall type?

updTVars :: (Int -> TypeExpr) -> TypeExpr -> TypeExpr  Deterministic 

update all type variables

updTCons :: ((String,String) -> [TypeExpr] -> TypeExpr) -> TypeExpr -> TypeExpr  Deterministic 

update all type constructors

updFuncTypes :: (TypeExpr -> TypeExpr -> TypeExpr) -> TypeExpr -> TypeExpr  Deterministic 

update all functional types

updForallTypes :: ([(Int,Kind)] -> TypeExpr -> TypeExpr) -> TypeExpr -> TypeExpr  Deterministic 

update all forall types

argTypes :: TypeExpr -> [TypeExpr]  Deterministic 

get argument types from functional type

Further infos:
  • solution complete, i.e., able to compute all solutions

resultType :: TypeExpr -> TypeExpr  Deterministic 

get result type from (nested) functional type

Further infos:
  • solution complete, i.e., able to compute all solutions

rnmAllVarsInTypeExpr :: (Int -> Int) -> TypeExpr -> TypeExpr  Deterministic 

rename variables in type expression

updQNamesInTypeExpr :: ((String,String) -> (String,String)) -> TypeExpr -> TypeExpr  Deterministic 

update all qualified names in type expression

trOp :: ((String,String) -> Fixity -> Int -> a) -> OpDecl -> a  Deterministic 

transform operator declaration

opName :: OpDecl -> (String,String)  Deterministic 

get name from operator declaration

opFixity :: OpDecl -> Fixity  Deterministic 

get fixity of operator declaration

opPrecedence :: OpDecl -> Int  Deterministic 

get precedence of operator declaration

updOp :: ((String,String) -> (String,String)) -> (Fixity -> Fixity) -> (Int -> Int) -> OpDecl -> OpDecl  Deterministic 

update operator declaration

updOpName :: ((String,String) -> (String,String)) -> OpDecl -> OpDecl  Deterministic 

update name of operator declaration

updOpFixity :: (Fixity -> Fixity) -> OpDecl -> OpDecl  Deterministic 

update fixity of operator declaration

updOpPrecedence :: (Int -> Int) -> OpDecl -> OpDecl  Deterministic 

update precedence of operator declaration

trFunc :: ((String,String) -> Int -> Visibility -> TypeExpr -> Rule -> a) -> FuncDecl -> a  Deterministic 

transform function

funcName :: FuncDecl -> (String,String)  Deterministic 

get name of function

funcArity :: FuncDecl -> Int  Deterministic 

get arity of function

funcVisibility :: FuncDecl -> Visibility  Deterministic 

get visibility of function

funcType :: FuncDecl -> TypeExpr  Deterministic 

get type of function

funcRule :: FuncDecl -> Rule  Deterministic 

get rule of function

updFunc :: ((String,String) -> (String,String)) -> (Int -> Int) -> (Visibility -> Visibility) -> (TypeExpr -> TypeExpr) -> (Rule -> Rule) -> FuncDecl -> FuncDecl  Deterministic 

update function

updFuncName :: ((String,String) -> (String,String)) -> FuncDecl -> FuncDecl  Deterministic 

update name of function

updFuncArity :: (Int -> Int) -> FuncDecl -> FuncDecl  Deterministic 

update arity of function

updFuncVisibility :: (Visibility -> Visibility) -> FuncDecl -> FuncDecl  Deterministic 

update visibility of function

updFuncType :: (TypeExpr -> TypeExpr) -> FuncDecl -> FuncDecl  Deterministic 

update type of function

updFuncRule :: (Rule -> Rule) -> FuncDecl -> FuncDecl  Deterministic 

update rule of function

isExternal :: FuncDecl -> Bool  Deterministic 

is function externally defined?

allVarsInFunc :: FuncDecl -> [Int]  Deterministic 

get variable names in a function declaration

funcArgs :: FuncDecl -> [Int]  Deterministic 

get arguments of function, if not externally defined

funcBody :: FuncDecl -> Expr  Deterministic 

get body of function, if not externally defined

funcRHS :: FuncDecl -> [Expr]  Deterministic 

rnmAllVarsInFunc :: (Int -> Int) -> FuncDecl -> FuncDecl  Deterministic 

rename all variables in function

updQNamesInFunc :: ((String,String) -> (String,String)) -> FuncDecl -> FuncDecl  Deterministic 

update all qualified names in function

updFuncArgs :: ([Int] -> [Int]) -> FuncDecl -> FuncDecl  Deterministic 

update arguments of function, if not externally defined

updFuncBody :: (Expr -> Expr) -> FuncDecl -> FuncDecl  Deterministic 

update body of function, if not externally defined

trRule :: ([Int] -> Expr -> a) -> (String -> a) -> Rule -> a  Deterministic 

transform rule

ruleArgs :: Rule -> [Int]  Deterministic 

get rules arguments if it's not external

ruleBody :: Rule -> Expr  Deterministic 

get rules body if it's not external

ruleExtDecl :: Rule -> String  Deterministic 

get rules external declaration

isRuleExternal :: Rule -> Bool  Deterministic 

is rule external?

updRule :: ([Int] -> [Int]) -> (Expr -> Expr) -> (String -> String) -> Rule -> Rule  Deterministic 

update rule

updRuleArgs :: ([Int] -> [Int]) -> Rule -> Rule  Deterministic 

update rules arguments

updRuleBody :: (Expr -> Expr) -> Rule -> Rule  Deterministic 

update rules body

updRuleExtDecl :: (String -> String) -> Rule -> Rule  Deterministic 

update rules external declaration

allVarsInRule :: Rule -> [Int]  Deterministic 

get variable names in a functions rule

rnmAllVarsInRule :: (Int -> Int) -> Rule -> Rule  Deterministic 

rename all variables in rule

updQNamesInRule :: ((String,String) -> (String,String)) -> Rule -> Rule  Deterministic 

update all qualified names in rule

trCombType :: a -> (Int -> a) -> a -> (Int -> a) -> CombType -> a  Deterministic 

transform combination type

isCombTypeFuncCall :: CombType -> Bool  Deterministic 

is type of combination FuncCall?

isCombTypeFuncPartCall :: CombType -> Bool  Deterministic 

is type of combination FuncPartCall?

isCombTypeConsCall :: CombType -> Bool  Deterministic 

is type of combination ConsCall?

isCombTypeConsPartCall :: CombType -> Bool  Deterministic 

is type of combination ConsPartCall?

missingArgs :: CombType -> Int  Deterministic 

varNr :: Expr -> Int  Deterministic 

get internal number of variable

literal :: Expr -> Literal  Deterministic 

get literal if expression is literal expression

combType :: Expr -> CombType  Deterministic 

get combination type of a combined expression

combName :: Expr -> (String,String)  Deterministic 

get name of a combined expression

combArgs :: Expr -> [Expr]  Deterministic 

get arguments of a combined expression

missingCombArgs :: Expr -> Int  Deterministic 

get number of missing arguments if expression is combined

letBinds :: Expr -> [(Int,Expr)]  Deterministic 

get indices of variables in let declaration

letBody :: Expr -> Expr  Deterministic 

get body of let declaration

freeVars :: Expr -> [Int]  Deterministic 

get variable indices from declaration of free variables

freeExpr :: Expr -> Expr  Deterministic 

get expression from declaration of free variables

orExps :: Expr -> [Expr]  Deterministic 

get expressions from or-expression

caseType :: Expr -> CaseType  Deterministic 

get case-type of case expression

caseExpr :: Expr -> Expr  Deterministic 

get scrutinee of case expression

caseBranches :: Expr -> [BranchExpr]  Deterministic 

get branch expressions from case expression

isVar :: Expr -> Bool  Deterministic 

is expression a variable?

isLit :: Expr -> Bool  Deterministic 

is expression a literal expression?

isComb :: Expr -> Bool  Deterministic 

is expression combined?

isLet :: Expr -> Bool  Deterministic 

is expression a let expression?

isFree :: Expr -> Bool  Deterministic 

is expression a declaration of free variables?

isOr :: Expr -> Bool  Deterministic 

is expression an or-expression?

isCase :: Expr -> Bool  Deterministic 

is expression a case expression?

trExpr :: (Int -> a) -> (Literal -> a) -> (CombType -> (String,String) -> [a] -> a) -> ([(Int,a)] -> a -> a) -> ([Int] -> a -> a) -> (a -> a -> a) -> (CaseType -> a -> [b] -> a) -> (Pattern -> a -> b) -> (a -> TypeExpr -> a) -> Expr -> a  Deterministic 

transform expression

updVars :: (Int -> Expr) -> Expr -> Expr  Deterministic 

update all variables in given expression

updLiterals :: (Literal -> Expr) -> Expr -> Expr  Deterministic 

update all literals in given expression

updCombs :: (CombType -> (String,String) -> [Expr] -> Expr) -> Expr -> Expr  Deterministic 

update all combined expressions in given expression

updLets :: ([(Int,Expr)] -> Expr -> Expr) -> Expr -> Expr  Deterministic 

update all let expressions in given expression

updFrees :: ([Int] -> Expr -> Expr) -> Expr -> Expr  Deterministic 

update all free declarations in given expression

updOrs :: (Expr -> Expr -> Expr) -> Expr -> Expr  Deterministic 

update all or expressions in given expression

updCases :: (CaseType -> Expr -> [BranchExpr] -> Expr) -> Expr -> Expr  Deterministic 

update all case expressions in given expression

updBranches :: (Pattern -> Expr -> BranchExpr) -> Expr -> Expr  Deterministic 

update all case branches in given expression

updTypeds :: (Expr -> TypeExpr -> Expr) -> Expr -> Expr  Deterministic 

update all typed expressions in given expression

isFuncCall :: Expr -> Bool  Deterministic 

is expression a call of a function where all arguments are provided?

isFuncPartCall :: Expr -> Bool  Deterministic 

is expression a partial function call?

isConsCall :: Expr -> Bool  Deterministic 

is expression a call of a constructor?

isConsPartCall :: Expr -> Bool  Deterministic 

is expression a partial constructor call?

isGround :: Expr -> Bool  Deterministic 

is expression fully evaluated?

allVars :: Expr -> [Int]  Deterministic 

get all variables (also pattern variables) in expression

rnmAllVars :: (Int -> Int) -> Expr -> Expr  Deterministic 

rename all variables (also in patterns) in expression

updQNames :: ((String,String) -> (String,String)) -> Expr -> Expr  Deterministic 

update all qualified names in expression

trBranch :: (Pattern -> Expr -> a) -> BranchExpr -> a  Deterministic 

transform branch expression

branchPattern :: BranchExpr -> Pattern  Deterministic 

get pattern from branch expression

branchExpr :: BranchExpr -> Expr  Deterministic 

get expression from branch expression

updBranch :: (Pattern -> Pattern) -> (Expr -> Expr) -> BranchExpr -> BranchExpr  Deterministic 

update branch expression

updBranchPattern :: (Pattern -> Pattern) -> BranchExpr -> BranchExpr  Deterministic 

update pattern of branch expression

updBranchExpr :: (Expr -> Expr) -> BranchExpr -> BranchExpr  Deterministic 

update expression of branch expression

trPattern :: ((String,String) -> [Int] -> a) -> (Literal -> a) -> Pattern -> a  Deterministic 

transform pattern

patCons :: Pattern -> (String,String)  Deterministic 

get name from constructor pattern

patArgs :: Pattern -> [Int]  Deterministic 

get arguments from constructor pattern

patLiteral :: Pattern -> Literal  Deterministic 

get literal from literal pattern

isConsPattern :: Pattern -> Bool  Deterministic 

is pattern a constructor pattern?

updPattern :: ((String,String) -> (String,String)) -> ([Int] -> [Int]) -> (Literal -> Literal) -> Pattern -> Pattern  Deterministic 

update pattern

updPatCons :: ((String,String) -> (String,String)) -> Pattern -> Pattern  Deterministic 

update constructors name of pattern

updPatArgs :: ([Int] -> [Int]) -> Pattern -> Pattern  Deterministic 

update arguments of constructor pattern

updPatLiteral :: (Literal -> Literal) -> Pattern -> Pattern  Deterministic 

update literal of pattern

patExpr :: Pattern -> Expr  Deterministic 

build expression from pattern