squeal-postgresql-0.4.0.0: Squeal PostgreSQL Library

Copyright(c) Eitan Chatav 2017
Maintainereitan@morphism.tech
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Squeal.PostgreSQL.Binary

Contents

Description

This module provides binary encoding and decoding between Haskell and PostgreSQL types.

Instances are governed by the Generic and HasDatatypeInfo typeclasses, so you absolutely do not need to define your own instances to decode retrieved rows into Haskell values or to encode Haskell values into statement parameters.

Let's see some examples. We'll need some imports

>>> import Data.Int (Int16)
>>> import Data.Text (Text)
>>> import Control.Monad (void)
>>> import Control.Monad.Base (liftBase)
>>> import Squeal.PostgreSQL

Define a Haskell datatype Row that will serve as both the input and output of a simple round trip query.

>>> data Row = Row { col1 :: Int16, col2 :: Text, col3 :: Maybe Bool } deriving (Eq, GHC.Generic)
>>> instance Generic Row
>>> instance HasDatatypeInfo Row
>>> :{
let
  roundTrip :: Query '[] (TuplePG Row) (RowPG Row)
  roundTrip = values_ $
    parameter @1 int2 `as` #col1 :*
    parameter @2 text `as` #col2 :*
    parameter @3 bool `as` #col3
:}

So long as we can encode the parameters and then decode the result of the query, the input and output should be equal.

>>> let input = Row 2 "hi" (Just True)
>>> :{
void . withConnection "host=localhost port=5432 dbname=exampledb" $ do
  result <- runQueryParams roundTrip input
  Just output <- firstRow result
  liftBase . print $ input == output
:}
True

In addition to being able to encode and decode basic Haskell types like Int16 and Text, Squeal permits you to encode and decode Haskell types to Postgres array, enumerated and composite types and json. Let's see another example, this time using the Vector type which corresponds to variable length arrays and homogeneous tuples which correspond to fixed length arrays. We can even create multi-dimensional fixed length arrays.

>>> :{
data Row = Row
  { col1 :: Vector Int16
  , col2 :: (Maybe Int16,Maybe Int16)
  , col3 :: ((Int16,Int16),(Int16,Int16),(Int16,Int16))
  } deriving (Eq, GHC.Generic)
:}
>>> instance Generic Row
>>> instance HasDatatypeInfo Row

Once again, we define a simple round trip query.

>>> :{
let
  roundTrip :: Query '[] (TuplePG Row) (RowPG Row)
  roundTrip = values_ $
    parameter @1 (int2 & vararray)                  `as` #col1 :*
    parameter @2 (int2 & fixarray @2)               `as` #col2 :*
    parameter @3 (int2 & fixarray @2 & fixarray @3) `as` #col3
:}
>>> :set -XOverloadedLists
>>> let input = Row [1,2] (Just 1,Nothing) ((1,2),(3,4),(5,6))
>>> :{
void . withConnection "host=localhost port=5432 dbname=exampledb" $ do
  result <- runQueryParams roundTrip input
  Just output <- firstRow result
  liftBase . print $ input == output
:}
True

Enumerated (enum) types are data types that comprise a static, ordered set of values. They are equivalent to Haskell algebraic data types whose constructors are nullary. An example of an enum type might be the days of the week, or a set of status values for a piece of data.

>>> data Schwarma = Beef | Lamb | Chicken deriving (Eq, Show, GHC.Generic)
>>> instance Generic Schwarma
>>> instance HasDatatypeInfo Schwarma

A composite type represents the structure of a row or record; it is essentially just a list of field names and their data types.

>>> data Person = Person {name :: Text, age :: Int32} deriving (Eq, Show, GHC.Generic)
>>> instance Generic Person
>>> instance HasDatatypeInfo Person
>>> instance Aeson.FromJSON Person
>>> instance Aeson.ToJSON Person

We can create the equivalent Postgres types directly from their Haskell types.

>>> :{
type Schema =
  '[ "schwarma" ::: 'Typedef (PG (Enumerated Schwarma))
   , "person" ::: 'Typedef (PG (Composite Person))
   ]
:}
>>> :{
let
  setup :: Definition '[] Schema
  setup =
    createTypeEnumFrom @Schwarma #schwarma >>>
    createTypeCompositeFrom @Person #person
:}

