hint-0.9.0.3: Runtime Haskell interpreter (GHC API wrapper)
LicenseBSD-style
Maintainermvdan@mvdan.cc
Stabilityexperimental
Portabilitynon-portable (GHC API)
Safe HaskellNone
LanguageHaskell98

Language.Haskell.Interpreter

Description

A Haskell interpreter built on top of the GHC API

Synopsis

The interpreter monad transformer

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

Methods

fromSession :: FromSession m a Source #

modifySessionRef :: ModifySessionRef m a Source #

runGhc :: RunGhc m a Source #

Instances

Instances details
(MonadIO m, MonadMask m, Functor m) => MonadInterpreter (InterpreterT m) Source # 
Instance details

Defined in Hint.InterpreterT

Methods

fromSession :: FromSession (InterpreterT m) a Source #

modifySessionRef :: ModifySessionRef (InterpreterT m) a Source #

runGhc :: RunGhc (InterpreterT m) a Source #

data InterpreterT m a Source #

Instances

Instances details
MonadTrans InterpreterT Source # 
Instance details

Defined in Hint.InterpreterT

Methods

lift :: Monad m => m a -> InterpreterT m a #

Monad m => Monad (InterpreterT m) Source # 
Instance details

Defined in Hint.InterpreterT

Methods

(>>=) :: InterpreterT m a -> (a -> InterpreterT m b) -> InterpreterT m b #

(>>) :: InterpreterT m a -> InterpreterT m b -> InterpreterT m b #

return :: a -> InterpreterT m a #

Functor m => Functor (InterpreterT m) Source # 
Instance details

Defined in Hint.InterpreterT

Methods

fmap :: (a -> b) -> InterpreterT m a -> InterpreterT m b #

(<$) :: a -> InterpreterT m b -> InterpreterT m a #

Monad m => Applicative (InterpreterT m) Source # 
Instance details

Defined in Hint.InterpreterT

Methods

pure :: a -> InterpreterT m a #

(<*>) :: InterpreterT m (a -> b) -> InterpreterT m a -> InterpreterT m b #

liftA2 :: (a -> b -> c) -> InterpreterT m a -> InterpreterT m b -> InterpreterT m c #

(*>) :: InterpreterT m a -> InterpreterT m b -> InterpreterT m b #

(<*) :: InterpreterT m a -> InterpreterT m b -> InterpreterT m a #

MonadIO m => MonadIO (InterpreterT m) Source # 
Instance details

Defined in Hint.InterpreterT

Methods

liftIO :: IO a -> InterpreterT m a #

(MonadIO m, MonadMask m) => MonadCatch (InterpreterT m) Source # 
Instance details

Defined in Hint.InterpreterT

Methods

catch :: Exception e => InterpreterT m a -> (e -> InterpreterT m a) -> InterpreterT m a

(MonadIO m, MonadMask m) => MonadMask (InterpreterT m) Source # 
Instance details

Defined in Hint.InterpreterT

Methods

mask :: ((forall a. InterpreterT m a -> InterpreterT m a) -> InterpreterT m b) -> InterpreterT m b

uninterruptibleMask :: ((forall a. InterpreterT m a -> InterpreterT m a) -> InterpreterT m b) -> InterpreterT m b

generalBracket :: InterpreterT m a -> (a -> ExitCase b -> InterpreterT m c) -> (a -> InterpreterT m b) -> InterpreterT m (b, c)

MonadCatch m => MonadThrow (InterpreterT m) Source # 
Instance details

Defined in Hint.InterpreterT

Methods

throwM :: Exception e => e -> InterpreterT m a

(MonadIO m, MonadMask m, Functor m) => MonadInterpreter (InterpreterT m) Source # 
Instance details

Defined in Hint.InterpreterT

Methods

fromSession :: FromSession (InterpreterT m) a Source #

modifySessionRef :: ModifySessionRef (InterpreterT m) a Source #

runGhc :: RunGhc (InterpreterT m) a Source #

Running the interpreter

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

Executes the interpreter. Returns Left InterpreterError in case of error.

NB. In hint-0.7.0 and earlier, the underlying ghc was accidentally overwriting certain signal handlers (SIGINT, SIGHUP, SIGTERM, SIGQUIT on Posix systems, Ctrl-C handler on Windows).

Interpreter options

data OptionVal m Source #

Constructors

forall a. (Option m a) := a 

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

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.

data Extension Source #

