squeal-postgresql-0.8.0.0: Squeal PostgreSQL Library
Copyright(c) Eitan Chatav 2010
Maintainereitan@morphism.tech
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Squeal.PostgreSQL.Type

Description

storage newtypes

Synopsis

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 }.

>>> :kind! PG Money
PG Money :: PGType
= 'PGmoney

Constructors

Money 

Fields

Instances

Instances details
Eq Money Source # 
Instance details

Defined in Squeal.PostgreSQL.Type

Methods

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

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

Ord Money Source # 
Instance details

Defined in Squeal.PostgreSQL.Type

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.Type

Show Money Source # 
Instance details

Defined in Squeal.PostgreSQL.Type

Methods

showsPrec :: Int -> Money -> ShowS #

show :: Money -> String #

showList :: [Money] -> ShowS #

Generic Money Source # 
Instance details

Defined in Squeal.PostgreSQL.Type

Associated Types

type Rep Money :: Type -> Type #

Methods

from :: Money -> Rep Money x #

to :: Rep Money x -> Money #

Generic Money Source # 
Instance details

Defined in Squeal.PostgreSQL.Type

Associated Types

type Code Money :: [[Type]] #

Methods

from :: Money -> Rep Money #

to :: Rep Money -> Money #

HasDatatypeInfo Money Source # 
Instance details

Defined in Squeal.PostgreSQL.Type

Associated Types

type DatatypeInfoOf Money :: DatatypeInfo #

Methods

datatypeInfo :: proxy Money -> DatatypeInfo (Code Money) #

IsPG Money Source #

PGmoney

Instance details

Defined in Squeal.PostgreSQL.Type.PG

Associated Types

type PG Money :: PGType Source #

FromPG Money Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Decode

Inline Money Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Inline

Methods

inline :: forall (null :: PGType -> NullType). Money -> Expr (null (PG Money)) Source #

ToPG db Money Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Encode

type Rep Money Source # 
Instance details

Defined in Squeal.PostgreSQL.Type

