squeal-postgresql-0.5.1.0: Squeal PostgreSQL Library

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

Squeal.PostgreSQL.PG

Contents

Description

PG provides type families for turning Haskell Types into corresponding Postgres types.

Synopsis

PG embeddings

type family PG (hask :: Type) :: PGType Source #

The PG type family embeds a subset of Haskell types as Postgres types. As an open type family, PG is extensible.

>>> :kind! PG LocalTime
PG LocalTime :: PGType
= 'PGtimestamp
>>> newtype MyDouble = My Double
>>> :set -XTypeFamilies
>>> type instance PG MyDouble = 'PGfloat8
Instances
type PG Bool Source #

PGbool

Instance details

Defined in Squeal.PostgreSQL.PG

type PG Bool = PGbool
type PG Char Source #

PGchar 1

Instance details

Defined in Squeal.PostgreSQL.PG

type PG Char = PGchar 1
type PG Double Source #

PGfloat8

Instance details

Defined in Squeal.PostgreSQL.PG

type PG Float Source #

PGfloat4

Instance details

Defined in Squeal.PostgreSQL.PG

type PG Int16 Source #

PGint2

Instance details

Defined in Squeal.PostgreSQL.PG

type PG Int16 = PGint2
type PG Int32 Source #

PGint4

Instance details

Defined in Squeal.PostgreSQL.PG

type PG Int32 = PGint4
type PG Int64 Source #

PGint8

Instance details

Defined in Squeal.PostgreSQL.PG

type PG Int64 = PGint8
type PG Word16 Source #

PGint2

Instance details

Defined in Squeal.PostgreSQL.PG

type PG Word32 Source #

PGint4

Instance details

Defined in Squeal.PostgreSQL.PG

type PG Word64 Source #

PGint8

Instance details

Defined in Squeal.PostgreSQL.PG

type PG ByteString Source #

PGbytea

Instance details

Defined in Squeal.PostgreSQL.PG

type PG ByteString Source #

PGbytea

Instance details

Defined in Squeal.PostgreSQL.PG

type PG Scientific Source #

PGnumeric

Instance details

Defined in Squeal.PostgreSQL.PG

type PG Text Source #

PGtext

Instance details

Defined in Squeal.PostgreSQL.PG

type PG Text = PGtext
type PG UTCTime Source #

PGtimestamptz

Instance details

Defined in Squeal.PostgreSQL.PG

type PG Value Source #

PGjson

Instance details

Defined in Squeal.PostgreSQL.PG

type PG Value = PGjson
type PG Text Source #

PGtext

Instance details

Defined in Squeal.PostgreSQL.PG

type PG Text = PGtext
type PG String Source #

PGtext

Instance details

Defined in Squeal.PostgreSQL.PG

type PG UUID Source #

PGuuid

Instance details

Defined in Squeal.PostgreSQL.PG

type PG UUID = PGuuid
type PG Day Source #

PGdate

Instance details

Defined in Squeal.PostgreSQL.PG

type PG Day = PGdate
type PG DiffTime Source #

PGinterval

Instance details

Defined in Squeal.PostgreSQL.PG

type PG TimeOfDay Source #

PGtime

Instance details

Defined in Squeal.PostgreSQL.PG

type PG LocalTime Source #

PGtimestamp

Instance details

Defined in Squeal.PostgreSQL.PG

type PG Money Source #

PGmoney

Instance details

Defined in Squeal.PostgreSQL.PG

type PG (NetAddr IP) Source #

PGinet

Instance details

Defined in Squeal.PostgreSQL.PG

type PG (NetAddr IP) = PGinet
type PG (FixArray hask) Source #

PGfixarray (DimPG hask) (FixPG hask)

Instance details

Defined in Squeal.PostgreSQL.PG

type PG (FixArray hask) = PGfixarray (DimPG hask) (FixPG hask)
type PG (VarArray [hask]) Source # 
Instance details

