squeal-postgresql-0.3.2.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.

>>> import Data.Int (Int16)
>>> import Data.Text (Text)
>>> data Row = Row { col1 :: Int16, col2 :: Text } deriving (Eq, GHC.Generic)
>>> instance Generic Row
>>> instance HasDatatypeInfo Row
>>> import Control.Monad (void)
>>> import Control.Monad.Base (liftBase)
>>> import Squeal.PostgreSQL
>>> :{
let
  query :: Query '[]
    '[ 'NotNull 'PGint2, 'NotNull 'PGtext]
    '["col1" ::: 'NotNull 'PGint2, "col2" ::: 'NotNull 'PGtext]
  query = values_ (param @1 `as` #col1 :* param @2 `as` #col2)
:}
>>> :{
let
  roundtrip :: IO ()
  roundtrip = void . withConnection "host=localhost port=5432 dbname=exampledb" $ do
    result <- runQueryParams query (2 :: Int16, "hi" :: Text)
    Just row <- firstRow result
    liftBase . print $ row == Row 2 "hi"
:}
>>> roundtrip
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 which are equivalent to Postgres enumerated and composite types.

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 (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. They are almost equivalent to Haskell record types. However, because of the potential presence of NULL all the record fields must be Maybes of basic types.

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

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

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

Then we can perform roundtrip queries;

>>> :{
let
  querySchwarma :: Query Schema
    '[ 'NotNull (EnumFrom Schwarma)]
    '["fromOnly" ::: 'NotNull (EnumFrom Schwarma)]
  querySchwarma = values_ (parameter @1 #schwarma `as` #fromOnly)
:}
>>> :{
let
  queryPerson :: Query Schema
    '[ 'NotNull (CompositeFrom Person)]
    '["fromOnly" ::: 'NotNull (CompositeFrom Person)]
  queryPerson = values_ (parameter @1 #person `as` #fromOnly)
:}

And finally drop the types.

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

Now let's run it.

>>> :{
let
  session = do
    result1 <- runQueryParams querySchwarma (Only Chicken)
    Just (Only schwarma) <- firstRow result1
    liftBase $ print (schwarma :: Schwarma)
    result2 <- runQueryParams queryPerson (Only (Person (Just "Faisal") (Just 24)))
    Just (Only person) <- firstRow result2
    liftBase $ print (person :: Person)
in
  void . withConnection "host=localhost port=5432 dbname=exampledb" $
    define setup
    & pqThen session
    & pqThen (define teardown)
:}
Chicken
Person {name = Just "Faisal", age = Just 24}
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 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 #

(SListI fields, MapMaybes xs, IsProductType x (Maybes xs), AllZip ToAliasedParam xs fields, FieldNamesFrom x ~ AliasesOf fields, All HasAliasedOid fields) => ToParam x (PGcomposite fields) Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

Methods

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

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

Defined in Squeal.PostgreSQL.Binary

Methods

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

ToParam (NetAddr IP) PGinet Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

(HasOid pg, ToParam x pg) => ToParam (Vector (Maybe x)) (PGvararray pg) Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

ToParam (TimeOfDay, TimeZone) PGtimetz Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

class ToColumnParam (x :: Type) (ty :: NullityType) where Source #

A ToColumnParam constraint lifts the ToParam encoding of a Type to a NullityType, encoding Maybes to Nulls. You should not define instances of ToColumnParam, just use the provided instances.

Minimal complete definition

toColumnParam

Methods

toColumnParam :: x -> K (Maybe ByteString) ty Source #

>>> toColumnParam @Int16 @('NotNull 'PGint2) 0
K (Just "\NUL\NUL")
>>> toColumnParam @(Maybe Int16) @('Null 'PGint2) (Just 0)
K (Just "\NUL\NUL")
>>> toColumnParam @(Maybe Int16) @('Null 'PGint2) Nothing
K Nothing
Instances
ToParam x pg => ToColumnParam x (NotNull pg) Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

ToParam x pg => ToColumnParam (Maybe x) (Null pg) 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 ByteString)) 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 ToColumnParam xs tys) => ToParams x tys Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

Methods

toParams :: x -> NP (K (Maybe ByteString)) 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 :: proxy pg -> Value y Source #

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

Defined in Squeal.PostgreSQL.Binary

Methods

fromValue :: proxy PGbool -> Value Bool Source #

FromValue PGint2 Int16 Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

Methods

fromValue :: proxy PGint2 -> Value Int16 Source #

