opaleye-0.5.3.0: An SQL-generating DSL targeting PostgreSQL

Safe HaskellNone
LanguageHaskell2010

Opaleye.Constant

Synopsis

Documentation

constant :: Default Constant haskells columns => haskells -> columns Source #

constant provides a convenient typeclass wrapper around the Column creation functions in Opaleye.PGTypes. Besides convenience it doesn't provide any additional functionality.

It can be used with functions like runInsert to insert custom Haskell types into the database. The following is an example of a function for inserting custom types.

  customInsert
     :: ( Default Constant haskells columns )
     => Connection
     -> Table columns columns'
     -> haskells
     -> IO Int64
  customInsert conn table haskells = runInsert conn table $ constant haskells

In order to use this function with your custom types, you need to define an instance of Default Constant for your custom types.

newtype Constant haskells columns Source #

Constructors

Constant 

Fields

Instances

SumProfunctor Constant Source # 

Methods

(+++!) :: Constant a b -> Constant a' b' -> Constant (Either a a') (Either b b') #

ProductProfunctor Constant Source # 

Methods

empty :: Constant () () #

(***!) :: Constant a b -> Constant a' b' -> Constant (a, a') (b, b') #

Profunctor Constant Source # 

Methods

dimap :: (a -> b) -> (c -> d) -> Constant b c -> Constant a d #

lmap :: (a -> b) -> Constant b c -> Constant a c #

rmap :: (b -> c) -> Constant a b -> Constant a c #

(#.) :: Coercible * c b => (b -> c) -> Constant a b -> Constant a c #

(.#) :: Coercible * b a => Constant b c -> (a -> b) -> Constant a c #

Default Constant Bool (Column PGBool) Source # 
Default Constant Double (Column PGFloat8) Source # 
Default Constant Int (Column PGInt4) Source # 
Default Constant Int32 (Column PGInt4) Source # 
Default Constant Int64 (Column PGInt8) Source # 
Default Constant ByteString (Column PGJsonb) Source # 
Default Constant ByteString (Column PGJson) Source # 
Default Constant ByteString (Column PGBytea) Source # 
Default Constant ByteString (Column PGJsonb) Source # 
Default Constant ByteString (Column PGJson) Source # 
Default Constant ByteString (Column PGBytea) Source # 
Default Constant String (Column PGText) Source # 
Default Constant Text (Column PGText) Source # 
Default Constant UTCTime (Column PGTimestamptz) Source # 
Default Constant Value (Column PGJsonb) Source # 
Default Constant Value (Column PGJson) Source # 
Default Constant Text (Column PGText) Source # 
Default Constant LocalTime (Column PGTimestamp) Source # 
Default Constant TimeOfDay (Column PGTime) Source # 
Default Constant Day (Column PGDate) Source # 
Default Constant UUID (Column PGUuid) Source # 
(Default Constant a (Column b), IsSqlType b) => Default Constant [a] (Column (PGArray b)) Source # 

Methods

def :: Constant [a] (Column (PGArray b)) #

Default Constant haskell (Column sql) => Default Constant (Maybe haskell) (Maybe (Column sql)) Source # 

Methods

def :: Constant (Maybe haskell) (Maybe (Column sql)) #

Default Constant haskell (Column sql) => Default Constant (Maybe haskell) (Column (Nullable sql)) Source # 

Methods

def :: Constant (Maybe haskell) (Column (Nullable sql)) #

Default Constant (CI Text) (Column PGCitext) Source # 
Default Constant (CI Text) (Column PGCitext) Source # 
Default Constant (PGRange Int) (Column (PGRange PGInt4)) Source # 
Default Constant (PGRange Int64) (Column (PGRange PGInt8)) Source # 
Default Constant (PGRange UTCTime) (Column (PGRange PGTimestamptz)) Source # 
Default Constant (PGRange LocalTime) (Column (PGRange PGTimestamp)) Source # 
Default Constant (PGRange Day) (Column (PGRange PGDate)) Source # 
Functor (Constant a) Source # 

Methods

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

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

Applicative (Constant a) Source # 

Methods

pure :: a -> Constant a a #

(<*>) :: Constant a (a -> b) -> Constant a a -> Constant a b #

(*>) :: Constant a a -> Constant a b -> Constant a b #

(<*) :: Constant a a -> Constant a b -> Constant a a #