opaleye-0.6.7003.1: An SQL-generating DSL targeting PostgreSQL

Safe HaskellNone
LanguageHaskell2010

Opaleye.Constant

Synopsis

Documentation

toFields :: Default Constant haskells fields => haskells -> fields Source #

toFields provides a convenient typeclass wrapper around the Column creation functions in Opaleye.SqlTypes. 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 fields )
     => Connection
     -> Table fields fields'
     -> haskells
     -> IO Int64
  customInsert conn table haskells = runInsert conn table $ toFields haskells

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

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

newtype Constant haskells fields Source #

Constructors

Constant 

Fields

Instances
Profunctor Constant Source # 
Instance details

Defined in Opaleye.Constant

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 => q b c -> Constant a b -> Constant a c #

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

ProductProfunctor Constant Source # 
Instance details

Defined in Opaleye.Constant

Methods

purePP :: b -> Constant a b #

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

empty :: Constant () () #

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

SumProfunctor Constant Source # 
Instance details

Defined in Opaleye.Constant

Methods

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

Default Constant Bool (Column SqlBool) Source # 
Instance details

Defined in Opaleye.Constant

Default Constant Double (Column SqlFloat8) Source # 
Instance details

Defined in Opaleye.Constant

Default Constant Int (Column SqlInt4) Source # 
Instance details

Defined in Opaleye.Constant

Default Constant Int32 (Column SqlInt4) Source # 
Instance details

Defined in Opaleye.Constant

Default Constant Int64 (Column SqlInt8) Source # 
Instance details

Defined in Opaleye.Constant

Default Constant ByteString (Column SqlJsonb) Source # 
Instance details

Defined in Opaleye.Constant

Default Constant ByteString (Column SqlJson) Source # 
Instance details

Defined in Opaleye.Constant

Default Constant ByteString (Column SqlBytea) Source # 
Instance details

Defined in Opaleye.Constant

Default Constant ByteString (Column SqlJsonb) Source # 
Instance details

Defined in Opaleye.Constant

Default Constant ByteString (Column SqlJson) Source # 
Instance details

Defined in Opaleye.Constant

Default Constant ByteString (Column SqlBytea) Source # 
Instance details

Defined in Opaleye.Constant

Default Constant Scientific (Column SqlNumeric) Source # 
Instance details

Defined in Opaleye.Constant

Default Constant String (Column SqlText) Source # 
Instance details

Defined in Opaleye.Constant

Default Constant Text (Column SqlText) Source # 
Instance details

Defined in Opaleye.Constant

Default Constant UTCTime (Column SqlTimestamptz) Source # 
Instance details

Defined in Opaleye.Constant

Default Constant Value (Column SqlJsonb) Source # 
Instance details

Defined in Opaleye.Constant

Default Constant Value (Column SqlJson) Source # 
Instance details

Defined in Opaleye.Constant

Default Constant Text (Column SqlText) Source # 
Instance details

Defined in Opaleye.Constant

Default Constant ZonedTime (Column SqlTimestamptz) Source # 
Instance details

Defined in Opaleye.Constant

Default Constant LocalTime (Column SqlTimestamp) Source # 
Instance details

Defined in Opaleye.Constant

Default Constant TimeOfDay (Column SqlTime) Source # 
Instance details

Defined in Opaleye.Constant

Default Constant Day (Column SqlDate) Source # 
Instance details

Defined in Opaleye.Constant

Default Constant UUID (Column SqlUuid) Source # 
Instance details

Defined in Opaleye.Constant

(Default Constant a (Column b), IsSqlType b) => Default Constant [a] (Column (SqlArray b)) Source # 
Instance details

Defined in Opaleye.Constant

Methods

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

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

Defined in Opaleye.Constant

Methods

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

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

Defined in Opaleye.Constant

Methods

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

Default Constant (CI Text) (Column SqlCitext) Source # 
Instance details

Defined in Opaleye.Constant

Default Constant (CI Text) (Column SqlCitext) Source # 
Instance details

Defined in Opaleye.Constant

Default Constant (PGRange Int) (Column (SqlRange SqlInt4)) Source # 
Instance details

Defined in Opaleye.Constant

Default Constant (PGRange Int64) (Column (SqlRange SqlInt8)) Source # 
Instance details

Defined in Opaleye.Constant

Default Constant (PGRange Scientific) (Column (SqlRange SqlNumeric)) Source # 
Instance details

Defined in Opaleye.Constant

Default Constant (PGRange UTCTime) (Column (SqlRange SqlTimestamptz)) Source # 
Instance details

Defined in Opaleye.Constant

Default Constant (PGRange LocalTime) (Column (SqlRange SqlTimestamp)) Source # 
Instance details

Defined in Opaleye.Constant

Default Constant (PGRange Day) (Column (SqlRange SqlDate)) Source # 
Instance details

Defined in Opaleye.Constant

Functor (Constant a) Source # 
Instance details

Defined in Opaleye.Constant

Methods

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

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

Applicative (Constant a) Source # 
Instance details

Defined in Opaleye.Constant

Methods

pure :: a0 -> Constant a a0 #

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

liftA2 :: (a0 -> b -> c) -> Constant a a0 -> Constant a b -> Constant a c #

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

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