curry-base-1.1.1: Functions for manipulating Curry programs

Copyright(c) 2016 - 2017 Finn Teegen
2018 Kai-Oliver Prott
LicenseBSD-3-clause
Maintainerfte@informatik.uni-kiel.de
Stabilityexperimental
Portabilityportable
Safe HaskellSafe
LanguageHaskell2010

Curry.FlatCurry.Typed.Goodies

Description

This library provides selector functions, test and update operations as well as some useful auxiliary functions for TypedFlatCurry 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 TypedFlatCurry 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

Documentation

trTProg :: (String -> [String] -> [TypeDecl] -> [TFuncDecl] -> [OpDecl] -> b) -> TProg -> b Source #

transform program

tProgName :: TProg -> String Source #

get name from program

tProgImports :: TProg -> [String] Source #

get imports from program

tProgTypes :: TProg -> [TypeDecl] Source #

get type declarations from program

tProgTFuncs :: TProg -> [TFuncDecl] Source #

get functions from program

tProgOps :: TProg -> [OpDecl] Source #

get infix operators from program

updTProg :: (String -> String) -> ([String] -> [String]) -> ([TypeDecl] -> [TypeDecl]) -> ([TFuncDecl] -> [TFuncDecl]) -> ([OpDecl] -> [OpDecl]) -> TProg -> TProg Source #

update program

updTProgName :: Update TProg String Source #

update name of program

updTProgImports :: Update TProg [String] Source #

update imports of program

updTProgTypes :: Update TProg [TypeDecl] Source #

update type declarations of program

updTProgTFuncs :: Update TProg [TFuncDecl] Source #

update functions of program

updTProgOps :: Update TProg [OpDecl] Source #

update infix operators of program

allVarsInTProg :: TProg -> [(VarIndex, TypeExpr)] Source #

get all program variables (also from patterns)

updTProgTExps :: Update TProg TExpr Source #

lift transformation on expressions to program

rnmAllVarsInTProg :: Update TProg VarIndex Source #

rename programs variables

updQNamesInTProg :: Update TProg QName Source #

update all qualified names in program

rnmTProg :: String -> TProg -> TProg Source #

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

trTFunc :: (QName -> Int -> Visibility -> TypeExpr -> TRule -> b) -> TFuncDecl -> b Source #

transform function

tFuncName :: TFuncDecl -> QName Source #

get name of function

tFuncArity :: TFuncDecl -> Int Source #

get arity of function

tFuncVisibility :: TFuncDecl -> Visibility Source #

get visibility of function

tFuncType :: TFuncDecl -> TypeExpr Source #

get type of function

tFuncTRule :: TFuncDecl -> TRule Source #

get rule of function

updTFunc :: (QName -> QName) -> (Int -> Int) -> (Visibility -> Visibility) -> (TypeExpr -> TypeExpr) -> (TRule -> TRule) -> TFuncDecl -> TFuncDecl Source #

update function

updTFuncName :: Update TFuncDecl QName Source #

update name of function

updTFuncArity :: Update TFuncDecl Int Source #

update arity of function

updTFuncVisibility :: Update TFuncDecl Visibility Source #

update visibility of function

updFuncType :: Update TFuncDecl TypeExpr Source #

update type of function

updTFuncTRule :: Update TFuncDecl TRule Source #

update rule of function

isPublicTFunc :: TFuncDecl -> Bool Source #

is function public?

isExternal :: TFuncDecl -> Bool Source #

is function externally defined?

allVarsInTFunc :: TFuncDecl -> [(VarIndex, TypeExpr)] Source #

get variable names in a function declaration

tFuncArgs :: TFuncDecl -> [(VarIndex, TypeExpr)] Source #

get arguments of function, if not externally defined

tFuncBody :: TFuncDecl -> TExpr Source #

get body of function, if not externally defined

tFuncRHS :: TFuncDecl -> [TExpr] Source #

get the right-hand-sides of a FuncDecl

rnmAllVarsInTFunc :: Update TFuncDecl VarIndex Source #

rename all variables in function

updQNamesInTFunc :: Update TFuncDecl QName Source #