This represents language extensions beyond Haskell 98 that are supported by GHC (it was taken from Cabal's Language.Haskell.Extension)

Constructors

OverlappingInstances 
UndecidableInstances 
IncoherentInstances 
DoRec 
RecursiveDo 
ParallelListComp 
MultiParamTypeClasses 
MonomorphismRestriction 
FunctionalDependencies 
Rank2Types 
RankNTypes 
PolymorphicComponents 
ExistentialQuantification 
ScopedTypeVariables 
PatternSignatures 
ImplicitParams 
FlexibleContexts 
FlexibleInstances 
EmptyDataDecls 
CPP 
KindSignatures 
BangPatterns 
TypeSynonymInstances 
TemplateHaskell 
ForeignFunctionInterface 
Arrows 
Generics 
ImplicitPrelude 
NamedFieldPuns 
PatternGuards 
GeneralizedNewtypeDeriving 
ExtensibleRecords 
RestrictedTypeSynonyms 
HereDocuments 
MagicHash 
TypeFamilies 
StandaloneDeriving 
UnicodeSyntax 
UnliftedFFITypes 
InterruptibleFFI 
CApiFFI 
LiberalTypeSynonyms 
TypeOperators 
RecordWildCards 
RecordPuns 
DisambiguateRecordFields 
TraditionalRecordSyntax 
OverloadedStrings 
GADTs 
GADTSyntax 
MonoPatBinds 
RelaxedPolyRec 
ExtendedDefaultRules 
UnboxedTuples 
DeriveDataTypeable 
DeriveGeneric 
DefaultSignatures 
InstanceSigs 
ConstrainedClassMethods 
PackageImports 
ImpredicativeTypes 
NewQualifiedOperators 
PostfixOperators 
QuasiQuotes 
TransformListComp 
MonadComprehensions 
ViewPatterns 
XmlSyntax 
RegularPatterns 
TupleSections 
GHCForeignImportPrim 
NPlusKPatterns 
DoAndIfThenElse 
MultiWayIf 
LambdaCase 
RebindableSyntax 
ExplicitForAll 
DatatypeContexts 
MonoLocalBinds 
DeriveFunctor 
DeriveTraversable 
DeriveFoldable 
NondecreasingIndentation 
SafeImports 
Safe 
Trustworthy 
Unsafe 
ConstraintKinds 
PolyKinds 
DataKinds 
ParallelArrays 
RoleAnnotations 
OverloadedLists 
EmptyCase 
AutoDeriveTypeable 
NegativeLiterals 
BinaryLiterals 
NumDecimals 
NullaryTypeClasses 
ExplicitNamespaces 
AllowAmbiguousTypes 
JavaScriptFFI 
PatternSynonyms 
PartialTypeSignatures 
NamedWildCards 
DeriveAnyClass 
DeriveLift 
StaticPointers 
StrictData 
Strict 
ApplicativeDo 
DuplicateRecordFields 
TypeApplications 
TypeInType 
UndecidableSuperClasses 
MonadFailDesugaring 
TemplateHaskellQuotes 
OverloadedLabels 
TypeFamilyDependencies 
NoOverlappingInstances 
NoUndecidableInstances 
NoIncoherentInstances 
NoDoRec 
NoRecursiveDo 
NoParallelListComp 
NoMultiParamTypeClasses 
NoMonomorphismRestriction 
NoFunctionalDependencies 
NoRank2Types 
NoRankNTypes 
NoPolymorphicComponents 
NoExistentialQuantification 
NoScopedTypeVariables 
NoPatternSignatures 
NoImplicitParams 
NoFlexibleContexts 
NoFlexibleInstances 
NoEmptyDataDecls 
NoCPP 
NoKindSignatures 
NoBangPatterns 
NoTypeSynonymInstances 
NoTemplateHaskell 
NoForeignFunctionInterface 
NoArrows 
NoGenerics 
NoImplicitPrelude 
NoNamedFieldPuns 
NoPatternGuards 
NoGeneralizedNewtypeDeriving 
NoExtensibleRecords 
NoRestrictedTypeSynonyms 
NoHereDocuments 
NoMagicHash 
NoTypeFamilies 
NoStandaloneDeriving 
NoUnicodeSyntax 
NoUnliftedFFITypes 
NoInterruptibleFFI 
NoCApiFFI 
NoLiberalTypeSynonyms 
NoTypeOperators 
NoRecordWildCards 
NoRecordPuns 
NoDisambiguateRecordFields 
NoTraditionalRecordSyntax 
NoOverloadedStrings 
NoGADTs 
NoGADTSyntax 
NoMonoPatBinds 
NoRelaxedPolyRec 
NoExtendedDefaultRules 
NoUnboxedTuples 
NoDeriveDataTypeable 
NoDeriveGeneric 
NoDefaultSignatures 
NoInstanceSigs 
NoConstrainedClassMethods 
NoPackageImports 
NoImpredicativeTypes 
NoNewQualifiedOperators 
NoPostfixOperators 
NoQuasiQuotes 
NoTransformListComp 
NoMonadComprehensions 
NoViewPatterns 
NoXmlSyntax 
NoRegularPatterns 
NoTupleSections 
NoGHCForeignImportPrim 
NoNPlusKPatterns 
NoDoAndIfThenElse 
NoMultiWayIf 
NoLambdaCase 
NoRebindableSyntax 
NoExplicitForAll 
NoDatatypeContexts 
NoMonoLocalBinds 
NoDeriveFunctor 
NoDeriveTraversable 
NoDeriveFoldable 
NoNondecreasingIndentation 
NoSafeImports 
NoSafe 
NoTrustworthy 
NoUnsafe 
NoConstraintKinds 
NoPolyKinds 
NoDataKinds 
NoParallelArrays 
NoRoleAnnotations 
NoOverloadedLists 
NoEmptyCase 
NoAutoDeriveTypeable 
NoNegativeLiterals 
NoBinaryLiterals 
NoNumDecimals 
NoNullaryTypeClasses 
NoExplicitNamespaces 
NoAllowAmbiguousTypes 
NoJavaScriptFFI 
NoPatternSynonyms 
NoPartialTypeSignatures 
NoNamedWildCards 
NoDeriveAnyClass 
NoDeriveLift 
NoStaticPointers 
NoStrictData 
NoStrict 
NoApplicativeDo 
NoDuplicateRecordFields 
NoTypeApplications 
NoTypeInType 
NoUndecidableSuperClasses 
NoMonadFailDesugaring 
NoTemplateHaskellQuotes 
NoOverloadedLabels 
NoTypeFamilyDependencies 
UnknownExtension String 

Instances

Instances details
Eq Extension Source # 
Instance details

Defined in Hint.Extension

Read Extension Source # 
Instance details

Defined in Hint.Extension

Show Extension Source # 
Instance details

Defined in Hint.Extension

installedModulesInScope :: MonadInterpreter m => Option m Bool 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. 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.

Context handling

type ModuleName = String Source #

Module names are _not_ filepaths.

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

Returns True if the module was interpreted.

data ModuleImport Source #

Represent module import statement. See setImportsF

Instances

Instances details
Show ModuleImport Source # 
Instance details

Defined in Hint.Base

data ImportList Source #

Instances

Instances details
Eq ImportList Source # 
Instance details

Defined in Hint.Base

Show ImportList Source # 
Instance details

Defined in Hint.Base

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.

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] 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, setImportsQ, and setImportsF 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.:

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

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