Defined in Squeal.PostgreSQL.PG

type PG (VarArray [hask]) = PGvararray (NullPG hask)
type PG (VarArray (Vector hask)) Source #

PGvararray (NullPG hask)

Instance details

Defined in Squeal.PostgreSQL.PG

type PG (VarArray (Vector hask)) = PGvararray (NullPG hask)
type PG (Enumerated hask) Source #

PGenum (LabelsPG hask)

Instance details

Defined in Squeal.PostgreSQL.PG

type PG (Enumerated hask) = PGenum (LabelsPG hask)
type PG (Composite hask) Source #

PGcomposite (RowPG hask)

Instance details

Defined in Squeal.PostgreSQL.PG

type PG (Composite hask) = PGcomposite (RowPG hask)
type PG (Jsonb hask) Source #

PGjsonb

Instance details

Defined in Squeal.PostgreSQL.PG

type PG (Jsonb hask) = PGjsonb
type PG (Json hask) Source #

PGjson

Instance details

Defined in Squeal.PostgreSQL.PG

type PG (Json hask) = PGjson
type PG (TimeOfDay, TimeZone) Source #

PGtimetz

Instance details

Defined in Squeal.PostgreSQL.PG

type family NullPG (hask :: Type) :: NullityType where ... Source #

NullPG turns a Haskell type into a NullityType.

>>> :kind! NullPG Double
NullPG Double :: NullityType
= 'NotNull 'PGfloat8
>>> :kind! NullPG (Maybe Double)
NullPG (Maybe Double) :: NullityType
= 'Null 'PGfloat8

Equations

NullPG (Maybe hask) = Null (PG hask) 
NullPG hask = NotNull (PG hask) 

type family TuplePG (hask :: Type) :: [NullityType] where ... Source #

TuplePG turns a Haskell tuple type (including record types) into the corresponding list of NullityTypes.

