haskell-tools-daemon-1.0.0.4: Background process for Haskell-tools that editors can connect to.

Safe HaskellNone
LanguageHaskell2010

Language.Haskell.Tools.Daemon.Protocol

Contents

Description

This module declares the messages that can be sent from the client to the daemon engine and from the engine to the client.

Synopsis

Documentation

data ClientMessage Source #

The messages expected from the client.

Constructors

KeepAlive

A simple ping message to check that the server is running.

Reset

A message that instructs the server to reset its internal state and re-load loaded packages.

Handshake

Tells the client version and asks the servers version.

Fields

SetPackageDB

Sets the package database for the engine to use.

Fields

AddPackages

Registers packages to the engine. They will be subject to subsequent refactorings. Will cause the packages to be loaded, resulting in LoadingModules, LoadedModule or CompilationProblem responses.

Fields

RemovePackages

Deregisters the given packages from the engine. They will not be subjects of further refactorings.

Fields

SetWorkingDir

Sets the working directory for the compilation. Important when compiling code that loads resources based on relative pathes.

SetGHCFlags

Sets the compilation flags. The unused flags are returned via the UnusedFlags response.

Fields

PerformRefactoring

Orders the engine to perform the refactoring on the module given with the selection and details. Successful refactorings will cause re-loading of modules. If shutdownAfter or diffMode is not set, after the refactoring, modules are re-loaded, LoadingModules, LoadedModule responses are sent.

Fields

UndoLast

Asks the daemon to undo the last refactoring.

Disconnect

Stops the engine. It replies with Disconnected.

ReLoad

Instructs the engine to re-load a changed module. LoadingModules, LoadedModule responses may be sent.

Stop

Stops the server. OBSOLATE

Instances

Show ClientMessage Source # 
Generic ClientMessage Source # 

Associated Types

type Rep ClientMessage :: * -> * #

FromJSON ClientMessage Source # 
type Rep ClientMessage Source # 
type Rep ClientMessage = D1 * (MetaData "ClientMessage" "Language.Haskell.Tools.Daemon.Protocol" "haskell-tools-daemon-1.0.0.4-5xRPvdYipy5J23vtgQpZOi" False) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "KeepAlive" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "Reset" PrefixI False) (U1 *)) (C1 * (MetaCons "Handshake" PrefixI True) (S1 * (MetaSel (Just Symbol "clientVersion") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Int]))))) ((:+:) * (C1 * (MetaCons "SetPackageDB" PrefixI True) (S1 * (MetaSel (Just Symbol "pkgDB") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * PackageDB))) ((:+:) * (C1 * (MetaCons "AddPackages" PrefixI True) (S1 * (MetaSel (Just Symbol "addedPathes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [FilePath]))) (C1 * (MetaCons "RemovePackages" PrefixI True) (S1 * (MetaSel (Just Symbol "removedPathes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [FilePath])))))) ((:+:) * ((:+:) * (C1 * (MetaCons "SetWorkingDir" PrefixI True) (S1 * (MetaSel (Just Symbol "newWorkingDir") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * FilePath))) ((:+:) * (C1 * (MetaCons "SetGHCFlags" PrefixI True) (S1 * (MetaSel (Just Symbol "ghcFlags") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [String]))) (C1 * (MetaCons "PerformRefactoring" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "refactoring") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String)) ((:*:) * (S1 * (MetaSel (Just Symbol "modulePath") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * FilePath)) (S1 * (MetaSel (Just Symbol "editorSelection") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String)))) ((:*:) * (S1 * (MetaSel (Just Symbol "details") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [String])) ((:*:) * (S1 * (MetaSel (Just Symbol "shutdownAfter") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool)) (S1 * (MetaSel (Just Symbol "diffMode") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool)))))))) ((:+:) * ((:+:) * (C1 * (MetaCons "UndoLast" PrefixI False) (U1 *)) (C1 * (MetaCons "Disconnect" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "ReLoad" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "addedModules") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [FilePath])) ((:*:) * (S1 * (MetaSel (Just Symbol "changedModules") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [FilePath])) (S1 * (MetaSel (Just Symbol "removedModules") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [FilePath]))))) (C1 * (MetaCons "Stop" PrefixI False) (U1 *))))))

data ResponseMsg Source #

The possible responses that the server can give.

Constructors

KeepAliveResponse

A response to KeepAlive

HandshakeResponse

Tells the version of the server.

Fields

ErrorMessage

An error message marking internal problems or user mistakes. TODO: separate internal problems and user mistakes.

Fields

CompilationProblem

A response that tells there are errors in the source code given.

Fields

DiffInfo

Information about changes that would be caused by the refactoring.

Fields

LoadingModules

The traversal of the project is done, now the engine is loading the given modules.

