squeal-postgresql-0.1.1.4: Squeal PostgreSQL Library

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

Squeal.PostgreSQL.Binary

Contents

Description

Binary encoding and decoding between Haskell and PostgreSQL types.

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 # 
ToParam Double PGfloat8 Source # 
ToParam Float PGfloat4 Source # 
ToParam Int16 PGint2 Source # 
ToParam Int32 PGint4 Source # 
ToParam Int64 PGint8 Source # 
ToParam Word16 PGint2 Source # 
ToParam Word32 PGint4 Source # 
ToParam Word64 PGint8 Source # 
ToParam ByteString PGbytea Source # 
ToParam ByteString PGbytea Source # 
ToParam Scientific PGnumeric Source # 
ToParam Text PGtext Source # 
ToParam UTCTime PGtimestamptz Source # 
ToParam Value PGjson Source # 
ToParam Value PGjsonb Source # 
ToParam Text PGtext Source # 
ToParam UUID PGuuid Source # 
ToParam Day PGdate Source # 
ToParam DiffTime PGinterval Source # 
ToParam TimeOfDay PGtime Source # 
ToParam LocalTime PGtimestamp Source # 
ToParam Char (PGchar 1) Source # 
ToParam (NetAddr IP) PGinet Source # 
ToParam (TimeOfDay, TimeZone) PGtimetz Source # 

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

