ghc-8.0.0.20160204: The GHC API

Safe HaskellNone
LanguageHaskell2010

GHCi

Contents

Description

Interacting with the interpreter, whether it is running on an external process or in the current process.

Synopsis

High-level interface to the interpreter

evalStmt :: HscEnv -> Bool -> EvalExpr ForeignHValue -> IO (EvalStatus_ [ForeignHValue] [HValueRef]) Source

Execute an action of type IO [a], returning ForeignHValues for each of the results.

data EvalStatus_ a b :: TYPE Lifted -> TYPE Lifted -> TYPE Lifted Source

Instances

Show a => Show (EvalStatus_ a b) 
Generic (EvalStatus_ a b) 

Associated Types

type Rep (EvalStatus_ a b) :: * -> * Source

Methods

from :: EvalStatus_ a b -> Rep (EvalStatus_ a b) x Source

to :: Rep (EvalStatus_ a b) x -> EvalStatus_ a b Source

Binary a => Binary (EvalStatus_ a b) 

Methods

put :: EvalStatus_ a b -> Put Source

get :: Get (EvalStatus_ a b) Source

type Rep (EvalStatus_ a b) = D1 (MetaData "EvalStatus_" "GHCi.Message" "ghci-8.0.0.20160204" False) ((:+:) (C1 (MetaCons "EvalComplete" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word64)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (EvalResult a))))) (C1 (MetaCons "EvalBreak" PrefixI False) ((:*:) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 HValueRef)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (RemoteRef (ResumeContext b)))) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (RemotePtr CostCentreStack)))))))) 

data EvalExpr a :: TYPE Lifted -> TYPE Lifted Source

We can pass simple expressions to EvalStmt, consisting of values and application. This allows us to wrap the statement to be executed in another function, which is used by GHCi to implement :set args and :set prog. It might be worthwhile to extend this little language in the future.

Constructors

EvalThis a 
EvalApp (EvalExpr a) (EvalExpr a) 

evalIO :: HscEnv -> ForeignHValue -> IO () Source

Execute an action of type IO ()

evalString :: HscEnv -> ForeignHValue -> IO String Source

Execute an action of type IO String

evalStringToIOString :: HscEnv -> ForeignHValue -> String -> IO String Source

Execute an action of type String -> IO String

mallocData :: HscEnv -> ByteString -> IO (RemotePtr ()) Source

Allocate and store the given bytes in memory, returning a pointer to the memory in the remote process.

createBCOs :: HscEnv -> [ResolvedBCO] -> IO [HValueRef] Source

Create a set of BCOs that may be mutually recursive.

The object-code linker

loadDLL :: HscEnv -> String -> IO (Maybe String) Source

loadDLL loads a dynamic library using the OS's native linker (i.e. dlopen() on Unix, LoadLibrary() on Windows). It takes either an absolute pathname to the file, or a relative filename (e.g. "libfoo.so" or "foo.dll"). In the latter case, loadDLL searches the standard locations for the appropriate library.

Returns:

Nothing => success Just err_msg => failure

Lower-level API using messages

iservCmd :: Binary a => HscEnv -> Message a -> IO a Source

Run a command in the interpreter's context. With -fexternal-interpreter, the command is serialized and sent to an external iserv process, and the response is deserialized (hence the Binary constraint). With -fno-external-interpreter we execute the command directly here.

data Message a :: TYPE Lifted -> TYPE Lifted where Source

A Message a is a message that returns a value of type a

Constructors

Shutdown :: Message ()

Exit the iserv process

InitLinker :: Message () 
LookupSymbol :: Message (Maybe (RemotePtr ())) 
LookupClosure :: Message (Maybe HValueRef) 
LoadDLL :: Message (Maybe String) 
LoadArchive :: Message () 
LoadObj :: Message () 
UnloadObj :: Message () 
AddLibrarySearchPath :: Message (RemotePtr ()) 
RemoveLibrarySearchPath :: Message Bool 
ResolveObjs :: Message Bool 
FindSystemLibrary :: Message (Maybe String) 
CreateBCOs :: Message [HValueRef]

Create a set of BCO objects, and return HValueRefs to them