Fields

LoadedModule

The engine has loaded the given module.

UnusedFlags

Returns the flags that are not used by the engine.

Fields

Disconnected

The engine has closed the connection.

Instances

Show ResponseMsg Source # 
Generic ResponseMsg Source # 

Associated Types

type Rep ResponseMsg :: * -> * #

ToJSON ResponseMsg Source # 
type Rep ResponseMsg Source # 
type Rep ResponseMsg = D1 * (MetaData "ResponseMsg" "Language.Haskell.Tools.Daemon.Protocol" "haskell-tools-daemon-1.0.0.4-5xRPvdYipy5J23vtgQpZOi" False) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "KeepAliveResponse" PrefixI False) (U1 *)) (C1 * (MetaCons "HandshakeResponse" PrefixI True) (S1 * (MetaSel (Just Symbol "serverVersion") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Int])))) ((:+:) * (C1 * (MetaCons "ErrorMessage" PrefixI True) (S1 * (MetaSel (Just Symbol "errorMsg") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String))) (C1 * (MetaCons "CompilationProblem" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "markers") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Marker])) (S1 * (MetaSel (Just Symbol "errorHints") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [String])))))) ((:+:) * ((:+:) * (C1 * (MetaCons "DiffInfo" PrefixI True) (S1 * (MetaSel (Just Symbol "diffInfo") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String))) (C1 * (MetaCons "LoadingModules" PrefixI True) (S1 * (MetaSel (Just Symbol "modulesToLoad") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [FilePath])))) ((:+:) * (C1 * (MetaCons "LoadedModule" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "loadedModulePath") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * FilePath)) (S1 * (MetaSel (Just Symbol "loadedModuleName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String)))) ((:+:) * (C1 * (MetaCons "UnusedFlags" PrefixI True) (S1 * (MetaSel (Just Symbol "unusedFlags") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [String]))) (C1 * (MetaCons "Disconnected" PrefixI False) (U1 *))))))

data Marker Source #

Constructors

Marker 

Instances

Eq Marker Source # 

Methods

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

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

Show Marker Source # 
Generic Marker Source # 

Associated Types

type Rep Marker :: * -> * #

Methods

from :: Marker -> Rep Marker x #

to :: Rep Marker x -> Marker #

ToJSON Marker Source # 
type Rep Marker Source # 
type Rep Marker = D1 * (MetaData "Marker" "Language.Haskell.Tools.Daemon.Protocol" "haskell-tools-daemon-1.0.0.4-5xRPvdYipy5J23vtgQpZOi" False) (C1 * (MetaCons "Marker" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "location") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * SrcSpan)) ((:*:) * (S1 * (MetaSel (Just Symbol "severity") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Severity)) (S1 * (MetaSel (Just Symbol "message") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String)))))

data Severity Source #

Constructors

Error 
Warning 
Info 

Instances

Eq Severity Source # 
Show Severity Source # 
Generic Severity Source # 

Associated Types

type Rep Severity :: * -> * #

Methods

from :: Severity -> Rep Severity x #

to :: Rep Severity x -> Severity #

ToJSON Severity Source # 
type Rep Severity Source # 
type Rep Severity = D1 * (MetaData "Severity" "Language.Haskell.Tools.Daemon.Protocol" "haskell-tools-daemon-1.0.0.4-5xRPvdYipy5J23vtgQpZOi" False) ((:+:) * (C1 * (MetaCons "Error" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "Warning" PrefixI False) (U1 *)) (C1 * (MetaCons "Info" PrefixI False) (U1 *))))

data UndoRefactor Source #

Instances

Show UndoRefactor Source # 
Generic UndoRefactor Source # 

Associated Types

type Rep UndoRefactor :: * -> * #

NFData UndoRefactor Source # 

Methods

rnf :: UndoRefactor -> () #

ToJSON UndoRefactor Source # 
type Rep UndoRefactor Source # 
type Rep UndoRefactor = D1 * (MetaData "UndoRefactor" "Language.Haskell.Tools.Daemon.Protocol" "haskell-tools-daemon-1.0.0.4-5xRPvdYipy5J23vtgQpZOi" False) ((:+:) * (C1 * (MetaCons "RemoveAdded" PrefixI True) (S1 * (MetaSel (Just Symbol "undoRemovePath") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * FilePath))) ((:+:) * (C1 * (MetaCons "RestoreRemoved" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "undoRestorePath") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * FilePath)) (S1 * (MetaSel (Just Symbol "undoRestoreContents") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String)))) (C1 * (MetaCons "UndoChanges" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "undoChangedPath") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * FilePath)) (S1 * (MetaSel (Just Symbol "undoDiff") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * FileDiff))))))

type FileDiff = [(Int, Int, String)] Source #

Orphan instances