module Opaleye.SqlTypes (
sqlInt4,
sqlDouble,
sqlInt8,
sqlNumeric,
SqlInt4,
SqlFloat8,
SqlNumeric,
SqlInt8,
SqlInt2,
SqlFloat4,
sqlDay,
sqlUTCTime,
sqlLocalTime,
sqlZonedTime,
sqlTimeOfDay,
SqlDate,
SqlTime,
SqlTimestamp,
SqlTimestamptz,
sqlJSON,
sqlStrictJSON,
sqlLazyJSON,
sqlValueJSON,
SqlJson,
sqlJSONB,
sqlStrictJSONB,
sqlLazyJSONB,
sqlValueJSONB,
SqlJsonb,
sqlString,
sqlStrictText,
sqlLazyText,
sqlCiStrictText,
sqlCiLazyText,
SqlText,
SqlCitext,
sqlArray,
SqlArray,
sqlRange,
SqlRange,
P.IsRangeType,
sqlBool,
sqlUUID,
sqlLazyByteString,
sqlStrictByteString,
SqlBool,
SqlUuid,
SqlBytea,
P.IsSqlType,
module Opaleye.SqlTypes,
) where
import qualified Opaleye.Field as F
import qualified Opaleye.Internal.PGTypesExternal as P
import Opaleye.Internal.PGTypesExternal (IsSqlType, IsRangeType)
import Opaleye.Internal.PGTypesExternal (SqlBool,
SqlDate,
SqlFloat4,
SqlFloat8,
SqlInt8,
SqlInt4,
SqlInt2,
SqlNumeric,
SqlText,
SqlTime,
SqlTimestamp,
SqlTimestamptz,
SqlUuid,
SqlCitext,
SqlArray,
SqlBytea,
SqlJson,
SqlJsonb,
SqlRange)
import qualified Data.Aeson as Ae
import qualified Data.ByteString as SByteString
import qualified Data.ByteString.Lazy as LByteString
import qualified Data.CaseInsensitive as CI
import Data.Int (Int64)
import Data.Scientific as Sci
import qualified Data.Text as SText
import qualified Data.Text.Lazy as LText
import qualified Data.Time as Time
import qualified Data.UUID as UUID
import qualified Database.PostgreSQL.Simple.Range as R
sqlString :: String -> F.Field SqlText
sqlString :: String -> Field SqlText
sqlString = String -> Column SqlText
String -> Field SqlText
P.pgString
sqlLazyByteString :: LByteString.ByteString -> F.Field SqlBytea
sqlLazyByteString :: ByteString -> Field SqlBytea
sqlLazyByteString = ByteString -> Column SqlBytea
ByteString -> Field SqlBytea
P.pgLazyByteString
sqlStrictByteString :: SByteString.ByteString -> F.Field SqlBytea
sqlStrictByteString :: ByteString -> Field SqlBytea
sqlStrictByteString = ByteString -> Column SqlBytea
ByteString -> Field SqlBytea
P.pgStrictByteString
sqlStrictText :: SText.Text -> F.Field SqlText
sqlStrictText :: Text -> Field SqlText
sqlStrictText = Text -> Column SqlText
Text -> Field SqlText
P.pgStrictText
sqlLazyText :: LText.Text -> F.Field SqlText
sqlLazyText :: Text -> Field SqlText
sqlLazyText = Text -> Column SqlText
Text -> Field SqlText
P.pgLazyText
sqlNumeric :: Sci.Scientific -> F.Field SqlNumeric
sqlNumeric :: Scientific -> Field SqlNumeric
sqlNumeric = Scientific -> Column SqlNumeric
Scientific -> Field SqlNumeric
P.pgNumeric
sqlInt4 :: Int -> F.Field SqlInt4
sqlInt4 :: Int -> Field SqlInt4
sqlInt4 = Int -> Column SqlInt4
Int -> Field SqlInt4
P.pgInt4
sqlInt8 :: Int64 -> F.Field SqlInt8
sqlInt8 :: Int64 -> Field SqlInt8
sqlInt8 = Int64 -> Column SqlInt8
Int64 -> Field SqlInt8
P.pgInt8
sqlDouble :: Double -> F.Field SqlFloat8
sqlDouble :: Double -> Field SqlFloat8
sqlDouble = Double -> Column SqlFloat8
Double -> Field SqlFloat8
P.pgDouble
sqlBool :: Bool -> F.Field SqlBool
sqlBool :: Bool -> Field SqlBool
sqlBool = Bool -> Column SqlBool
Bool -> Field SqlBool
P.pgBool
sqlUUID :: UUID.UUID -> F.Field SqlUuid
sqlUUID :: UUID -> Field SqlUuid
sqlUUID = UUID -> Column SqlUuid
UUID -> Field SqlUuid
P.pgUUID
sqlDay :: Time.Day -> F.Field SqlDate
sqlDay :: Day -> Field SqlDate
sqlDay = Day -> Column SqlDate
Day -> Field SqlDate
P.pgDay
sqlUTCTime :: Time.UTCTime -> F.Field SqlTimestamptz
sqlUTCTime :: UTCTime -> Field SqlTimestamptz
sqlUTCTime = UTCTime -> Column SqlTimestamptz
UTCTime -> Field SqlTimestamptz
P.pgUTCTime
sqlLocalTime :: Time.LocalTime -> F.Field SqlTimestamp
sqlLocalTime :: LocalTime -> Field SqlTimestamp
sqlLocalTime = LocalTime -> Column SqlTimestamp
LocalTime -> Field SqlTimestamp
P.pgLocalTime
sqlZonedTime :: Time.ZonedTime -> F.Field SqlTimestamptz
sqlZonedTime :: ZonedTime -> Field SqlTimestamptz
sqlZonedTime = ZonedTime -> Column SqlTimestamptz
ZonedTime -> Field SqlTimestamptz
P.pgZonedTime
sqlTimeOfDay :: Time.TimeOfDay -> F.Field SqlTime
sqlTimeOfDay :: TimeOfDay -> Field SqlTime
sqlTimeOfDay = TimeOfDay -> Column SqlTime
TimeOfDay -> Field SqlTime
P.pgTimeOfDay
sqlCiStrictText :: CI.CI SText.Text -> F.Field SqlCitext
sqlCiStrictText :: CI Text -> Field SqlCitext
sqlCiStrictText = CI Text -> Column SqlCitext
CI Text -> Field SqlCitext
P.pgCiStrictText
sqlCiLazyText :: CI.CI LText.Text -> F.Field SqlCitext
sqlCiLazyText :: CI Text -> Field SqlCitext
sqlCiLazyText = CI Text -> Column SqlCitext
CI Text -> Field SqlCitext
P.pgCiLazyText
sqlJSON :: String -> F.Field SqlJson
sqlJSON :: String -> Field SqlJson
sqlJSON = String -> Column SqlJson
String -> Field SqlJson
P.pgJSON
sqlStrictJSON :: SByteString.ByteString -> F.Field SqlJson
sqlStrictJSON :: ByteString -> Field SqlJson
sqlStrictJSON = ByteString -> Column SqlJson
ByteString -> Field SqlJson
P.pgStrictJSON
sqlLazyJSON :: LByteString.ByteString -> F.Field SqlJson
sqlLazyJSON :: ByteString -> Field SqlJson
sqlLazyJSON = ByteString -> Column SqlJson
ByteString -> Field SqlJson
P.pgLazyJSON
sqlValueJSON :: Ae.ToJSON a => a -> F.Field SqlJson
sqlValueJSON :: a -> Field SqlJson
sqlValueJSON = a -> Field SqlJson
forall a. ToJSON a => a -> Column SqlJson
P.pgValueJSON
sqlJSONB :: String -> F.Field SqlJsonb
sqlJSONB :: String -> Field SqlJsonb
sqlJSONB = String -> Column SqlJsonb
String -> Field SqlJsonb
P.pgJSONB
sqlStrictJSONB :: SByteString.ByteString -> F.Field SqlJsonb
sqlStrictJSONB :: ByteString -> Field SqlJsonb
sqlStrictJSONB = ByteString -> Column SqlJsonb
ByteString -> Field SqlJsonb
P.pgStrictJSONB
sqlLazyJSONB :: LByteString.ByteString -> F.Field SqlJsonb
sqlLazyJSONB :: ByteString -> Field SqlJsonb
sqlLazyJSONB = ByteString -> Column SqlJsonb
ByteString -> Field SqlJsonb
P.pgLazyJSONB
sqlValueJSONB :: Ae.ToJSON a => a -> F.Field SqlJsonb
sqlValueJSONB :: a -> Field SqlJsonb
sqlValueJSONB = a -> Field SqlJsonb
forall a. ToJSON a => a -> Column SqlJsonb
P.pgValueJSONB
sqlArray :: IsSqlType b => (a -> F.Field b) -> [a] -> F.Field (SqlArray b)
sqlArray :: (a -> Field b) -> [a] -> Field (SqlArray b)
sqlArray = (a -> Field b) -> [a] -> Field (SqlArray b)
forall a b.
IsSqlType b =>
(a -> Column b) -> [a] -> Column (PGArray b)
P.pgArray
sqlRange :: IsRangeType b
=> (a -> F.Field b)
-> R.RangeBound a
-> R.RangeBound a
-> F.Field (SqlRange b)
sqlRange :: (a -> Field b)
-> RangeBound a -> RangeBound a -> Field (SqlRange b)
sqlRange = (a -> Field b)
-> RangeBound a -> RangeBound a -> Field (SqlRange b)
forall a b.
IsRangeType b =>
(a -> Column b)
-> RangeBound a -> RangeBound a -> Column (PGRange b)
P.pgRange