hint-0.2.4.1: Runtime Haskell interpreter (GHC API wrapper)Source codeContentsIndex
Language.Haskell.Interpreter.GHC
Portabilitynon-portable (GHC API)
Stabilityexperimental
Maintainerjcpetruzza@gmail.com
Contents
Session handling
Error handling
The interpreter type
Running the interpreter
Interpreter options
Context handling
Module querying
Type inference
Evaluation
Description
A Haskell interpreter built on top of the GHC API
Synopsis
data InterpreterSession
newSession :: IO InterpreterSession
newSessionUsing :: FilePath -> IO InterpreterSession
data InterpreterError
= UnknownError String
| WontCompile [GhcError]
| NotAllowed String
| GhcException GhcException
data GhcError = GhcError {
errMsg :: String
}
data Interpreter a
withSession :: InterpreterSession -> Interpreter a -> IO a
setUseLanguageExtensions :: Bool -> Interpreter ()
data Optimizations
= None
| Some
| All
setOptimizations :: Optimizations -> Interpreter ()
setInstalledModsAreInScopeQualified :: Bool -> Interpreter ()
type ModuleName = String
loadModules :: [String] -> Interpreter ()
getLoadedModules :: Interpreter [ModuleName]
setTopLevelModules :: [ModuleName] -> Interpreter ()
setImports :: [ModuleName] -> Interpreter ()
reset :: Interpreter ()
data ModuleElem
= Fun Id
| Class Id [Id]
| Data Id [Id]
type Id = String
name :: ModuleElem -> Id
children :: ModuleElem -> [Id]
getModuleExports :: ModuleName -> Interpreter [ModuleElem]
typeOf :: String -> Interpreter String
typeChecks :: String -> Interpreter Bool
kindOf :: String -> Interpreter String
interpret :: Typeable a => String -> a -> Interpreter a
infer :: Typeable a => a
eval :: String -> Interpreter String
Session handling
data InterpreterSession Source
newSession :: IO InterpreterSessionSource
Builds a new session using the (hopefully) correct path to the GHC in use. (the path is determined at build time of the package)
newSessionUsing :: FilePath -> IO InterpreterSessionSource
Builds a new session, given the path to a GHC installation (e.g. /usr/local/lib/ghc-6.6).
Error handling
data InterpreterError Source
Constructors
UnknownError String
WontCompile [GhcError]
NotAllowed String
GhcException GhcExceptionGhcExceptions from the underlying GHC API are caught and rethrown as this.
show/hide Instances
data GhcError Source
Constructors
GhcError
errMsg :: String
show/hide Instances
The interpreter type
data Interpreter a Source
show/hide Instances
Running the interpreter
withSession :: InterpreterSession -> Interpreter a -> IO aSource

Executes the interpreter using a given session. This is a thread-safe operation, if the InterpreterSession is in-use, the call will block until the other one finishes.

In case of error, it will throw a dynamic InterpreterError exception.

Interpreter options
setUseLanguageExtensions :: Bool -> Interpreter ()Source
Set to true to allow GHC's extensions to Haskell 98.
data Optimizations Source
Constructors
None
Some
All
show/hide Instances
setOptimizations :: Optimizations -> Interpreter ()Source
Set the optimization level (none, some, all)
setInstalledModsAreInScopeQualified :: Bool -> Interpreter ()Source

When set to True, every module in every available package is implicitly imported qualified. This is very convenient for interactive evaluation, but can be a problem in sandboxed environments (e.g. System.Unsafe.unsafePerformIO is in scope').

Default value is True.

Observe that due to limitations in the GHC-API, when set to False, the private symbols in interpreted modules will not be in scope.

Context handling
type ModuleName = StringSource
Module names are _not_ filepaths.
loadModules :: [String] -> Interpreter ()Source

Tries to load all the requested modules from their source file. Modules my be indicated by their ModuleName (e.g. "My.Module") or by the full path to its source file.

The interpreter is reset both before loading the modules and in the event of an error.

getLoadedModules :: Interpreter [ModuleName]Source
Returns the list of modules loaded with loadModules.
setTopLevelModules :: [ModuleName] -> Interpreter ()Source

Sets the modules whose context is used during evaluation. All bindings of these modules are in scope, not only those exported.

Modules must be interpreted to use this function.

setImports :: [ModuleName] -> Interpreter ()Source
Sets the modules whose exports must be in context.
reset :: Interpreter ()Source
All imported modules are cleared from the context, and loaded modules are unloaded. It is similar to a :load in GHCi, but observe that not even the Prelude will be in context after a reset.
Module querying
data ModuleElem Source
Constructors
Fun Id
Class Id [Id]
Data Id [Id]
show/hide Instances
type Id = StringSource
An Id for a class, a type constructor, a data constructor, a binding, etc
name :: ModuleElem -> IdSource
children :: ModuleElem -> [Id]Source
getModuleExports :: ModuleName -> Interpreter [ModuleElem]Source
Gets an abstract representation of all the entities exported by the module. It is similar to the :browse command in GHCi.
Type inference
typeOf :: String -> Interpreter StringSource
Returns a string representation of the type of the expression.
typeChecks :: String -> Interpreter BoolSource
Tests if the expression type checks.
kindOf :: String -> Interpreter StringSource
Returns a string representation of the kind of the type expression.
Evaluation
interpret :: Typeable a => String -> a -> Interpreter aSource
Evaluates an expression, given a witness for its monomorphic type.
infer :: Typeable a => aSource

Convenience functions to be used with interpret to provide witnesses. Example:

  • interpret "head [True,False]" (as :: Bool)
  • interpret "head $ map show [True,False]" infer >>= flip interpret (as :: Bool)
eval :: String -> Interpreter StringSource
eval expr will evaluate show expr. It will succeed only if expr has type t and there is a Show instance for t.
Produced by Haddock version 2.3.0