opaleye-0.6.7000.0: 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 # 

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 #

ProductProfunctor Constant Source # 

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 # 

Methods

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

Default Constant Bool (Column SqlBool) Source # 
Default Constant Double (Column SqlFloat8) Source # 
Default Constant Int (Column SqlInt4) Source # 
Default Constant Int32 (Column SqlInt4) Source # 
Default Constant Int64 (Column SqlInt8) Source # 
Default Constant ByteString (Column SqlJsonb) Source # 
Default Constant ByteString (Column SqlJson) Source # 
Default Constant ByteString (Column SqlBytea) Source # 
Default Constant ByteString (Column SqlJsonb) Source # 
Default Constant ByteString (Column SqlJson) Source # 
Default Constant ByteString (Column SqlBytea) Source # 
Default Constant Scientific (Column SqlNumeric) Source # 
Default Constant String (Column SqlText) Source # 
Default Constant Text (Column SqlText) Source # 
Default Constant UTCTime (Column SqlTimestamptz) Source # 
Default Constant Value (Column SqlJsonb) Source # 
Default Constant Value (Column SqlJson) Source # 
Default Constant Text (Column SqlText) Source # 
Default Constant ZonedTime (Column SqlTimestamptz) Source # 
Default Constant LocalTime (Column SqlTimestamp) Source # 
Default Constant TimeOfDay (Column SqlTime) Source # 
Default Constant Day (Column SqlDate) Source # 
Default Constant UUID (Column SqlUuid) Source # 
(Default Constant a (Column b), IsSqlType b) => Default Constant [a] (Column (SqlArray b)) Source # 

Methods

def :: Constant [a] (Column (SqlArray 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 SqlCitext) Source # 
Default Constant (CI Text) (Column SqlCitext) Source # 
Default Constant (PGRange Int) (Column (SqlRange SqlInt4)) Source # 
Default Constant (PGRange Int64) (Column (SqlRange SqlInt8)) Source # 
Default Constant (PGRange Scientific) (Column (SqlRange SqlNumeric)) Source # 
Default Constant (PGRange UTCTime) (Column (SqlRange SqlTimestamptz)) Source # 
Default Constant (PGRange LocalTime) (Column (SqlRange SqlTimestamp)) Source # 
Default Constant (PGRange Day) (Column (SqlRange SqlDate)) 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 #

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

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

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