ghcid-0.6.10: GHCi based bare bones IDE

Safe HaskellNone
LanguageHaskell2010

Language.Haskell.Ghcid

Description

Library for spawning and working with Ghci sessions.

Synopsis

Documentation

data Ghci Source #

A GHCi session. Created with startGhci, closed with stopGhci.

The interactions with a Ghci session must all occur single-threaded, or an error will be raised. The only exception is interrupt, which aborts a running computation, or does nothing if no computation is running.

Instances

Eq Ghci Source # 

Methods

(==) :: Ghci -> Ghci -> Bool #

(/=) :: Ghci -> Ghci -> Bool #

data GhciError Source #

GHCi shut down

Instances

Eq GhciError Source # 
Data GhciError Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GhciError -> c GhciError #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c GhciError #

toConstr :: GhciError -> Constr #

dataTypeOf :: GhciError -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c GhciError) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c GhciError) #

gmapT :: (forall b. Data b => b -> b) -> GhciError -> GhciError #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GhciError -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GhciError -> r #

gmapQ :: (forall d. Data d => d -> u) -> GhciError -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GhciError -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GhciError -> m GhciError #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GhciError -> m GhciError #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GhciError -> m GhciError #

Ord GhciError Source # 
Show GhciError Source # 
Exception GhciError Source #

Make GhciError an exception

data Stream Source #

The stream Ghci is talking over.

Constructors

Stdout 
Stderr 

Instances

Bounded Stream Source # 
Enum Stream Source # 
Eq Stream Source # 

Methods

(==) :: Stream -> Stream -> Bool #

(/=) :: Stream -> Stream -> Bool #

Data Stream Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Stream -> c Stream #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Stream #

toConstr :: Stream -> Constr #

dataTypeOf :: Stream -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Stream) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Stream) #

gmapT :: (forall b. Data b => b -> b) -> Stream -> Stream #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Stream -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Stream -> r #

gmapQ :: (forall d. Data d => d -> u) -> Stream -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Stream -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Stream -> m Stream #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Stream -> m Stream #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Stream -> m Stream #

Ord Stream Source # 
Read Stream Source # 
Show Stream Source # 

data Load Source #

Load messages

Instances

Eq Load Source # 

Methods

(==) :: Load -> Load -> Bool #

(/=) :: Load -> Load -> Bool #

Ord Load Source # 

Methods

compare :: Load -> Load -> Ordering #

(<) :: Load -> Load -> Bool #

(<=) :: Load -> Load -> Bool #

(>) :: Load -> Load -> Bool #

(>=) :: Load -> Load -> Bool #

max :: Load -> Load -> Load #

min :: Load -> Load -> Load #

Show Load Source # 

Methods

showsPrec :: Int -> Load -> ShowS #

show :: Load -> String #

showList :: [Load] -> ShowS #

data Severity Source #

Severity of messages

Constructors

Warning 
Error 

Instances

Bounded Severity Source # 
Enum Severity Source # 
Eq Severity Source # 
Data Severity Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Severity -> c Severity #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Severity #

toConstr :: Severity -> Constr #

dataTypeOf :: Severity -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Severity) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Severity) #

gmapT :: (forall b. Data b => b -> b) -> Severity -> Severity #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Severity -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Severity -> r #

gmapQ :: (forall d. Data d => d -> u) -> Severity -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Severity -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Severity -> m Severity #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Severity -> m Severity #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Severity -> m Severity #

Ord Severity Source # 
Read Severity Source # 
Show Severity Source # 

startGhci :: String -> Maybe FilePath -> (Stream -> String -> IO ()) -> IO (Ghci, [Load]) Source #

Start GHCi, returning a function to perform further operation, as well as the result of the initial loading. If you do not call stopGhci then the underlying process may be leaked. The callback will be given the messages produced while loading, useful if invoking something like "cabal repl" which might compile dependent packages before really loading.

stopGhci :: Ghci -> IO () Source #

Stop GHCi. Attempts to interrupt and execute :quit:, but if that doesn't complete within 5 seconds it just terminates the process.

interrupt :: Ghci -> IO () Source #

Interrupt Ghci, stopping the current computation (if any), but leaving the process open to new input.

process :: Ghci -> ProcessHandle Source #

Obtain the progress handle behind a GHCi instance.

execStream :: Ghci -> String -> (Stream -> String -> IO ()) -> IO () Source #

Execute a command, calling a callback on each response. The callback will be called single threaded.

showModules :: Ghci -> IO [(String, FilePath)] Source #

List the modules currently loaded, with module name and source file.

reload :: Ghci -> IO [Load] Source #

Perform a reload, list the messages that reload generated.

exec :: Ghci -> String -> IO [String] Source #

Send a command, get lines of result. Must be called single-threaded.

quit :: Ghci -> IO () Source #

Send :quit and wait for the process to quit.