module Hasql.Transaction.Private.Statements
where
import Hasql.Transaction.Private.Prelude
import Hasql.Transaction.Private.Model
import qualified Hasql.Statement as A
import qualified Hasql.Encoders as B
import qualified Hasql.Decoders as C
import qualified Hasql.Transaction.Private.SQL as D
beginTransaction :: IsolationLevel -> Mode -> Bool -> A.Statement () ()
beginTransaction :: IsolationLevel -> Mode -> Bool -> Statement () ()
beginTransaction IsolationLevel
isolation Mode
mode Bool
preparable =
ByteString -> Params () -> Result () -> Bool -> Statement () ()
forall a b.
ByteString -> Params a -> Result b -> Bool -> Statement a b
A.Statement (IsolationLevel -> Mode -> ByteString
D.beginTransaction IsolationLevel
isolation Mode
mode) Params ()
B.noParams Result ()
C.noResult Bool
preparable
commitTransaction :: Bool -> A.Statement () ()
commitTransaction :: Bool -> Statement () ()
commitTransaction Bool
preparable =
ByteString -> Params () -> Result () -> Bool -> Statement () ()
forall a b.
ByteString -> Params a -> Result b -> Bool -> Statement a b
A.Statement ByteString
"COMMIT" Params ()
B.noParams Result ()
C.noResult Bool
preparable
abortTransaction :: Bool -> A.Statement () ()
abortTransaction :: Bool -> Statement () ()
abortTransaction Bool
preparable =
ByteString -> Params () -> Result () -> Bool -> Statement () ()
forall a b.
ByteString -> Params a -> Result b -> Bool -> Statement a b
A.Statement ByteString
"ABORT" Params ()
B.noParams Result ()
C.noResult Bool
preparable
declareCursor :: ByteString -> ByteString -> B.Params a -> A.Statement a ()
declareCursor :: ByteString -> ByteString -> Params a -> Statement a ()
declareCursor ByteString
name ByteString
sql Params a
encoder =
ByteString -> Params a -> Result () -> Bool -> Statement a ()
forall a b.
ByteString -> Params a -> Result b -> Bool -> Statement a b
A.Statement (ByteString -> ByteString -> ByteString
D.declareCursor ByteString
name ByteString
sql) Params a
encoder Result ()
C.noResult Bool
False
closeCursor :: A.Statement ByteString ()
closeCursor :: Statement ByteString ()
closeCursor =
ByteString
-> Params ByteString
-> Result ()
-> Bool
-> Statement ByteString ()
forall a b.
ByteString -> Params a -> Result b -> Bool -> Statement a b
A.Statement ByteString
"CLOSE $1" ((NullableOrNot Value ByteString -> Params ByteString
forall a. NullableOrNot Value a -> Params a
B.param (NullableOrNot Value ByteString -> Params ByteString)
-> (Value ByteString -> NullableOrNot Value ByteString)
-> Value ByteString
-> Params ByteString
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Value ByteString -> NullableOrNot Value ByteString
forall (encoder :: * -> *) a. encoder a -> NullableOrNot encoder a
B.nonNullable) Value ByteString
B.bytea) Result ()
C.noResult Bool
True
fetchFromCursor :: (b -> a -> b) -> b -> C.Row a -> A.Statement (Int64, ByteString) b
fetchFromCursor :: (b -> a -> b) -> b -> Row a -> Statement (Int64, ByteString) b
fetchFromCursor b -> a -> b
step b
init Row a
rowDec =
ByteString
-> Params (Int64, ByteString)
-> Result b
-> Bool
-> Statement (Int64, ByteString) b
forall a b.
ByteString -> Params a -> Result b -> Bool -> Statement a b
A.Statement ByteString
forall p. IsString p => p
sql Params (Int64, ByteString)
encoder Result b
decoder Bool
True
where
sql :: p
sql =
p
"FETCH FORWARD $1 FROM $2"
encoder :: Params (Int64, ByteString)
encoder =
Params Int64 -> Params ByteString -> Params (Int64, ByteString)
forall (f :: * -> *) a1 a2.
Divisible f =>
f a1 -> f a2 -> f (a1, a2)
contrazip2
((NullableOrNot Value Int64 -> Params Int64
forall a. NullableOrNot Value a -> Params a
B.param (NullableOrNot Value Int64 -> Params Int64)
-> (Value Int64 -> NullableOrNot Value Int64)
-> Value Int64
-> Params Int64
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Value Int64 -> NullableOrNot Value Int64
forall (encoder :: * -> *) a. encoder a -> NullableOrNot encoder a
B.nonNullable) Value Int64
B.int8)
((NullableOrNot Value ByteString -> Params ByteString
forall a. NullableOrNot Value a -> Params a
B.param (NullableOrNot Value ByteString -> Params ByteString)
-> (Value ByteString -> NullableOrNot Value ByteString)
-> Value ByteString
-> Params ByteString
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Value ByteString -> NullableOrNot Value ByteString
forall (encoder :: * -> *) a. encoder a -> NullableOrNot encoder a
B.nonNullable) Value ByteString
B.bytea)
decoder :: Result b
decoder =
(b -> a -> b) -> b -> Row a -> Result b
forall a b. (a -> b -> a) -> a -> Row b -> Result a
C.foldlRows b -> a -> b
step b
init Row a
rowDec