hint-0.3.0.0: Runtime Haskell interpreter (GHC API wrapper)Source codeContentsIndex
Language.Haskell.Interpreter
Portabilitynon-portable (GHC API)
Stabilityexperimental
Maintainerjcpetruzza@gmail.com
Contents
The interpreter monad transformer
Running the interpreter
Interpreter options
Context handling
Module querying
Type inference
Evaluation
Error handling
Miscellaneous
Description
A Haskell interpreter built on top of the GHC API
Synopsis
class (MonadCatchIO m, MonadError InterpreterError m) => MonadInterpreter m where
fromSession :: FromSession m a
modifySessionRef :: ModifySessionRef m a
runGhc :: RunGhc m a
data InterpreterT m a
type Interpreter = InterpreterT IO
runInterpreter :: (MonadCatchIO m, Functor m) => InterpreterT m a -> m (Either InterpreterError a)
data Option m a
data OptionVal m = forall a . (Option m a) := a
get :: MonadInterpreter m => Option m a -> m a
set :: MonadInterpreter m => [OptionVal m] -> m ()
languageExtensions :: MonadInterpreter m => Option m [Extension]
availableExtensions :: [Extension]
glasgowExtensions :: [Extension]
data Extension
= OverlappingInstances
| UndecidableInstances
| IncoherentInstances
| RecursiveDo
| ParallelListComp
| MultiParamTypeClasses
| NoMonomorphismRestriction
| FunctionalDependencies
| Rank2Types
| RankNTypes
| PolymorphicComponents
| ExistentialQuantification
| ScopedTypeVariables
| PatternSignatures
| ImplicitParams
| FlexibleContexts
| FlexibleInstances
| EmptyDataDecls
| CPP
| KindSignatures
| BangPatterns
| TypeSynonymInstances
| TemplateHaskell
| ForeignFunctionInterface
| Arrows
| Generics
| NoImplicitPrelude
| NamedFieldPuns
| PatternGuards
| GeneralizedNewtypeDeriving
| ExtensibleRecords
| RestrictedTypeSynonyms
| HereDocuments
| MagicHash
| TypeFamilies
| StandaloneDeriving
| UnicodeSyntax
| UnliftedFFITypes
| LiberalTypeSynonyms
| TypeOperators
| RecordWildCards
| RecordPuns
| DisambiguateRecordFields
| OverloadedStrings
| GADTs
| NoMonoPatBinds
| RelaxedPolyRec
| ExtendedDefaultRules
| UnboxedTuples
| DeriveDataTypeable
| ConstrainedClassMethods
| PackageImports
| ImpredicativeTypes
| NewQualifiedOperators
| PostfixOperators
| QuasiQuotes
| TransformListComp
| ViewPatterns
| XmlSyntax
| RegularPatterns
| UnknownExtension String
installedModulesInScope :: MonadInterpreter m => Option m Bool
setUseLanguageExtensions :: MonadInterpreter m => Bool -> m ()
setInstalledModsAreInScopeQualified :: MonadInterpreter m => Bool -> m ()
type ModuleName = String
loadModules :: MonadInterpreter m => [String] -> m ()
getLoadedModules :: MonadInterpreter m => m [ModuleName]
setTopLevelModules :: MonadInterpreter m => [ModuleName] -> m ()
setImports :: MonadInterpreter m => [ModuleName] -> m ()
setImportsQ :: MonadInterpreter m => [(ModuleName, Maybe String)] -> m ()
reset :: MonadInterpreter m => m ()
data ModuleElem
= Fun Id
| Class Id [Id]
| Data Id [Id]
type Id = String
name :: ModuleElem -> Id
children :: ModuleElem -> [Id]
getModuleExports :: MonadInterpreter m => ModuleName -> m [ModuleElem]
typeOf :: MonadInterpreter m => String -> m String
typeChecks :: MonadInterpreter m => String -> m Bool
kindOf :: MonadInterpreter m => String -> m String
interpret :: (MonadInterpreter m, Typeable a) => String -> a -> m a
as :: Typeable a => a
infer :: Typeable a => a
eval :: MonadInterpreter m => String -> m String
data InterpreterError
= UnknownError String
| WontCompile [GhcError]
| NotAllowed String
| GhcException String
newtype GhcError = GhcError {
errMsg :: String
}
ghcVersion :: Int
module Control.Monad.Trans
The interpreter monad transformer
class (MonadCatchIO m, MonadError InterpreterError m) => MonadInterpreter m whereSource
Methods
fromSession :: FromSession m aSource
modifySessionRef :: ModifySessionRef m aSource
runGhc :: RunGhc m aSource
show/hide Instances
data InterpreterT m a Source
show/hide Instances
type Interpreter = InterpreterT IOSource
Running the interpreter
runInterpreter :: (MonadCatchIO m, Functor m) => InterpreterT m a -> m (Either InterpreterError a)Source
Executes the interpreter. Returns Left InterpreterError in case of error.
Interpreter options
data Option m a Source

Available options are:

data OptionVal m Source
Constructors
forall a . (Option m a) := a
get :: MonadInterpreter m => Option m a -> m aSource
Retrieves the value of an option.
set :: MonadInterpreter m => [OptionVal m] -> m ()Source

