{-# LANGUAGE OverloadedStrings #-} module Pgvector (Vector (..)) where import qualified Data.ByteString.Char8 as BS import Database.PostgreSQL.Simple.FromField import Database.PostgreSQL.Simple.ToField data Vector = Vector [Float] deriving (Int -> Vector -> ShowS [Vector] -> ShowS Vector -> String forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [Vector] -> ShowS $cshowList :: [Vector] -> ShowS show :: Vector -> String $cshow :: Vector -> String showsPrec :: Int -> Vector -> ShowS $cshowsPrec :: Int -> Vector -> ShowS Show) instance ToField Vector where toField :: Vector -> Action toField = forall a. ToField a => a -> Action toField forall b c a. (b -> c) -> (a -> b) -> a -> c . Vector -> String encodeVector instance FromField Vector where fromField :: FieldParser Vector fromField Field f Maybe ByteString mdat = do ByteString typ <- Field -> Conversion ByteString typename Field f if ByteString typ forall a. Eq a => a -> a -> Bool /= ByteString "vector" then forall a err. (Typeable a, Exception err) => (String -> Maybe Oid -> String -> String -> String -> err) -> Field -> String -> Conversion a returnError String -> Maybe Oid -> String -> String -> String -> ResultError Incompatible Field f String "" else case Maybe ByteString mdat of Maybe ByteString Nothing -> forall a err. (Typeable a, Exception err) => (String -> Maybe Oid -> String -> String -> String -> err) -> Field -> String -> Conversion a returnError String -> Maybe Oid -> String -> String -> String -> ResultError UnexpectedNull Field f String "" Just ByteString dat -> forall (m :: * -> *) a. Monad m => a -> m a return forall a b. (a -> b) -> a -> b $! String -> Vector decodeVector (ByteString -> String BS.unpack ByteString dat) encodeVector :: Vector -> String encodeVector :: Vector -> String encodeVector (Vector [Float] v) = forall a. Show a => a -> String show [Float] v decodeVector :: String -> Vector decodeVector :: String -> Vector decodeVector String v = [Float] -> Vector Vector (forall a. Read a => String -> a read String v)