curry-base-1.1.1: Functions for manipulating Curry programs

Copyright(c) Sebastian Fischer 2006
Björn Peemöller 2011
LicenseBSD-3-clause
Maintainerbjp@informatik.uni-kiel.de
Stabilityexperimental
Portabilityportable
Safe HaskellSafe
LanguageHaskell2010

Curry.FlatCurry.Goodies

Description

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

Documentation

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

Update of a type's component

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

transform program

progName :: Prog -> String Source #

get name from program

progImports :: Prog -> [String] Source #

get imports from program

progTypes :: Prog -> [TypeDecl] Source #

get type declarations from program

progFuncs :: Prog -> [FuncDecl] Source #

get functions from program

progOps :: Prog -> [OpDecl] Source #

get infix operators from program

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

update program

updProgName :: Update Prog String Source #

update name of program

updProgImports :: Update Prog [String] Source #

update imports of program

updProgTypes :: Update Prog [TypeDecl] Source #

update type declarations of program

updProgFuncs :: Update Prog [FuncDecl] Source #

update functions of program

updProgOps :: Update Prog [OpDecl] Source #

update infix operators of program

allVarsInProg :: Prog -> [VarIndex] Source #

get all program variables (also from patterns)

updProgExps :: Update Prog Expr Source #

lift transformation on expressions to program

rnmAllVarsInProg :: Update Prog VarIndex Source #

rename programs variables

updQNamesInProg :: Update Prog QName Source #

update all qualified names in program

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

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?

isForallType :: TypeExpr -> Bool Source #

is type declaration a forall 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

updForallTypes :: ([TVarIndex] -> TypeExpr -> TypeExpr) -> TypeExpr -> TypeExpr Source #

update all forall 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

trFunc :: (QName -> Int -> Visibility -> TypeExpr -> Rule -> a) -> FuncDecl -> a Source #

transform function

funcName :: FuncDecl -> QName Source #

get name of function

funcArity :: FuncDecl -> Int Source #

get arity of function

funcVisibility :: FuncDecl -> Visibility Source #

get visibility of function

funcType :: FuncDecl -> TypeExpr Source #

get type of function

funcRule :: FuncDecl -> Rule Source #

get rule of function

updFunc :: (QName -> QName) -> (Int -> Int) -> (Visibility -> Visibility) -> (TypeExpr -> TypeExpr) -> (Rule -> Rule) -> FuncDecl -> FuncDecl Source #

update function

updFuncName :: Update FuncDecl QName Source #

update name of function

updFuncArity :: Update FuncDecl Int Source #

update arity of function

updFuncVisibility :: Update FuncDecl Visibility Source #

update visibility of function

updFuncType :: Update FuncDecl TypeExpr Source #

update type of function

updFuncRule :: Update FuncDecl Rule Source #

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

funcArgs :: FuncDecl -> [VarIndex] Source #

get arguments of function, if not externally defined

funcBody :: FuncDecl -> Expr Source #

get body of function, if not externally defined

funcRHS :: FuncDecl -> [Expr] Source #

get the right-hand-sides of a FuncDecl

rnmAllVarsInFunc :: Update FuncDecl VarIndex Source #

rename all variables in function

updQNamesInFunc :: Update FuncDecl QName Source #

update all qualified names in function

updFuncArgs :: Update FuncDecl [VarIndex] Source #

update arguments of function, if not externally defined

updFuncBody :: Update FuncDecl Expr Source #

update body of function, if not externally defined

trRule :: ([VarIndex] -> Expr -> a) -> (String -> a) -> Rule -> a Source #

transform rule

ruleArgs :: Rule -> [VarIndex] Source #

get rules arguments if it's not external

ruleBody :: Rule -> Expr Source #

get rules body if it's not external

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

updRuleArgs :: Update Rule [VarIndex] Source #

update rules arguments

updRuleBody :: Update Rule Expr Source #

update rules body

updRuleExtDecl :: Update Rule String Source #

update rules external declaration

allVarsInRule :: Rule -> [VarIndex] Source #

get variable names in a functions rule

rnmAllVarsInRule :: Update Rule VarIndex Source #

rename all variables in rule

updQNamesInRule :: Update Rule QName Source #

update all qualified names in 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?

varNr :: Expr -> VarIndex Source #

get internal number of variable

literal :: Expr -> Literal Source #

get literal if expression is literal expression

combType :: Expr -> CombType Source #

get combination type of a combined expression

combName :: Expr -> QName Source #

get name of a combined expression

combArgs :: Expr -> [Expr] Source #

get arguments of a combined expression

missingCombArgs :: Expr -> Int Source #

get number of missing arguments if expression is combined

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

get indices of varoables in let declaration

letBody :: Expr -> Expr Source #

get body of let declaration

freeVars :: Expr -> [VarIndex] Source #

get variable indices from declaration of free variables

freeExpr :: Expr -> Expr Source #

get expression from declaration of free variables

orExps :: Expr -> [Expr] Source #

get expressions from or-expression

caseType :: Expr -> CaseType Source #

get case-type of case expression

caseExpr :: Expr -> Expr Source #

get scrutinee of case expression

caseBranches :: Expr -> [BranchExpr] Source #

get branch expressions from case expression

isVar :: Expr -> Bool Source #

is expression a variable?

isLit :: Expr -> Bool Source #

is expression a literal expression?

isComb :: Expr -> Bool Source #

is expression combined?

isLet :: Expr -> Bool Source #

is expression a let expression?

isFree :: Expr -> Bool Source #

is expression a declaration of free variables?

isOr :: Expr -> Bool Source #

is expression an or-expression?

isCase :: Expr -> Bool Source #

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

updVars :: (VarIndex -> Expr) -> Expr -> Expr Source #

update all variables in given expression

updLiterals :: (Literal -> Expr) -> Expr -> Expr Source #

update all literals in given 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?

isGround :: Expr -> Bool Source #

is expression fully evaluated?

allVars :: Expr -> [VarIndex] Source #

get all variables (also pattern variables) in expression

rnmAllVars :: Update Expr VarIndex Source #

rename all variables (also in patterns) in expression

updQNames :: Update Expr QName Source #

update all qualified names in expression

trBranch :: (Pattern -> Expr -> a) -> BranchExpr -> a Source #

transform branch expression

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

trPattern :: (QName -> [VarIndex] -> a) -> (Literal -> a) -> Pattern -> a Source #

transform pattern

patCons :: Pattern -> QName Source #

get name from constructor pattern

patArgs :: Pattern -> [VarIndex] Source #

get arguments from constructor pattern

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

updPatCons :: (QName -> QName) -> Pattern -> Pattern Source #

update constructors name of pattern

updPatArgs :: ([VarIndex] -> [VarIndex]) -> Pattern -> Pattern Source #

update arguments of constructor pattern

updPatLiteral :: (Literal -> Literal) -> Pattern -> Pattern Source #

update literal of pattern

patExpr :: Pattern -> Expr Source #

build expression from pattern

isPublic :: Visibility -> Bool Source #

Is this a public Visibility?