| Safe Haskell | None |
|---|---|
| Language | Haskell98 |
HsDev.Server.Types
- type ServerMonadBase m = (MonadCatchIO m, MonadBaseControl IO m)
- data Session = Session {
- sessionDatabase :: Async Database
- sessionWriteCache :: Database -> ServerM IO ()
- sessionReadCache :: (FilePath -> ExceptT String IO Structured) -> ServerM IO (Maybe Database)
- sessionLog :: Level -> String -> IO ()
- sessionLogger :: Log
- sessionListenLog :: IO [String]
- sessionLogWait :: IO ()
- sessionWatcher :: Watcher
- sessionGhc :: Worker Ghc
- sessionGhci :: Worker Ghc
- sessionGhcMod :: Worker (ReaderT WorkerMap IO)
- sessionExit :: IO ()
- sessionWait :: IO ()
- sessionDefines :: [(String, String)]
- class (ServerMonadBase m, MonadLog m) => SessionMonad m where
- getSession :: m Session
- 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 ()
- data CommandError = CommandError {}
- commandErrorMsg :: Lens' CommandError String
- commandErrorDetails :: Lens' CommandError [Pair]
- commandError :: CommandMonad m => String -> [Pair] -> m a
- commandError_ :: CommandMonad m => String -> m a
- class (SessionMonad m, MonadError CommandError m, MonadPlus m) => CommandMonad m where
- getOptions :: m CommandOptions
- askOptions :: CommandMonad m => (CommandOptions -> a) -> m a
- newtype ClientM m a = ClientM {
- runClientM :: ServerM (ExceptT CommandError (ReaderT CommandOptions m)) a
- withSession :: Session -> ServerM m a -> m a
- serverListen :: SessionMonad m => m [String]
- serverWait :: SessionMonad m => m ()
- serverUpdateDB :: SessionMonad m => Database -> m ()
- serverWriteCache :: SessionMonad m => Database -> m ()
- serverReadCache :: SessionMonad m => (FilePath -> ExceptT String IO Structured) -> m (Maybe Database)
- 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 ServerOpts = ServerOpts {}
- data ClientOpts = ClientOpts {
- clientPort :: Int
- clientPretty :: Bool
- clientStdin :: Bool
- clientTimeout :: Int
- clientSilent :: Bool
- serverOptsArgs :: ServerOpts -> [String]
- data Request = Request {}
- data Command
- = Ping
- | Listen
- | AddData { }
- | Scan {
- scanProjects :: [FilePath]
- scanSandboxes :: [Cabal]
- scanFiles :: [FilePath]
- scanPaths :: [FilePath]
- scanContents :: [FileContents]
- scanGhcOpts :: [String]
- scanDocs :: Bool
- scanInferTypes :: Bool
- | RefineDocs {
- docsProjects :: [FilePath]
- docsFiles :: [FilePath]
- docsModules :: [String]
- | InferTypes {
- inferProjects :: [FilePath]
- inferFiles :: [FilePath]
- inferModules :: [String]
- | Remove {
- removeProjects :: [FilePath]
- removeSandboxes :: [Cabal]
- removeFiles :: [FilePath]
- | RemoveAll
- | InfoModules [TargetFilter]
- | InfoPackages
- | InfoProjects
- | InfoSandboxes
- | InfoSymbol SearchQuery [TargetFilter] Bool
- | InfoModule SearchQuery [TargetFilter]
- | InfoResolve FilePath Bool
- | InfoProject (Either String FilePath)
- | InfoSandbox FilePath
- | Lookup String FilePath
- | Whois String FilePath
- | ResolveScopeModules SearchQuery FilePath
- | ResolveScope SearchQuery Bool FilePath
- | Complete String Bool FilePath
- | Hayoo {
- hayooQuery :: String
- hayooPage :: Int
- hayooPages :: Int
- | CabalList {
- cabalListPackages :: [String]
- | Lint {
- lintFiles :: [FilePath]
- lintContents :: [FileContents]
- | Check {
- checkFiles :: [FilePath]
- checkContents :: [FileContents]
- checkGhcOpts :: [String]
- | CheckLint { }
- | Types {
- typesFiles :: [FilePath]
- typesContents :: [FileContents]
- typesGhcOpts :: [String]
- | GhcMod { }
- | AutoFix { }
- | GhcEval {
- ghcEvalExpressions :: [String]
- | Link { }
- | Exit
- data AddedContents
- data GhcModCommand
- = GhcModLang
- | GhcModFlags
- | GhcModType Position FilePath [String]
- | GhcModLint [FilePath] [String]
- | GhcModCheck [FilePath] [String]
- | GhcModCheckLint [FilePath] [String] [String]
- data AutoFixCommand
- data FileContents = FileContents FilePath String
- data TargetFilter
- data SearchQuery = SearchQuery String SearchType
- data SearchType
- class FromCmd a where
Documentation
type ServerMonadBase m = (MonadCatchIO m, MonadBaseControl IO m) Source
Constructors
| Session | |
Fields
| |
Instances
| Monad m => MonadReader Session (ServerM m) Source |
class (ServerMonadBase m, MonadLog m) => SessionMonad m where Source
Methods
getSession :: m Session Source
Instances
| ServerMonadBase m => SessionMonad (ServerM m) Source | |
| ServerMonadBase m => SessionMonad (ClientM m) Source | |
| ServerMonadBase m => SessionMonad (UpdateM m) Source |
askSession :: SessionMonad m => (Session -> a) -> m a Source
Constructors
| ServerM | |
Fields
| |
Instances
| 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 | |
| MonadCatchIO m => MonadCatchIO (ServerM m) Source | |
| MonadThrow m => MonadThrow (ServerM m) Source | |
| MonadCatch m => MonadCatch (ServerM m) Source | |
| MonadIO m => MonadIO (ServerM m) Source | |
| MonadCatchIO m => MonadLog (ServerM m) Source | |
| ServerMonadBase m => SessionMonad (ServerM m) Source | |
| type StM (ServerM m) a = StM (ReaderT Session m) a Source |
data CommandOptions Source
Constructors
| CommandOptions | |
Fields
| |
Instances
data CommandError Source
Constructors
| CommandError | |
Fields | |
Instances
| Monoid CommandError Source | |
| Monad m => MonadError CommandError (ClientM m) Source | |
| Monad m => MonadError CommandError (UpdateM m) |
commandError :: CommandMonad m => String -> [Pair] -> m a Source
commandError_ :: CommandMonad m => String -> m a Source
class (SessionMonad m, MonadError CommandError m, MonadPlus m) => CommandMonad m where Source
Methods
Instances
| ServerMonadBase m => CommandMonad (ClientM m) Source | |
| ServerMonadBase m => CommandMonad (UpdateM m) Source |
askOptions :: CommandMonad m => (CommandOptions -> a) -> m a Source
Constructors
| ClientM | |
Fields
| |
Instances
| MonadTrans ClientM Source | |
| Monad m => MonadError CommandError (ClientM m) 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 | |
| Monad m => Applicative (ClientM m) Source | |
| MonadCatchIO m => MonadCatchIO (ClientM m) Source | |
| Monad m => Alternative (ClientM m) Source | |
| Monad m => MonadPlus (ClientM m) Source | |
| MonadThrow m => MonadThrow (ClientM m) Source | |
| MonadCatch m => MonadCatch (ClientM m) Source | |
| MonadIO m => MonadIO (ClientM m) Source | |
| MonadCatchIO m => MonadLog (ClientM m) Source | |
| ServerMonadBase m => SessionMonad (ClientM m) Source | |
| ServerMonadBase m => CommandMonad (ClientM m) Source | |
| type StM (ClientM m) a = StM (ServerM (ExceptT CommandError (ReaderT CommandOptions m))) a Source |
withSession :: Session -> ServerM m a -> m a Source
Run action on session
serverListen :: SessionMonad m => m [String] Source
Listen server's log
serverWait :: SessionMonad m => m () Source
Wait for server
serverUpdateDB :: SessionMonad m => Database -> m () Source
Update database
serverWriteCache :: SessionMonad m => Database -> m () Source
Server write cache
serverReadCache :: SessionMonad m => (FilePath -> ExceptT String IO Structured) -> m (Maybe Database) Source
Server read cache
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
Constructors
| Version | |
| Start ServerOpts | |
| Run ServerOpts | |
| Stop ClientOpts | |
| Connect ClientOpts | |
| Remote ClientOpts Bool Command |
Instances
data ServerOpts Source
Server options
Constructors
| ServerOpts | |
Fields
| |
Instances
data ClientOpts Source
Client options
Constructors
| ClientOpts | |
Fields
| |
Instances
serverOptsArgs :: ServerOpts -> [String] Source
Constructors
| Request | |
Fields
| |
Command from client
Constructors
data AddedContents Source
Constructors
| AddedDatabase Database | |
| AddedModule InspectedModule | |
| AddedProject Project |
data GhcModCommand Source
Constructors
| GhcModLang | |
| GhcModFlags | |
| GhcModType Position FilePath [String] | |
| GhcModLint [FilePath] [String] | |
| GhcModCheck [FilePath] [String] | |
| GhcModCheckLint [FilePath] [String] [String] |
data AutoFixCommand Source
Constructors
| AutoFixShow [Note OutputMessage] | |
| AutoFixFix [Note Correction] [Note Correction] Bool |
data FileContents Source
Constructors
| FileContents FilePath String |
data TargetFilter Source
data SearchQuery Source
Constructors
| SearchQuery String SearchType |
data SearchType Source
Constructors
| SearchExact | |
| SearchPrefix | |
| SearchInfix | |
| SearchSuffix | |
| SearchRegex |
Instances