FreeHValueRefs :: Message ()

Release HValueRefs

MallocData :: Message (RemotePtr ())

Malloc some data and return a RemotePtr to it

MallocStrings :: Message [RemotePtr ()] 
PrepFFI :: Message (RemotePtr C_ffi_cif)

Calls prepareForeignCall

FreeFFI :: Message ()

Free data previously created by PrepFFI

MkConInfoTable :: Message (RemotePtr StgInfoTable)

Create an info table for a constructor

EvalStmt :: Message (EvalStatus_ [HValueRef] [HValueRef])

Evaluate a statement

ResumeStmt :: Message (EvalStatus_ [HValueRef] [HValueRef])

Resume evaluation of a statement after a breakpoint

AbandonStmt :: Message ()

Abandon evaluation of a statement after a breakpoint

EvalString :: Message (EvalResult String)

Evaluate something of type IO String

EvalStringToString :: Message (EvalResult String)

Evaluate something of type String -> IO String

EvalIO :: Message (EvalResult ())

Evaluate something of type IO ()

MkCostCentres :: Message [RemotePtr CostCentre]

Create a set of CostCentres with the same module name

CostCentreStackInfo :: Message [String]

Show a CostCentreStack as a [String]

NewBreakArray :: Message (RemoteRef BreakArray)

Create a new array of breakpoint flags

EnableBreakpoint :: Message ()

Enable a breakpoint

BreakpointStatus :: Message Bool

Query the status of a breakpoint (True = enabled)

GetBreakpointVar :: Message (Maybe HValueRef)

Get a reference to a free variable at a breakpoint

StartTH :: Message (RemoteRef (IORef QState))

Start a new TH module, return a state token that should be

FinishTH :: Message ()

Run TH module finalizers, and free the HValueRef

RunTH :: Message ByteString

Evaluate a TH computation.

Returns a ByteString, because we have to force the result before returning it to ensure there are no errors lurking in it. The TH types don't have NFData instances, and even if they did, we have to serialize the value anyway, so we might as well serialize it to force it.

NewName :: Message (THResult Name) 
Report :: Message (THResult ()) 
LookupName :: Message (THResult (Maybe Name)) 
Reify :: Message (THResult Info) 
ReifyFixity :: Message (THResult (Maybe Fixity)) 
ReifyInstances :: Message (THResult [Dec]) 
ReifyRoles :: Message (THResult [Role]) 
ReifyAnnotations :: Message (THResult [ByteString]) 
ReifyModule :: Message (THResult ModuleInfo) 
ReifyConStrictness :: Message (THResult [DecidedStrictness]) 
AddDependentFile :: Message (THResult ()) 
AddTopDecls :: Message (THResult ()) 
IsExtEnabled :: Message (THResult Bool) 
ExtsEnabled :: Message (THResult [Extension]) 
StartRecover :: Message () 
EndRecover :: Message () 
QDone :: Message ()

RunTH finished successfully; return value follows

QException :: Message ()

RunTH threw an exception

QFail :: Message ()

RunTH called fail

Instances

withIServ :: (MonadIO m, ExceptionMonad m) => HscEnv -> (IServ -> m a) -> m a Source

Grab a lock on the IServ and do something with it. Overloaded because this is used from TcM as well as IO.

iservCall :: Binary a => IServ -> Message a -> IO a Source

Send a Message and receive the response from the iserv process

readIServ :: IServ -> Get a -> IO a Source

Read a value from the iserv process

writeIServ :: IServ -> Put -> IO () Source

Send a value to the iserv process

mkFinalizedHValue :: HscEnv -> RemoteRef a -> IO (ForeignRef a) Source

Creates a ForeignRef that will automatically release the RemoteRef when it is no longer referenced.

wormhole :: DynFlags -> ForeignRef a -> IO a Source

Convert a ForeignRef to the value it references directly. This only works when the interpreter is running in the same process as the compiler, so it fails when -fexternal-interpreter is on.

wormholeRef :: DynFlags -> RemoteRef a -> IO a Source

Convert an RemoteRef to the value it references directly. This only works when the interpreter is running in the same process as the compiler, so it fails when -fexternal-interpreter is on.