ihaskell-0.10.3.0: A Haskell backend kernel for the Jupyter project.
Safe HaskellSafe-Inferred
LanguageHaskell2010

IHaskell.Eval.Util

Synopsis

Initialization

initGhci :: GhcMonad m => Maybe String -> m () Source #

Initialize the GHC API. Run this as the first thing in the runGhc. This initializes some dyn flags (ExtendedDefaultRules, NoMonomorphismRestriction), sets the target to interpreted, link in memory, sets a reasonable output width, and potentially a few other things. It should be invoked before other functions from this module.

We also require that the sandbox PackageConf (if any) is passed here as setSessionDynFlags will read the package database the first time (and only the first time) it is called.

Flags and extensions ** Set and unset flags.

extensionFlag :: String -> Maybe ExtFlag Source #

Find the extension that corresponds to a given flag. Create the corresponding ExtFlag via SetFlag or UnsetFlag. If no such extension exist, yield Nothing.

setExtension :: GhcMonad m => String -> m (Maybe String) Source #

Set an extension and update flags. Return Nothing on success. On failure, return an error message.

data ExtFlag Source #

A extension flag that can be set or unset.

Constructors

SetFlag ExtensionFlag 
UnsetFlag ExtensionFlag 

setFlags :: GhcMonad m => [String] -> m [String] Source #

Set a list of flags, as per GHCi's `:set`. This was adapted from GHC's InteractiveUI.hs (newDynFlags). It returns a list of error messages.

setWayDynFlag :: DynFlags -> DynFlags Source #

Consult the RTS to find if GHC has been built with dynamic linking and then turn on the dynamic way for GHC. Otherwise it does nothing.

Code Evaluation

evalImport :: GhcMonad m => String -> m () Source #

Evaluate a single import statement. If this import statement is importing a module which was previously imported implicitly (such as Prelude) or if this module has a hiding annotation, the previous import is removed.

evalDeclarations :: GhcMonad m => String -> m [String] Source #

Evaluate a series of declarations. Return all names which were bound by these declarations.

getType :: GhcMonad m => String -> m String Source #

Get the type of an expression and convert it to a string.

getDescription :: GhcMonad m => String -> m [String] Source #

A wrapper around getInfo. Return info about each name in the string.

Pretty printing

doc :: GhcMonad m => SDoc -> m String Source #

Convert an SDoc into a string. This is similar to the family of showSDoc functions, but does not impose an arbitrary width limit on the output (in terms of number of columns). Instead, it respsects the pprCols field in the structure returned by getSessionDynFlags, and thus gives a configurable width of output.

pprDynFlags Source #

Arguments

:: Bool

Whether to include flags which are on by default

-> DynFlags 
-> SDoc 

Pretty-print dynamic flags (taken from InteractiveUI module of `ghc-bin`)

pprLanguages Source #

Arguments

:: Bool

Whether to include flags which are on by default

-> DynFlags 
-> SDoc 

Pretty-print the base language and active options (taken from InteractiveUI module of `ghc-bin`)

Monad-loops

unfoldM :: IO (Maybe a) -> IO [a] Source #

This is unfoldM from monad-loops. It repeatedly runs an IO action until it return Nothing, and puts all the Justs in a list. If you find yourself using more functionality from monad-loops, just add the package dependency instead of copying more code from it.