hint-0.4.2.3: Runtime Haskell interpreter (GHC API wrapper)

LicenseBSD-style
Maintainerjcpetruzza@gmail.com
Stabilityexperimental
Portabilitynon-portable (GHC API)
Safe HaskellNone
LanguageHaskell98

Language.Haskell.Interpreter

Contents

Description

A Haskell interpreter built on top of the GHC API

Synopsis

The interpreter monad transformer

class (MonadIO m, MonadMask m) => MonadInterpreter m where

Methods

fromSession :: FromSession m a

modifySessionRef :: ModifySessionRef m a

runGhc :: RunGhc m a

Running the interpreter

runInterpreter :: (MonadIO m, MonadMask m, Functor m) => InterpreterT m a -> m (Either InterpreterError a)

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

data OptionVal m

Constructors

forall a . (Option m a) := a 

get :: MonadInterpreter m => Option m a -> m a

Retrieves the value of an option.

set :: MonadInterpreter m => [OptionVal m] -> m ()

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]

Language extensions in use by the interpreter.

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

availableExtensions :: [Extension]

List of the extensions known by the interpreter.

glasgowExtensions :: [Extension]

Deprecated: glasgowExtensions list is no longer maintained, will be removed soon

List of extensions turned on when the -fglasgow-exts flag is used

data Extension

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 Bool

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]

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 ()

Deprecated: Use set [languageExtensions := (ExtendedDefaultRules:glasgowExtensions)] instead.

setInstalledModsAreInScopeQualified :: MonadInterpreter m => Bool -> m ()

Deprecated: Use set [installedModulesInScope := b] instead.

Context handling

type ModuleName = String

Module names are _not_ filepaths.

isModuleInterpreted :: MonadInterpreter m => ModuleName -> m Bool

Returns True if the module was interpreted.

loadModules :: MonadInterpreter m => [String] -> m ()

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.

IMPORTANT: Like in a ghci session, this will also load (and interpret) any dependency that is not available via an installed package. Make sure that you are not loading any module that is also being used to compile your application. In particular, you need to avoid modules that define types that will later occur in an expression that you will want to interpret.

The problem in doing this is that those types will have two incompatible representations at runtime: 1) the one in the compiled code and 2) the one in the interpreted code. When interpreting such an expression (bringing it to program-code) you will likely get a segmentation fault, since the latter representation will be used where the program assumes the former.

The rule of thumb is: never make the interpreter run on the directory with the source code of your program! If you want your interpreted code to use some type that is defined in your program, then put the defining module on a library and make your program depend on that package.

getLoadedModules :: MonadInterpreter m => m [ModuleName]

Returns the list of modules loaded with loadModules.

setTopLevelModules :: MonadInterpreter m => [ModuleName] -> m ()

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 ()

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 ()

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

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

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

reset :: MonadInterpreter m => m ()

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

Constructors

Fun Id 
Class Id [Id] 
Data Id [Id] 

type Id = String

An Id for a class, a type constructor, a data constructor, a binding, etc

getModuleExports :: MonadInterpreter m => ModuleName -> m [ModuleElem]

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]

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]

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 String

Returns a string representation of the type of the expression.

typeChecks :: MonadInterpreter m => String -> m Bool

Tests if the expression type checks.

kindOf :: MonadInterpreter m => String -> m String

Returns a string representation of the kind of the type expression.

Evaluation

interpret :: (MonadInterpreter m, Typeable a) => String -> a -> m a

Evaluates an expression, given a witness for its monomorphic type.

as :: Typeable a => a

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 => a

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 String

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

Constructors

UnknownError String 
WontCompile [GhcError] 
NotAllowed String 
GhcException String

GhcExceptions from the underlying GHC API are caught and rethrown as this.

newtype GhcError

Constructors

GhcError 

Fields

errMsg :: String
 

Instances

data MultipleInstancesNotAllowed

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

ghcVersion :: Int

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 -> String

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