pinecone: Servant bindings to Pinecone

[ bsd3, library, program, unclassified ] [ Propose Tags ] [ Report a vulnerability ]

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

Read the README below for a fully worked usage example.

Otherwise, browse the Pinecone 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
Change log CHANGELOG.md
Dependencies aeson, base (>=4.15.0.0 && <5), containers, http-api-data, http-client, http-client-tls, pinecone, scientific, servant, servant-client, servant-client-core, text, time, vector [details]
License BSD-3-Clause
Copyright 2025 Mercury Technologies
Author Gabriella Gonzalez
Maintainer GenuineGabriella@gmail.com
Uploaded by GabrielGonzalez at 2025-04-03T22:39:35Z
Distributions Stackage:1.0.0
Executables pinecone-example
Downloads 1 total (1 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-04-04 [all 1 reports]

Readme for pinecone-1.0.0

[back to package description]

pinecone

This provides a binding to Pinecone's API using servant

Example usage:

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

import Pinecone
import Pinecone.Indexes
import Pinecone.Search
import Pinecone.Vectors

import qualified Control.Exception as Exception
import qualified Data.Text as Text
import qualified System.Environment as Environment

main :: IO ()
main = do
    controlEnv <- getClientEnv "https://api.pinecone.io"

    key <- Environment.getEnv "PINECONE_KEY"

    let token = Text.pack key

    let ControlMethods{..} = makeControlMethods controlEnv token

    let open = createIndexWithEmbedding _CreateIndexWithEmbedding
            { name = "test"
            , cloud = AWS
            , region = "us-east-1"
            , embed = EmbedRequest
                { model = "llama-text-embed-v2"
                , metric = Nothing
                , read_parameters = Nothing
                , write_parameters = Nothing
                }
            }

    let close IndexModel{ name } = deleteIndex name

    Exception.bracket open close \IndexModel{ name, host } -> do
        let waitUntilIndexReady = do
                IndexModel{ status } <- describeIndex name

                let Status{ ready } = status

                if ready
                    then return ()
                    else waitUntilIndexReady

        waitUntilIndexReady

        dataEnv <- getClientEnv host

        let DataMethods{..} = makeDataMethods dataEnv token

        upsertText "test" _Record{ id = "hi", text = "Hello, world!" }
        upsertText "test" _Record{ id = "bye", text = "Goodbye, world!" }

        -- Pinecone is eventually consistent, so we have to wait
        let waitUntilVectorsReady = do
                IndexStats{ totalVectorCount } <- getIndexStats _GetIndexStats

                if totalVectorCount == 2
                    then return ()
                    else waitUntilVectorsReady

        waitUntilVectorsReady

        Hits{ hits } <- searchWithText "test" SearchWithText
            { query = _Query{ top_k = 1, input = Just "best greeting"  }
            , fields = Nothing
            , rerank = Nothing
            }

        print (fmap _id hits) -- ["hi"]