Let's demonstrate how to associate our Haskell types Schwarma and Person with enumerated, composite or json types in Postgres. First create a Haskell Row type using the Enumerated, Composite and Json newtypes as fields.

>>> :{
data Row = Row
  { schwarma :: Enumerated Schwarma
  , person1 :: Composite Person
  , person2 :: Json Person
  } deriving (Eq, GHC.Generic)
:}
>>> instance Generic Row
>>> instance HasDatatypeInfo Row
>>> :{
let
  input = Row
    (Enumerated Chicken)
    (Composite (Person "Faisal" 24))
    (Json (Person "Ahmad" 48))
:}

Once again, define a round trip query.

>>> :{
let
  roundTrip :: Query Schema (TuplePG Row) (RowPG Row)
  roundTrip = values_ $
    parameter @1 (typedef #schwarma) `as` #schwarma :*
    parameter @2 (typedef #person)   `as` #person1  :*
    parameter @3 json                `as` #person2
:}

Finally, we can drop our type definitions.

>>> :{
let
  teardown :: Definition Schema '[]
  teardown = dropType #schwarma >>> dropType #person
:}

Now let's run it.

>>> :{
let
  session = do
    result <- runQueryParams roundTrip input
    Just output <- firstRow result
    liftBase . print $ input == output
in
  void . withConnection "host=localhost port=5432 dbname=exampledb" $
    define setup
    & pqThen session
    & pqThen (define teardown)
:}
True
Synopsis

Encoding

class ToParam (x :: Type) (pg :: PGType) where Source #

A ToParam constraint gives an encoding of a Haskell Type into into the binary format of a PostgreSQL PGType.

Minimal complete definition

toParam

Methods

toParam :: x -> K Encoding pg Source #

>>> :set -XTypeApplications -XDataKinds
>>> toParam @Bool @'PGbool False
K "\NUL"
>>> toParam @Int16 @'PGint2 0
K "\NUL\NUL"
>>> toParam @Int32 @'PGint4 0
K "\NUL\NUL\NUL\NUL"
>>> :set -XMultiParamTypeClasses
>>> newtype Id = Id { getId :: Int16 } deriving Show
>>> instance ToParam Id 'PGint2 where toParam = toParam . getId
>>> toParam @Id @'PGint2 (Id 1)
K "\NUL\SOH"
Instances
ToParam Bool PGbool Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

ToParam Double PGfloat8 Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

ToParam Float PGfloat4 Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

ToParam Int16 PGint2 Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

ToParam Int32 PGint4 Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

ToParam Int64 PGint8 Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

ToParam Word16 PGint2 Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

ToParam Word32 PGint4 Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

ToParam Word64 PGint8 Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

ToParam ByteString PGbytea Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

ToParam ByteString PGbytea Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

ToParam Scientific PGnumeric Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

ToParam String PGtext Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

ToParam Text PGtext Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

ToParam UTCTime PGtimestamptz Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

ToParam Value PGjson Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

ToParam Value PGjsonb Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

ToParam Text PGtext Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

ToParam UUID PGuuid Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

ToParam Day PGdate Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

ToParam DiffTime PGinterval Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

ToParam TimeOfDay PGtime Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

ToParam LocalTime PGtimestamp Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

ToParam Char (PGchar 1) Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

Methods

toParam :: Char -> K Encoding (PGchar 1) Source #

ToArray x (NotNull (PGvararray ty)) => ToParam x (PGvararray ty) Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

Methods

toParam :: x -> K Encoding (PGvararray ty) Source #

ToArray x (NotNull (PGfixarray n ty)) => ToParam x (PGfixarray n ty) Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

Methods

toParam :: x -> K Encoding (PGfixarray n ty) Source #

ToParam (NetAddr IP) PGinet Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

ToJSON x => ToParam (Jsonb x) PGjsonb Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

ToJSON x => ToParam (Json x) PGjson Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

(IsEnumType x, HasDatatypeInfo x, LabelsPG x ~ labels) => ToParam (Enumerated x) (PGenum labels) Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

Methods

toParam :: Enumerated x -> K Encoding (PGenum labels) Source #

(SListI fields, IsRecord x xs, AllZip ToField xs fields, All HasAliasedOid fields) => ToParam (Composite x) (PGcomposite fields) Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

Methods

toParam :: Composite x -> K Encoding (PGcomposite fields) Source #

ToParam (TimeOfDay, TimeZone) PGtimetz Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

class SListI tys => ToParams (x :: Type) (tys :: [NullityType]) where Source #

A ToParams constraint generically sequences the encodings of Types of the fields of a tuple or record to a row of ColumnTypes. You should not define instances of ToParams. Instead define Generic instances which in turn provide ToParams instances.

Minimal complete definition

toParams

Methods

toParams :: x -> NP (K (Maybe Encoding)) tys Source #

>>> type Params = '[ 'NotNull 'PGbool, 'Null 'PGint2]
>>> toParams @(Bool, Maybe Int16) @'[ 'NotNull 'PGbool, 'Null 'PGint2] (False, Just 0)
K (Just "\NUL") :* K (Just "\NUL\NUL") :* Nil
>>> :set -XDeriveGeneric
>>> data Tuple = Tuple { p1 :: Bool, p2 :: Maybe Int16} deriving GHC.Generic
>>> instance Generic Tuple
>>> toParams @Tuple @Params (Tuple False (Just 0))
K (Just "\NUL") :* K (Just "\NUL\NUL") :* Nil
Instances
(SListI tys, IsProductType x xs, AllZip ToNullityParam xs tys) => ToParams x tys Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

Methods

toParams :: x -> NP (K (Maybe Encoding)) tys Source #

Decoding

class FromValue (pg :: PGType) (y :: Type) where Source #

A FromValue constraint gives a parser from the binary format of a PostgreSQL PGType into a Haskell Type.

Minimal complete definition

fromValue

Methods

fromValue :: Value y Source #

>>> newtype Id = Id { getId :: Int16 } deriving Show
>>> instance FromValue 'PGint2 Id where fromValue = Id <$> fromValue @'PGint2
Instances
FromValue PGbool Bool Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

FromValue PGint2 Int16 Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

FromValue PGint4 Int32 Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

FromValue PGint8 Int64 Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

FromValue PGnumeric Scientific Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

FromValue PGfloat4 Float Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

FromValue PGfloat8 Double Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

FromValue PGtext String Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

FromValue PGtext Text Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

FromValue PGtext Text Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

FromValue PGbytea ByteString Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

FromValue PGbytea ByteString Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

FromValue PGtimestamp LocalTime Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

FromValue PGtimestamptz UTCTime Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

FromValue PGdate Day Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

FromValue PGtime TimeOfDay Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

FromValue PGinterval DiffTime Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

FromValue PGuuid UUID Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

FromValue PGjson Value Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

FromValue PGjsonb Value Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

FromValue PGinet (NetAddr IP) Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

FromJSON x => FromValue PGjson (Json x) Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

Methods

fromValue :: Value (Json x) Source #

FromJSON x => FromValue PGjsonb (Jsonb x) Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

Methods

fromValue :: Value (Jsonb x) Source #

FromValue PGtimetz (TimeOfDay, TimeZone) Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

FromValue (PGchar 1) Char Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

FromArray (NotNull (PGvararray ty)) y => FromValue (PGvararray ty) y Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

Methods

fromValue :: Value y Source #

(IsEnumType y, HasDatatypeInfo y, LabelsPG y ~ labels) => FromValue (PGenum labels) (Enumerated y) Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

FromRow fields y => FromValue (PGcomposite fields) (Composite y) Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

FromArray (NotNull (PGfixarray n ty)) y => FromValue (PGfixarray n ty) y Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

Methods

fromValue :: Value y Source #

class SListI result => FromRow (result :: RowType) y where Source #

A FromRow constraint generically sequences the parsings of the columns of a RowType into the fields of a record Type provided they have the same field names. You should not define instances of FromRow. Instead define Generic and HasDatatypeInfo instances which in turn provide FromRow instances.

Minimal complete definition

fromRow

Methods

fromRow :: NP (K (Maybe ByteString)) result -> Either Text y Source #

>>> :set -XOverloadedStrings
>>> import Data.Text
>>> newtype UserId = UserId { getUserId :: Int16 } deriving Show
>>> instance FromValue 'PGint2 UserId where fromValue = UserId <$> fromValue @'PGint2
>>> data UserRow = UserRow { userId :: UserId, userName :: Maybe Text } deriving (Show, GHC.Generic)
>>> instance Generic UserRow
>>> instance HasDatatypeInfo UserRow
>>> type User = '["userId" ::: 'NotNull 'PGint2, "userName" ::: 'Null 'PGtext]
>>> fromRow @User @UserRow (K (Just "\NUL\SOH") :* K (Just "bloodninja") :* Nil)
Right (UserRow {userId = UserId {getUserId = 1}, userName = Just "bloodninja"})
Instances
(SListI result, IsRecord y ys, AllZip FromField result ys) => FromRow result y Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

Methods

fromRow :: NP (K (Maybe ByteString)) result -> Either Text y Source #

Only

newtype Only x Source #

Only is a 1-tuple type, useful for encoding a single parameter with toParams or decoding a single value with fromRow.

>>> import Data.Text
>>> toParams @(Only (Maybe Text)) @'[ 'Null 'PGtext] (Only (Just "foo"))
K (Just "foo") :* Nil
>>> fromRow @'["fromOnly" ::: 'Null 'PGtext] @(Only (Maybe Text)) (K (Just "bar") :* Nil)
Right (Only {fromOnly = Just "bar"})

Constructors

Only 

Fields

Instances
Functor Only Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

Methods

fmap :: (a -> b) -> Only a -> Only b #

(<$) :: a -> Only b -> Only a #

Foldable Only Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

Methods

fold :: Monoid m => Only m -> m #

foldMap :: Monoid m => (a -> m) -> Only a -> m #

foldr :: (a -> b -> b) -> b -> Only a -> b #

foldr' :: (a -> b -> b) -> b -> Only a -> b #

foldl :: (b -> a -> b) -> b -> Only a -> b #

foldl' :: (b -> a -> b) -> b -> Only a -> b #

foldr1 :: (a -> a -> a) -> Only a -> a #

foldl1 :: (a -> a -> a) -> Only a -> a #

toList :: Only a -> [a] #

null :: Only a -> Bool #

length :: Only a -> Int #

elem :: Eq a => a -> Only a -> Bool #

maximum :: Ord a => Only a -> a #

minimum :: Ord a => Only a -> a #

sum :: Num a => Only a -> a #

product :: Num a => Only a -> a #

Traversable Only Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

Methods

traverse :: Applicative f => (a -> f b) -> Only a -> f (Only b) #

sequenceA :: Applicative f => Only (f a) -> f (Only a) #

mapM :: Monad m => (a -> m b) -> Only a -> m (Only b) #

sequence :: Monad m => Only (m a) -> m (Only a) #

Eq x => Eq (Only x) Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

Methods

(==) :: Only x -> Only x -> Bool #

(/=) :: Only x -> Only x -> Bool #

Ord x => Ord (Only x) Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

Methods

compare :: Only x -> Only x -> Ordering #

(<) :: Only x -> Only x -> Bool #

(<=) :: Only x -> Only x -> Bool #

(>) :: Only x -> Only x -> Bool #

(>=) :: Only x -> Only x -> Bool #

max :: Only x -> Only x -> Only x #

min :: Only x -> Only x -> Only x #

Read x => Read (Only x) Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

Show x => Show (Only x) Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

Methods

showsPrec :: Int -> Only x -> ShowS #

show :: Only x -> String #

showList :: [Only x] -> ShowS #

Generic (Only x) Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

Associated Types

type Rep (Only x) :: * -> * #

Methods

from :: Only x -> Rep (Only x) x0 #

to :: Rep (Only x) x0 -> Only x #

Generic (Only x) Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

Associated Types

type Code (Only x) :: [[*]] #

Methods

from :: Only x -> Rep (Only x) #

to :: Rep (Only x) -> Only x #

HasDatatypeInfo (Only x) Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

Associated Types

type DatatypeInfoOf (Only x) :: DatatypeInfo #

Methods

datatypeInfo :: proxy (Only x) -> DatatypeInfo (Code (Only x)) #

type Rep (Only x) Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

type Rep (Only x) = D1 (MetaData "Only" "Squeal.PostgreSQL.Binary" "squeal-postgresql-0.4.0.0-GuxxUOwtUmZB6qL3MLEXvb" True) (C1 (MetaCons "Only" PrefixI True) (S1 (MetaSel (Just "fromOnly") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 x)))
type Code (Only x) Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

type Code (Only x) = GCode (Only x)
type DatatypeInfoOf (Only x) Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary