-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | The library supporting GHC's interactive interpreter -- -- This library offers interfaces which mediate interactions between the -- ghci interactive shell and iserv, GHC's -- out-of-process interpreter backend. @package ghci @version 8.11.0.20200524 -- | Efficient serialisation for GHCi Instruction arrays -- -- Author: Ben Gamari module GHCi.BinaryArray -- | An efficient serialiser of UArray. putArray :: Binary i => UArray i a -> Put -- | An efficient deserialiser of UArray. getArray :: (Binary i, Ix i, MArray IOUArray a IO) => Get (UArray i a) -- | Break Arrays -- -- An array of bytes, indexed by a breakpoint number (breakpointId in -- Tickish) There is one of these arrays per module. -- -- Each byte is 1 if the corresponding breakpoint is enabled 0 otherwise module GHCi.BreakArray data BreakArray BA :: MutableByteArray# RealWorld -> BreakArray newBreakArray :: Int -> IO BreakArray getBreak :: BreakArray -> Int -> IO (Maybe Word8) setBreakOn :: BreakArray -> Int -> IO Bool setBreakOff :: BreakArray -> Int -> IO Bool showBreakArray :: BreakArray -> IO () module GHCi.FFI data FFIType FFIVoid :: FFIType FFIPointer :: FFIType FFIFloat :: FFIType FFIDouble :: FFIType FFISInt8 :: FFIType FFISInt16 :: FFIType FFISInt32 :: FFIType FFISInt64 :: FFIType FFIUInt8 :: FFIType FFIUInt16 :: FFIType FFIUInt32 :: FFIType FFIUInt64 :: FFIType data FFIConv FFICCall :: FFIConv FFIStdCall :: FFIConv data C_ffi_cif prepForeignCall :: FFIConv -> [FFIType] -> FFIType -> IO (Ptr C_ffi_cif) freeForeignCallInfo :: Ptr C_ffi_cif -> IO () instance Data.Binary.Class.Binary GHCi.FFI.FFIType instance GHC.Generics.Generic GHCi.FFI.FFIType instance GHC.Show.Show GHCi.FFI.FFIType instance Data.Binary.Class.Binary GHCi.FFI.FFIConv instance GHC.Generics.Generic GHCi.FFI.FFIConv instance GHC.Show.Show GHCi.FFI.FFIConv -- | Run-time info table support. This module provides support for creating -- and reading info tables in the running program. We use the RTS -- data structures directly via hsc2hs. module GHCi.InfoTable mkConInfoTable :: Bool -> Int -> Int -> Int -> Int -> ByteString -> IO (Ptr StgInfoTable) instance GHC.Show.Show GHCi.InfoTable.Arch -- | Types for referring to remote objects in Remote GHCi. For more -- details, see Note [External GHCi pointers] in -- compilerghciGHCi.hs -- -- For details on Remote GHCi, see Note [Remote GHCi] in -- compilerghciGHCi.hs. module GHCi.RemoteTypes newtype RemotePtr a RemotePtr :: Word64 -> RemotePtr a toRemotePtr :: Ptr a -> RemotePtr a fromRemotePtr :: RemotePtr a -> Ptr a castRemotePtr :: RemotePtr a -> RemotePtr b newtype HValue HValue :: Any -> HValue -- | A reference to a remote value. These are allocated and freed -- explicitly. data RemoteRef a -- | Make a reference to a local value that we can send remotely. This -- reference will keep the value that it refers to alive until -- freeRemoteRef is called. mkRemoteRef :: a -> IO (RemoteRef a) -- | Convert an HValueRef to an HValue. Should only be used if the HValue -- originated in this process. localRef :: RemoteRef a -> IO a -- | Release an HValueRef that originated in this process freeRemoteRef :: RemoteRef a -> IO () type HValueRef = RemoteRef HValue toHValueRef :: RemoteRef a -> RemoteRef HValue -- | An HValueRef with a finalizer data ForeignRef a -- | Create a ForeignRef from a RemoteRef. The finalizer -- should arrange to call freeHValueRef on the HValueRef. -- (since this function needs to be called in the process that created -- the HValueRef, it cannot be called directly from the -- finalizer). mkForeignRef :: RemoteRef a -> IO () -> IO (ForeignRef a) -- | Use a ForeignHValue withForeignRef :: ForeignRef a -> (RemoteRef a -> IO b) -> IO b type ForeignHValue = ForeignRef HValue unsafeForeignRefToRemoteRef :: ForeignRef a -> RemoteRef a finalizeForeignRef :: ForeignRef a -> IO () instance Data.Binary.Class.Binary (GHCi.RemoteTypes.RemoteRef a) instance GHC.Show.Show (GHCi.RemoteTypes.RemoteRef a) instance GHC.Show.Show (GHCi.RemoteTypes.RemotePtr a) instance Data.Binary.Class.Binary (GHCi.RemoteTypes.RemotePtr a) instance Control.DeepSeq.NFData (GHCi.RemoteTypes.RemotePtr a) instance Control.DeepSeq.NFData (GHCi.RemoteTypes.ForeignRef a) instance GHC.Show.Show GHCi.RemoteTypes.HValue -- | Primarily, this module consists of an interface to the C-land dynamic -- linker. module GHCi.ObjLink initObjLinker :: ShouldRetainCAFs -> IO () data ShouldRetainCAFs -- | Retain CAFs unconditionally in linked Haskell code. Note that this -- prevents any code from being unloaded. It should not be necessary -- unless you are GHCi or hs-plugins, which needs to be able call any -- function in the compiled code. RetainCAFs :: ShouldRetainCAFs -- | Do not retain CAFs. Everything reachable from foreign exports will be -- retained, due to the StablePtrs created by the module initialisation -- code. unloadObj frees these StablePtrs, which will allow the CAFs to -- be GC'd and the code to be removed. DontRetainCAFs :: ShouldRetainCAFs -- | 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. loadDLL :: String -> IO (Maybe String) loadArchive :: String -> IO () loadObj :: String -> IO () -- | unloadObj drops the given dynamic library from the symbol -- table as well as enables the library to be removed from memory during -- a future major GC. unloadObj :: String -> IO () -- | purgeObj drops the symbols for the dynamic library from the -- symbol table. Unlike unloadObj, the library will not be dropped -- memory during a future major GC. purgeObj :: String -> IO () lookupSymbol :: String -> IO (Maybe (Ptr a)) lookupClosure :: String -> IO (Maybe HValueRef) resolveObjs :: IO Bool addLibrarySearchPath :: String -> IO (Ptr ()) removeLibrarySearchPath :: Ptr () -> IO Bool findSystemLibrary :: String -> IO (Maybe String) module GHCi.Signals -- | Install standard signal handlers for catching ^C, which just throw an -- exception in the target thread. The current target thread is the -- thread at the head of the list in the MVar passed to -- installSignalHandlers. installSignalHandlers :: IO () module GHCi.StaticPtrTable -- | Used by GHCi to add an SPT entry for a set of interactive bindings. sptAddEntry :: Fingerprint -> HValue -> IO () module GHCi.TH.Binary instance Data.Binary.Class.Binary Language.Haskell.TH.Syntax.Loc instance Data.Binary.Class.Binary Language.Haskell.TH.Syntax.Name instance Data.Binary.Class.Binary Language.Haskell.TH.Syntax.ModName instance Data.Binary.Class.Binary Language.Haskell.TH.Syntax.NameFlavour instance Data.Binary.Class.Binary Language.Haskell.TH.Syntax.PkgName instance Data.Binary.Class.Binary Language.Haskell.TH.Syntax.NameSpace instance Data.Binary.Class.Binary Language.Haskell.TH.Syntax.Module instance Data.Binary.Class.Binary Language.Haskell.TH.Syntax.Info instance Data.Binary.Class.Binary Language.Haskell.TH.Syntax.Type instance Data.Binary.Class.Binary Language.Haskell.TH.Syntax.TyLit instance Data.Binary.Class.Binary Language.Haskell.TH.Syntax.Specificity instance Data.Binary.Class.Binary flag => Data.Binary.Class.Binary (Language.Haskell.TH.Syntax.TyVarBndr flag) instance Data.Binary.Class.Binary Language.Haskell.TH.Syntax.Role instance Data.Binary.Class.Binary Language.Haskell.TH.Syntax.Lit instance Data.Binary.Class.Binary Language.Haskell.TH.Syntax.Range instance Data.Binary.Class.Binary Language.Haskell.TH.Syntax.Stmt instance Data.Binary.Class.Binary Language.Haskell.TH.Syntax.Pat instance Data.Binary.Class.Binary Language.Haskell.TH.Syntax.Exp instance Data.Binary.Class.Binary Language.Haskell.TH.Syntax.Dec instance Data.Binary.Class.Binary Language.Haskell.TH.Syntax.Overlap instance Data.Binary.Class.Binary Language.Haskell.TH.Syntax.DerivClause instance Data.Binary.Class.Binary Language.Haskell.TH.Syntax.DerivStrategy instance Data.Binary.Class.Binary Language.Haskell.TH.Syntax.Guard instance Data.Binary.Class.Binary Language.Haskell.TH.Syntax.Body instance Data.Binary.Class.Binary Language.Haskell.TH.Syntax.Match instance Data.Binary.Class.Binary Language.Haskell.TH.Syntax.Fixity instance Data.Binary.Class.Binary Language.Haskell.TH.Syntax.TySynEqn instance Data.Binary.Class.Binary Language.Haskell.TH.Syntax.FunDep instance Data.Binary.Class.Binary Language.Haskell.TH.Syntax.AnnTarget instance Data.Binary.Class.Binary Language.Haskell.TH.Syntax.RuleBndr instance Data.Binary.Class.Binary Language.Haskell.TH.Syntax.Phases instance Data.Binary.Class.Binary Language.Haskell.TH.Syntax.RuleMatch instance Data.Binary.Class.Binary Language.Haskell.TH.Syntax.Inline instance Data.Binary.Class.Binary Language.Haskell.TH.Syntax.Pragma instance Data.Binary.Class.Binary Language.Haskell.TH.Syntax.Safety instance Data.Binary.Class.Binary Language.Haskell.TH.Syntax.Callconv instance Data.Binary.Class.Binary Language.Haskell.TH.Syntax.Foreign instance Data.Binary.Class.Binary Language.Haskell.TH.Syntax.Bang instance Data.Binary.Class.Binary Language.Haskell.TH.Syntax.SourceUnpackedness instance Data.Binary.Class.Binary Language.Haskell.TH.Syntax.SourceStrictness instance Data.Binary.Class.Binary Language.Haskell.TH.Syntax.DecidedStrictness instance Data.Binary.Class.Binary Language.Haskell.TH.Syntax.FixityDirection instance Data.Binary.Class.Binary Language.Haskell.TH.Syntax.OccName instance Data.Binary.Class.Binary Language.Haskell.TH.Syntax.Con instance Data.Binary.Class.Binary Language.Haskell.TH.Syntax.AnnLookup instance Data.Binary.Class.Binary Language.Haskell.TH.Syntax.ModuleInfo instance Data.Binary.Class.Binary Language.Haskell.TH.Syntax.Clause instance Data.Binary.Class.Binary Language.Haskell.TH.Syntax.InjectivityAnn instance Data.Binary.Class.Binary Language.Haskell.TH.Syntax.FamilyResultSig instance Data.Binary.Class.Binary Language.Haskell.TH.Syntax.TypeFamilyHead instance Data.Binary.Class.Binary Language.Haskell.TH.Syntax.PatSynDir instance Data.Binary.Class.Binary Language.Haskell.TH.Syntax.PatSynArgs instance Data.Binary.Class.Binary GHC.Serialized.Serialized instance Data.Binary.Class.Binary Language.Haskell.TH.Syntax.Bytes -- | Remote GHCi message types and serialization. -- -- For details on Remote GHCi, see Note [Remote GHCi] in -- compilerghciGHCi.hs. module GHCi.Message -- | A Message a is a message that returns a value of type -- a. These are requests sent from GHC to the server. data Message a -- | Exit the iserv process [Shutdown] :: Message () [RtsRevertCAFs] :: Message () [InitLinker] :: Message () [LookupSymbol] :: String -> Message (Maybe (RemotePtr ())) [LookupClosure] :: String -> Message (Maybe HValueRef) [LoadDLL] :: String -> Message (Maybe String) [LoadArchive] :: String -> Message () [LoadObj] :: String -> Message () [UnloadObj] :: String -> Message () [AddLibrarySearchPath] :: String -> Message (RemotePtr ()) [RemoveLibrarySearchPath] :: RemotePtr () -> Message Bool [ResolveObjs] :: Message Bool [FindSystemLibrary] :: String -> Message (Maybe String) -- | Create a set of BCO objects, and return HValueRefs to them Note: Each -- ByteString contains a Binary-encoded [ResolvedBCO], not a ResolvedBCO. -- The list is to allow us to serialise the ResolvedBCOs in parallel. See -- createBCOs in compilerghciGHCi.hsc. [CreateBCOs] :: [ByteString] -> Message [HValueRef] -- | Release HValueRefs [FreeHValueRefs] :: [HValueRef] -> Message () -- | Add entries to the Static Pointer Table [AddSptEntry] :: Fingerprint -> HValueRef -> Message () -- | Malloc some data and return a RemotePtr to it [MallocData] :: ByteString -> Message (RemotePtr ()) [MallocStrings] :: [ByteString] -> Message [RemotePtr ()] -- | Calls prepareForeignCall [PrepFFI] :: FFIConv -> [FFIType] -> FFIType -> Message (RemotePtr C_ffi_cif) -- | Free data previously created by PrepFFI [FreeFFI] :: RemotePtr C_ffi_cif -> Message () -- | Create an info table for a constructor [MkConInfoTable] :: Bool -> Int -> Int -> Int -> Int -> ByteString -> Message (RemotePtr StgInfoTable) -- | Evaluate a statement [EvalStmt] :: EvalOpts -> EvalExpr HValueRef -> Message (EvalStatus [HValueRef]) -- | Resume evaluation of a statement after a breakpoint [ResumeStmt] :: EvalOpts -> RemoteRef (ResumeContext [HValueRef]) -> Message (EvalStatus [HValueRef]) -- | Abandon evaluation of a statement after a breakpoint [AbandonStmt] :: RemoteRef (ResumeContext [HValueRef]) -> Message () -- | Evaluate something of type IO String [EvalString] :: HValueRef -> Message (EvalResult String) -- | Evaluate something of type String -> IO String [EvalStringToString] :: HValueRef -> String -> Message (EvalResult String) -- | Evaluate something of type IO () [EvalIO] :: HValueRef -> Message (EvalResult ()) -- | Create a set of CostCentres with the same module name [MkCostCentres] :: String -> [(String, String)] -> Message [RemotePtr CostCentre] -- | Show a CostCentreStack as a [String] [CostCentreStackInfo] :: RemotePtr CostCentreStack -> Message [String] -- | Create a new array of breakpoint flags [NewBreakArray] :: Int -> Message (RemoteRef BreakArray) -- | Enable a breakpoint [EnableBreakpoint] :: RemoteRef BreakArray -> Int -> Bool -> Message () -- | Query the status of a breakpoint (True = enabled) [BreakpointStatus] :: RemoteRef BreakArray -> Int -> Message Bool -- | Get a reference to a free variable at a breakpoint [GetBreakpointVar] :: HValueRef -> Int -> Message (Maybe HValueRef) -- | Start a new TH module, return a state token that should be [StartTH] :: Message (RemoteRef (IORef QState)) -- | 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. [RunTH] :: RemoteRef (IORef QState) -> HValueRef -> THResultType -> Maybe Loc -> Message (QResult ByteString) -- | Run the given mod finalizers. [RunModFinalizers] :: RemoteRef (IORef QState) -> [RemoteRef (Q ())] -> Message (QResult ()) -- | Remote interface to GHC.Exts.Heap.getClosureData. This is used by the -- GHCi debugger to inspect values in the heap for :print and type -- reconstruction. [GetClosure] :: HValueRef -> Message (GenClosure HValueRef) -- | Evaluate something. This is used to support :force in GHCi. [Seq] :: HValueRef -> Message (EvalStatus ()) -- | Resume forcing a free variable in a breakpoint (#2950) [ResumeSeq] :: RemoteRef (ResumeContext ()) -> Message (EvalStatus ()) data Msg Msg :: Message a -> Msg -- | Messages sent back to GHC from GHCi.TH, to implement the methods of -- Quasi. For an overview of how TH works with Remote GHCi, see -- Note [Remote Template Haskell] in GHCi.TH. data THMessage a [NewName] :: String -> THMessage (THResult Name) [Report] :: Bool -> String -> THMessage (THResult ()) [LookupName] :: Bool -> String -> THMessage (THResult (Maybe Name)) [Reify] :: Name -> THMessage (THResult Info) [ReifyFixity] :: Name -> THMessage (THResult (Maybe Fixity)) [ReifyType] :: Name -> THMessage (THResult Type) [ReifyInstances] :: Name -> [Type] -> THMessage (THResult [Dec]) [ReifyRoles] :: Name -> THMessage (THResult [Role]) [ReifyAnnotations] :: AnnLookup -> TypeRep -> THMessage (THResult [ByteString]) [ReifyModule] :: Module -> THMessage (THResult ModuleInfo) [ReifyConStrictness] :: Name -> THMessage (THResult [DecidedStrictness]) [AddDependentFile] :: FilePath -> THMessage (THResult ()) [AddTempFile] :: String -> THMessage (THResult FilePath) [AddModFinalizer] :: RemoteRef (Q ()) -> THMessage (THResult ()) [AddCorePlugin] :: String -> THMessage (THResult ()) [AddTopDecls] :: [Dec] -> THMessage (THResult ()) [AddForeignFilePath] :: ForeignSrcLang -> FilePath -> THMessage (THResult ()) [IsExtEnabled] :: Extension -> THMessage (THResult Bool) [ExtsEnabled] :: THMessage (THResult [Extension]) [StartRecover] :: THMessage () [EndRecover] :: Bool -> THMessage () [FailIfErrs] :: THMessage (THResult ()) -- | Indicates that this RunTH is finished, and the next message will be -- the result of RunTH (a QResult). [RunTHDone] :: THMessage () data THMsg THMsg :: THMessage a -> THMsg -- | Template Haskell return values data QResult a -- | RunTH finished successfully; return value follows QDone :: a -> QResult a -- | RunTH threw an exception QException :: String -> QResult a -- | RunTH called fail QFail :: String -> QResult a data EvalStatus_ a b EvalComplete :: Word64 -> EvalResult a -> EvalStatus_ a b EvalBreak :: Bool -> HValueRef -> Int -> Int -> RemoteRef (ResumeContext b) -> RemotePtr CostCentreStack -> EvalStatus_ a b type EvalStatus a = EvalStatus_ a a data EvalResult a EvalException :: SerializableException -> EvalResult a EvalSuccess :: a -> EvalResult a data EvalOpts EvalOpts :: Bool -> Bool -> Bool -> Bool -> EvalOpts [useSandboxThread] :: EvalOpts -> Bool [singleStep] :: EvalOpts -> Bool [breakOnException] :: EvalOpts -> Bool [breakOnError] :: EvalOpts -> Bool -- | 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. data EvalExpr a EvalThis :: a -> EvalExpr a EvalApp :: EvalExpr a -> EvalExpr a -> EvalExpr a data SerializableException EUserInterrupt :: SerializableException EExitCode :: ExitCode -> SerializableException EOtherException :: String -> SerializableException toSerializableException :: SomeException -> SerializableException fromSerializableException :: SerializableException -> SomeException data THResult a THException :: String -> THResult a THComplete :: a -> THResult a data THResultType THExp :: THResultType THPat :: THResultType THType :: THResultType THDec :: THResultType THAnnWrapper :: THResultType data ResumeContext a ResumeContext :: MVar () -> MVar (EvalStatus a) -> ThreadId -> ResumeContext a [resumeBreakMVar] :: ResumeContext a -> MVar () [resumeStatusMVar] :: ResumeContext a -> MVar (EvalStatus a) [resumeThreadId] :: ResumeContext a -> ThreadId -- | The server-side Template Haskell state. This is created by the StartTH -- message. A new one is created per module that GHC typechecks. data QState QState :: Map TypeRep Dynamic -> Maybe Loc -> Pipe -> QState -- | persistent data between splices in a module [qsMap] :: QState -> Map TypeRep Dynamic -- | location for current splice, if any [qsLocation] :: QState -> Maybe Loc -- | pipe to communicate with GHC [qsPipe] :: QState -> Pipe getMessage :: Get Msg putMessage :: Message a -> Put getTHMessage :: Get THMsg putTHMessage :: THMessage a -> Put data Pipe Pipe :: Handle -> Handle -> IORef (Maybe ByteString) -> Pipe [pipeRead] :: Pipe -> Handle [pipeWrite] :: Pipe -> Handle [pipeLeftovers] :: Pipe -> IORef (Maybe ByteString) remoteCall :: Binary a => Pipe -> Message a -> IO a remoteTHCall :: Binary a => Pipe -> THMessage a -> IO a readPipe :: Pipe -> Get a -> IO a writePipe :: Pipe -> Put -> IO () instance GHC.Show.Show a => GHC.Show.Show (GHCi.Message.QResult a) instance GHC.Generics.Generic (GHCi.Message.QResult a) instance GHC.Show.Show GHCi.Message.EvalOpts instance GHC.Generics.Generic GHCi.Message.EvalOpts instance GHC.Show.Show a => GHC.Show.Show (GHCi.Message.EvalExpr a) instance GHC.Generics.Generic (GHCi.Message.EvalExpr a) instance GHC.Show.Show GHCi.Message.SerializableException instance GHC.Generics.Generic GHCi.Message.SerializableException instance GHC.Show.Show a => GHC.Show.Show (GHCi.Message.EvalResult a) instance GHC.Generics.Generic (GHCi.Message.EvalResult a) instance GHC.Show.Show a => GHC.Show.Show (GHCi.Message.EvalStatus_ a b) instance GHC.Generics.Generic (GHCi.Message.EvalStatus_ a b) instance GHC.Show.Show a => GHC.Show.Show (GHCi.Message.THResult a) instance GHC.Generics.Generic (GHCi.Message.THResult a) instance GHC.Generics.Generic GHCi.Message.THResultType instance GHC.Show.Show GHCi.Message.THResultType instance GHC.Enum.Enum GHCi.Message.THResultType instance GHC.Show.Show (GHCi.Message.Message a) instance GHC.Show.Show (GHCi.Message.THMessage a) instance GHC.Show.Show GHCi.Message.QState instance Data.Binary.Class.Binary GHCi.Message.THResultType instance Data.Binary.Class.Binary a => Data.Binary.Class.Binary (GHCi.Message.THResult a) instance Data.Binary.Class.Binary a => Data.Binary.Class.Binary (GHCi.Message.EvalStatus_ a b) instance Data.Binary.Class.Binary a => Data.Binary.Class.Binary (GHCi.Message.EvalResult a) instance Data.Binary.Class.Binary GHCi.Message.SerializableException instance Data.Binary.Class.Binary a => Data.Binary.Class.Binary (GHCi.Message.EvalExpr a) instance Data.Binary.Class.Binary GHCi.Message.EvalOpts instance Data.Binary.Class.Binary a => Data.Binary.Class.Binary (GHCi.Message.QResult a) instance Data.Binary.Class.Binary GHC.IO.Exception.ExitCode instance Data.Binary.Class.Binary (GHC.Ptr.Ptr a) instance Data.Binary.Class.Binary (GHC.Ptr.FunPtr a) instance Data.Binary.Class.Binary GHC.Exts.Heap.InfoTable.Types.StgInfoTable instance Data.Binary.Class.Binary GHC.Exts.Heap.ClosureTypes.ClosureType instance Data.Binary.Class.Binary GHC.Exts.Heap.Closures.PrimType instance Data.Binary.Class.Binary a => Data.Binary.Class.Binary (GHC.Exts.Heap.Closures.GenClosure a) -- | Running TH splices module GHCi.TH -- | The implementation of the StartTH message: create a new IORef -- QState, and return a RemoteRef to it. startTH :: IO (RemoteRef (IORef QState)) -- | Runs the mod finalizers. -- -- The references must be created on the caller process. runModFinalizerRefs :: Pipe -> RemoteRef (IORef QState) -> [RemoteRef (Q ())] -> IO () -- | The implementation of the RunTH message runTH :: Pipe -> RemoteRef (IORef QState) -> HValueRef -> THResultType -> Maybe Loc -> IO ByteString -- | The exception thrown by "fail" in the GHCiQ monad data GHCiQException GHCiQException :: QState -> String -> GHCiQException instance GHC.Show.Show GHCi.TH.GHCiQException instance GHC.Exception.Type.Exception GHCi.TH.GHCiQException instance Control.Monad.Fail.MonadFail GHCi.TH.GHCiQ instance Language.Haskell.TH.Syntax.Quasi GHCi.TH.GHCiQ instance GHC.Base.Functor GHCi.TH.GHCiQ instance GHC.Base.Applicative GHCi.TH.GHCiQ instance GHC.Base.Monad GHCi.TH.GHCiQ instance Control.Monad.IO.Class.MonadIO GHCi.TH.GHCiQ module SizedSeq data SizedSeq a SizedSeq :: {-# UNPACK #-} !Word -> [a] -> SizedSeq a emptySS :: SizedSeq a addToSS :: SizedSeq a -> a -> SizedSeq a addListToSS :: SizedSeq a -> [a] -> SizedSeq a ssElts :: SizedSeq a -> [a] sizeSS :: SizedSeq a -> Word instance GHC.Show.Show a => GHC.Show.Show (SizedSeq.SizedSeq a) instance GHC.Generics.Generic (SizedSeq.SizedSeq a) instance GHC.Base.Functor SizedSeq.SizedSeq instance Data.Foldable.Foldable SizedSeq.SizedSeq instance Data.Traversable.Traversable SizedSeq.SizedSeq instance Data.Binary.Class.Binary a => Data.Binary.Class.Binary (SizedSeq.SizedSeq a) instance Control.DeepSeq.NFData a => Control.DeepSeq.NFData (SizedSeq.SizedSeq a) module GHCi.ResolvedBCO -- | A ResolvedBCO is one in which all the Name references -- have been resolved to actual addresses or RemoteHValues. -- -- Note, all arrays are zero-indexed (we assume this when -- serializing/deserializing) data ResolvedBCO ResolvedBCO :: Bool -> {-# UNPACK #-} !Int -> UArray Int Word16 -> UArray Int Word64 -> UArray Int Word64 -> SizedSeq ResolvedBCOPtr -> ResolvedBCO [resolvedBCOIsLE] :: ResolvedBCO -> Bool [resolvedBCOArity] :: ResolvedBCO -> {-# UNPACK #-} !Int [resolvedBCOInstrs] :: ResolvedBCO -> UArray Int Word16 [resolvedBCOBitmap] :: ResolvedBCO -> UArray Int Word64 [resolvedBCOLits] :: ResolvedBCO -> UArray Int Word64 [resolvedBCOPtrs] :: ResolvedBCO -> SizedSeq ResolvedBCOPtr data ResolvedBCOPtr -- | reference to the Nth BCO in the current set ResolvedBCORef :: {-# UNPACK #-} !Int -> ResolvedBCOPtr -- | reference to a previously created BCO ResolvedBCOPtr :: {-# UNPACK #-} !RemoteRef HValue -> ResolvedBCOPtr -- | reference to a static ptr ResolvedBCOStaticPtr :: {-# UNPACK #-} !RemotePtr () -> ResolvedBCOPtr -- | a nested BCO ResolvedBCOPtrBCO :: ResolvedBCO -> ResolvedBCOPtr -- | Resolves to the MutableArray# inside the BreakArray ResolvedBCOPtrBreakArray :: {-# UNPACK #-} !RemoteRef BreakArray -> ResolvedBCOPtr isLittleEndian :: Bool instance GHC.Show.Show GHCi.ResolvedBCO.ResolvedBCO instance GHC.Generics.Generic GHCi.ResolvedBCO.ResolvedBCO instance GHC.Show.Show GHCi.ResolvedBCO.ResolvedBCOPtr instance GHC.Generics.Generic GHCi.ResolvedBCO.ResolvedBCOPtr instance Data.Binary.Class.Binary GHCi.ResolvedBCO.ResolvedBCO instance Data.Binary.Class.Binary GHCi.ResolvedBCO.ResolvedBCOPtr -- | Create real byte-code objects from ResolvedBCOs. module GHCi.CreateBCO createBCOs :: [ResolvedBCO] -> IO [HValueRef] -- | Execute GHCi messages. -- -- For details on Remote GHCi, see Note [Remote GHCi] in -- compilerghciGHCi.hs. module GHCi.Run run :: Message a -> IO a redirectInterrupts :: ThreadId -> IO a -> IO a