Safe Haskell | None |
---|---|
Language | Haskell98 |
Synopsis
- mkVar :: Maybe String -> Int -> Type -> Var
- freshName :: Int -> String
- goalType :: Type -> Type -> Bool
- createSubgoals :: Type -> [Type]
- subgoals :: Type -> Maybe (Type, [Type])
- withSubgoal :: [(Type, CoreExpr, Int)] -> Type -> [(CoreExpr, Int)]
- unifyWith :: Type -> [Type]
- fromAnf :: CoreExpr -> CoreExpr
- fromAnf' :: CoreExpr -> [(Var, CoreExpr)] -> (CoreExpr, [(Var, CoreExpr)])
- coreToHs :: SpecType -> Var -> CoreExpr -> String
- symbols :: String
- pprintSymbols :: String -> String
- pprintSym :: String -> Char -> String
- discardModName :: Var -> String
- rmModName :: String -> String
- maintainLParen :: [String] -> String
- maintainRParen :: [String] -> String
- pprintFormals :: Int -> Var -> CoreExpr -> Int -> [Var] -> String
- caseIndent :: Int
- indent :: Int -> String
- errorExprPp :: CoreExpr -> Bool
- pprintVar :: Var -> String
- pprintBody :: [Var] -> Int -> CoreExpr -> String
- fixApplication :: String -> String
- handleCommas :: [String] -> [String]
- fixCommas :: [String] -> [String]
- fixParen :: [String] -> [String]
- rmTypeAppl :: [String] -> [String]
- paren :: String -> String
- replaceNewLine :: String -> String
- pprintAlts :: [Var] -> Int -> Alt Var -> String
- countTcConstraints :: SpecType -> Int
- nonTrivial :: CoreExpr -> Bool
- nonTrivials :: [CoreExpr] -> Bool
- trivial :: CoreExpr -> Bool
- hasTrivial :: [CoreExpr] -> Bool
- allTrivial :: [[CoreExpr]] -> Bool
- rmTrivials :: [(CoreExpr, Int)] -> [(CoreExpr, Int)]
- isVar :: CoreExpr -> Bool
- returnsTuple :: Var -> Bool
- type SSEnv = HashMap Symbol (SpecType, Var)
- filterREnv :: HashMap Symbol SpecType -> HashMap Symbol SpecType
- getTopLvlBndrs :: CoreProgram -> [Var]
- getUniVars :: CoreProgram -> Var -> ([Var], [Var])
- getUniVars0 :: CoreExpr -> ([Var], [Var]) -> ([Var], [Var])
- getBody :: CoreBind -> Var -> CoreExpr
- varsP :: CoreProgram -> Var -> (CoreExpr -> [Var]) -> [Var]
- isInCB :: CoreBind -> Var -> Bool
- varsCB :: CoreBind -> (CoreExpr -> [Var]) -> [Var]
- varsE :: CoreExpr -> [Var]
- caseVarsE :: CoreExpr -> [Var]
- symbolToVar :: CoreProgram -> Var -> HashMap Symbol SpecType -> SSEnv
- argsP :: CoreProgram -> Var -> [Var]
- argsCB :: CoreBind -> [Var]
- argsE :: CoreExpr -> [Var]
- notrace :: String -> a -> a
Documentation
goalType :: Type -> Type -> Bool #
Assuming that the functions are instantiated when this function is called.
createSubgoals :: Type -> [Type] #
Assuming that goals are type variables or constructors. Note: We maintain ordering from the goal type. Not handled (compared to @varsInType): function types, type applications
fromAnf' :: CoreExpr -> [(Var, CoreExpr)] -> (CoreExpr, [(Var, CoreExpr)]) #
Replace let bindings in applications. > If you find a binding add it to the second argument. | (lhs, rhs) |
coreToHs :: SpecType -> Var -> CoreExpr -> String #
Function used for pretty printing core as Haskell source. Input does not contain let bindings.
pprintSymbols :: String -> String #
discardModName :: Var -> String #
maintainLParen :: [String] -> String #
maintainRParen :: [String] -> String #
caseIndent :: Int #
errorExprPp :: CoreExpr -> Bool #
fixApplication :: String -> String #
handleCommas :: [String] -> [String] #
rmTypeAppl :: [String] -> [String] #
replaceNewLine :: String -> String #
countTcConstraints :: SpecType -> Int #
nonTrivial :: CoreExpr -> Bool #
nonTrivials :: [CoreExpr] -> Bool #
hasTrivial :: [CoreExpr] -> Bool #
allTrivial :: [[CoreExpr]] -> Bool #
returnsTuple :: Var -> Bool #
filterREnv :: HashMap Symbol SpecType -> HashMap Symbol SpecType #
getTopLvlBndrs :: CoreProgram -> [Var] #
getUniVars :: CoreProgram -> Var -> ([Var], [Var]) #
That' s a hack to get the type variables we need for instantiation.
symbolToVar :: CoreProgram -> Var -> HashMap Symbol SpecType -> SSEnv #
argsP :: CoreProgram -> Var -> [Var] #