mcp-server: Library for building Model Context Protocol (MCP) servers

This is a package candidate release! Here you can preview how this package release will appear once published to the main package index (which can be accomplished via the 'maintain' link below). Please note that once a package has been published to the main package index it cannot be undone! Please consult the package uploading documentation for more information.

[maintain] [Publish]

A fully featured library for building MCP (Model Context Protocol) servers. Supports both low-level fine-grained handling and high-level derived interfaces for prompts, resources, and tools. Includes JSON-RPC transport, pagination, and stdin/stdout communication.


[Skip to Readme]

Properties

Versions 0.1.0.0, 0.1.0.0
Change log CHANGELOG.md
Dependencies aeson (>=2.0 && <3.0), base (>=4.20.0.0 && <4.21), bytestring (>=0.10 && <0.13), containers (>=0.6 && <0.8), mcp-server, network-uri (>=2.6 && <2.8), template-haskell (>=2.16 && <2.23), text (>=1.2 && <3.0) [details]
License BSD-3-Clause
Copyright 2025 Tom Wells
Author Tom Wells
Maintainer drshade@gmail.com
Category Network, Server, Service, MCP, JSON-RPC
Home page https://github.com/drshade/haskell-mcp-server
Bug tracker https://github.com/drshade/haskell-mcp-server/issues
Source repo head: git clone https://github.com/drshade/haskell-mcp-server.git
Uploaded by drshade at 2025-06-05T16:58:36Z

Modules

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees


Readme for mcp-server-0.1.0.0

[back to package description]

mcp-server

A fully-featured Haskell library for building Model Context Protocol (MCP) servers.

Features

Supported MCP Features

Quick Start

{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-}

import MCP.Server
import MCP.Server.Derive

-- Define your data types
data MyPrompt = Recipe { idea :: Text } | Shopping { items :: Text }
data MyResource = Menu | Specials  
data MyTool = Search { query :: Text } | Order { item :: Text }

-- Implement handlers
handlePrompt :: MyPrompt -> IO Content
handlePrompt (Recipe idea) = pure $ ContentText $ "Recipe for " <> idea
handlePrompt (Shopping items) = pure $ ContentText $ "Shopping list: " <> items

handleResource :: MyResource -> IO Content  
handleResource Menu = pure $ ContentText "Today's menu..."
handleResource Specials = pure $ ContentText "Daily specials..."

handleTool :: MyTool -> IO Content
handleTool (Search query) = pure $ ContentText $ "Search results for " <> query
handleTool (Order item) = pure $ ContentText $ "Ordered " <> item

-- Derive handlers automatically
main :: IO ()
main = runMcpServerStdIn serverInfo handlers
  where
    serverInfo = McpServerInfo
      { serverName = "My MCP Server"
      , serverVersion = "1.0.0" 
      , serverInstructions = "A sample MCP server"
      }
    handlers = McpServerHandlers
      { prompts = Just $(derivePromptHandler ''MyPrompt 'handlePrompt)
      , resources = Just $(deriveResourceHandler ''MyResource 'handleResource)  
      , tools = Just $(deriveToolHandler ''MyTool 'handleTool)
      }

Manual Handler Implementation

For fine-grained control, implement handlers manually:

import MCP.Server

-- Manual handler implementation
promptListHandler :: Maybe Cursor -> IO (PaginatedResult [PromptDefinition])
promptGetHandler :: PromptName -> [(ArgumentName, ArgumentValue)] -> IO (Either Error Content)
-- ... implement your custom logic

main :: IO ()
main = runMcpServerStdIn serverInfo handlers
  where
    handlers = McpServerHandlers
      { prompts = Just (promptListHandler, promptGetHandler)
      , resources = Nothing  -- Not supported
      , tools = Nothing      -- Not supported  
      }

Examples

The library includes three complete examples:

Docker Usage

I like to build and publish my MCP servers to Docker - which means that it's much easier to configure assistants such as Claude Desktop to run them.

# Build the image
docker build -t haskell-mcp-server .

# Run different examples
docker run -i --entrypoint="/usr/local/bin/template-haskell-example" haskell-mcp-server
docker run -i --entrypoint="/usr/local/bin/high-level-example" haskell-mcp-server

And then configure Claude by editing claude_desktop_config.json:

{
    "mcpServers": {
       "haskell-mcp-server-example": {
            "command": "docker",
            "args": [
                "run",
                "-i",
                "--entrypoint=/usr/local/bin/template-haskell-example",
                "drshade/haskell-mcp-server"
            ]
        }
    }
}

Documentation

Contributing

Contributions are welcome! Please see the issue tracker for open issues and feature requests.

Disclaimer - AI Assistance

I am not sure whether there is any stigma associated with this but Claude helped me write a lot of this library. I started with a very specific specification of what I wanted to achieve and worked shoulder-to-shoulder with Claude to implement and refactor the library until I was happy with it. A few of the features such as the Derive functions are a little out of my comfort zone to have manually written, so I appreciated having an expert guide me here - however I do suspect that this implementation may be sub-par and I do intend to refactor and rewrite large pieces of this through regular maintenance.

License

BSD-3-Clause