>>> :kind! TuplePG (Double, Maybe Char)
TuplePG (Double, Maybe Char) :: [NullityType]
= '[ 'NotNull 'PGfloat8, 'Null ('PGchar 1)]

Equations

TuplePG hask = TupleOf (TupleCodeOf hask (Code hask)) 

type family RowPG (hask :: Type) :: RowType where ... Source #

RowPG turns a Haskell Type into a RowType.

RowPG may be applied to normal Haskell record types provided they have Generic and HasDatatypeInfo instances;

>>> data Person = Person { name :: Strict.Text, age :: Int32 } deriving GHC.Generic
>>> instance SOP.Generic Person
>>> instance SOP.HasDatatypeInfo Person
>>> :kind! RowPG Person
RowPG Person :: [(Symbol, NullityType)]
= '["name" ::: 'NotNull 'PGtext, "age" ::: 'NotNull 'PGint4]

Equations

RowPG hask = RowOf (RecordCodeOf hask) 

Storage newtypes

newtype Money Source #

The Money newtype stores a monetary value in terms of the number of cents, i.e. $2,000.20 would be expressed as Money { cents = 200020 }.

>>> import Control.Monad (void)
>>> import Control.Monad.IO.Class (liftIO)
>>> import Squeal.PostgreSQL
>>> :{
let
  roundTrip :: Query_ (Public '[]) (Only Money) (Only Money)
  roundTrip = values_ $ parameter @1 money `as` #fromOnly
:}
>>> let input = Only (Money 20020)
>>> :{
withConnection "host=localhost port=5432 dbname=exampledb" $ do
  result <- runQueryParams roundTrip input
  Just output <- firstRow result
  liftIO . print $ input == output
:}
True

Constructors

Money 

Fields

Instances
Eq Money Source # 
Instance details

Defined in Squeal.PostgreSQL.PG

Methods

(==) :: Money -> Money -> Bool #

(/=) :: Money -> Money -> Bool #

Ord Money Source # 
Instance details

Defined in Squeal.PostgreSQL.PG

Methods

compare :: Money -> Money -> Ordering #

(<) :: Money -> Money -> Bool #

(<=) :: Money -> Money -> Bool #

(>) :: Money -> Money -> Bool #

(>=) :: Money -> Money -> Bool #

max :: Money -> Money -> Money #

min :: Money -> Money -> Money #

Read Money Source # 
Instance details

Defined in Squeal.PostgreSQL.PG

Show Money Source # 
Instance details

Defined in Squeal.PostgreSQL.PG

Methods

showsPrec :: Int -> Money -> ShowS #

show :: Money -> String #

showList :: [Money] -> ShowS #

Generic Money Source # 
Instance details

Defined in Squeal.PostgreSQL.PG

Associated Types

type Rep Money :: Type -> Type #

Methods

from :: Money -> Rep Money x #

to :: Rep Money x -> Money #

FromValue PGmoney Money Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

ToParam Money PGmoney Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

type Rep Money Source # 
Instance details

Defined in Squeal.PostgreSQL.PG

type Rep Money = D1 (MetaData "Money" "Squeal.PostgreSQL.PG" "squeal-postgresql-0.5.1.0-1zXd1HFs4I2ArqqDdrCP04" True) (C1 (MetaCons "Money" PrefixI True) (S1 (MetaSel (Just "cents") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int64)))
type PG Money Source #

PGmoney

Instance details

Defined in Squeal.PostgreSQL.PG

newtype Json hask Source #

The Json newtype is an indication that the Haskell type it's applied to should be stored as a PGjson.

Constructors

Json 

Fields

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

Defined in Squeal.PostgreSQL.Binary

Methods

fromValue :: Value (Json x) Source #

Eq hask => Eq (Json hask) Source # 
Instance details

Defined in Squeal.PostgreSQL.PG

Methods

(==) :: Json hask -> Json hask -> Bool #

(/=) :: Json hask -> Json hask -> Bool #

Ord hask => Ord (Json hask) Source # 
Instance details

Defined in Squeal.PostgreSQL.PG

Methods

compare :: Json hask -> Json hask -> Ordering #

(<) :: Json hask -> Json hask -> Bool #

(<=) :: Json hask -> Json hask -> Bool #

(>) :: Json hask -> Json hask -> Bool #

(>=) :: Json hask -> Json hask -> Bool #

max :: Json hask -> Json hask -> Json hask #

min :: Json hask -> Json hask -> Json hask #

Read hask => Read (Json hask) Source # 
Instance details

Defined in Squeal.PostgreSQL.PG

Methods

readsPrec :: Int -> ReadS (Json hask) #

readList :: ReadS [Json hask] #

readPrec :: ReadPrec (Json hask) #

readListPrec :: ReadPrec [Json hask] #

Show hask => Show (Json hask) Source # 
Instance details

Defined in Squeal.PostgreSQL.PG

Methods

showsPrec :: Int -> Json hask -> ShowS #

show :: Json hask -> String #

showList :: [Json hask] -> ShowS #

Generic (Json hask) Source # 
Instance details

Defined in Squeal.PostgreSQL.PG

Associated Types

type Rep (Json hask) :: Type -> Type #

Methods

from :: Json hask -> Rep (Json hask) x #

to :: Rep (Json hask) x -> Json hask #

ToJSON hask => Literal (Json hask) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Literal

Methods

literal :: Json hask -> Expr (null (PG (Json hask))) Source #

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

Defined in Squeal.PostgreSQL.Binary

type Rep (Json hask) Source # 
Instance details

Defined in Squeal.PostgreSQL.PG

type Rep (Json hask) = D1 (MetaData "Json" "Squeal.PostgreSQL.PG" "squeal-postgresql-0.5.1.0-1zXd1HFs4I2ArqqDdrCP04" True) (C1 (MetaCons "Json" PrefixI True) (S1 (MetaSel (Just "getJson") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 hask)))
type PG (Json hask) Source #

PGjson

Instance details

Defined in Squeal.PostgreSQL.PG

type PG (Json hask) = PGjson

newtype Jsonb hask Source #

The Jsonb newtype is an indication that the Haskell type it's applied to should be stored as a PGjsonb.

Constructors

Jsonb 

Fields

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

Defined in Squeal.PostgreSQL.Binary

Methods

fromValue :: Value (Jsonb x) Source #

Eq hask => Eq (Jsonb hask) Source # 
Instance details

Defined in Squeal.PostgreSQL.PG

Methods

(==) :: Jsonb hask -> Jsonb hask -> Bool #

(/=) :: Jsonb hask -> Jsonb hask -> Bool #

Ord hask => Ord (Jsonb hask) Source # 
Instance details

Defined in Squeal.PostgreSQL.PG

Methods

compare :: Jsonb hask -> Jsonb hask -> Ordering #

(<) :: Jsonb hask -> Jsonb hask -> Bool #

(<=) :: Jsonb hask -> Jsonb hask -> Bool #

(>) :: Jsonb hask -> Jsonb hask -> Bool #

(>=) :: Jsonb hask -> Jsonb hask -> Bool #

max :: Jsonb hask -> Jsonb hask -> Jsonb hask #

min :: Jsonb hask -> Jsonb hask -> Jsonb hask #

Read hask => Read (Jsonb hask) Source # 
Instance details

Defined in Squeal.PostgreSQL.PG

Methods

readsPrec :: Int -> ReadS (Jsonb hask) #

readList :: ReadS [Jsonb hask] #

readPrec :: ReadPrec (Jsonb hask) #

readListPrec :: ReadPrec [Jsonb hask] #

Show hask => Show (Jsonb hask) Source # 
Instance details

Defined in Squeal.PostgreSQL.PG

Methods

showsPrec :: Int -> Jsonb hask -> ShowS #

show :: Jsonb hask -> String #

showList :: [Jsonb hask] -> ShowS #

Generic (Jsonb hask) Source # 
Instance details

Defined in Squeal.PostgreSQL.PG

Associated Types

type Rep (Jsonb hask) :: Type -> Type #

Methods

from :: Jsonb hask -> Rep (Jsonb hask) x #

to :: Rep (Jsonb hask) x -> Jsonb hask #

ToJSON hask => Literal (Jsonb hask) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Literal

Methods

literal :: Jsonb hask -> Expr (null (PG (Jsonb hask))) Source #

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

Defined in Squeal.PostgreSQL.Binary

type Rep (Jsonb hask) Source # 
Instance details

Defined in Squeal.PostgreSQL.PG

type Rep (Jsonb hask) = D1 (MetaData "Jsonb" "Squeal.PostgreSQL.PG" "squeal-postgresql-0.5.1.0-1zXd1HFs4I2ArqqDdrCP04" True) (C1 (MetaCons "Jsonb" PrefixI True) (S1 (MetaSel (Just "getJsonb") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 hask)))
type PG (Jsonb hask) Source #

PGjsonb

Instance details

Defined in Squeal.PostgreSQL.PG

type PG (Jsonb hask) = PGjsonb

newtype Composite record Source #

The Composite newtype is an indication that the Haskell type it's applied to should be stored as a PGcomposite.

Constructors

Composite 

Fields

Instances
Eq record => Eq (Composite record) Source # 
Instance details

Defined in Squeal.PostgreSQL.PG

Methods

(==) :: Composite record -> Composite record -> Bool #

(/=) :: Composite record -> Composite record -> Bool #

Ord record => Ord (Composite record) Source # 
Instance details

Defined in Squeal.PostgreSQL.PG

Methods

compare :: Composite record -> Composite record -> Ordering #

(<) :: Composite record -> Composite record -> Bool #

(<=) :: Composite record -> Composite record -> Bool #

(>) :: Composite record -> Composite record -> Bool #

(>=) :: Composite record -> Composite record -> Bool #

max :: Composite record -> Composite record -> Composite record #

min :: Composite record -> Composite record -> Composite record #

Read record => Read (Composite record) Source # 
Instance details

Defined in Squeal.PostgreSQL.PG

Methods

readsPrec :: Int -> ReadS (Composite record) #

readList :: ReadS [Composite record] #

readPrec :: ReadPrec (Composite record) #

readListPrec :: ReadPrec [Composite record] #

Show record => Show (Composite record) Source # 
Instance details

Defined in Squeal.PostgreSQL.PG

Methods

showsPrec :: Int -> Composite record -> ShowS #

show :: Composite record -> String #

showList :: [Composite record] -> ShowS #

Generic (Composite record) Source # 
Instance details

Defined in Squeal.PostgreSQL.PG

Associated Types

type Rep (Composite record) :: Type -> Type #

Methods

from :: Composite record -> Rep (Composite record) x #

to :: Rep (Composite record) x -> Composite record #

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

Defined in Squeal.PostgreSQL.Binary

(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 #

type Rep (Composite record) Source # 
Instance details

Defined in Squeal.PostgreSQL.PG

type Rep (Composite record) = D1 (MetaData "Composite" "Squeal.PostgreSQL.PG" "squeal-postgresql-0.5.1.0-1zXd1HFs4I2ArqqDdrCP04" True) (C1 (MetaCons "Composite" PrefixI True) (S1 (MetaSel (Just "getComposite") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 record)))
type PG (Composite hask) Source #

PGcomposite (RowPG hask)

Instance details

Defined in Squeal.PostgreSQL.PG

type PG (Composite hask) = PGcomposite (RowPG hask)

newtype Enumerated enum Source #

The Enumerated newtype is an indication that the Haskell type it's applied to should be stored as a PGenum.

Constructors

Enumerated 

Fields

Instances
Eq enum => Eq (Enumerated enum) Source # 
Instance details

Defined in Squeal.PostgreSQL.PG

Methods

(==) :: Enumerated enum -> Enumerated enum -> Bool #

(/=) :: Enumerated enum -> Enumerated enum -> Bool #

Ord enum => Ord (Enumerated enum) Source # 
Instance details

Defined in Squeal.PostgreSQL.PG

Methods

compare :: Enumerated enum -> Enumerated enum -> Ordering #

(<) :: Enumerated enum -> Enumerated enum -> Bool #

(<=) :: Enumerated enum -> Enumerated enum -> Bool #

(>) :: Enumerated enum -> Enumerated enum -> Bool #

(>=) :: Enumerated enum -> Enumerated enum -> Bool #

max :: Enumerated enum -> Enumerated enum -> Enumerated enum #

min :: Enumerated enum -> Enumerated enum -> Enumerated enum #

Read enum => Read (Enumerated enum) Source # 
Instance details

Defined in Squeal.PostgreSQL.PG

Show enum => Show (Enumerated enum) Source # 
Instance details

Defined in Squeal.PostgreSQL.PG

Methods

showsPrec :: Int -> Enumerated enum -> ShowS #

show :: Enumerated enum -> String #

showList :: [Enumerated enum] -> ShowS #

Generic (Enumerated enum) Source # 
Instance details

Defined in Squeal.PostgreSQL.PG

Associated Types

type Rep (Enumerated enum) :: Type -> Type #

Methods

from :: Enumerated enum -> Rep (Enumerated enum) x #

to :: Rep (Enumerated enum) x -> Enumerated enum #

ToParam (Enumerated enum) (PG (Enumerated enum)) => Literal (Enumerated enum) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Literal

Methods

literal :: Enumerated enum -> Expr (null (PG (Enumerated enum))) Source #

(IsEnumType y, HasDatatypeInfo y, LabelsPG y ~ labels) => FromValue (PGenum labels) (Enumerated y) 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 #

type Rep (Enumerated enum) Source # 
Instance details

Defined in Squeal.PostgreSQL.PG

type Rep (Enumerated enum) = D1 (MetaData "Enumerated" "Squeal.PostgreSQL.PG" "squeal-postgresql-0.5.1.0-1zXd1HFs4I2ArqqDdrCP04" True) (C1 (MetaCons "Enumerated" PrefixI True) (S1 (MetaSel (Just "getEnumerated") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 enum)))
type PG (Enumerated hask) Source #

PGenum (LabelsPG hask)

Instance details

Defined in Squeal.PostgreSQL.PG

type PG (Enumerated hask) = PGenum (LabelsPG hask)

newtype VarArray arr Source #

The VarArray newtype is an indication that the Haskell type it's applied to should be stored as a PGvararray.

>>> :kind! PG (VarArray (Vector Double))
PG (VarArray (Vector Double)) :: PGType
= 'PGvararray ('NotNull 'PGfloat8)

Constructors

VarArray 

Fields

Instances
Eq arr => Eq (VarArray arr) Source # 
Instance details

Defined in Squeal.PostgreSQL.PG

Methods

(==) :: VarArray arr -> VarArray arr -> Bool #

(/=) :: VarArray arr -> VarArray arr -> Bool #

Ord arr => Ord (VarArray arr) Source # 
Instance details

Defined in Squeal.PostgreSQL.PG

Methods

compare :: VarArray arr -> VarArray arr -> Ordering #

(<) :: VarArray arr -> VarArray arr -> Bool #

(<=) :: VarArray arr -> VarArray arr -> Bool #

(>) :: VarArray arr -> VarArray arr -> Bool #

(>=) :: VarArray arr -> VarArray arr -> Bool #

max :: VarArray arr -> VarArray arr -> VarArray arr #

min :: VarArray arr -> VarArray arr -> VarArray arr #

Read arr => Read (VarArray arr) Source # 
Instance details

Defined in Squeal.PostgreSQL.PG

Show arr => Show (VarArray arr) Source # 
Instance details

Defined in Squeal.PostgreSQL.PG

Methods

showsPrec :: Int -> VarArray arr -> ShowS #

show :: VarArray arr -> String #

showList :: [VarArray arr] -> ShowS #

Generic (VarArray arr) Source # 
Instance details

Defined in Squeal.PostgreSQL.PG

Associated Types

type Rep (VarArray arr) :: Type -> Type #

Methods

from :: VarArray arr -> Rep (VarArray arr) x #

to :: Rep (VarArray arr) x -> VarArray arr #

FromValue pg y => FromValue (PGvararray (Null pg)) (VarArray [Maybe y]) Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

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

Defined in Squeal.PostgreSQL.Binary

FromValue pg y => FromValue (PGvararray (NotNull pg)) (VarArray [y]) Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

Methods

fromValue :: Value (VarArray [y]) Source #

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

Defined in Squeal.PostgreSQL.Binary

(ToNullityParam x ty, ty ~ nullity pg, HasOid pg) => ToParam (VarArray [x]) (PGvararray ty) Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

Methods

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

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

Defined in Squeal.PostgreSQL.Binary

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

Defined in Squeal.PostgreSQL.Binary

type Rep (VarArray arr) Source # 
Instance details

Defined in Squeal.PostgreSQL.PG

type Rep (VarArray arr) = D1 (MetaData "VarArray" "Squeal.PostgreSQL.PG" "squeal-postgresql-0.5.1.0-1zXd1HFs4I2ArqqDdrCP04" True) (C1 (MetaCons "VarArray" PrefixI True) (S1 (MetaSel (Just "getVarArray") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 arr)))
type PG (VarArray [hask]) Source # 
Instance details

Defined in Squeal.PostgreSQL.PG

type PG (VarArray [hask]) = PGvararray (NullPG hask)
type PG (VarArray (Vector hask)) Source #

PGvararray (NullPG hask)

Instance details

Defined in Squeal.PostgreSQL.PG

type PG (VarArray (Vector hask)) = PGvararray (NullPG hask)

newtype FixArray arr Source #

The FixArray newtype is an indication that the Haskell type it's applied to should be stored as a PGfixarray.

>>> :kind! PG (FixArray ((Double, Double), (Double, Double)))
PG (FixArray ((Double, Double), (Double, Double))) :: PGType
= 'PGfixarray '[2, 2] ('NotNull 'PGfloat8)

Constructors

FixArray 

Fields

Instances
Eq arr => Eq (FixArray arr) Source # 
Instance details

Defined in Squeal.PostgreSQL.PG

Methods

(==) :: FixArray arr -> FixArray arr -> Bool #

(/=) :: FixArray arr -> FixArray arr -> Bool #

Ord arr => Ord (FixArray arr) Source # 
Instance details

Defined in Squeal.PostgreSQL.PG

Methods

compare :: FixArray arr -> FixArray arr -> Ordering #

(<) :: FixArray arr -> FixArray arr -> Bool #

(<=) :: FixArray arr -> FixArray arr -> Bool #

(>) :: FixArray arr -> FixArray arr -> Bool #

(>=) :: FixArray arr -> FixArray arr -> Bool #

max :: FixArray arr -> FixArray arr -> FixArray arr #

min :: FixArray arr -> FixArray arr -> FixArray arr #

Read arr => Read (FixArray arr) Source # 
Instance details

Defined in Squeal.PostgreSQL.PG

Show arr => Show (FixArray arr) Source # 
Instance details

Defined in Squeal.PostgreSQL.PG

Methods

showsPrec :: Int -> FixArray arr -> ShowS #

show :: FixArray arr -> String #

showList :: [FixArray arr] -> ShowS #

Generic (FixArray arr) Source # 
Instance details

Defined in Squeal.PostgreSQL.PG

Associated Types

type Rep (FixArray arr) :: Type -> Type #

Methods

from :: FixArray arr -> Rep (FixArray arr) x #

to :: Rep (FixArray arr) x -> FixArray arr #

(ToFixArray x dims ty, ty ~ nullity pg, HasOid pg) => ToParam (FixArray x) (PGfixarray dims ty) Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

Methods

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

FromFixArray dims ty y => FromValue (PGfixarray dims ty) (FixArray y) Source # 
Instance details

Defined in Squeal.PostgreSQL.Binary

type Rep (FixArray arr) Source # 
Instance details

Defined in Squeal.PostgreSQL.PG

type Rep (FixArray arr) = D1 (MetaData "FixArray" "Squeal.PostgreSQL.PG" "squeal-postgresql-0.5.1.0-1zXd1HFs4I2ArqqDdrCP04" True) (C1 (MetaCons "FixArray" PrefixI True) (S1 (MetaSel (Just "getFixArray") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 arr)))
type PG (FixArray hask) Source #

PGfixarray (DimPG hask) (FixPG hask)

Instance details

Defined in Squeal.PostgreSQL.PG

type PG (FixArray hask) = PGfixarray (DimPG hask) (FixPG hask)

Type families

type family LabelsPG (hask :: Type) :: [ConstructorName] where ... Source #

The LabelsPG type family calculates the constructors of a Haskell enum type.

>>> data Schwarma = Beef | Lamb | Chicken deriving GHC.Generic
>>> instance SOP.Generic Schwarma
>>> instance SOP.HasDatatypeInfo Schwarma
>>> :kind! LabelsPG Schwarma
LabelsPG Schwarma :: [Type.ConstructorName]
= '["Beef", "Lamb", "Chicken"]

type family DimPG (hask :: Type) :: [Nat] where ... Source #

DimPG turns Haskell nested homogeneous tuples into a list of lengths.

Equations

DimPG (x, x) = 2 ': DimPG x 
DimPG (x, x, x) = 3 ': DimPG x 
DimPG (x, x, x, x) = 4 ': DimPG x 
DimPG (x, x, x, x, x) = 5 ': DimPG x 
DimPG (x, x, x, x, x, x) = 6 ': DimPG x 
DimPG (x, x, x, x, x, x, x) = 7 ': DimPG x 
DimPG (x, x, x, x, x, x, x, x) = 8 ': DimPG x 
DimPG (x, x, x, x, x, x, x, x, x) = 9 ': DimPG x 
DimPG (x, x, x, x, x, x, x, x, x, x) = 10 ': DimPG x 
DimPG x = '[] 

type family FixPG (hask :: Type) :: NullityType where ... Source #

FixPG extracts NullPG of the base type of nested homogeneous tuples.

Equations

FixPG (x, x) = FixPG x 
FixPG (x, x, x) = FixPG x 
FixPG (x, x, x, x) = FixPG x 
FixPG (x, x, x, x, x) = FixPG x 
FixPG (x, x, x, x, x, x) = FixPG x 
FixPG (x, x, x, x, x, x, x) = FixPG x 
FixPG (x, x, x, x, x, x, x, x) = FixPG x 
FixPG (x, x, x, x, x, x, x, x, x) = FixPG x 
FixPG (x, x, x, x, x, x, x, x, x, x) = FixPG x 
FixPG (x, x, x, x, x, x, x, x, x, x, x) = FixPG x 
FixPG x = NullPG x 

type family TupleOf (tuple :: [Type]) :: [NullityType] where ... Source #

TupleOf turns a list of Haskell Types into a list of NullityTypes.

Equations

TupleOf '[] = '[] 
TupleOf (hask ': tuple) = NullPG hask ': TupleOf tuple 

type family TupleCodeOf (hask :: Type) (code :: [[Type]]) :: [Type] where ... Source #

TupleCodeOf takes the Code of a haskell Type and if it's a simple product returns it, otherwise giving a TypeError.

Equations

TupleCodeOf hask '[tuple] = tuple 
TupleCodeOf hask '[] = TypeError (((Text "The type `" :<>: ShowType hask) :<>: Text "' is not a tuple type.") :$$: Text "It is a void type with no constructors.") 
TupleCodeOf hask (_ ': (_ ': _)) = TypeError (((Text "The type `" :<>: ShowType hask) :<>: Text "' is not a tuple type.") :$$: Text "It is a sum type with more than one constructor.") 

type family RowOf (record :: [(Symbol, Type)]) :: RowType where ... Source #

RowOf applies NullPG to the fields of a list.

Equations

RowOf '[] = '[] 
RowOf ((col ::: ty) ': record) = (col ::: NullPG ty) ': RowOf record 

type family ConstructorsOf (datatype :: DatatypeInfo) :: [ConstructorInfo] where ... Source #

Calculates constructors of a datatype.

Equations

ConstructorsOf (ADT _module _datatype constructors) = constructors 
ConstructorsOf (Newtype _module _datatype constructor) = '[constructor] 

type family ConstructorNameOf (constructor :: ConstructorInfo) :: ConstructorName where ... Source #

Calculates the name of a nullary constructor, otherwise generates a type error.

Equations

ConstructorNameOf (Constructor name) = name 
ConstructorNameOf (Infix name _assoc _fix) = TypeError (Text "ConstructorNameOf error: non-nullary constructor " :<>: Text name) 
ConstructorNameOf (Record name _fields) = TypeError (Text "ConstructorNameOf error: non-nullary constructor " :<>: Text name) 

type family ConstructorNamesOf (constructors :: [ConstructorInfo]) :: [ConstructorName] where ... Source #

Calculate the names of nullary constructors.

Equations

ConstructorNamesOf '[] = '[] 
ConstructorNamesOf (constructor ': constructors) = ConstructorNameOf constructor ': ConstructorNamesOf constructors