Safe Haskell | None |
---|---|
Language | Haskell98 |
- type ServerMonadBase m = (MonadIO m, MonadMask m, MonadBaseControl IO m, Alternative m, MonadPlus m)
- data SessionLog = SessionLog {
- sessionLogger :: Log
- sessionListenLog :: IO [Message]
- sessionLogWait :: IO ()
- data Session = Session {
- sessionSqlDatabase :: Connection
- sessionSqlPath :: String
- sessionLog :: SessionLog
- sessionWatcher :: Watcher
- sessionFileContents :: Path -> Maybe Text -> IO ()
- sessionGhc :: GhcWorker
- sessionUpdater :: Worker (ServerM IO)
- sessionResolveEnvironment :: LookupTable (Maybe Path) (Environment, FixitiesTable)
- sessionExit :: IO ()
- sessionWait :: IO ()
- sessionClients :: Chan (IO ())
- sessionDefines :: [(String, String)]
- class (ServerMonadBase m, MonadLog m) => SessionMonad m where
- askSession :: SessionMonad m => (Session -> a) -> m a
- newtype ServerM m a = ServerM {
- runServerM :: ReaderT Session m a
- data CommandOptions = CommandOptions {
- commandOptionsRoot :: FilePath
- commandOptionsNotify :: Notification -> IO ()
- commandOptionsLink :: IO ()
- commandOptionsHold :: IO ()
- class (SessionMonad m, MonadPlus m) => CommandMonad m where
- askOptions :: CommandMonad m => (CommandOptions -> a) -> m a
- newtype ClientM m a = ClientM {
- runClientM :: ServerM (ReaderT CommandOptions m) a
- withSession :: Session -> ServerM m a -> m a
- serverListen :: SessionMonad m => m [Message]
- serverSetLogLevel :: SessionMonad m => Level -> m Level
- serverWait :: SessionMonad m => m ()
- serverWaitClients :: SessionMonad m => m ()
- serverSqlDatabase :: SessionMonad m => m Connection
- openSqlConnection :: SessionMonad m => m Connection
- closeSqlConnection :: SessionMonad m => Connection -> m ()
- withSqlConnection :: SessionMonad m => m a -> m a
- withSqlTransaction :: SessionMonad m => ServerM IO a -> m a
- serverSetFileContents :: SessionMonad m => Path -> Maybe Text -> m ()
- inSessionGhc :: SessionMonad m => GhcM a -> m a
- inSessionUpdater :: SessionMonad m => ServerM IO a -> m a
- postSessionUpdater :: SessionMonad m => ServerM IO a -> m (Async a)
- serverExit :: SessionMonad m => m ()
- commandRoot :: CommandMonad m => m FilePath
- commandNotify :: CommandMonad m => Notification -> m ()
- commandLink :: CommandMonad m => m ()
- commandHold :: CommandMonad m => m ()
- data ServerCommand
- data ConnectionPort
- data ServerOpts = ServerOpts {}
- silentOpts :: ServerOpts
- data ClientOpts = ClientOpts {}
- serverOptsArgs :: ServerOpts -> [String]
- data Request = Request {}
- data Command
- = Ping
- | Listen (Maybe String)
- | SetLogLevel String
- | Scan {
- scanProjects :: [Path]
- scanCabal :: Bool
- scanSandboxes :: [Path]
- scanFiles :: [FileSource]
- scanPaths :: [Path]
- scanGhcOpts :: [String]
- scanDocs :: Bool
- scanInferTypes :: Bool
- | SetFileContents Path (Maybe Text)
- | RefineDocs {
- docsProjects :: [Path]
- docsFiles :: [Path]
- | InferTypes {
- inferProjects :: [Path]
- inferFiles :: [Path]
- | Remove {
- removeProjects :: [Path]
- removeCabal :: Bool
- removeSandboxes :: [Path]
- removeFiles :: [Path]
- | RemoveAll
- | InfoPackages
- | InfoProjects
- | InfoSandboxes
- | InfoSymbol SearchQuery [TargetFilter] Bool Bool
- | InfoModule SearchQuery [TargetFilter] Bool Bool
- | InfoProject (Either Text Path)
- | InfoSandbox Path
- | Lookup Text Path
- | Whois Text Path
- | Whoat Int Int Path
- | ResolveScopeModules SearchQuery Path
- | ResolveScope SearchQuery Path
- | FindUsages Int Int Path
- | Complete Text Bool Path
- | Hayoo {
- hayooQuery :: String
- hayooPage :: Int
- hayooPages :: Int
- | CabalList {
- cabalListPackages :: [Text]
- | UnresolvedSymbols {
- unresolvedFiles :: [Path]
- | Lint {
- lintFiles :: [FileSource]
- lintHlintOpts :: [String]
- | Check {
- checkFiles :: [FileSource]
- checkGhcOpts :: [String]
- checkClear :: Bool
- | CheckLint {
- checkLintFiles :: [FileSource]
- checkLintGhcOpts :: [String]
- checkLintOpts :: [String]
- checkLinkClear :: Bool
- | Types {
- typesFiles :: [FileSource]
- typesGhcOpts :: [String]
- typesClear :: Bool
- | AutoFix [Note OutputMessage]
- | Refactor [Note Refact] [Note Refact] Bool
- | Rename Text Text Path
- | GhcEval { }
- | GhcType { }
- | Langs
- | Flags
- | Link { }
- | StopGhc
- | Exit
- data FileSource = FileSource {
- fileSource :: Path
- fileContents :: Maybe Text
- data TargetFilter
- data SearchQuery = SearchQuery Text SearchType
- data SearchType
- class FromCmd a where
Documentation
type ServerMonadBase m = (MonadIO m, MonadMask m, MonadBaseControl IO m, Alternative m, MonadPlus m) Source #
data SessionLog Source #
SessionLog | |
|
Session | |
|
class (ServerMonadBase m, MonadLog m) => SessionMonad m where Source #
getSession :: m Session Source #
localSession :: (Session -> Session) -> m a -> m a Source #
ServerMonadBase m => SessionMonad (ClientM m) Source # | |
ServerMonadBase m => SessionMonad (ServerM m) Source # | |
ServerMonadBase m => SessionMonad (UpdateM m) Source # | |
(SessionMonad m, Monoid w) => SessionMonad (WriterT w m) Source # | |
SessionMonad m => SessionMonad (StateT s m) Source # | |
SessionMonad m => SessionMonad (ReaderT * r m) Source # | |
askSession :: SessionMonad m => (Session -> a) -> m a Source #
ServerM | |
|
MonadTrans ServerM Source # | |
Monad m => MonadReader Session (ServerM m) Source # | |
MonadBase b m => MonadBase b (ServerM m) Source # | |
MonadBaseControl b m => MonadBaseControl b (ServerM m) Source # | |
Monad m => Monad (ServerM m) Source # | |
Functor m => Functor (ServerM m) Source # | |
Applicative m => Applicative (ServerM m) Source # | |
MonadPlus m => MonadPlus (ServerM m) Source # | |
Alternative m => Alternative (ServerM m) Source # | |
MonadIO m => MonadIO (ServerM m) Source # | |
MonadThrow m => MonadThrow (ServerM m) Source # | |
MonadCatch m => MonadCatch (ServerM m) Source # | |
MonadMask m => MonadMask (ServerM m) Source # | |
(MonadIO m, MonadMask m) => MonadLog (ServerM m) Source # | |
ServerMonadBase m => SessionMonad (ServerM m) Source # | |
MFunctor * ServerM Source # | |
type StM (ServerM m) a Source # | |
data CommandOptions Source #
CommandOptions | |
|
class (SessionMonad m, MonadPlus m) => CommandMonad m where Source #
getOptions :: m CommandOptions Source #
ServerMonadBase m => CommandMonad (ClientM m) Source # | |
ServerMonadBase m => CommandMonad (UpdateM m) Source # | |
(CommandMonad m, Monoid w) => CommandMonad (WriterT w m) Source # | |
CommandMonad m => CommandMonad (StateT s m) Source # | |
CommandMonad m => CommandMonad (ReaderT * r m) Source # | |
askOptions :: CommandMonad m => (CommandOptions -> a) -> m a Source #
ClientM | |
|
MonadTrans ClientM Source # | |
MonadBase b m => MonadBase b (ClientM m) Source # | |
MonadBaseControl b m => MonadBaseControl b (ClientM m) Source # | |
Monad m => Monad (ClientM m) Source # | |
Functor m => Functor (ClientM m) Source # | |
Applicative m => Applicative (ClientM m) Source # | |
MonadPlus m => MonadPlus (ClientM m) Source # | |
Alternative m => Alternative (ClientM m) Source # | |
MonadIO m => MonadIO (ClientM m) Source # | |
MonadThrow m => MonadThrow (ClientM m) Source # | |
MonadCatch m => MonadCatch (ClientM m) Source # | |
MonadMask m => MonadMask (ClientM m) Source # | |
(MonadIO m, MonadMask m) => MonadLog (ClientM m) Source # | |
ServerMonadBase m => CommandMonad (ClientM m) Source # | |
ServerMonadBase m => SessionMonad (ClientM m) Source # | |
MFunctor * ClientM Source # | |
type StM (ClientM m) a Source # | |
withSession :: Session -> ServerM m a -> m a Source #
Run action on session
serverListen :: SessionMonad m => m [Message] Source #
Listen server's log
serverSetLogLevel :: SessionMonad m => Level -> m Level Source #
Set server's log config
serverWait :: SessionMonad m => m () Source #
Wait for server
serverWaitClients :: SessionMonad m => m () Source #
Wait while clients disconnects
serverSqlDatabase :: SessionMonad m => m Connection Source #
Get sql connection
openSqlConnection :: SessionMonad m => m Connection Source #
Open new sql connection
closeSqlConnection :: SessionMonad m => Connection -> m () Source #
Close sql connection
withSqlConnection :: SessionMonad m => m a -> m a Source #
Locally opens new connection, updating Session
withSqlTransaction :: SessionMonad m => ServerM IO a -> m a Source #
With sql transaction
serverSetFileContents :: SessionMonad m => Path -> Maybe Text -> m () Source #
Set custom file contents
inSessionGhc :: SessionMonad m => GhcM a -> m a Source #
In ghc session
inSessionUpdater :: SessionMonad m => ServerM IO a -> m a Source #
In updater
postSessionUpdater :: SessionMonad m => ServerM IO a -> m (Async a) Source #
Post to updater and return
serverExit :: SessionMonad m => m () Source #
Exit session
commandRoot :: CommandMonad m => m FilePath Source #
commandNotify :: CommandMonad m => Notification -> m () Source #
commandLink :: CommandMonad m => m () Source #
commandHold :: CommandMonad m => m () Source #
data ServerCommand Source #
Server control command
data ConnectionPort Source #
data ServerOpts Source #
Server options
silentOpts :: ServerOpts Source #
Silent server with no connection, useful for ghci
data ClientOpts Source #
Client options
ClientOpts | |
|
serverOptsArgs :: ServerOpts -> [String] Source #
Command from client
data FileSource Source #
data TargetFilter Source #
data SearchQuery Source #
data SearchType Source #