{-# OPTIONS_HADDOCK not-home #-}

{-# LANGUAGE FlexibleContexts, FlexibleInstances, MultiParamTypeClasses #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DataKinds #-}

module Opaleye.Internal.RunQuery where

import           Control.Applicative
  (Applicative, pure, (<$>), (*>), (<*>), liftA2)

import qualified Database.PostgreSQL.Simple as PGS
import qualified Database.PostgreSQL.Simple.Cursor  as PGSC (Cursor)
import           Database.PostgreSQL.Simple.Internal (RowParser)
import qualified Database.PostgreSQL.Simple.FromField as PGS
import           Database.PostgreSQL.Simple.FromField
  (FieldParser, fromField, pgArrayFieldParser, optionalField)
import           Database.PostgreSQL.Simple.FromRow (fromRow, fieldWith)
import           Database.PostgreSQL.Simple.Types (fromPGArray, Only(..))
import           Database.PostgreSQL.Simple.Newtypes ( Aeson )

import           Opaleye.Internal.Column (Field_, Field, FieldNullable,
                                          Nullability(Nullable, NonNullable))
import qualified Opaleye.Internal.PackMap as PackMap
import qualified Opaleye.Internal.QueryArr as Q
import qualified Opaleye.Internal.Unpackspec as U
import qualified Opaleye.Internal.PGTypesExternal as T
import qualified Opaleye.Internal.PGTypes as IPT (strictDecodeUtf8)
import qualified Opaleye.Select as S
import qualified Opaleye.Sql as S

import qualified Data.Profunctor as P
import           Data.Profunctor (dimap)
import qualified Data.Profunctor.Product as PP
import qualified Data.Profunctor.Product.Default as D

import qualified Data.Aeson as Ae
import qualified Data.CaseInsensitive as CI
import qualified Data.Text as ST
import qualified Data.Text.Encoding as STE
import qualified Data.Text.Lazy as LT
import qualified Data.Text.Lazy.Encoding as LTE
import qualified Data.ByteString as SBS
import qualified Data.ByteString.Lazy as LBS
import qualified Data.Time.Compat as Time
import qualified Data.Scientific as Sci
import qualified Data.String as String
import           Data.UUID (UUID)
import           GHC.Int (Int32, Int64)

-- { Only needed for postgresql-simple FieldParsers

import           Database.PostgreSQL.Simple.FromField
  (ResultError(UnexpectedNull, Incompatible), typeInfo, returnError)
import qualified Database.PostgreSQL.Simple.TypeInfo as TI
import qualified Database.PostgreSQL.Simple.Range as PGSR
import           Data.Typeable (Typeable)

-- }

-- | A 'FromField' @sqlType@ @haskellType@
-- encodes how to turn
-- a value of Postgres type @sqlType@ into a value of Haskell type
-- @haskellType@.  For example a value of type 'FromField'
-- 'T.SqlText' 'String' encodes how to turn a 'T.SqlText' result from the
-- database into a Haskell 'String'.
--
-- \"'FromField' @sqlType@ @haskellType@\" corresponds to
-- postgresql-simple's \"'FieldParser' @haskellType@\".

-- This is *not* a Product Profunctor because it is the only way I
-- know of to get the instance generation to work for non-Nullable and
-- Nullable types at once.

-- I can no longer remember what the above comment means, but it might
-- be that we can't add nullability to a RowParser, only to a
-- FieldParser, so we have to have some type that we know contains
-- just a FieldParser.

newtype FromField sqlType haskellType = FromField (FieldParser haskellType)

instance Functor (FromField u) where
  fmap :: forall a b. (a -> b) -> FromField u a -> FromField u b
fmap a -> b
f (FromField FieldParser a
fp) = forall sqlType haskellType.
FieldParser haskellType -> FromField sqlType haskellType
FromField ((forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap) a -> b
f FieldParser a
fp)

-- | A 'FromFields'
--   specifies how to convert Postgres values (@fields@)
--   into Haskell values (@haskells@).  Most likely you will never need
--   to create one of these or handle one directly.  It will be provided
--   for you by the 'D.Default' 'FromFields' instance.
--
-- \"'FromFields' @fields@ @haskells@\" corresponds to
-- postgresql-simple's \"'RowParser' @haskells@\".  \"'Default'
-- 'FromFields' @fields@ @haskells@\" corresponds to
-- postgresql-simple's \"@FromRow@ @haskells@\".
data FromFields fields haskells =
   FromFields (U.Unpackspec fields ())
              (fields -> RowParser haskells)
              -- We never actually look at the columns except to see
              -- its "type" in the case of a sum profunctor
              (fields -> Int)
              -- How many columns have we requested?  If we
              -- asked for zero columns then the SQL generator will
              -- have to put a dummy 0 into the SELECT statement,
              -- since we can't select zero columns.  In that case we
              -- have to make sure we read a single Int.
              --
              -- NB this does have to be a function of 'columns'
              -- because we have a `SumProfunctor` instance.  For some
              -- values of 'columns' there may be zero columns and for
              -- other values one or more, for example, 'Maybe (Column
              -- SqlInt4)' has no columns when it is Nothing and one
              -- column when it is Just.

{-# DEPRECATED fieldQueryRunnerColumn "Will be removed in version 0.10.  Use fromPGSFromField instead." #-}
fieldQueryRunnerColumn :: PGS.FromField haskell => FromField pgType haskell
fieldQueryRunnerColumn :: forall haskell pgType.
FromField haskell =>
FromField pgType haskell
fieldQueryRunnerColumn = forall haskell pgType.
FromField haskell =>
FromField pgType haskell
fromPGSFromField

fromPGSFromField :: PGS.FromField haskell => FromField pgType haskell
fromPGSFromField :: forall haskell pgType.
FromField haskell =>
FromField pgType haskell
fromPGSFromField = forall haskell pgType.
FieldParser haskell -> FromField pgType haskell
fromPGSFieldParser forall a. FromField a => FieldParser a
fromField

{-# DEPRECATED fieldParserQueryRunnerColumn " Will be removed in version 0.10.  Use fromPGSFieldParser instead." #-}
fieldParserQueryRunnerColumn :: FieldParser haskell -> FromField pgType haskell
fieldParserQueryRunnerColumn :: forall haskell pgType.
FieldParser haskell -> FromField pgType haskell
fieldParserQueryRunnerColumn = forall haskell pgType.
FieldParser haskell -> FromField pgType haskell
fromPGSFieldParser

fromPGSFieldParser :: FieldParser haskell -> FromField pgType haskell
fromPGSFieldParser :: forall haskell pgType.
FieldParser haskell -> FromField pgType haskell
fromPGSFieldParser = forall sqlType haskellType.
FieldParser haskellType -> FromField sqlType haskellType
FromField

fromFields :: FromField a b -> FromFields (Field a) b
fromFields :: forall a b. FromField a b -> FromFields (Field a) b
fromFields (FromField FieldParser b
fp) = forall haskells (n :: Nullability) a.
FieldParser haskells -> FromFields (Field_ n a) haskells
fieldParserFromFields FieldParser b
fp

fieldParserFromFields :: FieldParser haskells -> FromFields (Field_ n a) haskells
fieldParserFromFields :: forall haskells (n :: Nullability) a.
FieldParser haskells -> FromFields (Field_ n a) haskells
fieldParserFromFields FieldParser haskells
fp = forall fields haskells.
Unpackspec fields ()
-> (fields -> RowParser haskells)
-> (fields -> Int)
-> FromFields fields haskells
FromFields (forall (p :: * -> * -> *) b c a.
Profunctor p =>
(b -> c) -> p a b -> p a c
P.rmap (forall a b. a -> b -> a
const ()) forall (n :: Nullability) a. Unpackspec (Field_ n a) (Field_ n a)
U.unpackspecField) (forall a b. a -> b -> a
const (forall a. FieldParser a -> RowParser a
fieldWith FieldParser haskells
fp)) (forall a b. a -> b -> a
const Int
1)

{-# DEPRECATED queryRunner "Use fromFields instead.  Will be removed in version 0.10." #-}
queryRunner :: FromField a b -> FromFields (Field a) b
queryRunner :: forall a b. FromField a b -> FromFields (Field a) b
queryRunner = forall a b. FromField a b -> FromFields (Field a) b
fromFields

fromFieldsNullable :: FromField a b -> FromFields (FieldNullable a) (Maybe b)
fromFieldsNullable :: forall a b. FromField a b -> FromFields (FieldNullable a) (Maybe b)
fromFieldsNullable (FromField FieldParser b
fp) = forall haskells (n :: Nullability) a.
FieldParser haskells -> FromFields (Field_ n a) haskells
fieldParserFromFields (forall a. FieldParser a -> FieldParser (Maybe a)
optionalField FieldParser b
fp)

unsafeFromFieldRaw :: FromField a (PGS.Field, Maybe SBS.ByteString)
unsafeFromFieldRaw :: forall a. FromField a (Field, Maybe ByteString)
unsafeFromFieldRaw = forall haskell pgType.
FieldParser haskell -> FromField pgType haskell
fromPGSFieldParser (\Field
f Maybe ByteString
mdata -> forall (f :: * -> *) a. Applicative f => a -> f a
pure (Field
f, Maybe ByteString
mdata))

-- { Instances for automatic derivation

instance DefaultFromField a b =>
         D.Default FromFields (Field a) b where
  def :: FromFields (Field a) b
def = forall a b. FromField a b -> FromFields (Field a) b
fromFields forall sqlType haskellType.
DefaultFromField sqlType haskellType =>
FromField sqlType haskellType
defaultFromField

instance DefaultFromField a b =>
         D.Default FromFields (FieldNullable a) (Maybe b)
  where def :: FromFields (FieldNullable a) (Maybe b)
def = forall a b. FromField a b -> FromFields (FieldNullable a) (Maybe b)
fromFieldsNullable forall sqlType haskellType.
DefaultFromField sqlType haskellType =>
FromField sqlType haskellType
defaultFromField


-- }

-- { Instances that must be provided once for each type.  Instances
--   for Nullable are derived automatically from these.

-- | A 'DefaultFromField' @sqlType@ @haskellType@ represents
-- the default way to turn a @sqlType@ result from the database into a
-- Haskell value of type @haskellType@.
--
-- \"'DefaultFromField' @sqlType@ @haskellType@\" corresponds
-- to postgresql-simple's \"'FromField' @haskellType@\".
--
-- Creating an instance of 'DefaultFromField' for your own types is
-- necessary for retrieving those types from the database.
--
-- You should use one of the three methods below for writing a
-- 'DefaultFromField' instance.
--
-- 1. If you already have a postgresql-simple 'PGS.FromField' instance for
-- your @haskellType@, use
-- 'fromPGSFromField'.  (This is how most of the built-in instances are
-- defined.)
--
-- 2. If you don't have a postgresql-simple 'PGS.FromField' instance, but
-- you do have an Opaleye 'FromField' value for the type it wraps use
-- 'Opaleye.RunSelect.unsafeFromField' if possible.  See the documentation for
-- 'Opaleye.RunSelect.unsafeFromField' for an example.
--
-- 3. If you have a more complicated case, but not a 'PGS.FromField' instance,
-- write a 'FieldParser' for your type and use 'fromPGSFieldParser'.
-- You can also add a 'FromField' instance using this.
class DefaultFromField sqlType haskellType where
  defaultFromField         :: FromField sqlType haskellType

instance DefaultFromField sqlType haskellType
    => D.Default FromField sqlType haskellType where
  def :: FromField sqlType haskellType
def = forall sqlType haskellType.
DefaultFromField sqlType haskellType =>
FromField sqlType haskellType
defaultFromField

instance DefaultFromField T.SqlNumeric Sci.Scientific where
  defaultFromField :: FromField SqlNumeric Scientific
defaultFromField = forall haskell pgType.
FromField haskell =>
FromField pgType haskell
fromPGSFromField

instance DefaultFromField T.SqlInt4 Int where
  defaultFromField :: FromField SqlInt4 Int
defaultFromField = forall haskell pgType.
FromField haskell =>
FromField pgType haskell
fromPGSFromField

instance DefaultFromField T.SqlInt4 Int32 where
  defaultFromField :: FromField SqlInt4 Int32
defaultFromField = forall haskell pgType.
FromField haskell =>
FromField pgType haskell
fromPGSFromField

instance DefaultFromField T.SqlInt8 Int64 where
  defaultFromField :: FromField SqlInt8 Int64
defaultFromField = forall haskell pgType.
FromField haskell =>
FromField pgType haskell
fromPGSFromField

instance DefaultFromField T.SqlText String where
  defaultFromField :: FromField SqlText String
defaultFromField = forall haskell pgType.
FromField haskell =>
FromField pgType haskell
fromPGSFromField

instance DefaultFromField T.SqlFloat8 Double where
  defaultFromField :: FromField SqlFloat8 Double
defaultFromField = forall haskell pgType.
FromField haskell =>
FromField pgType haskell
fromPGSFromField

instance DefaultFromField T.SqlBool Bool where
  defaultFromField :: FromField SqlBool Bool
defaultFromField = forall haskell pgType.
FromField haskell =>
FromField pgType haskell
fromPGSFromField

instance DefaultFromField T.SqlUuid UUID where
  defaultFromField :: FromField SqlUuid UUID
defaultFromField = forall haskell pgType.
FromField haskell =>
FromField pgType haskell
fromPGSFromField

instance DefaultFromField T.SqlBytea SBS.ByteString where
  defaultFromField :: FromField SqlBytea ByteString
defaultFromField = forall haskell pgType.
FromField haskell =>
FromField pgType haskell
fromPGSFromField

instance DefaultFromField T.SqlBytea LBS.ByteString where
  defaultFromField :: FromField SqlBytea ByteString
defaultFromField = forall haskell pgType.
FromField haskell =>
FromField pgType haskell
fromPGSFromField

instance DefaultFromField T.SqlText ST.Text where
  defaultFromField :: FromField SqlText Text
defaultFromField = forall haskell pgType.
FromField haskell =>
FromField pgType haskell
fromPGSFromField

instance DefaultFromField T.SqlText LT.Text where
  defaultFromField :: FromField SqlText Text
defaultFromField = forall haskell pgType.
FromField haskell =>
FromField pgType haskell
fromPGSFromField

instance DefaultFromField T.SqlVarcharN String where
  defaultFromField :: FromField SqlVarcharN String
defaultFromField = forall haskell pgType.
FromField haskell =>
FromField pgType haskell
fromPGSFromField

instance DefaultFromField T.SqlVarcharN ST.Text where
  defaultFromField :: FromField SqlVarcharN Text
defaultFromField = forall haskell pgType.
FromField haskell =>
FromField pgType haskell
fromPGSFromField

instance DefaultFromField T.SqlVarcharN LT.Text where
  defaultFromField :: FromField SqlVarcharN Text
defaultFromField = forall haskell pgType.
FromField haskell =>
FromField pgType haskell
fromPGSFromField

instance DefaultFromField T.SqlDate Time.Day where
  defaultFromField :: FromField SqlDate Day
defaultFromField = forall haskell pgType.
FromField haskell =>
FromField pgType haskell
fromPGSFromField

instance DefaultFromField T.SqlTimestamptz Time.UTCTime where
  defaultFromField :: FromField SqlTimestamptz UTCTime
defaultFromField = forall haskell pgType.
FromField haskell =>
FromField pgType haskell
fromPGSFromField

instance DefaultFromField T.SqlTimestamp Time.LocalTime where
  defaultFromField :: FromField SqlTimestamp LocalTime
defaultFromField = forall haskell pgType.
FromField haskell =>
FromField pgType haskell
fromPGSFromField

instance DefaultFromField T.SqlTimestamptz Time.ZonedTime where
  defaultFromField :: FromField SqlTimestamptz ZonedTime
defaultFromField = forall haskell pgType.
FromField haskell =>
FromField pgType haskell
fromPGSFromField

instance DefaultFromField T.SqlInterval Time.CalendarDiffTime where
  defaultFromField :: FromField SqlInterval CalendarDiffTime
defaultFromField = forall haskell pgType.
FromField haskell =>
FromField pgType haskell
fromPGSFromField

instance DefaultFromField T.SqlTime Time.TimeOfDay where
  defaultFromField :: FromField SqlTime TimeOfDay
defaultFromField = forall haskell pgType.
FromField haskell =>
FromField pgType haskell
fromPGSFromField

instance DefaultFromField T.SqlCitext (CI.CI ST.Text) where
  defaultFromField :: FromField SqlCitext (CI Text)
defaultFromField = forall haskell pgType.
FromField haskell =>
FromField pgType haskell
fromPGSFromField

instance DefaultFromField T.SqlCitext (CI.CI LT.Text) where
  defaultFromField :: FromField SqlCitext (CI Text)
defaultFromField = forall haskell pgType.
FromField haskell =>
FromField pgType haskell
fromPGSFromField

instance DefaultFromField T.SqlJson String where
  defaultFromField :: FromField SqlJson String
defaultFromField = forall haskell pgType.
FieldParser haskell -> FromField pgType haskell
fromPGSFieldParser FieldParser String
jsonFieldParser

instance DefaultFromField T.SqlJson ST.Text where
  defaultFromField :: FromField SqlJson Text
defaultFromField = forall haskell pgType.
FieldParser haskell -> FromField pgType haskell
fromPGSFieldParser FieldParser Text
jsonFieldTextParser

instance DefaultFromField T.SqlJson LT.Text where
  defaultFromField :: FromField SqlJson Text
defaultFromField = forall haskell pgType.
FieldParser haskell -> FromField pgType haskell
fromPGSFieldParser FieldParser Text
jsonFieldLazyTextParser

instance DefaultFromField T.SqlJson SBS.ByteString where
  defaultFromField :: FromField SqlJson ByteString
defaultFromField = forall haskell pgType.
FieldParser haskell -> FromField pgType haskell
fromPGSFieldParser FieldParser ByteString
jsonFieldByteParser

instance DefaultFromField T.SqlJson LBS.ByteString where
  defaultFromField :: FromField SqlJson ByteString
defaultFromField = forall haskell pgType.
FieldParser haskell -> FromField pgType haskell
fromPGSFieldParser FieldParser ByteString
jsonFieldLazyByteParser

instance DefaultFromField T.SqlJson Ae.Value where
  defaultFromField :: FromField SqlJson Value
defaultFromField = forall haskell pgType.
FromField haskell =>
FromField pgType haskell
fromPGSFromField

instance (Ae.FromJSON a, Typeable a) => DefaultFromField T.SqlJson (Aeson a) where
  defaultFromField :: FromField SqlJson (Aeson a)
defaultFromField = forall haskell pgType.
FromField haskell =>
FromField pgType haskell
fromPGSFromField

instance DefaultFromField T.SqlJsonb String where
  defaultFromField :: FromField SqlJsonb String
defaultFromField = forall haskell pgType.
FieldParser haskell -> FromField pgType haskell
fromPGSFieldParser FieldParser String
jsonbFieldParser

instance DefaultFromField T.SqlJsonb ST.Text where
  defaultFromField :: FromField SqlJsonb Text
defaultFromField = forall haskell pgType.
FieldParser haskell -> FromField pgType haskell
fromPGSFieldParser FieldParser Text
jsonbFieldTextParser

instance DefaultFromField T.SqlJsonb LT.Text where
  defaultFromField :: FromField SqlJsonb Text
defaultFromField = forall haskell pgType.
FieldParser haskell -> FromField pgType haskell
fromPGSFieldParser FieldParser Text
jsonbFieldLazyTextParser

instance DefaultFromField T.SqlJsonb SBS.ByteString where
  defaultFromField :: FromField SqlJsonb ByteString
defaultFromField = forall haskell pgType.
FieldParser haskell -> FromField pgType haskell
fromPGSFieldParser FieldParser ByteString
jsonbFieldByteParser

instance DefaultFromField T.SqlJsonb LBS.ByteString where
  defaultFromField :: FromField SqlJsonb ByteString
defaultFromField = forall haskell pgType.
FieldParser haskell -> FromField pgType haskell
fromPGSFieldParser FieldParser ByteString
jsonbFieldLazyByteParser

instance DefaultFromField T.SqlJsonb Ae.Value where
  defaultFromField :: FromField SqlJsonb Value
defaultFromField = forall haskell pgType.
FromField haskell =>
FromField pgType haskell
fromPGSFromField

instance (Ae.FromJSON a, Typeable a) => DefaultFromField T.SqlJsonb (Aeson a) where
  defaultFromField :: FromField SqlJsonb (Aeson a)
defaultFromField = forall haskell pgType.
FromField haskell =>
FromField pgType haskell
fromPGSFromField

-- No CI String instance since postgresql-simple doesn't define FromField (CI String)

instance (Typeable b, DefaultFromField a b) =>
         DefaultFromField (T.SqlArray_ NonNullable a) [b] where
  defaultFromField :: FromField (SqlArray_ 'NonNullable a) [b]
defaultFromField = forall h f.
Typeable h =>
FromField f h -> FromField (SqlArray_ 'NonNullable f) [h]
fromFieldArray forall sqlType haskellType.
DefaultFromField sqlType haskellType =>
FromField sqlType haskellType
defaultFromField

fromFieldArray :: Typeable h => FromField f h -> FromField (T.SqlArray_ NonNullable f) [h]
fromFieldArray :: forall h f.
Typeable h =>
FromField f h -> FromField (SqlArray_ 'NonNullable f) [h]
fromFieldArray (FromField FieldParser h
f) =
  forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. PGArray a -> [a]
fromPGArray (forall sqlType haskellType.
FieldParser haskellType -> FromField sqlType haskellType
FromField (forall a. Typeable a => FieldParser a -> FieldParser (PGArray a)
pgArrayFieldParser FieldParser h
f))

fromFieldArrayNullable :: Typeable h => FromField f h -> FromField (T.SqlArray_ 'Nullable f) [Maybe h]
fromFieldArrayNullable :: forall h f.
Typeable h =>
FromField f h -> FromField (SqlArray_ 'Nullable f) [Maybe h]
fromFieldArrayNullable (FromField FieldParser h
f) =
  forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. PGArray a -> [a]
fromPGArray (forall sqlType haskellType.
FieldParser haskellType -> FromField sqlType haskellType
FromField (forall a. Typeable a => FieldParser a -> FieldParser (PGArray a)
pgArrayFieldParser (forall a. FieldParser a -> FieldParser (Maybe a)
optionalField FieldParser h
f)))

-- }

instance (Typeable b, DefaultFromField a b) =>
         DefaultFromField (T.SqlRange a) (PGSR.PGRange b) where
  defaultFromField :: FromField (SqlRange a) (PGRange b)
defaultFromField = forall b a.
Typeable b =>
FromField a b -> FromField (SqlRange a) (PGRange b)
fromFieldRange forall sqlType haskellType.
DefaultFromField sqlType haskellType =>
FromField sqlType haskellType
defaultFromField

instance (Typeable b, DefaultFromField a b) =>
         DefaultFromField (T.SqlArray_ Nullable a) [Maybe b] where
  defaultFromField :: FromField (SqlArray_ 'Nullable a) [Maybe b]
defaultFromField = forall h f.
Typeable h =>
FromField f h -> FromField (SqlArray_ 'Nullable f) [Maybe h]
fromFieldArrayNullable forall sqlType haskellType.
DefaultFromField sqlType haskellType =>
FromField sqlType haskellType
defaultFromField

fromFieldRange :: Typeable b
               => FromField a b
               -> FromField (T.SqlRange a) (PGSR.PGRange b)
fromFieldRange :: forall b a.
Typeable b =>
FromField a b -> FromField (SqlRange a) (PGRange b)
fromFieldRange (FromField FieldParser b
pff) = forall sqlType haskellType.
FieldParser haskellType -> FromField sqlType haskellType
FromField (forall a. Typeable a => FieldParser a -> FieldParser (PGRange a)
PGSR.fromFieldRange FieldParser b
pff)

-- Boilerplate instances

instance Functor (FromFields c) where
  fmap :: forall a b. (a -> b) -> FromFields c a -> FromFields c b
fmap a -> b
f (FromFields Unpackspec c ()
u c -> RowParser a
r c -> Int
b) = forall fields haskells.
Unpackspec fields ()
-> (fields -> RowParser haskells)
-> (fields -> Int)
-> FromFields fields haskells
FromFields Unpackspec c ()
u ((forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap) a -> b
f c -> RowParser a
r) c -> Int
b

instance Applicative (FromFields c) where
  pure :: forall a. a -> FromFields c a
pure = forall a b c. (a -> b -> c) -> b -> a -> c
flip (forall fields haskells.
Unpackspec fields ()
-> (fields -> RowParser haskells)
-> (fields -> Int)
-> FromFields fields haskells
FromFields (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())) (forall a b. a -> b -> a
const Int
0)
         forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a. Applicative f => a -> f a
pure
         forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a. Applicative f => a -> f a
pure
  FromFields Unpackspec c ()
uf c -> RowParser (a -> b)
rf c -> Int
bf <*> :: forall a b.
FromFields c (a -> b) -> FromFields c a -> FromFields c b
<*> FromFields Unpackspec c ()
ux c -> RowParser a
rx c -> Int
bx =
    forall fields haskells.
Unpackspec fields ()
-> (fields -> RowParser haskells)
-> (fields -> Int)
-> FromFields fields haskells
FromFields (Unpackspec c ()
uf forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Unpackspec c ()
ux) (forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
(<*>) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> c -> RowParser (a -> b)
rf forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> c -> RowParser a
rx) (forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 forall a. Num a => a -> a -> a
(+) c -> Int
bf c -> Int
bx)

instance P.Profunctor FromFields where
  dimap :: forall a b c d.
(a -> b) -> (c -> d) -> FromFields b c -> FromFields a d
dimap a -> b
f c -> d
g (FromFields Unpackspec b ()
u b -> RowParser c
r b -> Int
b) =
    forall fields haskells.
Unpackspec fields ()
-> (fields -> RowParser haskells)
-> (fields -> Int)
-> FromFields fields haskells
FromFields (forall (p :: * -> * -> *) a b c.
Profunctor p =>
(a -> b) -> p b c -> p a c
P.lmap a -> b
f Unpackspec b ()
u) (forall (p :: * -> * -> *) a b c d.
Profunctor p =>
(a -> b) -> (c -> d) -> p b c -> p a d
P.dimap a -> b
f (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap c -> d
g) b -> RowParser c
r) (forall (p :: * -> * -> *) a b c.
Profunctor p =>
(a -> b) -> p b c -> p a c
P.lmap a -> b
f b -> Int
b)

instance PP.ProductProfunctor FromFields where
  purePP :: forall b a. b -> FromFields a b
purePP = forall (f :: * -> *) a. Applicative f => a -> f a
pure
  **** :: forall c a b.
FromFields c (a -> b) -> FromFields c a -> FromFields c b
(****) = forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
(<*>)

instance PP.SumProfunctor FromFields where
  FromFields a b
f +++! :: forall a b a' b'.
FromFields a b
-> FromFields a' b' -> FromFields (Either a a') (Either b b')
+++! FromFields a' b'
g = forall fields haskells.
Unpackspec fields ()
-> (fields -> RowParser haskells)
-> (fields -> Int)
-> FromFields fields haskells
FromFields (forall (p :: * -> * -> *) b c a.
Profunctor p =>
(b -> c) -> p a b -> p a c
P.rmap (forall a b. a -> b -> a
const ()) (Unpackspec a ()
fu forall (p :: * -> * -> *) a b a' b'.
SumProfunctor p =>
p a b -> p a' b' -> p (Either a a') (Either b b')
PP.+++! Unpackspec a' ()
gu))
                         (forall (p :: * -> * -> *) (f :: * -> *) a b a' b'.
(SumProfunctor p, Functor f) =>
p a (f b) -> p a' (f b') -> p (Either a a') (f (Either b b'))
PackMap.eitherFunction a -> RowParser b
fr a' -> RowParser b'
gr)
                         (forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either a -> Int
fb a' -> Int
gb)
    where FromFields Unpackspec a ()
fu a -> RowParser b
fr a -> Int
fb = FromFields a b
f
          FromFields Unpackspec a' ()
gu a' -> RowParser b'
gr a' -> Int
gb = FromFields a' b'
g

-- }

-- { Allow @postgresql-simple@ conversions from JSON types to 'String'

jsonFieldParser, jsonbFieldParser :: FieldParser String
jsonFieldParser :: FieldParser String
jsonFieldParser  = ByteString -> FieldParser String
jsonFieldTypeParser (forall a. IsString a => String -> a
String.fromString String
"json")
jsonbFieldParser :: FieldParser String
jsonbFieldParser = ByteString -> FieldParser String
jsonFieldTypeParser (forall a. IsString a => String -> a
String.fromString String
"jsonb")

jsonFieldTextParser, jsonbFieldTextParser :: FieldParser ST.Text
jsonFieldTextParser :: FieldParser Text
jsonFieldTextParser  = ByteString -> FieldParser Text
jsonFieldTypeTextParser (forall a. IsString a => String -> a
String.fromString String
"json")
jsonbFieldTextParser :: FieldParser Text
jsonbFieldTextParser = ByteString -> FieldParser Text
jsonFieldTypeTextParser (forall a. IsString a => String -> a
String.fromString String
"jsonb")

jsonFieldLazyTextParser, jsonbFieldLazyTextParser :: FieldParser LT.Text
jsonFieldLazyTextParser :: FieldParser Text
jsonFieldLazyTextParser  = ByteString -> FieldParser Text
jsonFieldTypeLazyTextParser (forall a. IsString a => String -> a
String.fromString String
"json")
jsonbFieldLazyTextParser :: FieldParser Text
jsonbFieldLazyTextParser = ByteString -> FieldParser Text
jsonFieldTypeLazyTextParser (forall a. IsString a => String -> a
String.fromString String
"jsonb")

jsonFieldByteParser, jsonbFieldByteParser :: FieldParser SBS.ByteString
jsonFieldByteParser :: FieldParser ByteString
jsonFieldByteParser  = ByteString -> FieldParser ByteString
jsonFieldTypeByteParser (forall a. IsString a => String -> a
String.fromString String
"json")
jsonbFieldByteParser :: FieldParser ByteString
jsonbFieldByteParser = ByteString -> FieldParser ByteString
jsonFieldTypeByteParser (forall a. IsString a => String -> a
String.fromString String
"jsonb")

jsonFieldLazyByteParser, jsonbFieldLazyByteParser :: FieldParser LBS.ByteString
jsonFieldLazyByteParser :: FieldParser ByteString
jsonFieldLazyByteParser  = ByteString -> FieldParser ByteString
jsonFieldTypeLazyByteParser (forall a. IsString a => String -> a
String.fromString String
"json")
jsonbFieldLazyByteParser :: FieldParser ByteString
jsonbFieldLazyByteParser = ByteString -> FieldParser ByteString
jsonFieldTypeLazyByteParser (forall a. IsString a => String -> a
String.fromString String
"jsonb")

-- typenames, not type Oids are used in order to avoid creating
-- a dependency on 'Database.PostgreSQL.LibPQ'
--
-- Eventually we want to move this to postgresql-simple
--
--     https://github.com/tomjaguarpaw/haskell-opaleye/issues/329
jsonFieldTypeByteParser :: SBS.ByteString -> FieldParser SBS.ByteString
jsonFieldTypeByteParser :: ByteString -> FieldParser ByteString
jsonFieldTypeByteParser ByteString
jsonTypeName Field
field Maybe ByteString
mData = do
    TypeInfo
ti <- Field -> Conversion TypeInfo
typeInfo Field
field
    if TypeInfo -> ByteString
TI.typname TypeInfo
ti forall a. Eq a => a -> a -> Bool
== ByteString
jsonTypeName
       then Conversion ByteString
convert
       else forall a err.
(Typeable a, Exception err) =>
(String -> Maybe Oid -> String -> String -> String -> err)
-> Field -> String -> Conversion a
returnError String -> Maybe Oid -> String -> String -> String -> ResultError
Incompatible Field
field String
"types incompatible"
  where
    convert :: Conversion ByteString
convert = case Maybe ByteString
mData of
        Just ByteString
bs -> forall (f :: * -> *) a. Applicative f => a -> f a
pure ByteString
bs
        Maybe ByteString
_       -> forall a err.
(Typeable a, Exception err) =>
(String -> Maybe Oid -> String -> String -> String -> err)
-> Field -> String -> Conversion a
returnError String -> Maybe Oid -> String -> String -> String -> ResultError
UnexpectedNull Field
field String
""

withJsonByteStringParser :: (SBS.ByteString -> b)
                         -> SBS.ByteString -> FieldParser b
withJsonByteStringParser :: forall b. (ByteString -> b) -> ByteString -> FieldParser b
withJsonByteStringParser ByteString -> b
f = (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap) ByteString -> b
f ByteString -> FieldParser ByteString
jsonFieldTypeByteParser

jsonFieldTypeParser :: SBS.ByteString -> FieldParser String
jsonFieldTypeParser :: ByteString -> FieldParser String
jsonFieldTypeParser = forall b. (ByteString -> b) -> ByteString -> FieldParser b
withJsonByteStringParser ByteString -> String
IPT.strictDecodeUtf8

jsonFieldTypeTextParser :: SBS.ByteString -> FieldParser ST.Text
jsonFieldTypeTextParser :: ByteString -> FieldParser Text
jsonFieldTypeTextParser = forall b. (ByteString -> b) -> ByteString -> FieldParser b
withJsonByteStringParser ByteString -> Text
STE.decodeUtf8

jsonFieldTypeLazyTextParser :: SBS.ByteString -> FieldParser LT.Text
jsonFieldTypeLazyTextParser :: ByteString -> FieldParser Text
jsonFieldTypeLazyTextParser = forall b. (ByteString -> b) -> ByteString -> FieldParser b
withJsonByteStringParser (ByteString -> Text
LTE.decodeUtf8 forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ByteString
LBS.fromStrict)

jsonFieldTypeLazyByteParser :: SBS.ByteString -> FieldParser LBS.ByteString
jsonFieldTypeLazyByteParser :: ByteString -> FieldParser ByteString
jsonFieldTypeLazyByteParser = forall b. (ByteString -> b) -> ByteString -> FieldParser b
withJsonByteStringParser ByteString -> ByteString
LBS.fromStrict

-- }

prepareRowParser :: FromFields columns haskells -> columns -> RowParser haskells
prepareRowParser :: forall columns haskells.
FromFields columns haskells -> columns -> RowParser haskells
prepareRowParser (FromFields Unpackspec columns ()
_ columns -> RowParser haskells
rowParser columns -> Int
numColumns) columns
cols =
  if columns -> Int
numColumns columns
cols forall a. Ord a => a -> a -> Bool
> Int
0
  then columns -> RowParser haskells
rowParser columns
cols
  else (forall a. FromRow a => RowParser a
fromRow :: RowParser (Only Int)) forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> columns -> RowParser haskells
rowParser columns
cols
     -- If we are selecting zero columns then the SQL
     -- generator will have to put a dummy 0 into the
     -- SELECT statement, since we can't select zero
     -- columns.  In that case we have to make sure we
     -- read a single Int.
     --
     -- See: Opaleye.Internal.Sql

-- | Cursor within a transaction.
data Cursor haskells = EmptyCursor | Cursor (RowParser haskells) PGSC.Cursor

prepareQuery :: FromFields fields haskells -> S.Select fields -> (Maybe PGS.Query, RowParser haskells)
prepareQuery :: forall fields haskells.
FromFields fields haskells
-> Select fields -> (Maybe Query, RowParser haskells)
prepareQuery qr :: FromFields fields haskells
qr@(FromFields Unpackspec fields ()
u fields -> RowParser haskells
_ fields -> Int
_) Select fields
q = (Maybe Query
sql, RowParser haskells
parser)
  where sql :: Maybe PGS.Query
        sql :: Maybe Query
sql = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. IsString a => String -> a
String.fromString (forall fields b.
Unpackspec fields b -> Select fields -> Maybe String
S.showSqlExplicit Unpackspec fields ()
u Select fields
q)
        -- FIXME: We're doing work twice here
        (fields
b, PrimQuery
_) = forall a. Select a -> (a, PrimQuery)
Q.runSimpleSelectStart Select fields
q
        parser :: RowParser haskells
parser = forall columns haskells.
FromFields columns haskells -> columns -> RowParser haskells
prepareRowParser FromFields fields haskells
qr fields
b