Use this function to set or modify the value of any option. It is invoked like this:

set [opt1 := val1, opt2 := val2,... optk := valk]
languageExtensions :: MonadInterpreter m => Option m [Extension]Source

Language extensions in use by the interpreter.

Default is: [] (i.e. none, pure Haskell 98)

availableExtensions :: [Extension]Source
List of the extensions known by the interpreter.
glasgowExtensions :: [Extension]Source
List of extensions turned on when the -fglasgow-exts flag is used
data Extension Source
This represents language extensions beyond Haskell 98 that are supported by some implementations, usually in some special mode.
Constructors
OverlappingInstances
UndecidableInstances
IncoherentInstances
RecursiveDo
ParallelListComp
MultiParamTypeClasses
NoMonomorphismRestriction
FunctionalDependencies
Rank2Types
RankNTypes
PolymorphicComponents
ExistentialQuantification
ScopedTypeVariables
PatternSignaturesDeprecated, use ScopedTypeVariables instead.
ImplicitParams
FlexibleContexts
FlexibleInstances
EmptyDataDecls
CPP
KindSignatures
BangPatterns
TypeSynonymInstances
TemplateHaskell
ForeignFunctionInterface
Arrows
Generics
NoImplicitPrelude
NamedFieldPuns
PatternGuards
GeneralizedNewtypeDeriving
ExtensibleRecords
RestrictedTypeSynonyms
HereDocuments
MagicHash
TypeFamilies
StandaloneDeriving
UnicodeSyntax
UnliftedFFITypes
LiberalTypeSynonyms
TypeOperators
RecordWildCards
RecordPuns
DisambiguateRecordFields
OverloadedStrings
GADTs
NoMonoPatBinds
RelaxedPolyRec
ExtendedDefaultRules
UnboxedTuples
DeriveDataTypeable
ConstrainedClassMethods
PackageImports

Allow imports to be qualified by the package name that the module is intended to be imported from, e.g.

import "network" Network.Socket
ImpredicativeTypes
NewQualifiedOperators
PostfixOperators
QuasiQuotes
TransformListComp
ViewPatterns
XmlSyntaxAllow concrete XML syntax to be used in expressions and patterns, as per the Haskell Server Pages extension language: http://www.haskell.org/haskellwiki/HSP. The ideas behind it are discussed in the paper Haskell Server Pages through Dynamic Loading by Niklas Broberg, from Haskell Workshop '05.
RegularPatternsAllow regular pattern matching over lists, as discussed in the paper Regular Expression Patterns by Niklas Broberg, Andreas Farre and Josef Svenningsson, from ICFP '04.
UnknownExtension String
show/hide Instances
installedModulesInScope :: MonadInterpreter m => Option m BoolSource

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.

setUseLanguageExtensions :: MonadInterpreter m => Bool -> m ()Source
setInstalledModsAreInScopeQualified :: MonadInterpreter m => Bool -> m ()Source
Context handling
type ModuleName = StringSource
Module names are _not_ filepaths.
loadModules :: MonadInterpreter m => [String] -> m ()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 :: MonadInterpreter m => m [ModuleName]Source
Returns the list of modules loaded with loadModules.
setTopLevelModules :: MonadInterpreter m => [ModuleName] -> m ()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 :: MonadInterpreter m => [ModuleName] -> m ()Source

Sets the modules whose exports must be in context.

Warning: setImports and setImportsQ are mutually exclusive. If you have a list of modules to be used qualified and another list unqualified, then you need to do something like

  setImportsQ ((zip unqualified $ repeat Nothing) ++ qualifieds)
setImportsQ :: MonadInterpreter m => [(ModuleName, Maybe String)] -> m ()Source

Sets the modules whose exports must be in context; some of them may be qualified. E.g.:

setImports [(Prelude, Nothing), (Data.Map, Just M)].

Here, map will refer to Prelude.map and M.map to Data.Map.map.

reset :: MonadInterpreter m => m ()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 :: MonadInterpreter m => ModuleName -> m [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 :: MonadInterpreter m => String -> m StringSource
Returns a string representation of the type of the expression.
typeChecks :: MonadInterpreter m => String -> m BoolSource
Tests if the expression type checks.
kindOf :: MonadInterpreter m => String -> m StringSource
Returns a string representation of the kind of the type expression.
Evaluation
interpret :: (MonadInterpreter m, Typeable a) => String -> a -> m aSource
Evaluates an expression, given a witness for its monomorphic type.
as :: Typeable a => aSource
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 :: MonadInterpreter m => String -> m StringSource
eval expr will evaluate show expr. It will succeed only if expr has type t and there is a Show instance for t.
Error handling
data InterpreterError Source
Constructors
UnknownError String
WontCompile [GhcError]
NotAllowed String
GhcException StringGhcExceptions from the underlying GHC API are caught and rethrown as this.
show/hide Instances
newtype GhcError Source
Constructors
GhcError
errMsg :: String
show/hide Instances
Miscellaneous
ghcVersion :: IntSource

Version of the underlying ghc api. Values are:

  • 606 for GHC 6.6.x
  • 608 for GHC 6.8.x
  • 610 for GHC 6.10.x
  • etc...
module Control.Monad.Trans
Produced by Haddock version 2.6.0