type Rep Money = D1 ('MetaData "Money" "Squeal.PostgreSQL.Type" "squeal-postgresql-0.8.0.0-HHFIvalMWy63oPSAK2xG8g" 'True) (C1 ('MetaCons "Money" 'PrefixI 'True) (S1 ('MetaSel ('Just "cents") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int64)))
type Code Money Source # 
Instance details

Defined in Squeal.PostgreSQL.Type

type DatatypeInfoOf Money Source # 
Instance details

Defined in Squeal.PostgreSQL.Type

type PG Money Source # 
Instance details

Defined in Squeal.PostgreSQL.Type.PG

type PG Money = 'PGmoney

newtype Json hask Source #

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

>>> :kind! PG (Json [String])
PG (Json [String]) :: PGType
= 'PGjson

Constructors

Json 

Fields

Instances

Instances details
ToJSON x => ToPG db (Json x) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Encode

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

Defined in Squeal.PostgreSQL.Type

Methods

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

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

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

Defined in Squeal.PostgreSQL.Type

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.Type

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.Type

Methods

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

show :: Json hask -> String #

showList :: [Json hask] -> ShowS #

Generic (Json hask) Source # 
Instance details

Defined in Squeal.PostgreSQL.Type

Associated Types

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

Methods

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

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

Generic (Json hask) Source # 
Instance details

Defined in Squeal.PostgreSQL.Type

Associated Types

type Code (Json hask) :: [[Type]] #

Methods

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

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

HasDatatypeInfo (Json hask) Source # 
Instance details

Defined in Squeal.PostgreSQL.Type

Associated Types

type DatatypeInfoOf (Json hask) :: DatatypeInfo #

Methods

datatypeInfo :: proxy (Json hask) -> DatatypeInfo (Code (Json hask)) #

IsPG (Json hask) Source #

PGjson

Instance details

Defined in Squeal.PostgreSQL.Type.PG

Associated Types

type PG (Json hask) :: PGType Source #

FromJSON x => FromPG (Json x) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Decode

ToJSON x => Inline (Json x) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Inline

Methods

inline :: forall (null :: PGType -> NullType). Json x -> Expr (null (PG (Json x))) Source #

type Rep (Json hask) Source # 
Instance details

Defined in Squeal.PostgreSQL.Type

type Rep (Json hask) = D1 ('MetaData "Json" "Squeal.PostgreSQL.Type" "squeal-postgresql-0.8.0.0-HHFIvalMWy63oPSAK2xG8g" 'True) (C1 ('MetaCons "Json" 'PrefixI 'True) (S1 ('MetaSel ('Just "getJson") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 hask)))
type Code (Json hask) Source # 
Instance details

Defined in Squeal.PostgreSQL.Type

type Code (Json hask) = GCode (Json hask)
type DatatypeInfoOf (Json hask) Source # 
Instance details

Defined in Squeal.PostgreSQL.Type

type PG (Json hask) Source # 
Instance details

Defined in Squeal.PostgreSQL.Type.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.

>>> :kind! PG (Jsonb [String])
PG (Jsonb [String]) :: PGType
= 'PGjsonb

Constructors

Jsonb 

Fields

Instances

Instances details
ToJSON x => ToPG db (Jsonb x) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Encode

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

Defined in Squeal.PostgreSQL.Type

Methods

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

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

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

Defined in Squeal.PostgreSQL.Type

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.Type

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.Type

Methods

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

show :: Jsonb hask -> String #

showList :: [Jsonb hask] -> ShowS #

Generic (Jsonb hask) Source # 
Instance details

Defined in Squeal.PostgreSQL.Type

Associated Types

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

Methods

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

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

Generic (Jsonb hask) Source # 
Instance details

Defined in Squeal.PostgreSQL.Type

Associated Types

type Code (Jsonb hask) :: [[Type]] #

Methods

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

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

HasDatatypeInfo (Jsonb hask) Source # 
Instance details

Defined in Squeal.PostgreSQL.Type

Associated Types

type DatatypeInfoOf (Jsonb hask) :: DatatypeInfo #

Methods

datatypeInfo :: proxy (Jsonb hask) -> DatatypeInfo (Code (Jsonb hask)) #

IsPG (Jsonb hask) Source #

PGjsonb

Instance details

Defined in Squeal.PostgreSQL.Type.PG

Associated Types

type PG (Jsonb hask) :: PGType Source #

FromJSON x => FromPG (Jsonb x) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Decode

ToJSON x => Inline (Jsonb x) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Inline

Methods

inline :: forall (null :: PGType -> NullType). Jsonb x -> Expr (null (PG (Jsonb x))) Source #

type Rep (Jsonb hask) Source # 
Instance details

Defined in Squeal.PostgreSQL.Type

type Rep (Jsonb hask) = D1 ('MetaData "Jsonb" "Squeal.PostgreSQL.Type" "squeal-postgresql-0.8.0.0-HHFIvalMWy63oPSAK2xG8g" 'True) (C1 ('MetaCons "Jsonb" 'PrefixI 'True) (S1 ('MetaSel ('Just "getJsonb") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 hask)))
type Code (Jsonb hask) Source # 
Instance details

Defined in Squeal.PostgreSQL.Type

type Code (Jsonb hask) = GCode (Jsonb hask)
type DatatypeInfoOf (Jsonb hask) Source # 
Instance details

Defined in Squeal.PostgreSQL.Type

type PG (Jsonb hask) Source # 
Instance details

Defined in Squeal.PostgreSQL.Type.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.

>>> :{
data Complex = Complex
  { real :: Double
  , imaginary :: Double
  } deriving stock GHC.Generic
    deriving anyclass (SOP.Generic, SOP.HasDatatypeInfo)
:}
>>> :kind! PG (Composite Complex)
PG (Composite Complex) :: PGType
= 'PGcomposite
    '["real" ::: 'NotNull 'PGfloat8,
      "imaginary" ::: 'NotNull 'PGfloat8]

Constructors

Composite 

Fields

Instances

Instances details
(SListI fields, IsRecord x xs, AllZip (ToField db) fields xs, All (OidOfField db) fields, RowPG x ~ fields) => ToPG db (Composite x) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Encode

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

Defined in Squeal.PostgreSQL.Type

Methods

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

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

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

Defined in Squeal.PostgreSQL.Type

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.Type

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.Type

Methods

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

show :: Composite record -> String #

showList :: [Composite record] -> ShowS #

Generic (Composite record) Source # 
Instance details

Defined in Squeal.PostgreSQL.Type

Associated Types

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

Methods

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

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

Generic (Composite record) Source # 
Instance details

Defined in Squeal.PostgreSQL.Type

Associated Types

type Code (Composite record) :: [[Type]] #

Methods

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

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

HasDatatypeInfo (Composite record) Source # 
Instance details

Defined in Squeal.PostgreSQL.Type

Associated Types

type DatatypeInfoOf (Composite record) :: DatatypeInfo #

Methods

datatypeInfo :: proxy (Composite record) -> DatatypeInfo (Code (Composite record)) #

IsPG (Composite hask) Source #

PGcomposite (RowPG hask)

Instance details

Defined in Squeal.PostgreSQL.Type.PG

Associated Types

type PG (Composite hask) :: PGType Source #

(IsRecord y ys, AllZip FromField row ys, RowPG y ~ row) => FromPG (Composite y) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Decode

(IsRecord x xs, AllZip InlineField xs (RowPG x)) => Inline (Composite x) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Inline

Methods

inline :: forall (null :: PGType -> NullType). Composite x -> Expr (null (PG (Composite x))) Source #

type Rep (Composite record) Source # 
Instance details

Defined in Squeal.PostgreSQL.Type

type Rep (Composite record) = D1 ('MetaData "Composite" "Squeal.PostgreSQL.Type" "squeal-postgresql-0.8.0.0-HHFIvalMWy63oPSAK2xG8g" 'True) (C1 ('MetaCons "Composite" 'PrefixI 'True) (S1 ('MetaSel ('Just "getComposite") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 record)))
type Code (Composite record) Source # 
Instance details

Defined in Squeal.PostgreSQL.Type

type Code (Composite record) = GCode (Composite record)
type DatatypeInfoOf (Composite record) Source # 
Instance details

Defined in Squeal.PostgreSQL.Type

type PG (Composite hask) Source # 
Instance details

Defined in Squeal.PostgreSQL.Type.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.

>>> :kind! PG (Enumerated Ordering)
PG (Enumerated Ordering) :: PGType
= 'PGenum '["LT", "EQ", "GT"]

Constructors

Enumerated 

Fields

Instances

Instances details
(IsEnumType x, HasDatatypeInfo x, LabelsPG x ~ labels) => ToPG db (Enumerated x) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Encode

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

Defined in Squeal.PostgreSQL.Type

Methods

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

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

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

Defined in Squeal.PostgreSQL.Type

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.Type

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

Defined in Squeal.PostgreSQL.Type

Methods

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

show :: Enumerated enum -> String #

showList :: [Enumerated enum] -> ShowS #

Generic (Enumerated enum) Source # 
Instance details

Defined in Squeal.PostgreSQL.Type

Associated Types

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

Methods

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

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

Generic (Enumerated enum) Source # 
Instance details

Defined in Squeal.PostgreSQL.Type

Associated Types

type Code (Enumerated enum) :: [[Type]] #

Methods

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

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

HasDatatypeInfo (Enumerated enum) Source # 
Instance details

Defined in Squeal.PostgreSQL.Type

Associated Types

type DatatypeInfoOf (Enumerated enum) :: DatatypeInfo #

Methods

datatypeInfo :: proxy (Enumerated enum) -> DatatypeInfo (Code (Enumerated enum)) #

IsPG (Enumerated hask) Source #

PGenum (LabelsPG hask)

Instance details

Defined in Squeal.PostgreSQL.Type.PG

Associated Types

type PG (Enumerated hask) :: PGType Source #

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

Defined in Squeal.PostgreSQL.Session.Decode

(IsEnumType x, HasDatatypeInfo x) => Inline (Enumerated x) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Inline

Methods

inline :: forall (null :: PGType -> NullType). Enumerated x -> Expr (null (PG (Enumerated x))) Source #

type Rep (Enumerated enum) Source # 
Instance details

Defined in Squeal.PostgreSQL.Type

type Rep (Enumerated enum) = D1 ('MetaData "Enumerated" "Squeal.PostgreSQL.Type" "squeal-postgresql-0.8.0.0-HHFIvalMWy63oPSAK2xG8g" 'True) (C1 ('MetaCons "Enumerated" 'PrefixI 'True) (S1 ('MetaSel ('Just "getEnumerated") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 enum)))
type Code (Enumerated enum) Source # 
Instance details

Defined in Squeal.PostgreSQL.Type

type Code (Enumerated enum) = GCode (Enumerated enum)
type DatatypeInfoOf (Enumerated enum) Source # 
Instance details

Defined in Squeal.PostgreSQL.Type

type PG (Enumerated hask) Source # 
Instance details

Defined in Squeal.PostgreSQL.Type.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.

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

Constructors

VarArray 

Fields

Instances

Instances details
(NullPG x ~ ty, ToArray db ('[] :: [Nat]) ty x, OidOfNull db ty) => ToPG db (VarArray (Vector x)) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Encode

(NullPG x ~ ty, ToArray db ('[] :: [Nat]) ty x, OidOfNull db ty) => ToPG db (VarArray [x]) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Encode

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

Defined in Squeal.PostgreSQL.Type

Methods

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

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

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

Defined in Squeal.PostgreSQL.Type

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.Type

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

Defined in Squeal.PostgreSQL.Type

Methods

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

show :: VarArray arr -> String #

showList :: [VarArray arr] -> ShowS #

Generic (VarArray arr) Source # 
Instance details

Defined in Squeal.PostgreSQL.Type

Associated Types

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

Methods

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

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

Generic (VarArray arr) Source # 
Instance details

Defined in Squeal.PostgreSQL.Type

Associated Types

type Code (VarArray arr) :: [[Type]] #

Methods

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

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

HasDatatypeInfo (VarArray arr) Source # 
Instance details

Defined in Squeal.PostgreSQL.Type

Associated Types

type DatatypeInfoOf (VarArray arr) :: DatatypeInfo #

Methods

datatypeInfo :: proxy (VarArray arr) -> DatatypeInfo (Code (VarArray arr)) #

IsPG (VarArray [x]) Source #

PGvararray (NullPG x)

Instance details

Defined in Squeal.PostgreSQL.Type.PG

Associated Types

type PG (VarArray [x]) :: PGType Source #

IsPG (VarArray (Vector x)) Source #

PGvararray (NullPG x)

Instance details

Defined in Squeal.PostgreSQL.Type.PG

Associated Types

type PG (VarArray (Vector x)) :: PGType Source #

(FromArray ('[] :: [Nat]) ty y, ty ~ NullPG y) => FromPG (VarArray [y]) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Decode

(FromArray ('[] :: [Nat]) ty y, ty ~ NullPG y) => FromPG (VarArray (Vector y)) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Decode

InlineParam x (NullPG x) => Inline (VarArray [x]) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Inline

Methods

inline :: forall (null :: PGType -> NullType). VarArray [x] -> Expr (null (PG (VarArray [x]))) Source #

InlineParam x (NullPG x) => Inline (VarArray (Vector x)) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Inline

Methods

inline :: forall (null :: PGType -> NullType). VarArray (Vector x) -> Expr (null (PG (VarArray (Vector x)))) Source #

type Rep (VarArray arr) Source # 
Instance details

Defined in Squeal.PostgreSQL.Type

type Rep (VarArray arr) = D1 ('MetaData "VarArray" "Squeal.PostgreSQL.Type" "squeal-postgresql-0.8.0.0-HHFIvalMWy63oPSAK2xG8g" 'True) (C1 ('MetaCons "VarArray" 'PrefixI 'True) (S1 ('MetaSel ('Just "getVarArray") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 arr)))
type Code (VarArray arr) Source # 
Instance details

Defined in Squeal.PostgreSQL.Type

type Code (VarArray arr) = GCode (VarArray arr)
type DatatypeInfoOf (VarArray arr) Source # 
Instance details

Defined in Squeal.PostgreSQL.Type

type PG (VarArray [x]) Source # 
Instance details

Defined in Squeal.PostgreSQL.Type.PG

type PG (VarArray [x]) = 'PGvararray (NullPG x)
type PG (VarArray (Vector x)) Source # 
Instance details

Defined in Squeal.PostgreSQL.Type.PG

type PG (VarArray (Vector x)) = 'PGvararray (NullPG x)

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

Instances details
(ToArray db dims ty x, OidOfNull db ty) => ToPG db (FixArray x) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Encode

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

Defined in Squeal.PostgreSQL.Type

Methods

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

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

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

Defined in Squeal.PostgreSQL.Type

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.Type

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

Defined in Squeal.PostgreSQL.Type

Methods

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

show :: FixArray arr -> String #

showList :: [FixArray arr] -> ShowS #

Generic (FixArray arr) Source # 
Instance details

Defined in Squeal.PostgreSQL.Type

Associated Types

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

Methods

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

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

Generic (FixArray arr) Source # 
Instance details

Defined in Squeal.PostgreSQL.Type

Associated Types

type Code (FixArray arr) :: [[Type]] #

Methods

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

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

HasDatatypeInfo (FixArray arr) Source # 
Instance details

Defined in Squeal.PostgreSQL.Type

Associated Types

type DatatypeInfoOf (FixArray arr) :: DatatypeInfo #

Methods

datatypeInfo :: proxy (FixArray arr) -> DatatypeInfo (Code (FixArray arr)) #

IsPG (FixArray hask) Source #

PGfixarray (DimPG hask) (FixPG hask)

Instance details

Defined in Squeal.PostgreSQL.Type.PG

Associated Types

type PG (FixArray hask) :: PGType Source #

FromArray dims ty y => FromPG (FixArray y) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Decode

type Rep (FixArray arr) Source # 
Instance details

Defined in Squeal.PostgreSQL.Type

type Rep (FixArray arr) = D1 ('MetaData "FixArray" "Squeal.PostgreSQL.Type" "squeal-postgresql-0.8.0.0-HHFIvalMWy63oPSAK2xG8g" 'True) (C1 ('MetaCons "FixArray" 'PrefixI 'True) (S1 ('MetaSel ('Just "getFixArray") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 arr)))
type Code (FixArray arr) Source # 
Instance details

Defined in Squeal.PostgreSQL.Type

type Code (FixArray arr) = GCode (FixArray arr)
type DatatypeInfoOf (FixArray arr) Source # 
Instance details

Defined in Squeal.PostgreSQL.Type

type PG (FixArray hask) Source # 
Instance details

Defined in Squeal.PostgreSQL.Type.PG

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

data VarChar (n :: Nat) Source #

Variable-length text type with limit

>>> :kind! PG (VarChar 4)
PG (VarChar 4) :: PGType
= 'PGvarchar 4

Instances

Instances details
ToPG db (VarChar n) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Encode

Eq (VarChar n) Source # 
Instance details

Defined in Squeal.PostgreSQL.Type

Methods

(==) :: VarChar n -> VarChar n -> Bool #

(/=) :: VarChar n -> VarChar n -> Bool #

Ord (VarChar n) Source # 
Instance details

Defined in Squeal.PostgreSQL.Type

Methods

compare :: VarChar n -> VarChar n -> Ordering #

(<) :: VarChar n -> VarChar n -> Bool #

(<=) :: VarChar n -> VarChar n -> Bool #

(>) :: VarChar n -> VarChar n -> Bool #

(>=) :: VarChar n -> VarChar n -> Bool #

max :: VarChar n -> VarChar n -> VarChar n #

min :: VarChar n -> VarChar n -> VarChar n #

Read (VarChar n) Source # 
Instance details

Defined in Squeal.PostgreSQL.Type

Show (VarChar n) Source # 
Instance details

Defined in Squeal.PostgreSQL.Type

Methods

showsPrec :: Int -> VarChar n -> ShowS #

show :: VarChar n -> String #

showList :: [VarChar n] -> ShowS #

IsPG (VarChar n) Source #

PGvarchar

Instance details

Defined in Squeal.PostgreSQL.Type.PG

Associated Types

type PG (VarChar n) :: PGType Source #

KnownNat n => FromPG (VarChar n) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Decode

(KnownNat n, 1 <= n) => Inline (VarChar n) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Inline

Methods

inline :: forall (null :: PGType -> NullType). VarChar n -> Expr (null (PG (VarChar n))) Source #

type PG (VarChar n) Source # 
Instance details

Defined in Squeal.PostgreSQL.Type.PG

type PG (VarChar n) = 'PGvarchar n

varChar :: forall n. KnownNat n => Text -> Maybe (VarChar n) Source #

Constructor for VarChar

getVarChar :: VarChar n -> Text Source #

Access the Text of a VarChar

data FixChar (n :: Nat) Source #

Fixed-length, blank padded

>>> :kind! PG (FixChar 4)
PG (FixChar 4) :: PGType
= 'PGchar 4

Instances

Instances details
ToPG db (FixChar n) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Encode

Eq (FixChar n) Source # 
Instance details

Defined in Squeal.PostgreSQL.Type

Methods

(==) :: FixChar n -> FixChar n -> Bool #

(/=) :: FixChar n -> FixChar n -> Bool #

Ord (FixChar n) Source # 
Instance details

Defined in Squeal.PostgreSQL.Type

Methods

compare :: FixChar n -> FixChar n -> Ordering #

(<) :: FixChar n -> FixChar n -> Bool #

(<=) :: FixChar n -> FixChar n -> Bool #

(>) :: FixChar n -> FixChar n -> Bool #

(>=) :: FixChar n -> FixChar n -> Bool #

max :: FixChar n -> FixChar n -> FixChar n #

min :: FixChar n -> FixChar n -> FixChar n #

Read (FixChar n) Source # 
Instance details

Defined in Squeal.PostgreSQL.Type

Show (FixChar n) Source # 
Instance details

Defined in Squeal.PostgreSQL.Type

Methods

showsPrec :: Int -> FixChar n -> ShowS #

show :: FixChar n -> String #

showList :: [FixChar n] -> ShowS #

IsPG (FixChar n) Source #

PGvarchar

Instance details

Defined in Squeal.PostgreSQL.Type.PG

Associated Types

type PG (FixChar n) :: PGType Source #

KnownNat n => FromPG (FixChar n) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Decode

(KnownNat n, 1 <= n) => Inline (FixChar n) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Inline

Methods

inline :: forall (null :: PGType -> NullType). FixChar n -> Expr (null (PG (FixChar n))) Source #

type PG (FixChar n) Source # 
Instance details

Defined in Squeal.PostgreSQL.Type.PG

type PG (FixChar n) = 'PGchar n

fixChar :: forall n. KnownNat n => Text -> Maybe (FixChar n) Source #

Constructor for FixChar

getFixChar :: FixChar n -> Text Source #

Access the Text of a FixChar

newtype Only x Source #

Only is a 1-tuple type, useful for encoding or decoding a singleton

Constructors

Only 

Fields

Instances

Instances details
Functor Only Source # 
Instance details

Defined in Squeal.PostgreSQL.Type

Methods

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

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

Foldable Only Source # 
Instance details

Defined in Squeal.PostgreSQL.Type

Methods

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

foldMap :: Monoid m => (a -> m) -> Only a -> 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.Type

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.Type

Methods

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

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

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

Defined in Squeal.PostgreSQL.Type

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.Type

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

Defined in Squeal.PostgreSQL.Type

Methods

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

show :: Only x -> String #

showList :: [Only x] -> ShowS #

Generic (Only x) Source # 
Instance details

Defined in Squeal.PostgreSQL.Type

Associated Types

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

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.Type

Associated Types

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

Methods

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

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

HasDatatypeInfo (Only x) Source # 
Instance details

Defined in Squeal.PostgreSQL.Type

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.Type

type Rep (Only x) = D1 ('MetaData "Only" "Squeal.PostgreSQL.Type" "squeal-postgresql-0.8.0.0-HHFIvalMWy63oPSAK2xG8g" '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.Type

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

Defined in Squeal.PostgreSQL.Type