openai: Servant bindings to OpenAI

[ ai, api, bsd3, library, program, web ] [ Propose Tags ] [ Report a vulnerability ]

This package provides comprehensive and type-safe bindings to OpenAI, providing both a Servant interface and non-Servant interface for convenience.

Read the README below for a fully worked usage example.

Otherwise, browse the OpenAI.V1 module, which is the intended package entrypoint.


[Skip to Readme]

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees

Candidates

Versions [RSS] 1.0.0, 1.0.1, 1.1.0, 1.1.1, 1.2.0, 2.0.0, 2.1.0
Change log CHANGELOG.md
Dependencies aeson, base (>=4.15.0.0 && <5), bytestring, containers, filepath, http-api-data, http-client, http-client-tls, http-types, openai, servant, servant-client, servant-multipart-api, servant-multipart-client, text, time, unordered-containers, vector [details]
License BSD-3-Clause
Copyright 2024 Gabriella Gonzalez
Author Gabriella Gonzalez
Maintainer GenuineGabriella@gmail.com
Category AI, API, Web
Source repo head: git clone https://github.com/MercuryTechnologies/openai
Uploaded by asselinpaul at 2025-10-16T21:24:34Z
Distributions
Executables responses-stream-example, responses-tool-call-example, responses-example, weather-chatbot-example, openai-example
Downloads 104 total (22 in the last 30 days)
Rating (no votes yet) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs available [build log]
Last success reported on 2025-10-16 [all 1 reports]

Readme for openai-2.1.0

[back to package description]

openai

This provides a binding to OpenAI's API using servant

Example usage

{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns        #-}
{-# LANGUAGE OverloadedStrings     #-}
{-# LANGUAGE OverloadedLists       #-}

module Main where

import Data.Foldable (traverse_)
import OpenAI.V1
import OpenAI.V1.Chat.Completions

import qualified Data.Text as Text
import qualified Data.Text.IO as Text.IO
import qualified System.Environment as Environment

main :: IO ()
main = do
    key <- Environment.getEnv "OPENAI_KEY"

    clientEnv <- getClientEnv "https://api.openai.com"

    let Methods{ createChatCompletion } = makeMethods clientEnv (Text.pack key)

    text <- Text.IO.getLine

    ChatCompletionObject{ choices } <- createChatCompletion _CreateChatCompletion
        { messages = [ User{ content = [ Text{ text } ], name = Nothing } ]
        , model = "gpt-4o-mini"
        }

    let display Choice{ message } = Text.IO.putStrLn (messageToContent message)

    traverse_ display choices

Responses API (JSON)

{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns        #-}
{-# LANGUAGE OverloadedStrings     #-}

import qualified Data.Text as Text
import qualified OpenAI.V1 as V1
import qualified OpenAI.V1.Responses as Responses

main :: IO ()
main = do
    key <- System.Environment.getEnv "OPENAI_KEY"

    env <- V1.getClientEnv "https://api.openai.com"
    let V1.Methods{ createResponse } = V1.makeMethods env (Text.pack key) Nothing Nothing

    let req = Responses._CreateResponse
            { Responses.model = "gpt-5"
            , Responses.input = Just (Responses.Input
                [ Responses.Item_Input_Message
                    { Responses.role = Responses.User
                    , Responses.content = [ Responses.Input_Text{ Responses.text = "Say hello in one sentence." } ]
                    , Responses.status = Nothing
                    }
                ])
            }

    res <- createResponse req
    print res

Setup

This project uses Nix with flakes for development environment setup.

  1. Ensure you have Nix with flakes enabled
  2. Copy the sample environment file and configure your OpenAI API key:
# Copy the sample environment file
cp .envrc.sample .envrc
  1. Edit the .envrc file and replace the placeholder API key with your actual key

  2. Use direnv to automatically load the development environment:

# Install direnv if you haven't already
# macOS: brew install direnv
# Linux: your-package-manager install direnv

# Enable direnv hook in your shell
eval "$(direnv hook bash)" # or zsh, fish, etc.

# Clone the repository and enter the directory
git clone https://github.com/MercuryTechnologies/openai.git
cd openai

# Allow direnv (this will automatically load the environment)
direnv allow

Manual Setup

Without Nix:

# Clone the repository
git clone https://github.com/MercuryTechnologies/openai.git
cd openai

# Build with cabal
cabal build

Environment Variables

Set your OpenAI API key as an environment variable:

# Option 1: Set directly in your shell
export OPENAI_KEY="your-openai-api-key"

# Option 2: Using .envrc with direnv (recommended)
(umask 077; cp .envrc.sample .envrc)
# Edit .envrc to add your API key
direnv allow

The API key is needed for running the test suite and example program.

Testing

Run the test suite:

cabal test

The test suite is in the tasty/ directory with test data located in tasty/data/.

Running the Example

# Make sure your API key is set (either via .envrc or export)
# If using direnv with proper .envrc setup, this happens automatically

# Build and run the example
cabal run openai-example