{-# LANGUAGE ScopedTypeVariables #-} module Opaleye.Internal.PGTypes where import Opaleye.Internal.Column (Column(Column)) import qualified Opaleye.Internal.Column as C import qualified Opaleye.Internal.HaskellDB.PrimQuery as HPQ import Data.Proxy (Proxy(..)) import qualified Data.Text as SText import qualified Data.Text.Encoding as STextEncoding import qualified Data.Text.Lazy as LText import qualified Data.Text.Lazy.Encoding as LTextEncoding import qualified Data.ByteString as SByteString import qualified Data.ByteString.Lazy as LByteString import qualified Data.Time as Time import qualified Data.Time.Locale.Compat as Locale unsafePgFormatTime :: Time.FormatTime t => HPQ.Name -> String -> t -> Column c unsafePgFormatTime :: Name -> Name -> t -> Column c unsafePgFormatTime Name typeName Name formatString = Name -> Name -> Column c forall c. Name -> Name -> Column c castToType Name typeName (Name -> Column c) -> (t -> Name) -> t -> Column c forall b c a. (b -> c) -> (a -> b) -> a -> c . t -> Name format where format :: t -> Name format = TimeLocale -> Name -> t -> Name forall t. FormatTime t => TimeLocale -> Name -> t -> Name Time.formatTime TimeLocale Locale.defaultTimeLocale Name formatString literalColumn :: forall a. IsSqlType a => HPQ.Literal -> Column a literalColumn :: Literal -> Column a literalColumn = PrimExpr -> Column a forall pgType. PrimExpr -> Column pgType Column (PrimExpr -> Column a) -> (Literal -> PrimExpr) -> Literal -> Column a forall b c a. (b -> c) -> (a -> b) -> a -> c . Name -> PrimExpr -> PrimExpr HPQ.CastExpr (Proxy a -> Name forall sqlType (proxy :: * -> *). IsSqlType sqlType => proxy sqlType -> Name showSqlType (Proxy a forall k (t :: k). Proxy t Proxy :: Proxy a)) (PrimExpr -> PrimExpr) -> (Literal -> PrimExpr) -> Literal -> PrimExpr forall b c a. (b -> c) -> (a -> b) -> a -> c . Literal -> PrimExpr HPQ.ConstExpr castToType :: HPQ.Name -> String -> Column c castToType :: Name -> Name -> Column c castToType Name typeName = PrimExpr -> Column c forall pgType. PrimExpr -> Column pgType Column (PrimExpr -> Column c) -> (Name -> PrimExpr) -> Name -> Column c forall b c a. (b -> c) -> (a -> b) -> a -> c . Name -> PrimExpr -> PrimExpr HPQ.CastExpr Name typeName (PrimExpr -> PrimExpr) -> (Name -> PrimExpr) -> Name -> PrimExpr forall b c a. (b -> c) -> (a -> b) -> a -> c . Literal -> PrimExpr HPQ.ConstExpr (Literal -> PrimExpr) -> (Name -> Literal) -> Name -> PrimExpr forall b c a. (b -> c) -> (a -> b) -> a -> c . Name -> Literal HPQ.OtherLit strictDecodeUtf8 :: SByteString.ByteString -> String strictDecodeUtf8 :: ByteString -> Name strictDecodeUtf8 = Text -> Name SText.unpack (Text -> Name) -> (ByteString -> Text) -> ByteString -> Name forall b c a. (b -> c) -> (a -> b) -> a -> c . ByteString -> Text STextEncoding.decodeUtf8 lazyDecodeUtf8 :: LByteString.ByteString -> String lazyDecodeUtf8 :: ByteString -> Name lazyDecodeUtf8 = Text -> Name LText.unpack (Text -> Name) -> (ByteString -> Text) -> ByteString -> Name forall b c a. (b -> c) -> (a -> b) -> a -> c . ByteString -> Text LTextEncoding.decodeUtf8 class IsSqlType sqlType where showSqlType :: proxy sqlType -> String {-# MINIMAL showSqlType #-} instance IsSqlType a => IsSqlType (C.Nullable a) where showSqlType :: proxy (Nullable a) -> Name showSqlType proxy (Nullable a) _ = Proxy a -> Name forall sqlType (proxy :: * -> *). IsSqlType sqlType => proxy sqlType -> Name showSqlType (Proxy a forall k (t :: k). Proxy t Proxy :: Proxy a)