Portability | non-portable (GHC API) |
---|---|
Stability | experimental |
Maintainer | jcpetruzza@gmail.com |
Safe Haskell | None |
A Haskell interpreter built on top of the GHC API
- class (MonadIO m, MonadCatch 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 :: (MonadIO m, MonadCatch 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
- | DoRec
- | RecursiveDo
- | ParallelListComp
- | MultiParamTypeClasses
- | NoMonomorphismRestriction
- | FunctionalDependencies
- | Rank2Types
- | RankNTypes
- | PolymorphicComponents
- | ExistentialQuantification
- | ScopedTypeVariables
- | ImplicitParams
- | FlexibleContexts
- | FlexibleInstances
- | EmptyDataDecls
- | CPP
- | KindSignatures
- | BangPatterns
- | TypeSynonymInstances
- | TemplateHaskell
- | ForeignFunctionInterface
- | Arrows
- | Generics
- | NoImplicitPrelude
- | NamedFieldPuns
- | PatternGuards
- | GeneralizedNewtypeDeriving
- | ExtensibleRecords
- | RestrictedTypeSynonyms
- | HereDocuments
- | MagicHash
- | TypeFamilies
- | StandaloneDeriving
- | UnicodeSyntax
- | PatternSignatures
- | UnliftedFFITypes
- | LiberalTypeSynonyms
- | TypeOperators
- | RecordWildCards
- | RecordPuns
- | DisambiguateRecordFields
- | OverloadedStrings
- | GADTs
- | NoMonoPatBinds
- | RelaxedPolyRec
- | ExtendedDefaultRules
- | UnboxedTuples
- | DeriveDataTypeable
- | ConstrainedClassMethods
- | PackageImports
- | ImpredicativeTypes
- | NewQualifiedOperators
- | PostfixOperators
- | QuasiQuotes
- | TransformListComp
- | ViewPatterns
- | XmlSyntax
- | RegularPatterns
- | TupleSections
- | GHCForeignImportPrim
- | NPlusKPatterns
- | DoAndIfThenElse
- | RebindableSyntax
- | ExplicitForAll
- | DatatypeContexts
- | MonoLocalBinds
- | DeriveFunctor
- | DeriveTraversable
- | DeriveFoldable
- | UnknownExtension String
- installedModulesInScope :: MonadInterpreter m => Option m Bool
- searchPath :: MonadInterpreter m => Option m [FilePath]
- setUseLanguageExtensions :: MonadInterpreter m => Bool -> m ()
- setInstalledModsAreInScopeQualified :: MonadInterpreter m => Bool -> m ()
- type ModuleName = String
- isModuleInterpreted :: MonadInterpreter m => ModuleName -> m Bool
- 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
- type Id = String
- name :: ModuleElem -> Id
- children :: ModuleElem -> [Id]
- getModuleExports :: MonadInterpreter m => ModuleName -> m [ModuleElem]
- getModuleAnnotations :: (Data a, MonadInterpreter m) => a -> String -> m [a]
- getValAnnotations :: (Data a, MonadInterpreter m) => a -> String -> m [a]
- 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
- newtype GhcError = GhcError {}
- data MultipleInstancesNotAllowed = MultipleInstancesNotAllowed
- ghcVersion :: Int
- parens :: String -> String
- module Control.Monad.Trans
The interpreter monad transformer
class (MonadIO m, MonadCatch m) => MonadInterpreter m whereSource
fromSession :: FromSession m aSource
modifySessionRef :: ModifySessionRef m aSource
(MonadIO m, MonadCatch m, Functor m) => MonadInterpreter (InterpreterT m) |
data InterpreterT m a Source
MonadTrans InterpreterT | |
Monad m => Monad (InterpreterT m) | |
Functor m => Functor (InterpreterT m) | |
(Monad m, Applicative m) => Applicative (InterpreterT m) | |
MonadCatch m => MonadThrow (InterpreterT m) | |
(MonadCatch m, MonadIO m) => MonadCatch (InterpreterT m) | |
MonadIO m => MonadIO (InterpreterT m) | |
(MonadIO m, MonadCatch m, Functor m) => MonadInterpreter (InterpreterT m) |
type Interpreter = InterpreterT IOSource
Running the interpreter
runInterpreter :: (MonadIO m, MonadCatch m, Functor m) => InterpreterT m a -> m (Either InterpreterError a)Source
Executes the interpreter. Returns Left InterpreterError
in case of error.
NB. The underlying ghc will overwrite certain signal handlers (SIGINT, SIGHUP, SIGTERM, SIGQUIT on Posix systems, Ctrl-C handler on Windows). In future versions of hint, this might be controlled by the user.
Interpreter options
Available options are:
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
Deprecated: glasgowExtensions list is no longer maintained, will be removed soon
List of extensions turned on when the -fglasgow-exts
flag is used
This represents language extensions beyond Haskell 98
that are supported by GHC (it was taken from
Cabal's Language.Haskell.Extension
)
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. 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.
searchPath :: MonadInterpreter m => Option m [FilePath]Source
The search path for source files. Observe that every time it is set,
it overrides the previous search path. The default is ["."]
.
Keep in mind that by a limitation in ghc, "."
is always in scope.
setUseLanguageExtensions :: MonadInterpreter m => Bool -> m ()Source
Deprecated: Use set [languageExtensions := (ExtendedDefaultRules:glasgowExtensions)] instead.
setInstalledModsAreInScopeQualified :: MonadInterpreter m => Bool -> m ()Source
Deprecated: Use set [installedModulesInScope := b] instead.
Context handling
type ModuleName = StringSource
Module names are _not_ filepaths.
isModuleInterpreted :: MonadInterpreter m => ModuleName -> m BoolSource
Returns True if the module was interpreted.
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
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
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.
Anotations
Please note below that annotations are an experimental feature in GHC HEAD. In the snippets below we use 'LBRACE' and 'RBRACE' to mean '{' and '}' respectively. We cannot put the pragmas inline in the code since GHC scarfs them up.
getModuleAnnotations :: (Data a, MonadInterpreter m) => a -> String -> m [a]Source
Get the annotations associated with a particular module.
For example, given:
RBRACE-# ANN module (1 :: Int) #-LBRACE module SomeModule(g, h) where ...
Then after using loadModule
to load SomeModule into scope:
x <- getModuleAnnotations (as :: Int) SomeModule liftIO $ print x -- result is [1]
getValAnnotations :: (Data a, MonadInterpreter m) => a -> String -> m [a]Source
Get the annotations associated with a particular function
For example, given:
module SomeModule(g, h) where LBRACE-# ANN g (Just 1 :: Maybe Int) #-RBRACE g = f [f] LBRACE-# ANN h (Just 2 :: Maybe Int) #-RBRACE h = f
Then after using loadModule
to bring SomeModule into scope:
x <- liftM concat $ mapM (getValAnnotations (as :: Maybe Int)) ["g","h"] liftIO $ print x -- result is [Just 2, Just 1]
This can also work on data constructors and types with annotations.
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.
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)
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
UnknownError String | |
WontCompile [GhcError] | |
NotAllowed String | |
GhcException String | GhcExceptions from the underlying GHC API are caught and rethrown as this. |
data MultipleInstancesNotAllowed Source
The installed version of ghc is not thread-safe. This exception
is thrown whenever you try to execute runInterpreter
while another
instance is already running.
Miscellaneous
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...
parens :: String -> StringSource
Conceptually, parens s = "(" ++ s ++ ")"
, where s is any valid haskell
expression. In practice, it is harder than this.
Observe that if s
ends with a trailing comment, then parens s
would
be a malformed expression. The straightforward solution for this is to
put the closing parenthesis in a different line. However, now we are
messing with the layout rules and we don't know where s
is going to
be used!
Solution: parens s = "(let {foo =n" ++ s ++ "\n ;} in foo)"
where foo
does not occur in s
module Control.Monad.Trans