Copyright | (c) 2016 - 2017 Finn Teegen |
---|---|
License | BSD-3-clause |
Maintainer | fte@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 AnnotatedFlatCurry 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 AnnotatedFlatCurry 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
- trAProg :: (String -> [String] -> [TypeDecl] -> [AFuncDecl a] -> [OpDecl] -> b) -> AProg a -> b
- aProgName :: AProg a -> String
- aProgImports :: AProg a -> [String]
- aProgTypes :: AProg a -> [TypeDecl]
- aProgAFuncs :: AProg a -> [AFuncDecl a]
- aProgOps :: AProg a -> [OpDecl]
- updAProg :: (String -> String) -> ([String] -> [String]) -> ([TypeDecl] -> [TypeDecl]) -> ([AFuncDecl a] -> [AFuncDecl a]) -> ([OpDecl] -> [OpDecl]) -> AProg a -> AProg a
- updAProgName :: Update (AProg a) String
- updAProgImports :: Update (AProg a) [String]
- updAProgTypes :: Update (AProg a) [TypeDecl]
- updAProgAFuncs :: Update (AProg a) [AFuncDecl a]
- updAProgOps :: Update (AProg a) [OpDecl]
- allVarsInAProg :: AProg a -> [(VarIndex, a)]
- updAProgAExps :: Update (AProg a) (AExpr a)
- rnmAllVarsInAProg :: Update (AProg a) VarIndex
- updQNamesInAProg :: Update (AProg a) QName
- rnmAProg :: String -> AProg a -> AProg a
- trAFunc :: (QName -> Int -> Visibility -> TypeExpr -> ARule a -> b) -> AFuncDecl a -> b
- aFuncName :: AFuncDecl a -> QName
- aFuncArity :: AFuncDecl a -> Int
- aFuncVisibility :: AFuncDecl a -> Visibility
- aFuncType :: AFuncDecl a -> TypeExpr
- aFuncARule :: AFuncDecl a -> ARule a
- updAFunc :: (QName -> QName) -> (Int -> Int) -> (Visibility -> Visibility) -> (TypeExpr -> TypeExpr) -> (ARule a -> ARule a) -> AFuncDecl a -> AFuncDecl a
- updAFuncName :: Update (AFuncDecl a) QName
- updAFuncArity :: Update (AFuncDecl a) Int
- updAFuncVisibility :: Update (AFuncDecl a) Visibility
- updFuncType :: Update (AFuncDecl a) TypeExpr
- updAFuncARule :: Update (AFuncDecl a) (ARule a)
- isPublicAFunc :: AFuncDecl a -> Bool
- isExternal :: AFuncDecl a -> Bool
- allVarsInAFunc :: AFuncDecl a -> [(VarIndex, a)]
- aFuncArgs :: AFuncDecl a -> [(VarIndex, a)]
- aFuncBody :: AFuncDecl a -> AExpr a
- aFuncRHS :: AFuncDecl a -> [AExpr a]
- rnmAllVarsInAFunc :: Update (AFuncDecl a) VarIndex
- updQNamesInAFunc :: Update (AFuncDecl a) QName
- updAFuncArgs :: Update (AFuncDecl a) [(VarIndex, a)]
- updAFuncBody :: Update (AFuncDecl a) (AExpr a)
- trARule :: (a -> [(VarIndex, a)] -> AExpr a -> b) -> (a -> String -> b) -> ARule a -> b
- aRuleAnnot :: ARule a -> a
- aRuleArgs :: ARule a -> [(VarIndex, a)]
- aRuleBody :: ARule a -> AExpr a
- aRuleExtDecl :: ARule a -> String
- isARuleExternal :: ARule a -> Bool
- updARule :: (a -> b) -> ([(VarIndex, a)] -> [(VarIndex, b)]) -> (AExpr a -> AExpr b) -> (String -> String) -> ARule a -> ARule b
- updARuleAnnot :: Update (ARule a) a
- updARuleArgs :: Update (ARule a) [(VarIndex, a)]
- updARuleBody :: Update (ARule a) (AExpr a)
- updARuleExtDecl :: Update (ARule a) String
- allVarsInARule :: ARule a -> [(VarIndex, a)]
- rnmAllVarsInARule :: Update (ARule a) VarIndex
- updQNamesInARule :: Update (ARule a) QName
- annot :: AExpr a -> a
- varNr :: AExpr a -> VarIndex
- literal :: AExpr a -> Literal
- combType :: AExpr a -> CombType
- combName :: AExpr a -> (QName, a)
- combArgs :: AExpr a -> [AExpr a]
- missingCombArgs :: AExpr a -> Int
- letBinds :: AExpr a -> [((VarIndex, a), AExpr a)]
- letBody :: AExpr a -> AExpr a
- freeVars :: AExpr a -> [(VarIndex, a)]
- freeExpr :: AExpr a -> AExpr a
- orExps :: AExpr a -> [AExpr a]
- caseType :: AExpr a -> CaseType
- caseExpr :: AExpr a -> AExpr a
- caseBranches :: AExpr a -> [ABranchExpr a]
- isAVar :: AExpr a -> Bool
- isALit :: AExpr a -> Bool
- isAComb :: AExpr a -> Bool
- isALet :: AExpr a -> Bool
- isAFree :: AExpr a -> Bool
- isAOr :: AExpr a -> Bool
- isACase :: AExpr a -> Bool
- trAExpr :: (a -> VarIndex -> b) -> (a -> Literal -> b) -> (a -> CombType -> (QName, a) -> [b] -> b) -> (a -> [((VarIndex, a), b)] -> b -> b) -> (a -> [(VarIndex, a)] -> b -> b) -> (a -> b -> b -> b) -> (a -> CaseType -> b -> [c] -> b) -> (APattern a -> b -> c) -> (a -> b -> TypeExpr -> b) -> AExpr a -> b
- updVars :: (a -> VarIndex -> AExpr a) -> AExpr a -> AExpr a
- updLiterals :: (a -> Literal -> AExpr a) -> AExpr a -> AExpr a
- updCombs :: (a -> CombType -> (QName, a) -> [AExpr a] -> AExpr a) -> AExpr a -> AExpr a
- updLets :: (a -> [((VarIndex, a), AExpr a)] -> AExpr a -> AExpr a) -> AExpr a -> AExpr a
- updFrees :: (a -> [(VarIndex, a)] -> AExpr a -> AExpr a) -> AExpr a -> AExpr a
- updOrs :: (a -> AExpr a -> AExpr a -> AExpr a) -> AExpr a -> AExpr a
- updCases :: (a -> CaseType -> AExpr a -> [ABranchExpr a] -> AExpr a) -> AExpr a -> AExpr a
- updBranches :: (APattern a -> AExpr a -> ABranchExpr a) -> AExpr a -> AExpr a
- updTypeds :: (a -> AExpr a -> TypeExpr -> AExpr a) -> AExpr a -> AExpr a
- isFuncCall :: AExpr a -> Bool
- isFuncPartCall :: AExpr a -> Bool
- isConsCall :: AExpr a -> Bool
- isConsPartCall :: AExpr a -> Bool
- isGround :: AExpr a -> Bool
- allVars :: AExpr a -> [(VarIndex, a)]
- rnmAllVars :: Update (AExpr a) VarIndex
- updQNames :: Update (AExpr a) QName
- trABranch :: (APattern a -> AExpr a -> b) -> ABranchExpr a -> b
- aBranchAPattern :: ABranchExpr a -> APattern a
- aBranchAExpr :: ABranchExpr a -> AExpr a
- updABranch :: (APattern a -> APattern a) -> (AExpr a -> AExpr a) -> ABranchExpr a -> ABranchExpr a
- updABranchAPattern :: Update (ABranchExpr a) (APattern a)
- updABranchAExpr :: Update (ABranchExpr a) (AExpr a)
- trAPattern :: (a -> (QName, a) -> [(VarIndex, a)] -> b) -> (a -> Literal -> b) -> APattern a -> b
- aPatAnnot :: APattern a -> a
- aPatCons :: APattern a -> (QName, a)
- aPatArgs :: APattern a -> [(VarIndex, a)]
- aPatLiteral :: APattern a -> Literal
- isConsPattern :: APattern a -> Bool
- updAPattern :: (a -> a) -> ((QName, a) -> (QName, a)) -> ([(VarIndex, a)] -> [(VarIndex, a)]) -> (Literal -> Literal) -> APattern a -> APattern a
- updAPatAnnot :: (a -> a) -> APattern a -> APattern a
- updAPatCons :: ((QName, a) -> (QName, a)) -> APattern a -> APattern a
- updAPatArgs :: ([(VarIndex, a)] -> [(VarIndex, a)]) -> APattern a -> APattern a
- updAPatLiteral :: (Literal -> Literal) -> APattern a -> APattern a
- aPatExpr :: APattern a -> AExpr a
- type Update a b = (b -> b) -> a -> a
- 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
- updTVars :: (TVarIndex -> TypeExpr) -> TypeExpr -> TypeExpr
- updTCons :: (QName -> [TypeExpr] -> TypeExpr) -> TypeExpr -> TypeExpr
- updFuncTypes :: (TypeExpr -> 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
- trCombType :: a -> (Int -> a) -> a -> (Int -> a) -> CombType -> a
- isCombTypeFuncCall :: CombType -> Bool
- isCombTypeFuncPartCall :: CombType -> Bool
- isCombTypeConsCall :: CombType -> Bool
- isCombTypeConsPartCall :: CombType -> Bool
- isPublic :: Visibility -> Bool
Documentation
trAProg :: (String -> [String] -> [TypeDecl] -> [AFuncDecl a] -> [OpDecl] -> b) -> AProg a -> b Source #
transform program
aProgImports :: AProg a -> [String] Source #
get imports from program
aProgTypes :: AProg a -> [TypeDecl] Source #
get type declarations from program
aProgAFuncs :: AProg a -> [AFuncDecl a] Source #
get functions from program
updAProg :: (String -> String) -> ([String] -> [String]) -> ([TypeDecl] -> [TypeDecl]) -> ([AFuncDecl a] -> [AFuncDecl a]) -> ([OpDecl] -> [OpDecl]) -> AProg a -> AProg a Source #
update program
allVarsInAProg :: AProg a -> [(VarIndex, a)] Source #
get all program variables (also from patterns)
rnmAProg :: String -> AProg a -> AProg a Source #
rename program (update name of and all qualified names in program)
trAFunc :: (QName -> Int -> Visibility -> TypeExpr -> ARule a -> b) -> AFuncDecl a -> b Source #
transform function
aFuncArity :: AFuncDecl a -> Int Source #
get arity of function
aFuncVisibility :: AFuncDecl a -> Visibility Source #
get visibility of function
aFuncARule :: AFuncDecl a -> ARule a Source #
get rule of function
updAFunc :: (QName -> QName) -> (Int -> Int) -> (Visibility -> Visibility) -> (TypeExpr -> TypeExpr) -> (ARule a -> ARule a) -> AFuncDecl a -> AFuncDecl a Source #
update function
updAFuncVisibility :: Update (AFuncDecl a) Visibility Source #
update visibility of function
isPublicAFunc :: AFuncDecl a -> Bool Source #
is function public?
isExternal :: AFuncDecl a -> Bool Source #
is function externally defined?
allVarsInAFunc :: AFuncDecl a -> [(VarIndex, a)] Source #
get variable names in a function declaration
aFuncArgs :: AFuncDecl a -> [(VarIndex, a)] Source #
get arguments of function, if not externally defined
updAFuncArgs :: Update (AFuncDecl a) [(VarIndex, a)] Source #
update arguments of function, if not externally defined
updAFuncBody :: Update (AFuncDecl a) (AExpr a) Source #
update body of function, if not externally defined
trARule :: (a -> [(VarIndex, a)] -> AExpr a -> b) -> (a -> String -> b) -> ARule a -> b Source #
transform rule
aRuleAnnot :: ARule a -> a Source #
get rules annotation
aRuleExtDecl :: ARule a -> String Source #
get rules external declaration
isARuleExternal :: ARule a -> Bool Source #
is rule external?
updARule :: (a -> b) -> ([(VarIndex, a)] -> [(VarIndex, b)]) -> (AExpr a -> AExpr b) -> (String -> String) -> ARule a -> ARule b Source #
update rule
updARuleAnnot :: Update (ARule a) a Source #
update rules annotation
allVarsInARule :: ARule a -> [(VarIndex, a)] Source #
get variable names in a functions rule
missingCombArgs :: AExpr a -> Int Source #
get number of missing arguments if expression is combined
letBinds :: AExpr a -> [((VarIndex, a), AExpr a)] Source #
get indices of varoables in let declaration
freeVars :: AExpr a -> [(VarIndex, a)] Source #
get variable indices from declaration of free variables
caseBranches :: AExpr a -> [ABranchExpr a] Source #
get branch expressions from case expression
trAExpr :: (a -> VarIndex -> b) -> (a -> Literal -> b) -> (a -> CombType -> (QName, a) -> [b] -> b) -> (a -> [((VarIndex, a), b)] -> b -> b) -> (a -> [(VarIndex, a)] -> b -> b) -> (a -> b -> b -> b) -> (a -> CaseType -> b -> [c] -> b) -> (APattern a -> b -> c) -> (a -> b -> TypeExpr -> b) -> AExpr a -> b Source #
transform expression
updVars :: (a -> VarIndex -> AExpr a) -> AExpr a -> AExpr a Source #
update all variables in given expression
updLiterals :: (a -> Literal -> AExpr a) -> AExpr a -> AExpr a Source #
update all literals in given expression
updCombs :: (a -> CombType -> (QName, a) -> [AExpr a] -> AExpr a) -> AExpr a -> AExpr a Source #
update all combined expressions in given expression
updLets :: (a -> [((VarIndex, a), AExpr a)] -> AExpr a -> AExpr a) -> AExpr a -> AExpr a Source #
update all let expressions in given expression
updFrees :: (a -> [(VarIndex, a)] -> AExpr a -> AExpr a) -> AExpr a -> AExpr a Source #
update all free declarations in given expression
updOrs :: (a -> AExpr a -> AExpr a -> AExpr a) -> AExpr a -> AExpr a Source #
update all or expressions in given expression
updCases :: (a -> CaseType -> AExpr a -> [ABranchExpr a] -> AExpr a) -> AExpr a -> AExpr a Source #
update all case expressions in given expression
updBranches :: (APattern a -> AExpr a -> ABranchExpr a) -> AExpr a -> AExpr a Source #
update all case branches in given expression
updTypeds :: (a -> AExpr a -> TypeExpr -> AExpr a) -> AExpr a -> AExpr a Source #
update all typed expressions in given expression
isFuncCall :: AExpr a -> Bool Source #
is expression a call of a function where all arguments are provided?
isFuncPartCall :: AExpr a -> Bool Source #
is expression a partial function call?
isConsCall :: AExpr a -> Bool Source #
is expression a call of a constructor?
isConsPartCall :: AExpr a -> Bool Source #
is expression a partial constructor call?
allVars :: AExpr a -> [(VarIndex, a)] Source #
get all variables (also pattern variables) in expression
rnmAllVars :: Update (AExpr a) VarIndex Source #
rename all variables (also in patterns) in expression
aBranchAPattern :: ABranchExpr a -> APattern a Source #
get pattern from branch expression
aBranchAExpr :: ABranchExpr a -> AExpr a Source #
get expression from branch expression
updABranch :: (APattern a -> APattern a) -> (AExpr a -> AExpr a) -> ABranchExpr a -> ABranchExpr a Source #
update branch expression
updABranchAPattern :: Update (ABranchExpr a) (APattern a) Source #
update pattern of branch expression
updABranchAExpr :: Update (ABranchExpr a) (AExpr a) Source #
update expression of branch expression
trAPattern :: (a -> (QName, a) -> [(VarIndex, a)] -> b) -> (a -> Literal -> b) -> APattern a -> b Source #
transform pattern
aPatLiteral :: APattern a -> Literal Source #
get literal from literal pattern
isConsPattern :: APattern a -> Bool Source #
is pattern a constructor pattern?
updAPattern :: (a -> a) -> ((QName, a) -> (QName, a)) -> ([(VarIndex, a)] -> [(VarIndex, a)]) -> (Literal -> Literal) -> APattern a -> APattern a Source #
update pattern
updAPatAnnot :: (a -> a) -> APattern a -> APattern a Source #
update annotation of pattern
updAPatCons :: ((QName, a) -> (QName, a)) -> APattern a -> APattern a Source #
update constructors name of pattern
updAPatArgs :: ([(VarIndex, a)] -> [(VarIndex, a)]) -> APattern a -> APattern a Source #
update arguments of constructor pattern
updAPatLiteral :: (Literal -> Literal) -> APattern a -> APattern a Source #
update literal of pattern
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?
updTCons :: (QName -> [TypeExpr] -> TypeExpr) -> TypeExpr -> TypeExpr Source #
update all type constructors
updFuncTypes :: (TypeExpr -> TypeExpr -> TypeExpr) -> TypeExpr -> TypeExpr Source #
update all functional 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
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?
isPublic :: Visibility -> Bool Source #
Is this a public Visibility
?