Copyright | (C) 2025 Matthias Pall Gissurarson |
---|---|
License | MIT |
Maintainer | mpg@mpg.is |
Stability | experimental |
Portability | GHC |
Safe Haskell | Safe-Inferred |
Language | GHC2021 |
MCP.Server
Description
This module provides a complete MCP server implementation, including message handling, state management, and JSON-RPC communication over standard input/output streams.
Synopsis
- class Monad m => MCPServer m where
- handleListResources :: ListResourcesParams -> m ListResourcesResult
- handleReadResource :: ReadResourceParams -> m ReadResourceResult
- handleListResourceTemplates :: ListResourceTemplatesParams -> m ListResourceTemplatesResult
- handleListPrompts :: ListPromptsParams -> m ListPromptsResult
- handleGetPrompt :: GetPromptParams -> m GetPromptResult
- handleListTools :: ListToolsParams -> m ListToolsResult
- handleCallTool :: CallToolParams -> m CallToolResult
- handleComplete :: CompleteParams -> m CompleteResult
- handleSetLevel :: SetLevelParams -> m ()
- data ServerState = ServerState {}
- type MCPServerM = ReaderT ServerConfig (StateT ServerState (ExceptT Text IO))
- runMCPServer :: ServerConfig -> ServerState -> MCPServerM a -> IO (Either Text (a, ServerState))
- handleMessage :: MCPServer MCPServerM => ByteString -> MCPServerM (Maybe ())
- handleRequest :: MCPServer MCPServerM => JSONRPCRequest -> MCPServerM ()
- handleNotification :: JSONRPCNotification -> MCPServerM ()
- runServer :: MCPServer MCPServerM => ServerConfig -> IO ()
- data ServerConfig = ServerConfig {}
- sendResponse :: (MonadIO m, ToJSON a) => Handle -> RequestId -> a -> m ()
- sendNotification :: (MonadIO m, ToJSON a) => Handle -> Text -> a -> m ()
- sendError :: MonadIO m => Handle -> RequestId -> JSONRPCErrorInfo -> m ()
Server Interface
class Monad m => MCPServer m where Source #
Type class for implementing MCP server handlers
Methods
handleListResources :: ListResourcesParams -> m ListResourcesResult Source #
handleReadResource :: ReadResourceParams -> m ReadResourceResult Source #
handleListResourceTemplates :: ListResourceTemplatesParams -> m ListResourceTemplatesResult Source #
handleListPrompts :: ListPromptsParams -> m ListPromptsResult Source #
handleGetPrompt :: GetPromptParams -> m GetPromptResult Source #
handleListTools :: ListToolsParams -> m ListToolsResult Source #
handleCallTool :: CallToolParams -> m CallToolResult Source #
handleComplete :: CompleteParams -> m CompleteResult Source #
handleSetLevel :: SetLevelParams -> m () Source #
data ServerState Source #
Server state tracking initialization, capabilities, and subscriptions
Constructors
ServerState | |
Instances
Show ServerState Source # | |
Defined in MCP.Server Methods showsPrec :: Int -> ServerState -> ShowS # show :: ServerState -> String # showList :: [ServerState] -> ShowS # |
type MCPServerM = ReaderT ServerConfig (StateT ServerState (ExceptT Text IO)) Source #
The monad stack for MCP server operations
runMCPServer :: ServerConfig -> ServerState -> MCPServerM a -> IO (Either Text (a, ServerState)) Source #
Run an MCPServerM computation with the given config and initial state
Message Handling
handleMessage :: MCPServer MCPServerM => ByteString -> MCPServerM (Maybe ()) Source #
Handle an incoming JSON-RPC message
handleRequest :: MCPServer MCPServerM => JSONRPCRequest -> MCPServerM () Source #
Handle a JSON-RPC request
handleNotification :: JSONRPCNotification -> MCPServerM () Source #
Handle a JSON-RPC notification
Server Runner
runServer :: MCPServer MCPServerM => ServerConfig -> IO () Source #
Run the MCP server with the given configuration
data ServerConfig Source #
Configuration for running an MCP server
Constructors
ServerConfig | |
Instances
Show ServerConfig Source # | |
Defined in MCP.Server Methods showsPrec :: Int -> ServerConfig -> ShowS # show :: ServerConfig -> String # showList :: [ServerConfig] -> ShowS # |
Utilities
sendResponse :: (MonadIO m, ToJSON a) => Handle -> RequestId -> a -> m () Source #
Send a JSON-RPC response