A ToColumnParam constraint lifts the ToParam encoding of a Type to a ColumnType, 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 @('Required ('NotNull 'PGint2)) 0
K (Just "\NUL\NUL")
>>> toColumnParam @(Maybe Int16) @('Required ('Null 'PGint2)) (Just 0)
K (Just "\NUL\NUL")
>>> toColumnParam @(Maybe Int16) @('Required ('Null 'PGint2)) Nothing
K Nothing

Instances

ToParam x pg => ToColumnParam x (optionality (NotNull pg)) Source # 

Methods

toColumnParam :: x -> K ColumnType (Maybe ByteString) (optionality (NotNull pg)) Source #

ToParam x pg => ToColumnParam (Maybe x) (optionality (Null pg)) Source # 

Methods

toColumnParam :: Maybe x -> K ColumnType (Maybe ByteString) (optionality (Null pg)) Source #

class SListI tys => ToParams (x :: Type) (tys :: [ColumnType]) 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 PGparams = '[ 'Required ('NotNull 'PGbool), 'Required ('Null 'PGint2)]
>>> toParams @(Bool, Maybe Int16) @PGparams (False, Just 0)
K (Just "\NUL") :* (K (Just "\NUL\NUL") :* Nil)
>>> :set -XDeriveGeneric
>>> data Hparams = Hparams { col1 :: Bool, col2 :: Maybe Int16} deriving GHC.Generic
>>> instance Generic Hparams
>>> toParams @Hparams @PGparams (Hparams False (Just 0))
K (Just "\NUL") :* (K (Just "\NUL\NUL") :* Nil)

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 # 

Methods

fromValue :: proxy PGbool -> Value Bool Source #

FromValue PGint2 Int16 Source # 

Methods

fromValue :: proxy PGint2 -> Value Int16 Source #

FromValue PGint4 Int32 Source # 

Methods

fromValue :: proxy PGint4 -> Value Int32 Source #

FromValue PGint8 Int64 Source # 

Methods

fromValue :: proxy PGint8 -> Value Int64 Source #

FromValue PGnumeric Scientific Source # 
FromValue PGfloat4 Float Source # 

Methods

fromValue :: proxy PGfloat4 -> Value Float Source #

FromValue PGfloat8 Double Source # 

Methods

fromValue :: proxy PGfloat8 -> Value Double Source #

FromValue PGtext Text Source # 

Methods

fromValue :: proxy PGtext -> Value Text Source #

FromValue PGtext Text Source # 

Methods

fromValue :: proxy PGtext -> Value Text Source #

FromValue PGbytea ByteString Source # 
FromValue PGbytea ByteString Source # 
FromValue PGtimestamp LocalTime Source # 
FromValue PGtimestamptz UTCTime Source # 
FromValue PGdate Day Source # 

Methods

fromValue :: proxy PGdate -> Value Day Source #

FromValue PGtime TimeOfDay Source # 

Methods

fromValue :: proxy PGtime -> Value TimeOfDay Source #

FromValue PGinterval DiffTime Source # 
FromValue PGuuid UUID Source # 

Methods

fromValue :: proxy PGuuid -> Value UUID Source #

FromValue PGjson Value Source # 

Methods

fromValue :: proxy PGjson -> Value Value Source #

FromValue PGjsonb Value Source # 

Methods

fromValue :: proxy PGjsonb -> Value Value Source #

FromValue PGinet (NetAddr IP) Source # 

Methods

fromValue :: proxy PGinet -> Value (NetAddr IP) Source #

FromValue PGtimetz (TimeOfDay, TimeZone) Source # 
FromValue (PGchar 1) Char Source # 

Methods

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

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

A FromColumnValue constraint lifts the FromValue parser to a decoding of a (Symbol, ColumnType) 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" ::: 'Required ('NotNull 'PGint2)) @Id (K (Just "\NUL\SOH"))
Id {getId = 1}
>>> fromColumnValue @("col" ::: 'Required ('Null 'PGint2)) @(Maybe Id) (K (Just "\NUL\SOH"))
Just (Id {getId = 1})

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

A FromRow constraint generically sequences the parsings of the columns of a ColumnsType 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 Id = Id { getId :: Int16 } deriving Show
>>> instance FromValue 'PGint2 Id where fromValue = fmap Id . fromValue
>>> data Hrow = Hrow { userId :: Id, userName :: Maybe Text } deriving (Show, GHC.Generic)
>>> instance Generic Hrow
>>> instance HasDatatypeInfo Hrow
>>> type PGrow = '["userId" ::: 'Required ('NotNull 'PGint2), "userName" ::: 'Required ('Null 'PGtext)]
>>> fromRow @PGrow @Hrow (K (Just "\NUL\SOH") :* K (Just "bloodninja") :* Nil)
Hrow {userId = Id {getId = 1}, userName = Just "bloodninja"}

Instances

(SListI (Symbol, ColumnType) results, IsProductType y ys, AllZip (Symbol, ColumnType) Type FromColumnValue results ys, SameFields (DatatypeInfoOf y) results) => FromRow results y Source # 

Methods

fromRow :: NP (Symbol, ColumnType) (K (Symbol, ColumnType) (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)) @'[ 'Required ('Null 'PGtext)] (Only (Just "foo"))
K (Just "foo") :* Nil
>>> type PGShortRow = '["fromOnly" ::: 'Required ('Null 'PGtext)]
>>> fromRow @PGShortRow @(Only (Maybe Text)) (K (Just "bar") :* Nil)
Only {fromOnly = Just "bar"}

Constructors

Only 

Fields

Instances

Functor Only Source # 

Methods

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

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

Foldable Only Source # 

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 # 

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 # 

Methods

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

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

Ord x => Ord (Only x) Source # 

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 # 
Show x => Show (Only x) Source # 

Methods

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

show :: Only x -> String #

showList :: [Only x] -> ShowS #

Generic (Only x) Source # 

Associated Types

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

Methods

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

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

Generic (Only x) Source # 

Associated Types

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

Methods

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

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

HasDatatypeInfo (Only x) Source # 

Associated Types

type DatatypeInfoOf (Only x) :: DatatypeInfo #

Methods

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

type Rep (Only x) Source # 
type Rep (Only x) = D1 * (MetaData "Only" "Squeal.PostgreSQL.Binary" "squeal-postgresql-0.1.1.4-k5IDJoGvjq2Crr3wWyEON" True) (C1 * (MetaCons "Only" PrefixI True) (S1 * (MetaSel (Just Symbol "fromOnly") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * x)))
type Code (Only x) Source # 
type Code (Only x) = GCode (Only x)
type DatatypeInfoOf (Only x) Source #