FromValue PGint4 Int32 Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

Methods

fromValue :: proxy PGint4 -> Value Int32 Source #

FromValue PGint8 Int64 Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

Methods

fromValue :: proxy PGint8 -> Value Int64 Source #

FromValue PGnumeric Scientific Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

FromValue PGfloat4 Float Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

Methods

fromValue :: proxy PGfloat4 -> Value Float Source #

FromValue PGfloat8 Double Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

Methods

fromValue :: proxy PGfloat8 -> Value Double Source #

FromValue PGtext Text Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

Methods

fromValue :: proxy PGtext -> Value Text Source #

FromValue PGtext Text Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

Methods

fromValue :: proxy PGtext -> Value Text Source #

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

Methods

fromValue :: proxy PGdate -> Value Day Source #

FromValue PGtime TimeOfDay Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

Methods

fromValue :: proxy PGtime -> Value TimeOfDay Source #

FromValue PGinterval DiffTime Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

FromValue PGuuid UUID Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

Methods

fromValue :: proxy PGuuid -> Value UUID Source #

FromValue PGjson Value Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

Methods

fromValue :: proxy PGjson -> Value0 Value Source #

FromValue PGjsonb Value Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

Methods

fromValue :: proxy PGjsonb -> Value0 Value Source #

FromValue PGinet (NetAddr IP) Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

Methods

fromValue :: proxy PGinet -> Value (NetAddr IP) 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

Methods

fromValue :: proxy (PGchar 1) -> Value Char Source #

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

Defined in Squeal.PostgreSQL.Binary

Methods

fromValue :: proxy (PGenum labels) -> Value y Source #

(SListI fields, MapMaybes ys, IsProductType y (Maybes ys), AllZip FromAliasedValue fields ys, FieldNamesFrom y ~ AliasesOf fields) => FromValue (PGcomposite fields) y Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

Methods

fromValue :: proxy (PGcomposite fields) -> Value y Source #

FromValue pg y => FromValue (PGvararray pg) (Vector (Maybe y)) Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

Methods

fromValue :: proxy (PGvararray pg) -> Value (Vector (Maybe y)) Source #

FromValue pg y => FromValue (PGfixarray n pg) (Vector (Maybe y)) Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

Methods

fromValue :: proxy (PGfixarray n pg) -> Value (Vector (Maybe y)) Source #

class FromColumnValue (colty :: (Symbol, NullityType)) (y :: Type) where Source #

A FromColumnValue constraint lifts the FromValue parser to a decoding of a (Symbol, NullityType) to a Type, decoding Nulls to Maybes. You should not define instances for FromColumnValue, just use the provided instances.

Minimal complete definition

fromColumnValue

Methods

fromColumnValue :: K (Maybe ByteString) colty -> y Source #

>>> :set -XTypeOperators -XOverloadedStrings
>>> newtype Id = Id { getId :: Int16 } deriving Show
>>> instance FromValue 'PGint2 Id where fromValue = fmap Id . fromValue
>>> fromColumnValue @("col" ::: 'NotNull 'PGint2) @Id (K (Just "\NUL\SOH"))
Id {getId = 1}
>>> fromColumnValue @("col" ::: 'Null 'PGint2) @(Maybe Id) (K (Just "\NUL\SOH"))
Just (Id {getId = 1})
Instances
FromValue pg y => FromColumnValue (column ::: NotNull pg) y Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

Methods

fromColumnValue :: K (Maybe ByteString) (column ::: NotNull pg) -> y Source #

FromValue pg y => FromColumnValue (column ::: Null pg) (Maybe y) Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

Methods

fromColumnValue :: K (Maybe ByteString) (column ::: Null pg) -> Maybe y Source #

class SListI results => FromRow (results :: RelationType) y where Source #

A FromRow constraint generically sequences the parsings of the columns of a RelationType 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)) results -> y Source #

>>> :set -XOverloadedStrings
>>> import Data.Text
>>> newtype UserId = UserId { getUserId :: Int16 } deriving Show
>>> instance FromValue 'PGint2 UserId where fromValue = fmap UserId . fromValue
>>> 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)
UserRow {userId = UserId {getUserId = 1}, userName = Just "bloodninja"}
Instances
(SListI results, IsProductType y ys, AllZip FromColumnValue results ys, FieldNamesFrom y ~ AliasesOf results) => FromRow results y Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

Methods

fromRow :: NP (K (Maybe ByteString)) results -> 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)
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.3.2.0-C1DUTRQBZ7xFTzLk0tObU0" 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