update all qualified names in function

updTFuncArgs :: Update TFuncDecl [(VarIndex, TypeExpr)] Source #

update arguments of function, if not externally defined

updTFuncBody :: Update TFuncDecl TExpr Source #

update body of function, if not externally defined

trTRule :: ([(VarIndex, TypeExpr)] -> TExpr -> b) -> (TypeExpr -> String -> b) -> TRule -> b Source #

transform rule

tRuleArgs :: TRule -> [(VarIndex, TypeExpr)] Source #

get rules arguments if it's not external

tRuleBody :: TRule -> TExpr Source #

get rules body if it's not external

tRuleExtDecl :: TRule -> String Source #

get rules external declaration

isTRuleExternal :: TRule -> Bool Source #

is rule external?

updTRule :: (TypeExpr -> TypeExpr) -> ([(VarIndex, TypeExpr)] -> [(VarIndex, TypeExpr)]) -> (TExpr -> TExpr) -> (String -> String) -> TRule -> TRule Source #

update rule

updTRuleType :: Update TRule TypeExpr Source #

update rules TypeExpr

updTRuleArgs :: Update TRule [(VarIndex, TypeExpr)] Source #

update rules arguments

updTRuleBody :: Update TRule TExpr Source #

update rules body

updTRuleExtDecl :: Update TRule String Source #

update rules external declaration

allVarsInTRule :: TRule -> [(VarIndex, TypeExpr)] Source #

get variable names in a functions rule

rnmAllVarsInTRule :: Update TRule VarIndex Source #

rename all variables in rule

updQNamesInTRule :: Update TRule QName Source #

update all qualified names in rule

varNr :: TExpr -> VarIndex Source #

get internal number of variable

literal :: TExpr -> Literal Source #

get literal if expression is literal expression

combType :: TExpr -> CombType Source #

get combination type of a combined expression

combName :: TExpr -> QName Source #

get name of a combined expression

combArgs :: TExpr -> [TExpr] Source #

get arguments of a combined expression

missingCombArgs :: TExpr -> Int Source #

get number of missing arguments if expression is combined

letBinds :: TExpr -> [((VarIndex, TypeExpr), TExpr)] Source #

get indices of variables in let declaration

letBody :: TExpr -> TExpr Source #

get body of let declaration

freeVars :: TExpr -> [(VarIndex, TypeExpr)] Source #

get variable indices from declaration of free variables

freeExpr :: TExpr -> TExpr Source #

get expression from declaration of free variables

orExps :: TExpr -> [TExpr] Source #

get expressions from or-expression

caseType :: TExpr -> CaseType Source #

get case-type of case expression

caseExpr :: TExpr -> TExpr Source #

get scrutinee of case expression

caseBranches :: TExpr -> [TBranchExpr] Source #

get branch expressions from case expression

isTVarE :: TExpr -> Bool Source #

is expression a variable?

isTLit :: TExpr -> Bool Source #

is expression a literal expression?

isTComb :: TExpr -> Bool Source #

is expression combined?

isTLet :: TExpr -> Bool Source #

is expression a let expression?

isTFree :: TExpr -> Bool Source #

is expression a declaration of free variables?

isTOr :: TExpr -> Bool Source #

is expression an or-expression?

isTCase :: TExpr -> Bool Source #

is expression a case expression?

trTExpr :: (TypeExpr -> VarIndex -> b) -> (TypeExpr -> Literal -> b) -> (TypeExpr -> CombType -> QName -> [b] -> b) -> ([((VarIndex, TypeExpr), b)] -> b -> b) -> ([(VarIndex, TypeExpr)] -> b -> b) -> (b -> b -> b) -> (CaseType -> b -> [c] -> b) -> (TPattern -> b -> c) -> (b -> TypeExpr -> b) -> TExpr -> b Source #

transform expression

updVars :: (TypeExpr -> VarIndex -> TExpr) -> TExpr -> TExpr Source #

update all variables in given expression

updLiterals :: (TypeExpr -> Literal -> TExpr) -> TExpr -> TExpr Source #

update all literals in given expression

updCombs :: (TypeExpr -> CombType -> QName -> [TExpr] -> TExpr) -> TExpr -> TExpr Source #

update all combined expressions in given expression

updLets :: ([((VarIndex, TypeExpr), TExpr)] -> TExpr -> TExpr) -> TExpr -> TExpr Source #

update all let expressions in given expression

updFrees :: ([(VarIndex, TypeExpr)] -> TExpr -> TExpr) -> TExpr -> TExpr Source #

update all free declarations in given expression

updOrs :: (TExpr -> TExpr -> TExpr) -> TExpr -> TExpr Source #

update all or expressions in given expression

updCases :: (CaseType -> TExpr -> [TBranchExpr] -> TExpr) -> TExpr -> TExpr Source #

update all case expressions in given expression

updBranches :: (TPattern -> TExpr -> TBranchExpr) -> TExpr -> TExpr Source #

update all case branches in given expression

updTypeds :: (TExpr -> TypeExpr -> TExpr) -> TExpr -> TExpr Source #

update all typed expressions in given expression

isFuncCall :: TExpr -> Bool Source #

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

isFuncPartCall :: TExpr -> Bool Source #

is expression a partial function call?

isConsCall :: TExpr -> Bool Source #

is expression a call of a constructor?

isConsPartCall :: TExpr -> Bool Source #

is expression a partial constructor call?

isGround :: TExpr -> Bool Source #

is expression fully evaluated?

allVars :: TExpr -> [(VarIndex, TypeExpr)] Source #

get all variables (also pattern variables) in expression

rnmAllVars :: Update TExpr VarIndex Source #

rename all variables (also in patterns) in expression

updQNames :: Update TExpr QName Source #

update all qualified names in expression

trTBranch :: (TPattern -> TExpr -> b) -> TBranchExpr -> b Source #

transform branch expression

tBranchTPattern :: TBranchExpr -> TPattern Source #

get pattern from branch expression

tBranchTExpr :: TBranchExpr -> TExpr Source #

get expression from branch expression

updTBranch :: (TPattern -> TPattern) -> (TExpr -> TExpr) -> TBranchExpr -> TBranchExpr Source #

update branch expression

updTBranchTPattern :: Update TBranchExpr TPattern Source #

update pattern of branch expression

updTBranchTExpr :: Update TBranchExpr TExpr Source #

update expression of branch expression

trTPattern :: (TypeExpr -> QName -> [(VarIndex, TypeExpr)] -> b) -> (TypeExpr -> Literal -> b) -> TPattern -> b Source #

transform pattern

tPatCons :: TPattern -> QName Source #

get name from constructor pattern

tPatArgs :: TPattern -> [(VarIndex, TypeExpr)] Source #

get arguments from constructor pattern

tPatLiteral :: TPattern -> Literal Source #

get literal from literal pattern

isConsPattern :: TPattern -> Bool Source #

is pattern a constructor pattern?

updTPattern :: (TypeExpr -> TypeExpr) -> (QName -> QName) -> ([(VarIndex, TypeExpr)] -> [(VarIndex, TypeExpr)]) -> (Literal -> Literal) -> TPattern -> TPattern Source #

update pattern

updTPatType :: (TypeExpr -> TypeExpr) -> TPattern -> TPattern Source #

update TypeExpr of pattern

updTPatCons :: (QName -> QName) -> TPattern -> TPattern Source #

update constructors name of pattern

updTPatArgs :: ([(VarIndex, TypeExpr)] -> [(VarIndex, TypeExpr)]) -> TPattern -> TPattern Source #

update arguments of constructor pattern

updTPatLiteral :: (Literal -> Literal) -> TPattern -> TPattern Source #

update literal of pattern

tPatExpr :: TPattern -> TExpr Source #

build expression from pattern

type Update a b = (b -> b) -> a -> a Source #

Update of a type's component

trType :: (QName -> Visibility -> [TVarIndex] -> [ConsDecl] -> a) -> (QName -> Visibility -> [TVarIndex] -> TypeExpr -> a) -> TypeDecl -> a Source #

transform type declaration

typeName :: TypeDecl -> QName Source #

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

typeSyn :: TypeDecl -> TypeExpr Source #

get synonym of type declaration

isTypeSyn :: TypeDecl -> Bool Source #

is type declaration a type synonym?

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

updTypeName :: Update TypeDecl QName Source #

update name of type declaration

updTypeVisibility :: Update TypeDecl Visibility Source #

update visibility of type declaration

updTypeParams :: Update TypeDecl [TVarIndex] Source #

update type parameters of type declaration

updTypeConsDecls :: Update TypeDecl [ConsDecl] Source #

update constructor declarations of type declaration

updTypeSynonym :: Update TypeDecl TypeExpr Source #

update synonym of type declaration

updQNamesInType :: Update TypeDecl QName Source #

update all qualified names in type declaration

trCons :: (QName -> Int -> Visibility -> [TypeExpr] -> a) -> ConsDecl -> a Source #

transform constructor declaration

consName :: ConsDecl -> QName Source #

get name of constructor declaration

consArity :: ConsDecl -> Int Source #

get arity of constructor declaration

consVisibility :: ConsDecl -> Visibility Source #

get visibility of constructor declaration

isPublicCons :: ConsDecl -> Bool Source #

Is the constructor declaration public?

consArgs :: ConsDecl -> [TypeExpr] Source #

get arguments of constructor declaration

updCons :: (QName -> QName) -> (Int -> Int) -> (Visibility -> Visibility) -> ([TypeExpr] -> [TypeExpr]) -> ConsDecl -> ConsDecl Source #

update constructor declaration

updConsName :: Update ConsDecl QName Source #

update name of constructor declaration

updConsArity :: Update ConsDecl Int Source #

update arity of constructor declaration

updConsVisibility :: Update ConsDecl Visibility Source #

update visibility of constructor declaration

updConsArgs :: Update ConsDecl [TypeExpr] Source #

update arguments of constructor declaration

updQNamesInConsDecl :: Update ConsDecl QName Source #

update all qualified names in constructor declaration

tVarIndex :: TypeExpr -> TVarIndex Source #

get index from type variable

domain :: TypeExpr -> TypeExpr Source #

get domain from functional type

range :: TypeExpr -> TypeExpr Source #

get range from functional type

tConsName :: TypeExpr -> QName Source #

get name from constructed type

tConsArgs :: TypeExpr -> [TypeExpr] Source #

get arguments from constructed type

trTypeExpr :: (TVarIndex -> a) -> (QName -> [a] -> a) -> (a -> a -> a) -> ([TVarIndex] -> a -> a) -> TypeExpr -> a Source #

transform type expression

isTVar :: TypeExpr -> Bool Source #

is type expression a type variable?

isTCons :: TypeExpr -> Bool Source #

is type declaration a constructed type?

isFuncType :: TypeExpr -> Bool Source #

is type declaration a functional type?

updTVars :: (TVarIndex -> TypeExpr) -> TypeExpr -> TypeExpr Source #

update all type variables

updTCons :: (QName -> [TypeExpr] -> TypeExpr) -> TypeExpr -> TypeExpr Source #

update all type constructors

updFuncTypes :: (TypeExpr -> TypeExpr -> TypeExpr) -> TypeExpr -> TypeExpr Source #

update all functional types

argTypes :: TypeExpr -> [TypeExpr] Source #

get argument types from functional type

typeArity :: TypeExpr -> Int Source #

Compute the arity of a TypeExpr

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

trOp :: (QName -> Fixity -> Integer -> a) -> OpDecl -> a Source #

transform operator declaration

opName :: OpDecl -> QName Source #

get name from operator declaration

opFixity :: OpDecl -> Fixity Source #

get fixity of operator declaration

opPrecedence :: OpDecl -> Integer Source #

get precedence of operator declaration

updOp :: (QName -> QName) -> (Fixity -> Fixity) -> (Integer -> Integer) -> OpDecl -> OpDecl Source #

update operator declaration

updOpName :: Update OpDecl QName Source #

update name of operator declaration

updOpFixity :: Update OpDecl Fixity Source #

update fixity of operator declaration

updOpPrecedence :: Update OpDecl Integer Source #

update precedence of 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?