{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveGeneric #-}
module Server
( run
) where
import qualified Agda
import Control.Concurrent ( writeChan )
import Control.Monad ( void )
import Control.Monad.Reader ( MonadIO(liftIO) )
import Data.Aeson ( FromJSON
, ToJSON
)
import qualified Data.Aeson as JSON
import Data.Text ( pack )
import GHC.IO.IOMode ( IOMode(ReadWriteMode) )
import Language.LSP.Server hiding ( Options )
import Language.LSP.Types hiding ( Options(..)
, TextDocumentSyncClientCapabilities(..)
)
import Monad
import qualified Network.Simple.TCP as TCP
import Network.Socket ( socketToHandle )
import qualified Switchboard
import Switchboard ( Switchboard )
import qualified Server.Handler as Handler
import qualified Language.LSP.Server as LSP
import Options
run :: Options -> IO Int
run :: Options -> IO Int
run Options
options = do
case Options -> Maybe Int
optViaTCP Options
options of
Just Int
port -> do
IO Any -> IO ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void
(IO Any -> IO ()) -> IO Any -> IO ()
forall a b. (a -> b) -> a -> b
$ HostPreference -> String -> ((Socket, SockAddr) -> IO ()) -> IO Any
forall (m :: * -> *) a.
MonadIO m =>
HostPreference -> String -> ((Socket, SockAddr) -> IO ()) -> m a
TCP.serve (String -> HostPreference
TCP.Host String
"127.0.0.1") (Int -> String
forall a. Show a => a -> String
show Int
port)
(((Socket, SockAddr) -> IO ()) -> IO Any)
-> ((Socket, SockAddr) -> IO ()) -> IO Any
forall a b. (a -> b) -> a -> b
$ \(Socket
sock, SockAddr
_remoteAddr) -> do
Handle
handle <- Socket -> IOMode -> IO Handle
socketToHandle Socket
sock IOMode
ReadWriteMode
Int
_ <- LogAction IO (WithSeverity LspServerLog)
-> LogAction (LspM Config) (WithSeverity LspServerLog)
-> Handle
-> Handle
-> ServerDefinition Config
-> IO Int
forall config.
LogAction IO (WithSeverity LspServerLog)
-> LogAction (LspM config) (WithSeverity LspServerLog)
-> Handle
-> Handle
-> ServerDefinition config
-> IO Int
runServerWithHandles
#if MIN_VERSION_lsp(1,5,0)
LogAction IO (WithSeverity LspServerLog)
forall a. Monoid a => a
mempty LogAction (LspM Config) (WithSeverity LspServerLog)
forall a. Monoid a => a
mempty
#endif
Handle
handle Handle
handle (Options -> ServerDefinition Config
serverDefn Options
options)
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
Int -> IO Int
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Int
0
Maybe Int
Nothing -> do
ServerDefinition Config -> IO Int
forall config. ServerDefinition config -> IO Int
runServer (Options -> ServerDefinition Config
serverDefn Options
options)
where
serverDefn :: Options -> ServerDefinition Config
serverDefn :: Options -> ServerDefinition Config
serverDefn Options
options = ServerDefinition
{ defaultConfig :: Config
defaultConfig = Config
initConfig
, onConfigurationChange :: Config -> Value -> Either Text Config
onConfigurationChange = \Config
old Value
newRaw -> case Value -> Result Config
forall a. FromJSON a => Value -> Result a
JSON.fromJSON Value
newRaw of
JSON.Error String
s -> Text -> Either Text Config
forall a b. a -> Either a b
Left (Text -> Either Text Config) -> Text -> Either Text Config
forall a b. (a -> b) -> a -> b
$ String -> Text
pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ String
"Cannot parse server configuration: " String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
s
JSON.Success Config
new -> Config -> Either Text Config
forall a b. b -> Either a b
Right Config
new
, doInitialize :: LanguageContextEnv Config
-> Message 'Initialize
-> IO (Either ResponseError (LanguageContextEnv Config, Env))
doInitialize = \LanguageContextEnv Config
ctxEnv Message 'Initialize
_req -> do
Env
env <- LanguageContextEnv Config -> LspT Config IO Env -> IO Env
forall config (m :: * -> *) a.
LanguageContextEnv config -> LspT config m a -> m a
runLspT LanguageContextEnv Config
ctxEnv (Options -> LspT Config IO Env
forall (m :: * -> *).
(MonadIO m, MonadLsp Config m) =>
Options -> m Env
createInitEnv Options
options)
Switchboard
switchboard <- Env -> IO Switchboard
Switchboard.new Env
env
Switchboard -> LanguageContextEnv Config -> IO ()
Switchboard.setupLanguageContextEnv Switchboard
switchboard LanguageContextEnv Config
ctxEnv
Either ResponseError (LanguageContextEnv Config, Env)
-> IO (Either ResponseError (LanguageContextEnv Config, Env))
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either ResponseError (LanguageContextEnv Config, Env)
-> IO (Either ResponseError (LanguageContextEnv Config, Env)))
-> Either ResponseError (LanguageContextEnv Config, Env)
-> IO (Either ResponseError (LanguageContextEnv Config, Env))
forall a b. (a -> b) -> a -> b
$ (LanguageContextEnv Config, Env)
-> Either ResponseError (LanguageContextEnv Config, Env)
forall a b. b -> Either a b
Right (LanguageContextEnv Config
ctxEnv, Env
env)
, staticHandlers :: Handlers (ServerM (LspM Config))
staticHandlers = Handlers (ServerM (LspM Config))
handlers
, interpretHandler :: (LanguageContextEnv Config, Env) -> ServerM (LspM Config) <~> IO
interpretHandler = \(LanguageContextEnv Config
ctxEnv, Env
env) ->
(forall a. ServerM (LspM Config) a -> IO a)
-> (forall a. IO a -> ServerM (LspM Config) a)
-> ServerM (LspM Config) <~> IO
forall {k} (m :: k -> *) (n :: k -> *).
(forall (a :: k). m a -> n a)
-> (forall (a :: k). n a -> m a) -> m <~> n
Iso (LanguageContextEnv Config -> LspT Config IO a -> IO a
forall config (m :: * -> *) a.
LanguageContextEnv config -> LspT config m a -> m a
runLspT LanguageContextEnv Config
ctxEnv (LspT Config IO a -> IO a)
-> (ServerM (LspM Config) a -> LspT Config IO a)
-> ServerM (LspM Config) a
-> IO a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Env -> ServerM (LspM Config) a -> LspT Config IO a
forall (m :: * -> *) a. Env -> ServerM m a -> m a
runServerM Env
env) IO a -> ServerM (LspM Config) a
forall a. IO a -> ServerM (LspM Config) a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO
, options :: Options
options = Options
lspOptions
}
lspOptions :: LSP.Options
lspOptions :: Options
lspOptions = Options
defaultOptions { textDocumentSync = Just syncOptions }
syncOptions :: TextDocumentSyncOptions
syncOptions :: TextDocumentSyncOptions
syncOptions = TextDocumentSyncOptions { $sel:_openClose:TextDocumentSyncOptions :: Maybe Bool
_openClose = Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
True
, $sel:_change:TextDocumentSyncOptions :: Maybe TextDocumentSyncKind
_change = TextDocumentSyncKind -> Maybe TextDocumentSyncKind
forall a. a -> Maybe a
Just TextDocumentSyncKind
changeOptions
, $sel:_willSave:TextDocumentSyncOptions :: Maybe Bool
_willSave = Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
False
, $sel:_willSaveWaitUntil:TextDocumentSyncOptions :: Maybe Bool
_willSaveWaitUntil = Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
False
, $sel:_save:TextDocumentSyncOptions :: Maybe (Bool |? SaveOptions)
_save = (Bool |? SaveOptions) -> Maybe (Bool |? SaveOptions)
forall a. a -> Maybe a
Just ((Bool |? SaveOptions) -> Maybe (Bool |? SaveOptions))
-> (Bool |? SaveOptions) -> Maybe (Bool |? SaveOptions)
forall a b. (a -> b) -> a -> b
$ SaveOptions -> Bool |? SaveOptions
forall a b. b -> a |? b
InR SaveOptions
saveOptions
}
changeOptions :: TextDocumentSyncKind
changeOptions :: TextDocumentSyncKind
changeOptions = TextDocumentSyncKind
TdSyncIncremental
saveOptions :: SaveOptions
saveOptions :: SaveOptions
saveOptions = Maybe Bool -> SaveOptions
SaveOptions (Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
True)
handlers :: Handlers (ServerM (LspM Config))
handlers :: Handlers (ServerM (LspM Config))
handlers = [Handlers (ServerM (LspM Config))]
-> Handlers (ServerM (LspM Config))
forall a. Monoid a => [a] -> a
mconcat
[
SMethod 'CustomMethod
-> Handler (ServerM (LspM Config)) 'CustomMethod
-> Handlers (ServerM (LspM Config))
forall (m :: Method 'FromClient 'Request) (f :: * -> *).
SMethod m -> Handler f m -> Handlers f
requestHandler (Text -> SMethod 'CustomMethod
forall {f :: From} {t :: MethodType}. Text -> SMethod 'CustomMethod
SCustomMethod Text
"agda") (Handler (ServerM (LspM Config)) 'CustomMethod
-> Handlers (ServerM (LspM Config)))
-> Handler (ServerM (LspM Config)) 'CustomMethod
-> Handlers (ServerM (LspM Config))
forall a b. (a -> b) -> a -> b
$ \RequestMessage 'CustomMethod
req Either ResponseError Value -> ReaderT Env (LspM Config) ()
responder -> do
let RequestMessage Text
_ LspId 'CustomMethod
_i SMethod 'CustomMethod
_ MessageParams 'CustomMethod
params = RequestMessage 'CustomMethod
req
Value
response <- Value -> ServerM (LspM Config) Value
forall (m :: * -> *). MonadIO m => Value -> ServerM m Value
Agda.sendCommand MessageParams 'CustomMethod
Value
params
Either ResponseError Value -> ReaderT Env (LspM Config) ()
responder (Either ResponseError Value -> ReaderT Env (LspM Config) ())
-> Either ResponseError Value -> ReaderT Env (LspM Config) ()
forall a b. (a -> b) -> a -> b
$ Value -> Either ResponseError Value
forall a b. b -> Either a b
Right Value
response
,
SMethod 'TextDocumentHover
-> Handler (ServerM (LspM Config)) 'TextDocumentHover
-> Handlers (ServerM (LspM Config))
forall (m :: Method 'FromClient 'Request) (f :: * -> *).
SMethod m -> Handler f m -> Handlers f
requestHandler SMethod 'TextDocumentHover
STextDocumentHover (Handler (ServerM (LspM Config)) 'TextDocumentHover
-> Handlers (ServerM (LspM Config)))
-> Handler (ServerM (LspM Config)) 'TextDocumentHover
-> Handlers (ServerM (LspM Config))
forall a b. (a -> b) -> a -> b
$ \RequestMessage 'TextDocumentHover
req Either ResponseError (Maybe Hover) -> ReaderT Env (LspM Config) ()
responder -> do
let
RequestMessage Text
_ LspId 'TextDocumentHover
_ SMethod 'TextDocumentHover
_ (HoverParams (TextDocumentIdentifier Uri
uri) Position
pos Maybe ProgressToken
_workDone)
= RequestMessage 'TextDocumentHover
req
Maybe Hover
result <- Uri -> Position -> ServerM (LspM Config) (Maybe Hover)
Handler.onHover Uri
uri Position
pos
Either ResponseError (Maybe Hover) -> ReaderT Env (LspM Config) ()
responder (Either ResponseError (Maybe Hover)
-> ReaderT Env (LspM Config) ())
-> Either ResponseError (Maybe Hover)
-> ReaderT Env (LspM Config) ()
forall a b. (a -> b) -> a -> b
$ Maybe Hover -> Either ResponseError (Maybe Hover)
forall a b. b -> Either a b
Right Maybe Hover
result
]