Safe Haskell | Safe-Infered |
---|
- egisonVersion :: String
- showBanner :: IO ()
- showByebyeMessage :: IO ()
- loadLibraries :: Env -> IO ()
- escapeBackslashes :: String -> String
- evalString :: Env -> String -> IO String
- evalMain :: Env -> [String] -> IOThrowsError EgisonVal
- evalTopExpr :: Env -> TopExpr -> IOThrowsError String
- load :: Env -> String -> IOThrowsError ()
- eval :: Env -> EgisonExpr -> IOThrowsError EgisonVal
- iEval :: IntermidiateVal -> IOThrowsError EgisonVal
- innerValRefEval :: InnerValRef -> IOThrowsError InnerVal
- cRefEval :: ObjectRef -> IOThrowsError EgisonVal
- cRefEval1 :: ObjectRef -> IOThrowsError Object
- cEval :: Object -> IOThrowsError EgisonVal
- cEval1 :: Object -> IOThrowsError Object
- cApply1 :: ObjectRef -> ObjectRef -> IOThrowsError Object
- expandLoop :: Env -> Object -> IOThrowsError Object
- extendLet :: Env -> [(Args, EgisonExpr)] -> IOThrowsError Env
- makeFrame :: Args -> ObjectRef -> IOThrowsError [(Var, ObjectRef)]
- innerValRefsToObjRefList :: [InnerValRef] -> IOThrowsError [ObjectRef]
- patternMatch :: MatchFlag -> [MState] -> IOThrowsError [FrameList]
- inductiveMatch :: DestructInfo -> String -> ObjectRef -> IOThrowsError (ObjectRef, ObjectRef)
- primitivePatternMatch :: PrimitivePattern -> ObjectRef -> IOThrowsError (Maybe FrameList)
- primitivePatternMatchList :: [PrimitivePattern] -> [ObjectRef] -> IOThrowsError (Maybe FrameList)
- isEmptyCollection :: ObjectRef -> IOThrowsError Bool
- isEmptyInnerRefs :: [InnerValRef] -> IOThrowsError Bool
- isEmptyInnerVals :: [InnerVal] -> IOThrowsError Bool
- isEmptyCollectionForSnoc :: ObjectRef -> IOThrowsError Bool
- isEmptyInnerRefsForSnoc :: [InnerValRef] -> IOThrowsError Bool
- isEmptyInnerValsForSnoc :: [InnerVal] -> IOThrowsError Bool
- consDestruct :: ObjectRef -> IOThrowsError (ObjectRef, ObjectRef)
- consDestructInnerRefs :: [InnerValRef] -> IOThrowsError (ObjectRef, ObjectRef)
- consDestructInnerVals :: [InnerVal] -> IOThrowsError (ObjectRef, ObjectRef)
- snocDestruct :: ObjectRef -> IOThrowsError (ObjectRef, ObjectRef)
- snocDestructInnerRefs :: [InnerValRef] -> IOThrowsError (ObjectRef, ObjectRef)
- snocDestructInnerVals :: [InnerVal] -> IOThrowsError (ObjectRef, ObjectRef)
- collectionToObjRefList :: ObjectRef -> IOThrowsError [ObjectRef]
- tupleToObjRefList :: ObjectRef -> IOThrowsError [ObjectRef]
- innerRefsToObjRefList :: [InnerValRef] -> IOThrowsError [ObjectRef]
- innerValsToObjRefList :: [InnerVal] -> IOThrowsError [ObjectRef]
- primitiveBindings :: IO Env
- constants :: [(String, EgisonVal)]
- ioPrimitives :: [(String, [EgisonVal] -> IOThrowsError EgisonVal)]
- primitives :: [(String, [EgisonVal] -> ThrowsError EgisonVal)]
Documentation
showBanner :: IO ()Source
A utility function to display the egison console banner
showByebyeMessage :: IO ()Source
A utility function to display the egison console byebye message
loadLibraries :: Env -> IO ()Source
Load standard libraries into the given environment
escapeBackslashes :: String -> StringSource
A utility function to escape backslashes in the given string
evalTopExpr :: Env -> TopExpr -> IOThrowsError StringSource
Evaluate egison top expression that has already been loaded into haskell
eval :: Env -> EgisonExpr -> IOThrowsError EgisonValSource
Evaluate egison expression that has already been loaded into haskell
expandLoop :: Env -> Object -> IOThrowsError ObjectSource
:: Env | Environment |
-> [(Args, EgisonExpr)] | Extensions to the environment |
-> IOThrowsError Env | Extended environment |
Extend given environment by binding a series of values to a new environment for let.
patternMatch :: MatchFlag -> [MState] -> IOThrowsError [FrameList]Source
inductiveMatch :: DestructInfo -> String -> ObjectRef -> IOThrowsError (ObjectRef, ObjectRef)Source
primitivePatternMatchList :: [PrimitivePattern] -> [ObjectRef] -> IOThrowsError (Maybe FrameList)Source
ioPrimitives :: [(String, [EgisonVal] -> IOThrowsError EgisonVal)]Source
primitives :: [(String, [EgisonVal] -> ThrowsError EgisonVal)]Source