curry-base-1.0.0: Functions for manipulating Curry programs

Copyright(c) 2016 - 2017 Finn Teegen
LicenseBSD-3-clause
Maintainerbjp@informatik.uni-kiel.de
Stabilityexperimental
Portabilityportable
Safe HaskellSafe
LanguageHaskell2010

Curry.FlatCurry.Annotated.Goodies

Description

TODO

Synopsis

Documentation

trAProg :: (String -> [String] -> [TypeDecl] -> [AFuncDecl a] -> [OpDecl] -> b) -> AProg a -> b Source #

transform program

aProgName :: AProg a -> String Source #

get name from 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

aProgOps :: AProg a -> [OpDecl] Source #

get infix operators from program

updAProg :: (String -> String) -> ([String] -> [String]) -> ([TypeDecl] -> [TypeDecl]) -> ([AFuncDecl a] -> [AFuncDecl a]) -> ([OpDecl] -> [OpDecl]) -> AProg a -> AProg a Source #

update program

updAProgName :: Update (AProg a) String Source #

update name of program

updAProgImports :: Update (AProg a) [String] Source #

update imports of program

updAProgTypes :: Update (AProg a) [TypeDecl] Source #

update type declarations of program

updAProgAFuncs :: Update (AProg a) [AFuncDecl a] Source #

update functions of program

updAProgOps :: Update (AProg a) [OpDecl] Source #

update infix operators of program

allVarsInAProg :: AProg a -> [(VarIndex, a)] Source #

get all program variables (also from patterns)

updAProgAExps :: Update (AProg a) (AExpr a) Source #

lift transformation on expressions to program

rnmAllVarsInAProg :: Update (AProg a) VarIndex Source #

rename programs variables

updQNamesInAProg :: Update (AProg a) QName Source #

update all qualified names in program

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

aFuncName :: AFuncDecl a -> QName Source #

get name of function

aFuncArity :: AFuncDecl a -> Int Source #

get arity of function

aFuncVisibility :: AFuncDecl a -> Visibility Source #

get visibility of function

aFuncType :: AFuncDecl a -> TypeExpr Source #

get type 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

updAFuncName :: Update (AFuncDecl a) QName Source #

update name of function

updAFuncArity :: Update (AFuncDecl a) Int Source #

update arity of function

updAFuncVisibility :: Update (AFuncDecl a) Visibility Source #

update visibility of function

updFuncType :: Update (AFuncDecl a) TypeExpr Source #

update type of function

updAFuncARule :: Update (AFuncDecl a) (ARule a) Source #

update rule 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

aFuncBody :: AFuncDecl a -> AExpr a Source #

get body of function, if not externally defined

aFuncRHS :: AFuncDecl a -> [AExpr a] Source #

get the right-hand-sides of a FuncDecl

rnmAllVarsInAFunc :: Update (AFuncDecl a) VarIndex Source #

rename all variables in function

updQNamesInAFunc :: Update (AFuncDecl a) QName Source #

update all qualified names in function

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

aRuleArgs :: ARule a -> [(VarIndex, a)] Source #

get rules arguments if it's not external

aRuleBody :: ARule a -> AExpr a Source #

get rules body if it's not external

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

updARuleArgs :: Update (ARule a) [(VarIndex, a)] Source #

update rules arguments

updARuleBody :: Update (ARule a) (AExpr a) Source #

update rules body

updARuleExtDecl :: Update (ARule a) String Source #

update rules external declaration

allVarsInARule :: ARule a -> [(VarIndex, a)] Source #

get variable names in a functions rule

rnmAllVarsInARule :: Update (ARule a) VarIndex Source #

rename all variables in rule

updQNamesInARule :: Update (ARule a) QName Source #

update all qualified names in rule

annot :: AExpr a -> a Source #

get annoation of an expression

varNr :: AExpr a -> VarIndex Source #

get internal number of variable

literal :: AExpr a -> Literal Source #

get literal if expression is literal expression

combType :: AExpr a -> CombType Source #

get combination type of a combined expression

combName :: AExpr a -> (QName, a) Source #

get name of a combined expression

combArgs :: AExpr a -> [AExpr a] Source #

get arguments of a combined expression

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

letBody :: AExpr a -> AExpr a Source #

get body of let declaration

freeVars :: AExpr a -> [(VarIndex, a)] Source #

get variable indices from declaration of free variables

freeExpr :: AExpr a -> AExpr a Source #

get expression from declaration of free variables

orExps :: AExpr a -> [AExpr a] Source #

get expressions from or-expression

caseType :: AExpr a -> CaseType Source #

get case-type of case expression

caseExpr :: AExpr a -> AExpr a Source #

get scrutinee of case expression

caseBranches :: AExpr a -> [ABranchExpr a] Source #

get branch expressions from case expression

isAVar :: AExpr a -> Bool Source #

is expression a variable?

isALit :: AExpr a -> Bool Source #

is expression a literal expression?

isAComb :: AExpr a -> Bool Source #

is expression combined?

isALet :: AExpr a -> Bool Source #

is expression a let expression?

isAFree :: AExpr a -> Bool Source #

is expression a declaration of free variables?

isAOr :: AExpr a -> Bool Source #

is expression an or-expression?

isACase :: AExpr a -> Bool Source #

is expression a 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?

isGround :: AExpr a -> Bool Source #

is expression fully evaluated?

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

updQNames :: Update (AExpr a) QName Source #

update all qualified names in expression

trABranch :: (APattern a -> AExpr a -> b) -> ABranchExpr a -> b Source #

transform branch 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

aPatAnnot :: APattern a -> a Source #

get annotation from pattern

aPatCons :: APattern a -> (QName, a) Source #

get name from constructor pattern

aPatArgs :: APattern a -> [(VarIndex, a)] Source #

get arguments from constructor 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

aPatExpr :: APattern a -> AExpr a Source #

build expression from pattern