Safe Haskell | None |
---|---|
Language | Haskell2010 |
Client interface to the `ide-backend-server` process
It is important that none of the types here rely on the GHC library.
- type InProcess = Bool
- data GhcServer
- forkGhcServer :: [String] -> [FilePath] -> [String] -> IdeStaticInfo -> IdeCallbacks -> IO (Either ExternalException (GhcServer, GhcVersion))
- shutdownGhcServer :: GhcServer -> IO ()
- forceShutdownGhcServer :: GhcServer -> IO ()
- getGhcExitCode :: GhcServer -> IO (Maybe ExitCode)
- data RunActions a = RunActions {
- runWait :: IO (Either ByteString a)
- interrupt :: IO ()
- supplyStdin :: ByteString -> IO ()
- forceCancel :: IO ()
- runWaitAll :: forall a. RunActions a -> IO (ByteString, a)
- rpcCompile :: GhcServer -> Bool -> Targets -> (UpdateStatus -> IO ()) -> IO GhcCompileResult
- rpcRun :: forall a. GhcServer -> RunCmd -> (Maybe RunResult -> IO a) -> IO (RunActions a)
- rpcCrash :: GhcServer -> Maybe Int -> IO ()
- rpcSetEnv :: GhcServer -> [(String, Maybe String)] -> IO ()
- rpcSetArgs :: GhcServer -> [String] -> IO ()
- rpcBreakpoint :: GhcServer -> ModuleName -> SourceSpan -> Bool -> IO (Maybe Bool)
- rpcPrint :: GhcServer -> Name -> Bool -> Bool -> IO VariableEnv
- rpcLoad :: GhcServer -> [FilePath] -> IO (Maybe String)
- rpcUnload :: GhcServer -> [FilePath] -> IO ()
- rpcSetGhcOpts :: GhcServer -> [String] -> IO ([String], [String])
Starting and stopping the server
:: [String] | Initial ghc options |
-> [FilePath] | Relative includes |
-> [String] | RTS options |
-> IdeStaticInfo | Session setup info |
-> IdeCallbacks | Session callbacks |
-> IO (Either ExternalException (GhcServer, GhcVersion)) |
Start the ghc server
shutdownGhcServer :: GhcServer -> IO () Source
forceShutdownGhcServer :: GhcServer -> IO () Source
Interacting with the server
data RunActions a Source
Handles to the running code snippet, through which one can interact with the snippet.
Requirement: concurrent uses of supplyStdin
should be possible,
e.g., two threads that share a RunActions
should be able to provide
input concurrently without problems. (Currently this is ensured
by supplyStdin
writing to a channel.)
RunActions | |
|
runWaitAll :: forall a. RunActions a -> IO (ByteString, a) Source
:: GhcServer | GHC server |
-> Bool | Should we generate code? |
-> Targets | Targets |
-> (UpdateStatus -> IO ()) | Progress callback |
-> IO GhcCompileResult |
Compile or typecheck
:: GhcServer | GHC server |
-> RunCmd | Run command |
-> (Maybe RunResult -> IO a) | Translate run results
|
-> IO (RunActions a) |
Run code
NOTE: This is an interruptible operation
rpcSetArgs :: GhcServer -> [String] -> IO () Source
Set command line arguments
rpcBreakpoint :: GhcServer -> ModuleName -> SourceSpan -> Bool -> IO (Maybe Bool) Source
Set breakpoint
Returns Just
the old value of the break if successful, or Nothing
if
the breakpoint could not be found.