setImportsF :: MonadInterpreter m => [ModuleImport] -> m () Source #

Sets the modules whose exports must be in context; some may be qualified or have imports lists. E.g.:

setImportsF [ModuleImport Prelude NotQualified NoImportList, ModuleImport Data.Text (QualifiedAs $ Just Text) (HidingList ["pack"])]

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] 

Instances

Instances details
Eq ModuleElem Source # 
Instance details

Defined in Hint.Reflection

Read ModuleElem Source # 
Instance details

Defined in Hint.Reflection

Show ModuleElem Source # 
Instance details

Defined in Hint.Reflection

type Id = String Source #

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

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.

Annotations

Type inference

typeChecksWithDetails :: MonadInterpreter m => String -> m (Either [GhcError] String) Source #

Similar to typeChecks, but gives more information, e.g. the type errors.

typeOf :: MonadInterpreter m => String -> m String Source #

Returns a string representation of the type of the expression.

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

Tests if the expression type checks.

NB. Be careful if there is `-fdefer-type-errors` involved. Perhaps unsurprisingly, that can falsely make typeChecks and getType return True and Right _ respectively.

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

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

normalizeType :: MonadInterpreter m => String -> m String Source #

Returns a string representation of the normalized type expression. This is what the :kind! GHCi command prints after =.

Evaluation

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

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

as :: Typeable a => a Source #

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 Source #

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 Source #

eval expr will evaluate show expr. It will succeed only if expr has type t and there is a Show instance for t.

runStmt :: MonadInterpreter m => String -> m () Source #

Evaluate a statement in the IO monad, possibly binding new names.

Example:

runStmt "x <- return 42"
runStmt "print x"

Error handling

data InterpreterError Source #

Constructors

UnknownError String 
WontCompile [GhcError] 
NotAllowed String 
GhcException String

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

newtype GhcError Source #

Constructors

GhcError 

Fields

Instances

Instances details
Show GhcError Source # 
Instance details

Defined in Hint.Base

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

ghcVersion :: Int Source #

Version of the underlying ghc api. Values are:

  • 804 for GHC 8.4.x
  • 806 for GHC 8.6.x
  • etc...

parens :: String -> String Source #

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