{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE TypeApplications    #-}
module Database.PostgreSQL.PQTypes.Format (
    PQFormat(..)
  , pqFormatP
  , pqFormat0P
  , pqVariablesP
  , (:*:)(..)
  ) where

import Data.Functor.Identity
import Data.Int
import Data.Proxy
import Data.Time
import Data.Word
import Data.UUID.Types
import qualified Data.ByteString.Char8 as BS
import qualified Data.ByteString.Lazy.Char8 as BSL
import qualified Data.Text as T
import qualified Data.Text.Lazy as TL

----------------------------------------

-- | Methods in this class are supposed to be used with the
-- @TypeApplications@ extension.
class PQFormat t where
  -- | Map a type to its libpqtypes format.
  pqFormat :: BS.ByteString

  -- | Map type to its null-terminated libpqtypes format, so
  -- it can safely be used by 'unsafeUseAsCString'. Also, for
  -- a specific type it becomes a top level CAF, therefore it
  -- will be computed by GHC at most once.
  pqFormat0 :: BS.ByteString
  pqFormat0 = forall t. PQFormat t => ByteString
pqFormat @t ByteString -> Char -> ByteString
`BS.snoc` Char
'\0'

  -- | Map type to number of type formats it contains.
  pqVariables :: Int
  pqVariables = Int
1

-- Helpers that are parametrised by a 'Proxy t' instead of 't'.

pqFormatP :: forall t . PQFormat t => Proxy t -> BS.ByteString
pqFormatP :: forall t. PQFormat t => Proxy t -> ByteString
pqFormatP    Proxy t
_ = forall t. PQFormat t => ByteString
pqFormat @t

pqFormat0P :: forall t . PQFormat t => Proxy t -> BS.ByteString
pqFormat0P :: forall t. PQFormat t => Proxy t -> ByteString
pqFormat0P   Proxy t
_ = forall t. PQFormat t => ByteString
pqFormat0 @t

pqVariablesP :: forall t . PQFormat t => Proxy t -> Int
pqVariablesP :: forall t. PQFormat t => Proxy t -> Int
pqVariablesP Proxy t
_ = forall t. PQFormat t => Int
pqVariables @t

-- CARTESIAN PRODUCT

-- | Cartesian product of rows.
data a :*: b = a :*: b
  deriving ((a :*: b) -> (a :*: b) -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall a b. (Eq a, Eq b) => (a :*: b) -> (a :*: b) -> Bool
/= :: (a :*: b) -> (a :*: b) -> Bool
$c/= :: forall a b. (Eq a, Eq b) => (a :*: b) -> (a :*: b) -> Bool
== :: (a :*: b) -> (a :*: b) -> Bool
$c== :: forall a b. (Eq a, Eq b) => (a :*: b) -> (a :*: b) -> Bool
Eq, (a :*: b) -> (a :*: b) -> Bool
(a :*: b) -> (a :*: b) -> Ordering
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall {a} {b}. (Ord a, Ord b) => Eq (a :*: b)
forall a b. (Ord a, Ord b) => (a :*: b) -> (a :*: b) -> Bool
forall a b. (Ord a, Ord b) => (a :*: b) -> (a :*: b) -> Ordering
forall a b. (Ord a, Ord b) => (a :*: b) -> (a :*: b) -> a :*: b
min :: (a :*: b) -> (a :*: b) -> a :*: b
$cmin :: forall a b. (Ord a, Ord b) => (a :*: b) -> (a :*: b) -> a :*: b
max :: (a :*: b) -> (a :*: b) -> a :*: b
$cmax :: forall a b. (Ord a, Ord b) => (a :*: b) -> (a :*: b) -> a :*: b
>= :: (a :*: b) -> (a :*: b) -> Bool
$c>= :: forall a b. (Ord a, Ord b) => (a :*: b) -> (a :*: b) -> Bool
> :: (a :*: b) -> (a :*: b) -> Bool
$c> :: forall a b. (Ord a, Ord b) => (a :*: b) -> (a :*: b) -> Bool
<= :: (a :*: b) -> (a :*: b) -> Bool
$c<= :: forall a b. (Ord a, Ord b) => (a :*: b) -> (a :*: b) -> Bool
< :: (a :*: b) -> (a :*: b) -> Bool
$c< :: forall a b. (Ord a, Ord b) => (a :*: b) -> (a :*: b) -> Bool
compare :: (a :*: b) -> (a :*: b) -> Ordering
$ccompare :: forall a b. (Ord a, Ord b) => (a :*: b) -> (a :*: b) -> Ordering
Ord, Int -> (a :*: b) -> ShowS
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall a b. (Show a, Show b) => Int -> (a :*: b) -> ShowS
forall a b. (Show a, Show b) => [a :*: b] -> ShowS
forall a b. (Show a, Show b) => (a :*: b) -> String
showList :: [a :*: b] -> ShowS
$cshowList :: forall a b. (Show a, Show b) => [a :*: b] -> ShowS
show :: (a :*: b) -> String
$cshow :: forall a b. (Show a, Show b) => (a :*: b) -> String
showsPrec :: Int -> (a :*: b) -> ShowS
$cshowsPrec :: forall a b. (Show a, Show b) => Int -> (a :*: b) -> ShowS
Show)

instance (PQFormat t1, PQFormat t2) => PQFormat (t1 :*: t2) where
  pqFormat :: ByteString
pqFormat    = forall t. PQFormat t => ByteString
pqFormat @t1 ByteString -> ByteString -> ByteString
`BS.append` forall t. PQFormat t => ByteString
pqFormat @t2
  pqVariables :: Int
pqVariables = forall t. PQFormat t => Int
pqVariables @t1 forall a. Num a => a -> a -> a
+ forall t. PQFormat t => Int
pqVariables @t2

-- NULLables

instance PQFormat t => PQFormat (Maybe t) where
  pqFormat :: ByteString
pqFormat    = forall t. PQFormat t => ByteString
pqFormat @t
  pqVariables :: Int
pqVariables = forall t. PQFormat t => Int
pqVariables @t

-- NUMERICS

instance PQFormat Int16 where
  pqFormat :: ByteString
pqFormat = String -> ByteString
BS.pack String
"%int2"

instance PQFormat Int32 where
  pqFormat :: ByteString
pqFormat = String -> ByteString
BS.pack String
"%int4"

instance PQFormat Int64 where
  pqFormat :: ByteString
pqFormat = String -> ByteString
BS.pack String
"%int8"

instance PQFormat Int where
  pqFormat :: ByteString
pqFormat = String -> ByteString
BS.pack String
"%int8"

instance PQFormat Float where
  pqFormat :: ByteString
pqFormat = String -> ByteString
BS.pack String
"%float4"

instance PQFormat Double where
  pqFormat :: ByteString
pqFormat = String -> ByteString
BS.pack String
"%float8"

-- CHAR

instance PQFormat Char where
  pqFormat :: ByteString
pqFormat = String -> ByteString
BS.pack String
"%char"

instance PQFormat Word8 where
  pqFormat :: ByteString
pqFormat = String -> ByteString
BS.pack String
"%char"

-- VARIABLE-LENGTH CHARACTER TYPES

instance PQFormat String where
  pqFormat :: ByteString
pqFormat = String -> ByteString
BS.pack String
"%btext"

instance PQFormat T.Text where
  pqFormat :: ByteString
pqFormat = String -> ByteString
BS.pack String
"%btext"

instance PQFormat TL.Text where
  pqFormat :: ByteString
pqFormat = String -> ByteString
BS.pack String
"%btext"

instance PQFormat UUID where
  pqFormat :: ByteString
pqFormat = String -> ByteString
BS.pack String
"%uuid"

-- BYTEA

instance PQFormat BS.ByteString where
  pqFormat :: ByteString
pqFormat = String -> ByteString
BS.pack String
"%bytea"

instance PQFormat BSL.ByteString where
  pqFormat :: ByteString
pqFormat = String -> ByteString
BS.pack String
"%bytea"

-- DATE

instance PQFormat Day where
  pqFormat :: ByteString
pqFormat = String -> ByteString
BS.pack String
"%date"

-- TIME

instance PQFormat TimeOfDay where
  pqFormat :: ByteString
pqFormat = String -> ByteString
BS.pack String
"%time"

-- TIMESTAMP

instance PQFormat LocalTime where
  pqFormat :: ByteString
pqFormat = String -> ByteString
BS.pack String
"%timestamp"

-- TIMESTAMPTZ

instance PQFormat UTCTime where
  pqFormat :: ByteString
pqFormat = String -> ByteString
BS.pack String
"%timestamptz"

instance PQFormat ZonedTime where
  pqFormat :: ByteString
pqFormat = String -> ByteString
BS.pack String
"%timestamptz"

-- BOOL

instance PQFormat Bool where
  pqFormat :: ByteString
pqFormat = String -> ByteString
BS.pack String
"%bool"

-- TUPLES

instance PQFormat () where
  pqFormat :: ByteString
pqFormat = ByteString
BS.empty
  pqVariables :: Int
pqVariables = Int
0

instance (
    PQFormat t
  ) => PQFormat (Identity t) where
    pqFormat :: ByteString
pqFormat = forall t. PQFormat t => ByteString
pqFormat @t
    pqVariables :: Int
pqVariables = Int
1

instance (
    PQFormat t1, PQFormat t2
  ) => PQFormat (t1, t2) where
    pqFormat :: ByteString
pqFormat = [ByteString] -> ByteString
BS.concat [
        forall t. PQFormat t => ByteString
pqFormat @t1, forall t. PQFormat t => ByteString
pqFormat @t2
      ]
    pqVariables :: Int
pqVariables = Int
2

instance (
    PQFormat t1, PQFormat t2, PQFormat t3
  ) => PQFormat (t1, t2, t3) where
    pqFormat :: ByteString
pqFormat = [ByteString] -> ByteString
BS.concat [
        forall t. PQFormat t => ByteString
pqFormat @t1, forall t. PQFormat t => ByteString
pqFormat @t2, forall t. PQFormat t => ByteString
pqFormat @t3
      ]
    pqVariables :: Int
pqVariables = Int
3

instance (
    PQFormat t1, PQFormat t2, PQFormat t3, PQFormat t4
  ) => PQFormat (t1, t2, t3, t4) where
    pqFormat :: ByteString
pqFormat = [ByteString] -> ByteString
BS.concat [
        forall t. PQFormat t => ByteString
pqFormat @t1, forall t. PQFormat t => ByteString
pqFormat @t2, forall t. PQFormat t => ByteString
pqFormat @t3, forall t. PQFormat t => ByteString
pqFormat @t4
      ]
    pqVariables :: Int
pqVariables = Int
4

instance (
    PQFormat t1, PQFormat t2, PQFormat t3, PQFormat t4, PQFormat t5
  ) => PQFormat (t1, t2, t3, t4, t5) where
    pqFormat :: ByteString
pqFormat = [ByteString] -> ByteString
BS.concat [
        forall t. PQFormat t => ByteString
pqFormat @t1, forall t. PQFormat t => ByteString
pqFormat @t2, forall t. PQFormat t => ByteString
pqFormat @t3, forall t. PQFormat t => ByteString
pqFormat @t4
      , forall t. PQFormat t => ByteString
pqFormat @t5
      ]
    pqVariables :: Int
pqVariables = Int
5

instance (
    PQFormat t1, PQFormat t2, PQFormat t3, PQFormat t4, PQFormat t5, PQFormat t6
  ) => PQFormat (t1, t2, t3, t4, t5, t6) where
    pqFormat :: ByteString
pqFormat = [ByteString] -> ByteString
BS.concat [
        forall t. PQFormat t => ByteString
pqFormat @t1, forall t. PQFormat t => ByteString
pqFormat @t2, forall t. PQFormat t => ByteString
pqFormat @t3, forall t. PQFormat t => ByteString
pqFormat @t4
      , forall t. PQFormat t => ByteString
pqFormat @t5, forall t. PQFormat t => ByteString
pqFormat @t6
      ]
    pqVariables :: Int
pqVariables = Int
6

instance (
    PQFormat t1, PQFormat t2, PQFormat t3, PQFormat t4, PQFormat t5, PQFormat t6
  , PQFormat t7
  ) => PQFormat (t1, t2, t3, t4, t5, t6, t7) where
    pqFormat :: ByteString
pqFormat = [ByteString] -> ByteString
BS.concat [
        forall t. PQFormat t => ByteString
pqFormat @t1, forall t. PQFormat t => ByteString
pqFormat @t2, forall t. PQFormat t => ByteString
pqFormat @t3, forall t. PQFormat t => ByteString
pqFormat @t4
      , forall t. PQFormat t => ByteString
pqFormat @t5, forall t. PQFormat t => ByteString
pqFormat @t6, forall t. PQFormat t => ByteString
pqFormat @t7
      ]
    pqVariables :: Int
pqVariables = Int
7

instance (
    PQFormat t1, PQFormat t2, PQFormat t3, PQFormat t4, PQFormat t5, PQFormat t6
  , PQFormat t7, PQFormat t8
  ) => PQFormat (t1, t2, t3, t4, t5, t6, t7, t8) where
    pqFormat :: ByteString
pqFormat = [ByteString] -> ByteString
BS.concat [
        forall t. PQFormat t => ByteString
pqFormat @t1, forall t. PQFormat t => ByteString
pqFormat @t2, forall t. PQFormat t => ByteString
pqFormat @t3, forall t. PQFormat t => ByteString
pqFormat @t4
      , forall t. PQFormat t => ByteString
pqFormat @t5, forall t. PQFormat t => ByteString
pqFormat @t6, forall t. PQFormat t => ByteString
pqFormat @t7, forall t. PQFormat t => ByteString
pqFormat @t8
      ]
    pqVariables :: Int
pqVariables = Int
8

instance (
    PQFormat t1, PQFormat t2, PQFormat t3, PQFormat t4, PQFormat t5, PQFormat t6
  , PQFormat t7, PQFormat t8, PQFormat t9
  ) => PQFormat (t1, t2, t3, t4, t5, t6, t7, t8, t9) where
    pqFormat :: ByteString
pqFormat = [ByteString] -> ByteString
BS.concat [
        forall t. PQFormat t => ByteString
pqFormat @t1, forall t. PQFormat t => ByteString
pqFormat @t2, forall t. PQFormat t => ByteString
pqFormat @t3, forall t. PQFormat t => ByteString
pqFormat @t4
      , forall t. PQFormat t => ByteString
pqFormat @t5, forall t. PQFormat t => ByteString
pqFormat @t6, forall t. PQFormat t => ByteString
pqFormat @t7, forall t. PQFormat t => ByteString
pqFormat @t8
      , forall t. PQFormat t => ByteString
pqFormat @t9
      ]
    pqVariables :: Int
pqVariables = Int
9

instance (
    PQFormat t1, PQFormat t2, PQFormat t3, PQFormat t4, PQFormat t5, PQFormat t6
  , PQFormat t7, PQFormat t8, PQFormat t9, PQFormat t10
  ) => PQFormat (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10) where
    pqFormat :: ByteString
pqFormat = [ByteString] -> ByteString
BS.concat [
        forall t. PQFormat t => ByteString
pqFormat @t1, forall t. PQFormat t => ByteString
pqFormat @t2, forall t. PQFormat t => ByteString
pqFormat @t3, forall t. PQFormat t => ByteString
pqFormat @t4
      , forall t. PQFormat t => ByteString
pqFormat @t5, forall t. PQFormat t => ByteString
pqFormat @t6, forall t. PQFormat t => ByteString
pqFormat @t7, forall t. PQFormat t => ByteString
pqFormat @t8
      , forall t. PQFormat t => ByteString
pqFormat @t9, forall t. PQFormat t => ByteString
pqFormat @t10
      ]
    pqVariables :: Int
pqVariables = Int
10

instance (
    PQFormat t1, PQFormat t2, PQFormat t3, PQFormat t4, PQFormat t5, PQFormat t6
  , PQFormat t7, PQFormat t8, PQFormat t9, PQFormat t10, PQFormat t11
  ) => PQFormat (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11) where
    pqFormat :: ByteString
pqFormat = [ByteString] -> ByteString
BS.concat [
        forall t. PQFormat t => ByteString
pqFormat @t1, forall t. PQFormat t => ByteString
pqFormat @t2, forall t. PQFormat t => ByteString
pqFormat @t3, forall t. PQFormat t => ByteString
pqFormat @t4
      , forall t. PQFormat t => ByteString
pqFormat @t5, forall t. PQFormat t => ByteString
pqFormat @t6, forall t. PQFormat t => ByteString
pqFormat @t7, forall t. PQFormat t => ByteString
pqFormat @t8
      , forall t. PQFormat t => ByteString
pqFormat @t9, forall t. PQFormat t => ByteString
pqFormat @t10, forall t. PQFormat t => ByteString
pqFormat @t11
      ]
    pqVariables :: Int
pqVariables = Int
11

instance (
    PQFormat t1, PQFormat t2, PQFormat t3, PQFormat t4, PQFormat t5, PQFormat t6
  , PQFormat t7, PQFormat t8, PQFormat t9, PQFormat t10, PQFormat t11, PQFormat t12
  ) => PQFormat (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12) where
    pqFormat :: ByteString
pqFormat = [ByteString] -> ByteString
BS.concat [
        forall t. PQFormat t => ByteString
pqFormat @t1, forall t. PQFormat t => ByteString
pqFormat @t2, forall t. PQFormat t => ByteString
pqFormat @t3, forall t. PQFormat t => ByteString
pqFormat @t4
      , forall t. PQFormat t => ByteString
pqFormat @t5, forall t. PQFormat t => ByteString
pqFormat @t6, forall t. PQFormat t => ByteString
pqFormat @t7, forall t. PQFormat t => ByteString
pqFormat @t8
      , forall t. PQFormat t => ByteString
pqFormat @t9, forall t. PQFormat t => ByteString
pqFormat @t10, forall t. PQFormat t => ByteString
pqFormat @t11, forall t. PQFormat t => ByteString
pqFormat @t12
      ]
    pqVariables :: Int
pqVariables = Int
12

instance (
    PQFormat t1, PQFormat t2, PQFormat t3, PQFormat t4, PQFormat t5, PQFormat t6
  , PQFormat t7, PQFormat t8, PQFormat t9, PQFormat t10, PQFormat t11, PQFormat t12
  , PQFormat t13
  ) => PQFormat (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13) where
    pqFormat :: ByteString
pqFormat = [ByteString] -> ByteString
BS.concat [
        forall t. PQFormat t => ByteString
pqFormat @t1, forall t. PQFormat t => ByteString
pqFormat @t2, forall t. PQFormat t => ByteString
pqFormat @t3, forall t. PQFormat t => ByteString
pqFormat @t4
      , forall t. PQFormat t => ByteString
pqFormat @t5, forall t. PQFormat t => ByteString
pqFormat @t6, forall t. PQFormat t => ByteString
pqFormat @t7, forall t. PQFormat t => ByteString
pqFormat @t8
      , forall t. PQFormat t => ByteString
pqFormat @t9, forall t. PQFormat t => ByteString
pqFormat @t10, forall t. PQFormat t => ByteString
pqFormat @t11, forall t. PQFormat t => ByteString
pqFormat @t12
      , forall t. PQFormat t => ByteString
pqFormat @t13
      ]
    pqVariables :: Int
pqVariables = Int
13

instance (
    PQFormat t1, PQFormat t2, PQFormat t3, PQFormat t4, PQFormat t5, PQFormat t6
  , PQFormat t7, PQFormat t8, PQFormat t9, PQFormat t10, PQFormat t11, PQFormat t12
  , PQFormat t13, PQFormat t14
  ) => PQFormat (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14) where
    pqFormat :: ByteString
pqFormat = [ByteString] -> ByteString
BS.concat [
        forall t. PQFormat t => ByteString
pqFormat @t1, forall t. PQFormat t => ByteString
pqFormat @t2, forall t. PQFormat t => ByteString
pqFormat @t3, forall t. PQFormat t => ByteString
pqFormat @t4
      , forall t. PQFormat t => ByteString
pqFormat @t5, forall t. PQFormat t => ByteString
pqFormat @t6, forall t. PQFormat t => ByteString
pqFormat @t7, forall t. PQFormat t => ByteString
pqFormat @t8
      , forall t. PQFormat t => ByteString
pqFormat @t9, forall t. PQFormat t => ByteString
pqFormat @t10, forall t. PQFormat t => ByteString
pqFormat @t11, forall t. PQFormat t => ByteString
pqFormat @t12
      , forall t. PQFormat t => ByteString
pqFormat @t13, forall t. PQFormat t => ByteString
pqFormat @t14
      ]
    pqVariables :: Int
pqVariables = Int
14

instance (
    PQFormat t1, PQFormat t2, PQFormat t3, PQFormat t4, PQFormat t5, PQFormat t6
  , PQFormat t7, PQFormat t8, PQFormat t9, PQFormat t10, PQFormat t11, PQFormat t12
  , PQFormat t13, PQFormat t14, PQFormat t15
  ) => PQFormat (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14, t15) where
    pqFormat :: ByteString
pqFormat = [ByteString] -> ByteString
BS.concat [
        forall t. PQFormat t => ByteString
pqFormat @t1, forall t. PQFormat t => ByteString
pqFormat @t2, forall t. PQFormat t => ByteString
pqFormat @t3, forall t. PQFormat t => ByteString
pqFormat @t4
      , forall t. PQFormat t => ByteString
pqFormat @t5, forall t. PQFormat t => ByteString
pqFormat @t6, forall t. PQFormat t => ByteString
pqFormat @t7, forall t. PQFormat t => ByteString
pqFormat @t8
      , forall t. PQFormat t => ByteString
pqFormat @t9, forall t. PQFormat t => ByteString
pqFormat @t10, forall t. PQFormat t => ByteString
pqFormat @t11, forall t. PQFormat t => ByteString
pqFormat @t12
      , forall t. PQFormat t => ByteString
pqFormat @t13, forall t. PQFormat t => ByteString
pqFormat @t14, forall t. PQFormat t => ByteString
pqFormat @t15
      ]
    pqVariables :: Int
pqVariables = Int
15

instance (
    PQFormat t1, PQFormat t2, PQFormat t3, PQFormat t4, PQFormat t5, PQFormat t6
  , PQFormat t7, PQFormat t8, PQFormat t9, PQFormat t10, PQFormat t11, PQFormat t12
  , PQFormat t13, PQFormat t14, PQFormat t15, PQFormat t16
  ) => PQFormat (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14, t15, t16) where
    pqFormat :: ByteString
pqFormat = [ByteString] -> ByteString
BS.concat [
        forall t. PQFormat t => ByteString
pqFormat @t1, forall t. PQFormat t => ByteString
pqFormat @t2, forall t. PQFormat t => ByteString
pqFormat @t3, forall t. PQFormat t => ByteString
pqFormat @t4
      , forall t. PQFormat t => ByteString
pqFormat @t5, forall t. PQFormat t => ByteString
pqFormat @t6, forall t. PQFormat t => ByteString
pqFormat @t7, forall t. PQFormat t => ByteString
pqFormat @t8
      , forall t. PQFormat t => ByteString
pqFormat @t9, forall t. PQFormat t => ByteString
pqFormat @t10, forall t. PQFormat t => ByteString
pqFormat @t11, forall t. PQFormat t => ByteString
pqFormat @t12
      , forall t. PQFormat t => ByteString
pqFormat @t13, forall t. PQFormat t => ByteString
pqFormat @t14, forall t. PQFormat t => ByteString
pqFormat @t15, forall t. PQFormat t => ByteString
pqFormat @t16
      ]
    pqVariables :: Int
pqVariables = Int
16

instance (
    PQFormat t1, PQFormat t2, PQFormat t3, PQFormat t4, PQFormat t5, PQFormat t6
  , PQFormat t7, PQFormat t8, PQFormat t9, PQFormat t10, PQFormat t11, PQFormat t12
  , PQFormat t13, PQFormat t14, PQFormat t15, PQFormat t16, PQFormat t17
  ) => PQFormat (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14, t15, t16, t17) where
    pqFormat :: ByteString
pqFormat = [ByteString] -> ByteString
BS.concat [
        forall t. PQFormat t => ByteString
pqFormat @t1, forall t. PQFormat t => ByteString
pqFormat @t2, forall t. PQFormat t => ByteString
pqFormat @t3, forall t. PQFormat t => ByteString
pqFormat @t4
      , forall t. PQFormat t => ByteString
pqFormat @t5, forall t. PQFormat t => ByteString
pqFormat @t6, forall t. PQFormat t => ByteString
pqFormat @t7, forall t. PQFormat t => ByteString
pqFormat @t8
      , forall t. PQFormat t => ByteString
pqFormat @t9, forall t. PQFormat t => ByteString
pqFormat @t10, forall t. PQFormat t => ByteString
pqFormat @t11, forall t. PQFormat t => ByteString
pqFormat @t12
      , forall t. PQFormat t => ByteString
pqFormat @t13, forall t. PQFormat t => ByteString
pqFormat @t14, forall t. PQFormat t => ByteString
pqFormat @t15, forall t. PQFormat t => ByteString
pqFormat @t16
      , forall t. PQFormat t => ByteString
pqFormat @t17
      ]
    pqVariables :: Int
pqVariables = Int
17

instance (
    PQFormat t1, PQFormat t2, PQFormat t3, PQFormat t4, PQFormat t5, PQFormat t6
  , PQFormat t7, PQFormat t8, PQFormat t9, PQFormat t10, PQFormat t11, PQFormat t12
  , PQFormat t13, PQFormat t14, PQFormat t15, PQFormat t16, PQFormat t17, PQFormat t18
  ) => PQFormat (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14, t15, t16, t17, t18) where
    pqFormat :: ByteString
pqFormat = [ByteString] -> ByteString
BS.concat [
        forall t. PQFormat t => ByteString
pqFormat @t1, forall t. PQFormat t => ByteString
pqFormat @t2, forall t. PQFormat t => ByteString
pqFormat @t3, forall t. PQFormat t => ByteString
pqFormat @t4
      , forall t. PQFormat t => ByteString
pqFormat @t5, forall t. PQFormat t => ByteString
pqFormat @t6, forall t. PQFormat t => ByteString
pqFormat @t7, forall t. PQFormat t => ByteString
pqFormat @t8
      , forall t. PQFormat t => ByteString
pqFormat @t9, forall t. PQFormat t => ByteString
pqFormat @t10, forall t. PQFormat t => ByteString
pqFormat @t11, forall t. PQFormat t => ByteString
pqFormat @t12
      , forall t. PQFormat t => ByteString
pqFormat @t13, forall t. PQFormat t => ByteString
pqFormat @t14, forall t. PQFormat t => ByteString
pqFormat @t15, forall t. PQFormat t => ByteString
pqFormat @t16
      , forall t. PQFormat t => ByteString
pqFormat @t17, forall t. PQFormat t => ByteString
pqFormat @t18
      ]
    pqVariables :: Int
pqVariables = Int
18

instance (
    PQFormat t1, PQFormat t2, PQFormat t3, PQFormat t4, PQFormat t5, PQFormat t6
  , PQFormat t7, PQFormat t8, PQFormat t9, PQFormat t10, PQFormat t11, PQFormat t12
  , PQFormat t13, PQFormat t14, PQFormat t15, PQFormat t16, PQFormat t17, PQFormat t18
  , PQFormat t19
  ) => PQFormat (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14, t15, t16, t17, t18, t19) where
    pqFormat :: ByteString
pqFormat = [ByteString] -> ByteString
BS.concat [
        forall t. PQFormat t => ByteString
pqFormat @t1, forall t. PQFormat t => ByteString
pqFormat @t2, forall t. PQFormat t => ByteString
pqFormat @t3, forall t. PQFormat t => ByteString
pqFormat @t4
      , forall t. PQFormat t => ByteString
pqFormat @t5, forall t. PQFormat t => ByteString
pqFormat @t6, forall t. PQFormat t => ByteString
pqFormat @t7, forall t. PQFormat t => ByteString
pqFormat @t8
      , forall t. PQFormat t => ByteString
pqFormat @t9, forall t. PQFormat t => ByteString
pqFormat @t10, forall t. PQFormat t => ByteString
pqFormat @t11, forall t. PQFormat t => ByteString
pqFormat @t12
      , forall t. PQFormat t => ByteString
pqFormat @t13, forall t. PQFormat t => ByteString
pqFormat @t14, forall t. PQFormat t => ByteString
pqFormat @t15, forall t. PQFormat t => ByteString
pqFormat @t16
      , forall t. PQFormat t => ByteString
pqFormat @t17, forall t. PQFormat t => ByteString
pqFormat @t18, forall t. PQFormat t => ByteString
pqFormat @t19
      ]
    pqVariables :: Int
pqVariables = Int
19

instance (
    PQFormat t1, PQFormat t2, PQFormat t3, PQFormat t4, PQFormat t5, PQFormat t6
  , PQFormat t7, PQFormat t8, PQFormat t9, PQFormat t10, PQFormat t11, PQFormat t12
  , PQFormat t13, PQFormat t14, PQFormat t15, PQFormat t16, PQFormat t17, PQFormat t18
  , PQFormat t19, PQFormat t20
  ) => PQFormat (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14, t15, t16, t17, t18, t19, t20) where
    pqFormat :: ByteString
pqFormat = [ByteString] -> ByteString
BS.concat [
        forall t. PQFormat t => ByteString
pqFormat @t1, forall t. PQFormat t => ByteString
pqFormat @t2, forall t. PQFormat t => ByteString
pqFormat @t3, forall t. PQFormat t => ByteString
pqFormat @t4
      , forall t. PQFormat t => ByteString
pqFormat @t5, forall t. PQFormat t => ByteString
pqFormat @t6, forall t. PQFormat t => ByteString
pqFormat @t7, forall t. PQFormat t => ByteString
pqFormat @t8
      , forall t. PQFormat t => ByteString
pqFormat @t9, forall t. PQFormat t => ByteString
pqFormat @t10, forall t. PQFormat t => ByteString
pqFormat @t11, forall t. PQFormat t => ByteString
pqFormat @t12
      , forall t. PQFormat t => ByteString
pqFormat @t13, forall t. PQFormat t => ByteString
pqFormat @t14, forall t. PQFormat t => ByteString
pqFormat @t15, forall t. PQFormat t => ByteString
pqFormat @t16
      , forall t. PQFormat t => ByteString
pqFormat @t17, forall t. PQFormat t => ByteString
pqFormat @t18, forall t. PQFormat t => ByteString
pqFormat @t19, forall t. PQFormat t => ByteString
pqFormat @t20
      ]
    pqVariables :: Int
pqVariables = Int
20

instance (
    PQFormat t1, PQFormat t2, PQFormat t3, PQFormat t4, PQFormat t5, PQFormat t6
  , PQFormat t7, PQFormat t8, PQFormat t9, PQFormat t10, PQFormat t11, PQFormat t12
  , PQFormat t13, PQFormat t14, PQFormat t15, PQFormat t16, PQFormat t17, PQFormat t18
  , PQFormat t19, PQFormat t20, PQFormat t21
  ) => PQFormat (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14, t15, t16, t17, t18, t19, t20, t21) where
    pqFormat :: ByteString
pqFormat = [ByteString] -> ByteString
BS.concat [
        forall t. PQFormat t => ByteString
pqFormat @t1, forall t. PQFormat t => ByteString
pqFormat @t2, forall t. PQFormat t => ByteString
pqFormat @t3, forall t. PQFormat t => ByteString
pqFormat @t4
      , forall t. PQFormat t => ByteString
pqFormat @t5, forall t. PQFormat t => ByteString
pqFormat @t6, forall t. PQFormat t => ByteString
pqFormat @t7, forall t. PQFormat t => ByteString
pqFormat @t8
      , forall t. PQFormat t => ByteString
pqFormat @t9, forall t. PQFormat t => ByteString
pqFormat @t10, forall t. PQFormat t => ByteString
pqFormat @t11, forall t. PQFormat t => ByteString
pqFormat @t12
      , forall t. PQFormat t => ByteString
pqFormat @t13, forall t. PQFormat t => ByteString
pqFormat @t14, forall t. PQFormat t => ByteString
pqFormat @t15, forall t. PQFormat t => ByteString
pqFormat @t16
      , forall t. PQFormat t => ByteString
pqFormat @t17, forall t. PQFormat t => ByteString
pqFormat @t18, forall t. PQFormat t => ByteString
pqFormat @t19, forall t. PQFormat t => ByteString
pqFormat @t20
      , forall t. PQFormat t => ByteString
pqFormat @t21
      ]
    pqVariables :: Int
pqVariables = Int
21

instance (
    PQFormat t1, PQFormat t2, PQFormat t3, PQFormat t4, PQFormat t5, PQFormat t6
  , PQFormat t7, PQFormat t8, PQFormat t9, PQFormat t10, PQFormat t11, PQFormat t12
  , PQFormat t13, PQFormat t14, PQFormat t15, PQFormat t16, PQFormat t17, PQFormat t18
  , PQFormat t19, PQFormat t20, PQFormat t21, PQFormat t22
  ) => PQFormat (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14, t15, t16, t17, t18, t19, t20, t21,  t22) where
    pqFormat :: ByteString
pqFormat = [ByteString] -> ByteString
BS.concat [
        forall t. PQFormat t => ByteString
pqFormat @t1, forall t. PQFormat t => ByteString
pqFormat @t2, forall t. PQFormat t => ByteString
pqFormat @t3, forall t. PQFormat t => ByteString
pqFormat @t4
      , forall t. PQFormat t => ByteString
pqFormat @t5, forall t. PQFormat t => ByteString
pqFormat @t6, forall t. PQFormat t => ByteString
pqFormat @t7, forall t. PQFormat t => ByteString
pqFormat @t8
      , forall t. PQFormat t => ByteString
pqFormat @t9, forall t. PQFormat t => ByteString
pqFormat @t10, forall t. PQFormat t => ByteString
pqFormat @t11, forall t. PQFormat t => ByteString
pqFormat @t12
      , forall t. PQFormat t => ByteString
pqFormat @t13, forall t. PQFormat t => ByteString
pqFormat @t14, forall t. PQFormat t => ByteString
pqFormat @t15, forall t. PQFormat t => ByteString
pqFormat @t16
      , forall t. PQFormat t => ByteString
pqFormat @t17, forall t. PQFormat t => ByteString
pqFormat @t18, forall t. PQFormat t => ByteString
pqFormat @t19, forall t. PQFormat t => ByteString
pqFormat @t20
      , forall t. PQFormat t => ByteString
pqFormat @t21, forall t. PQFormat t => ByteString
pqFormat @t22
      ]
    pqVariables :: Int
pqVariables = Int
22

instance (
    PQFormat t1, PQFormat t2, PQFormat t3, PQFormat t4, PQFormat t5, PQFormat t6
  , PQFormat t7, PQFormat t8, PQFormat t9, PQFormat t10, PQFormat t11, PQFormat t12
  , PQFormat t13, PQFormat t14, PQFormat t15, PQFormat t16, PQFormat t17, PQFormat t18
  , PQFormat t19, PQFormat t20, PQFormat t21, PQFormat t22, PQFormat t23
  ) => PQFormat (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14, t15, t16, t17, t18, t19, t20, t21,  t22, t23) where
    pqFormat :: ByteString
pqFormat = [ByteString] -> ByteString
BS.concat [
        forall t. PQFormat t => ByteString
pqFormat @t1, forall t. PQFormat t => ByteString
pqFormat @t2, forall t. PQFormat t => ByteString
pqFormat @t3, forall t. PQFormat t => ByteString
pqFormat @t4
      , forall t. PQFormat t => ByteString
pqFormat @t5, forall t. PQFormat t => ByteString
pqFormat @t6, forall t. PQFormat t => ByteString
pqFormat @t7, forall t. PQFormat t => ByteString
pqFormat @t8
      , forall t. PQFormat t => ByteString
pqFormat @t9, forall t. PQFormat t => ByteString
pqFormat @t10, forall t. PQFormat t => ByteString
pqFormat @t11, forall t. PQFormat t => ByteString
pqFormat @t12
      , forall t. PQFormat t => ByteString
pqFormat @t13, forall t. PQFormat t => ByteString
pqFormat @t14, forall t. PQFormat t => ByteString
pqFormat @t15, forall t. PQFormat t => ByteString
pqFormat @t16
      , forall t. PQFormat t => ByteString
pqFormat @t17, forall t. PQFormat t => ByteString
pqFormat @t18, forall t. PQFormat t => ByteString
pqFormat @t19, forall t. PQFormat t => ByteString
pqFormat @t20
      , forall t. PQFormat t => ByteString
pqFormat @t21, forall t. PQFormat t => ByteString
pqFormat @t22, forall t. PQFormat t => ByteString
pqFormat @t23
      ]
    pqVariables :: Int
pqVariables = Int
23

instance (
    PQFormat t1, PQFormat t2, PQFormat t3, PQFormat t4, PQFormat t5, PQFormat t6
  , PQFormat t7, PQFormat t8, PQFormat t9, PQFormat t10, PQFormat t11, PQFormat t12
  , PQFormat t13, PQFormat t14, PQFormat t15, PQFormat t16, PQFormat t17, PQFormat t18
  , PQFormat t19, PQFormat t20, PQFormat t21, PQFormat t22, PQFormat t23, PQFormat t24
  ) => PQFormat (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14, t15, t16, t17, t18, t19, t20, t21,  t22, t23, t24) where
    pqFormat :: ByteString
pqFormat = [ByteString] -> ByteString
BS.concat [
        forall t. PQFormat t => ByteString
pqFormat @t1, forall t. PQFormat t => ByteString
pqFormat @t2, forall t. PQFormat t => ByteString
pqFormat @t3, forall t. PQFormat t => ByteString
pqFormat @t4
      , forall t. PQFormat t => ByteString
pqFormat @t5, forall t. PQFormat t => ByteString
pqFormat @t6, forall t. PQFormat t => ByteString
pqFormat @t7, forall t. PQFormat t => ByteString
pqFormat @t8
      , forall t. PQFormat t => ByteString
pqFormat @t9, forall t. PQFormat t => ByteString
pqFormat @t10, forall t. PQFormat t => ByteString
pqFormat @t11, forall t. PQFormat t => ByteString
pqFormat @t12
      , forall t. PQFormat t => ByteString
pqFormat @t13, forall t. PQFormat t => ByteString
pqFormat @t14, forall t. PQFormat t => ByteString
pqFormat @t15, forall t. PQFormat t => ByteString
pqFormat @t16
      , forall t. PQFormat t => ByteString
pqFormat @t17, forall t. PQFormat t => ByteString
pqFormat @t18, forall t. PQFormat t => ByteString
pqFormat @t19, forall t. PQFormat t => ByteString
pqFormat @t20
      , forall t. PQFormat t => ByteString
pqFormat @t21, forall t. PQFormat t => ByteString
pqFormat @t22, forall t. PQFormat t => ByteString
pqFormat @t23, forall t. PQFormat t => ByteString
pqFormat @t24
      ]
    pqVariables :: Int
pqVariables = Int
24

instance (
    PQFormat t1, PQFormat t2, PQFormat t3, PQFormat t4, PQFormat t5, PQFormat t6
  , PQFormat t7, PQFormat t8, PQFormat t9, PQFormat t10, PQFormat t11, PQFormat t12
  , PQFormat t13, PQFormat t14, PQFormat t15, PQFormat t16, PQFormat t17, PQFormat t18
  , PQFormat t19, PQFormat t20, PQFormat t21, PQFormat t22, PQFormat t23, PQFormat t24
  , PQFormat t25
  ) => PQFormat (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14, t15, t16, t17, t18, t19, t20, t21,  t22, t23, t24, t25) where
    pqFormat :: ByteString
pqFormat = [ByteString] -> ByteString
BS.concat [
        forall t. PQFormat t => ByteString
pqFormat @t1, forall t. PQFormat t => ByteString
pqFormat @t2, forall t. PQFormat t => ByteString
pqFormat @t3, forall t. PQFormat t => ByteString
pqFormat @t4
      , forall t. PQFormat t => ByteString
pqFormat @t5, forall t. PQFormat t => ByteString
pqFormat @t6, forall t. PQFormat t => ByteString
pqFormat @t7, forall t. PQFormat t => ByteString
pqFormat @t8
      , forall t. PQFormat t => ByteString
pqFormat @t9, forall t. PQFormat t => ByteString
pqFormat @t10, forall t. PQFormat t => ByteString
pqFormat @t11, forall t. PQFormat t => ByteString
pqFormat @t12
      , forall t. PQFormat t => ByteString
pqFormat @t13, forall t. PQFormat t => ByteString
pqFormat @t14, forall t. PQFormat t => ByteString
pqFormat @t15, forall t. PQFormat t => ByteString
pqFormat @t16
      , forall t. PQFormat t => ByteString
pqFormat @t17, forall t. PQFormat t => ByteString
pqFormat @t18, forall t. PQFormat t => ByteString
pqFormat @t19, forall t. PQFormat t => ByteString
pqFormat @t20
      , forall t. PQFormat t => ByteString
pqFormat @t21, forall t. PQFormat t => ByteString
pqFormat @t22, forall t. PQFormat t => ByteString
pqFormat @t23, forall t. PQFormat t => ByteString
pqFormat @t24
      , forall t. PQFormat t => ByteString
pqFormat @t25
      ]
    pqVariables :: Int
pqVariables = Int
25

instance (
    PQFormat t1, PQFormat t2, PQFormat t3, PQFormat t4, PQFormat t5, PQFormat t6
  , PQFormat t7, PQFormat t8, PQFormat t9, PQFormat t10, PQFormat t11, PQFormat t12
  , PQFormat t13, PQFormat t14, PQFormat t15, PQFormat t16, PQFormat t17, PQFormat t18
  , PQFormat t19, PQFormat t20, PQFormat t21, PQFormat t22, PQFormat t23, PQFormat t24
  , PQFormat t25, PQFormat t26
  ) => PQFormat (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14, t15, t16, t17, t18, t19, t20, t21,  t22, t23, t24, t25, t26) where
    pqFormat :: ByteString
pqFormat = [ByteString] -> ByteString
BS.concat [
        forall t. PQFormat t => ByteString
pqFormat @t1, forall t. PQFormat t => ByteString
pqFormat @t2, forall t. PQFormat t => ByteString
pqFormat @t3, forall t. PQFormat t => ByteString
pqFormat @t4
      , forall t. PQFormat t => ByteString
pqFormat @t5, forall t. PQFormat t => ByteString
pqFormat @t6, forall t. PQFormat t => ByteString
pqFormat @t7, forall t. PQFormat t => ByteString
pqFormat @t8
      , forall t. PQFormat t => ByteString
pqFormat @t9, forall t. PQFormat t => ByteString
pqFormat @t10, forall t. PQFormat t => ByteString
pqFormat @t11, forall t. PQFormat t => ByteString
pqFormat @t12
      , forall t. PQFormat t => ByteString
pqFormat @t13, forall t. PQFormat t => ByteString
pqFormat @t14, forall t. PQFormat t => ByteString
pqFormat @t15, forall t. PQFormat t => ByteString
pqFormat @t16
      , forall t. PQFormat t => ByteString
pqFormat @t17, forall t. PQFormat t => ByteString
pqFormat @t18, forall t. PQFormat t => ByteString
pqFormat @t19, forall t. PQFormat t => ByteString
pqFormat @t20
      , forall t. PQFormat t => ByteString
pqFormat @t21, forall t. PQFormat t => ByteString
pqFormat @t22, forall t. PQFormat t => ByteString
pqFormat @t23, forall t. PQFormat t => ByteString
pqFormat @t24
      , forall t. PQFormat t => ByteString
pqFormat @t25, forall t. PQFormat t => ByteString
pqFormat @t26
      ]
    pqVariables :: Int
pqVariables = Int
26

instance (
    PQFormat t1, PQFormat t2, PQFormat t3, PQFormat t4, PQFormat t5, PQFormat t6
  , PQFormat t7, PQFormat t8, PQFormat t9, PQFormat t10, PQFormat t11, PQFormat t12
  , PQFormat t13, PQFormat t14, PQFormat t15, PQFormat t16, PQFormat t17, PQFormat t18
  , PQFormat t19, PQFormat t20, PQFormat t21, PQFormat t22, PQFormat t23, PQFormat t24
  , PQFormat t25, PQFormat t26, PQFormat t27
  ) => PQFormat (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14, t15, t16, t17, t18, t19, t20, t21,  t22, t23, t24, t25, t26, t27) where
    pqFormat :: ByteString
pqFormat = [ByteString] -> ByteString
BS.concat [
        forall t. PQFormat t => ByteString
pqFormat @t1, forall t. PQFormat t => ByteString
pqFormat @t2, forall t. PQFormat t => ByteString
pqFormat @t3, forall t. PQFormat t => ByteString
pqFormat @t4
      , forall t. PQFormat t => ByteString
pqFormat @t5, forall t. PQFormat t => ByteString
pqFormat @t6, forall t. PQFormat t => ByteString
pqFormat @t7, forall t. PQFormat t => ByteString
pqFormat @t8
      , forall t. PQFormat t => ByteString
pqFormat @t9, forall t. PQFormat t => ByteString
pqFormat @t10, forall t. PQFormat t => ByteString
pqFormat @t11, forall t. PQFormat t => ByteString
pqFormat @t12
      , forall t. PQFormat t => ByteString
pqFormat @t13, forall t. PQFormat t => ByteString
pqFormat @t14, forall t. PQFormat t => ByteString
pqFormat @t15, forall t. PQFormat t => ByteString
pqFormat @t16
      , forall t. PQFormat t => ByteString
pqFormat @t17, forall t. PQFormat t => ByteString
pqFormat @t18, forall t. PQFormat t => ByteString
pqFormat @t19, forall t. PQFormat t => ByteString
pqFormat @t20
      , forall t. PQFormat t => ByteString
pqFormat @t21, forall t. PQFormat t => ByteString
pqFormat @t22, forall t. PQFormat t => ByteString
pqFormat @t23, forall t. PQFormat t => ByteString
pqFormat @t24
      , forall t. PQFormat t => ByteString
pqFormat @t25, forall t. PQFormat t => ByteString
pqFormat @t26, forall t. PQFormat t => ByteString
pqFormat @t27
      ]
    pqVariables :: Int
pqVariables = Int
27

instance (
    PQFormat t1, PQFormat t2, PQFormat t3, PQFormat t4, PQFormat t5, PQFormat t6
  , PQFormat t7, PQFormat t8, PQFormat t9, PQFormat t10, PQFormat t11, PQFormat t12
  , PQFormat t13, PQFormat t14, PQFormat t15, PQFormat t16, PQFormat t17, PQFormat t18
  , PQFormat t19, PQFormat t20, PQFormat t21, PQFormat t22, PQFormat t23, PQFormat t24
  , PQFormat t25, PQFormat t26, PQFormat t27, PQFormat t28
  ) => PQFormat (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14, t15, t16, t17, t18, t19, t20, t21,  t22, t23, t24, t25, t26, t27, t28) where
    pqFormat :: ByteString
pqFormat = [ByteString] -> ByteString
BS.concat [
        forall t. PQFormat t => ByteString
pqFormat @t1, forall t. PQFormat t => ByteString
pqFormat @t2, forall t. PQFormat t => ByteString
pqFormat @t3, forall t. PQFormat t => ByteString
pqFormat @t4
      , forall t. PQFormat t => ByteString
pqFormat @t5, forall t. PQFormat t => ByteString
pqFormat @t6, forall t. PQFormat t => ByteString
pqFormat @t7, forall t. PQFormat t => ByteString
pqFormat @t8
      , forall t. PQFormat t => ByteString
pqFormat @t9, forall t. PQFormat t => ByteString
pqFormat @t10, forall t. PQFormat t => ByteString
pqFormat @t11, forall t. PQFormat t => ByteString
pqFormat @t12
      , forall t. PQFormat t => ByteString
pqFormat @t13, forall t. PQFormat t => ByteString
pqFormat @t14, forall t. PQFormat t => ByteString
pqFormat @t15, forall t. PQFormat t => ByteString
pqFormat @t16
      , forall t. PQFormat t => ByteString
pqFormat @t17, forall t. PQFormat t => ByteString
pqFormat @t18, forall t. PQFormat t => ByteString
pqFormat @t19, forall t. PQFormat t => ByteString
pqFormat @t20
      , forall t. PQFormat t => ByteString
pqFormat @t21, forall t. PQFormat t => ByteString
pqFormat @t22, forall t. PQFormat t => ByteString
pqFormat @t23, forall t. PQFormat t => ByteString
pqFormat @t24
      , forall t. PQFormat t => ByteString
pqFormat @t25, forall t. PQFormat t => ByteString
pqFormat @t26, forall t. PQFormat t => ByteString
pqFormat @t27, forall t. PQFormat t => ByteString
pqFormat @t28
      ]
    pqVariables :: Int
pqVariables = Int
28

instance (
    PQFormat t1, PQFormat t2, PQFormat t3, PQFormat t4, PQFormat t5, PQFormat t6
  , PQFormat t7, PQFormat t8, PQFormat t9, PQFormat t10, PQFormat t11, PQFormat t12
  , PQFormat t13, PQFormat t14, PQFormat t15, PQFormat t16, PQFormat t17, PQFormat t18
  , PQFormat t19, PQFormat t20, PQFormat t21, PQFormat t22, PQFormat t23, PQFormat t24
  , PQFormat t25, PQFormat t26, PQFormat t27, PQFormat t28, PQFormat t29
  ) => PQFormat (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14, t15, t16, t17, t18, t19, t20, t21,  t22, t23, t24, t25, t26, t27, t28, t29) where
    pqFormat :: ByteString
pqFormat = [ByteString] -> ByteString
BS.concat [
        forall t. PQFormat t => ByteString
pqFormat @t1, forall t. PQFormat t => ByteString
pqFormat @t2, forall t. PQFormat t => ByteString
pqFormat @t3, forall t. PQFormat t => ByteString
pqFormat @t4
      , forall t. PQFormat t => ByteString
pqFormat @t5, forall t. PQFormat t => ByteString
pqFormat @t6, forall t. PQFormat t => ByteString
pqFormat @t7, forall t. PQFormat t => ByteString
pqFormat @t8
      , forall t. PQFormat t => ByteString
pqFormat @t9, forall t. PQFormat t => ByteString
pqFormat @t10, forall t. PQFormat t => ByteString
pqFormat @t11, forall t. PQFormat t => ByteString
pqFormat @t12
      , forall t. PQFormat t => ByteString
pqFormat @t13, forall t. PQFormat t => ByteString
pqFormat @t14, forall t. PQFormat t => ByteString
pqFormat @t15, forall t. PQFormat t => ByteString
pqFormat @t16
      , forall t. PQFormat t => ByteString
pqFormat @t17, forall t. PQFormat t => ByteString
pqFormat @t18, forall t. PQFormat t => ByteString
pqFormat @t19, forall t. PQFormat t => ByteString
pqFormat @t20
      , forall t. PQFormat t => ByteString
pqFormat @t21, forall t. PQFormat t => ByteString
pqFormat @t22, forall t. PQFormat t => ByteString
pqFormat @t23, forall t. PQFormat t => ByteString
pqFormat @t24
      , forall t. PQFormat t => ByteString
pqFormat @t25, forall t. PQFormat t => ByteString
pqFormat @t26, forall t. PQFormat t => ByteString
pqFormat @t27, forall t. PQFormat t => ByteString
pqFormat @t28
      , forall t. PQFormat t => ByteString
pqFormat @t29
      ]
    pqVariables :: Int
pqVariables = Int
29

instance (
    PQFormat t1, PQFormat t2, PQFormat t3, PQFormat t4, PQFormat t5, PQFormat t6
  , PQFormat t7, PQFormat t8, PQFormat t9, PQFormat t10, PQFormat t11, PQFormat t12
  , PQFormat t13, PQFormat t14, PQFormat t15, PQFormat t16, PQFormat t17, PQFormat t18
  , PQFormat t19, PQFormat t20, PQFormat t21, PQFormat t22, PQFormat t23, PQFormat t24
  , PQFormat t25, PQFormat t26, PQFormat t27, PQFormat t28, PQFormat t29, PQFormat t30
  ) => PQFormat (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14, t15, t16, t17, t18, t19, t20, t21,  t22, t23, t24, t25, t26, t27, t28, t29, t30) where
    pqFormat :: ByteString
pqFormat = [ByteString] -> ByteString
BS.concat [
        forall t. PQFormat t => ByteString
pqFormat @t1, forall t. PQFormat t => ByteString
pqFormat @t2, forall t. PQFormat t => ByteString
pqFormat @t3, forall t. PQFormat t => ByteString
pqFormat @t4
      , forall t. PQFormat t => ByteString
pqFormat @t5, forall t. PQFormat t => ByteString
pqFormat @t6, forall t. PQFormat t => ByteString
pqFormat @t7, forall t. PQFormat t => ByteString
pqFormat @t8
      , forall t. PQFormat t => ByteString
pqFormat @t9, forall t. PQFormat t => ByteString
pqFormat @t10, forall t. PQFormat t => ByteString
pqFormat @t11, forall t. PQFormat t => ByteString
pqFormat @t12
      , forall t. PQFormat t => ByteString
pqFormat @t13, forall t. PQFormat t => ByteString
pqFormat @t14, forall t. PQFormat t => ByteString
pqFormat @t15, forall t. PQFormat t => ByteString
pqFormat @t16
      , forall t. PQFormat t => ByteString
pqFormat @t17, forall t. PQFormat t => ByteString
pqFormat @t18, forall t. PQFormat t => ByteString
pqFormat @t19, forall t. PQFormat t => ByteString
pqFormat @t20
      , forall t. PQFormat t => ByteString
pqFormat @t21, forall t. PQFormat t => ByteString
pqFormat @t22, forall t. PQFormat t => ByteString
pqFormat @t23, forall t. PQFormat t => ByteString
pqFormat @t24
      , forall t. PQFormat t => ByteString
pqFormat @t25, forall t. PQFormat t => ByteString
pqFormat @t26, forall t. PQFormat t => ByteString
pqFormat @t27, forall t. PQFormat t => ByteString
pqFormat @t28
      , forall t. PQFormat t => ByteString
pqFormat @t29, forall t. PQFormat t => ByteString
pqFormat @t30
      ]
    pqVariables :: Int
pqVariables = Int
30

instance (
    PQFormat t1, PQFormat t2, PQFormat t3, PQFormat t4, PQFormat t5, PQFormat t6
  , PQFormat t7, PQFormat t8, PQFormat t9, PQFormat t10, PQFormat t11, PQFormat t12
  , PQFormat t13, PQFormat t14, PQFormat t15, PQFormat t16, PQFormat t17, PQFormat t18
  , PQFormat t19, PQFormat t20, PQFormat t21, PQFormat t22, PQFormat t23, PQFormat t24
  , PQFormat t25, PQFormat t26, PQFormat t27, PQFormat t28, PQFormat t29, PQFormat t30
  , PQFormat t31
  ) => PQFormat (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14, t15, t16, t17, t18, t19, t20, t21,  t22, t23, t24, t25, t26, t27, t28, t29, t30, t31) where
    pqFormat :: ByteString
pqFormat = [ByteString] -> ByteString
BS.concat [
        forall t. PQFormat t => ByteString
pqFormat @t1, forall t. PQFormat t => ByteString
pqFormat @t2, forall t. PQFormat t => ByteString
pqFormat @t3, forall t. PQFormat t => ByteString
pqFormat @t4
      , forall t. PQFormat t => ByteString
pqFormat @t5, forall t. PQFormat t => ByteString
pqFormat @t6, forall t. PQFormat t => ByteString
pqFormat @t7, forall t. PQFormat t => ByteString
pqFormat @t8
      , forall t. PQFormat t => ByteString
pqFormat @t9, forall t. PQFormat t => ByteString
pqFormat @t10, forall t. PQFormat t => ByteString
pqFormat @t11, forall t. PQFormat t => ByteString
pqFormat @t12
      , forall t. PQFormat t => ByteString
pqFormat @t13, forall t. PQFormat t => ByteString
pqFormat @t14, forall t. PQFormat t => ByteString
pqFormat @t15, forall t. PQFormat t => ByteString
pqFormat @t16
      , forall t. PQFormat t => ByteString
pqFormat @t17, forall t. PQFormat t => ByteString
pqFormat @t18, forall t. PQFormat t => ByteString
pqFormat @t19, forall t. PQFormat t => ByteString
pqFormat @t20
      , forall t. PQFormat t => ByteString
pqFormat @t21, forall t. PQFormat t => ByteString
pqFormat @t22, forall t. PQFormat t => ByteString
pqFormat @t23, forall t. PQFormat t => ByteString
pqFormat @t24
      , forall t. PQFormat t => ByteString
pqFormat @t25, forall t. PQFormat t => ByteString
pqFormat @t26, forall t. PQFormat t => ByteString
pqFormat @t27, forall t. PQFormat t => ByteString
pqFormat @t28
      , forall t. PQFormat t => ByteString
pqFormat @t29, forall t. PQFormat t => ByteString
pqFormat @t30, forall t. PQFormat t => ByteString
pqFormat @t31
      ]
    pqVariables :: Int
pqVariables = Int
31

instance (
    PQFormat t1, PQFormat t2, PQFormat t3, PQFormat t4, PQFormat t5, PQFormat t6
  , PQFormat t7, PQFormat t8, PQFormat t9, PQFormat t10, PQFormat t11, PQFormat t12
  , PQFormat t13, PQFormat t14, PQFormat t15, PQFormat t16, PQFormat t17, PQFormat t18
  , PQFormat t19, PQFormat t20, PQFormat t21, PQFormat t22, PQFormat t23, PQFormat t24
  , PQFormat t25, PQFormat t26, PQFormat t27, PQFormat t28, PQFormat t29, PQFormat t30
  , PQFormat t31, PQFormat t32
  ) => PQFormat (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14, t15, t16, t17, t18, t19, t20, t21,  t22, t23, t24, t25, t26, t27, t28, t29, t30, t31, t32) where
    pqFormat :: ByteString
pqFormat = [ByteString] -> ByteString
BS.concat [
        forall t. PQFormat t => ByteString
pqFormat @t1, forall t. PQFormat t => ByteString
pqFormat @t2, forall t. PQFormat t => ByteString
pqFormat @t3, forall t. PQFormat t => ByteString
pqFormat @t4
      , forall t. PQFormat t => ByteString
pqFormat @t5, forall t. PQFormat t => ByteString
pqFormat @t6, forall t. PQFormat t => ByteString
pqFormat @t7, forall t. PQFormat t => ByteString
pqFormat @t8
      , forall t. PQFormat t => ByteString
pqFormat @t9, forall t. PQFormat t => ByteString
pqFormat @t10, forall t. PQFormat t => ByteString
pqFormat @t11, forall t. PQFormat t => ByteString
pqFormat @t12
      , forall t. PQFormat t => ByteString
pqFormat @t13, forall t. PQFormat t => ByteString
pqFormat @t14, forall t. PQFormat t => ByteString
pqFormat @t15, forall t. PQFormat t => ByteString
pqFormat @t16
      , forall t. PQFormat t => ByteString
pqFormat @t17, forall t. PQFormat t => ByteString
pqFormat @t18, forall t. PQFormat t => ByteString
pqFormat @t19, forall t. PQFormat t => ByteString
pqFormat @t20
      , forall t. PQFormat t => ByteString
pqFormat @t21, forall t. PQFormat t => ByteString
pqFormat @t22, forall t. PQFormat t => ByteString
pqFormat @t23, forall t. PQFormat t => ByteString
pqFormat @t24
      , forall t. PQFormat t => ByteString
pqFormat @t25, forall t. PQFormat t => ByteString
pqFormat @t26, forall t. PQFormat t => ByteString
pqFormat @t27, forall t. PQFormat t => ByteString
pqFormat @t28
      , forall t. PQFormat t => ByteString
pqFormat @t29, forall t. PQFormat t => ByteString
pqFormat @t30, forall t. PQFormat t => ByteString
pqFormat @t31, forall t. PQFormat t => ByteString
pqFormat @t32
      ]
    pqVariables :: Int
pqVariables = Int
32

instance (
    PQFormat t1, PQFormat t2, PQFormat t3, PQFormat t4, PQFormat t5, PQFormat t6
  , PQFormat t7, PQFormat t8, PQFormat t9, PQFormat t10, PQFormat t11, PQFormat t12
  , PQFormat t13, PQFormat t14, PQFormat t15, PQFormat t16, PQFormat t17, PQFormat t18
  , PQFormat t19, PQFormat t20, PQFormat t21, PQFormat t22, PQFormat t23, PQFormat t24
  , PQFormat t25, PQFormat t26, PQFormat t27, PQFormat t28, PQFormat t29, PQFormat t30
  , PQFormat t31, PQFormat t32, PQFormat t33
  ) => PQFormat (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14, t15, t16, t17, t18, t19, t20, t21,  t22, t23, t24, t25, t26, t27, t28, t29, t30, t31, t32, t33) where
    pqFormat :: ByteString
pqFormat = [ByteString] -> ByteString
BS.concat [
        forall t. PQFormat t => ByteString
pqFormat @t1, forall t. PQFormat t => ByteString
pqFormat @t2, forall t. PQFormat t => ByteString
pqFormat @t3, forall t. PQFormat t => ByteString
pqFormat @t4
      , forall t. PQFormat t => ByteString
pqFormat @t5, forall t. PQFormat t => ByteString
pqFormat @t6, forall t. PQFormat t => ByteString
pqFormat @t7, forall t. PQFormat t => ByteString
pqFormat @t8
      , forall t. PQFormat t => ByteString
pqFormat @t9, forall t. PQFormat t => ByteString
pqFormat @t10, forall t. PQFormat t => ByteString
pqFormat @t11, forall t. PQFormat t => ByteString
pqFormat @t12
      , forall t. PQFormat t => ByteString
pqFormat @t13, forall t. PQFormat t => ByteString
pqFormat @t14, forall t. PQFormat t => ByteString
pqFormat @t15, forall t. PQFormat t => ByteString
pqFormat @t16
      , forall t. PQFormat t => ByteString
pqFormat @t17, forall t. PQFormat t => ByteString
pqFormat @t18, forall t. PQFormat t => ByteString
pqFormat @t19, forall t. PQFormat t => ByteString
pqFormat @t20
      , forall t. PQFormat t => ByteString
pqFormat @t21, forall t. PQFormat t => ByteString
pqFormat @t22, forall t. PQFormat t => ByteString
pqFormat @t23, forall t. PQFormat t => ByteString
pqFormat @t24
      , forall t. PQFormat t => ByteString
pqFormat @t25, forall t. PQFormat t => ByteString
pqFormat @t26, forall t. PQFormat t => ByteString
pqFormat @t27, forall t. PQFormat t => ByteString
pqFormat @t28
      , forall t. PQFormat t => ByteString
pqFormat @t29, forall t. PQFormat t => ByteString
pqFormat @t30, forall t. PQFormat t => ByteString
pqFormat @t31, forall t. PQFormat t => ByteString
pqFormat @t32
      , forall t. PQFormat t => ByteString
pqFormat @t33
      ]
    pqVariables :: Int
pqVariables = Int
33

instance (
    PQFormat t1, PQFormat t2, PQFormat t3, PQFormat t4, PQFormat t5, PQFormat t6
  , PQFormat t7, PQFormat t8, PQFormat t9, PQFormat t10, PQFormat t11, PQFormat t12
  , PQFormat t13, PQFormat t14, PQFormat t15, PQFormat t16, PQFormat t17, PQFormat t18
  , PQFormat t19, PQFormat t20, PQFormat t21, PQFormat t22, PQFormat t23, PQFormat t24
  , PQFormat t25, PQFormat t26, PQFormat t27, PQFormat t28, PQFormat t29, PQFormat t30
  , PQFormat t31, PQFormat t32, PQFormat t33, PQFormat t34
  ) => PQFormat (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14, t15, t16, t17, t18, t19, t20, t21,  t22, t23, t24, t25, t26, t27, t28, t29, t30, t31, t32, t33, t34) where
    pqFormat :: ByteString
pqFormat = [ByteString] -> ByteString
BS.concat [
        forall t. PQFormat t => ByteString
pqFormat @t1, forall t. PQFormat t => ByteString
pqFormat @t2, forall t. PQFormat t => ByteString
pqFormat @t3, forall t. PQFormat t => ByteString
pqFormat @t4
      , forall t. PQFormat t => ByteString
pqFormat @t5, forall t. PQFormat t => ByteString
pqFormat @t6, forall t. PQFormat t => ByteString
pqFormat @t7, forall t. PQFormat t => ByteString
pqFormat @t8
      , forall t. PQFormat t => ByteString
pqFormat @t9, forall t. PQFormat t => ByteString
pqFormat @t10, forall t. PQFormat t => ByteString
pqFormat @t11, forall t. PQFormat t => ByteString
pqFormat @t12
      , forall t. PQFormat t => ByteString
pqFormat @t13, forall t. PQFormat t => ByteString
pqFormat @t14, forall t. PQFormat t => ByteString
pqFormat @t15, forall t. PQFormat t => ByteString
pqFormat @t16
      , forall t. PQFormat t => ByteString
pqFormat @t17, forall t. PQFormat t => ByteString
pqFormat @t18, forall t. PQFormat t => ByteString
pqFormat @t19, forall t. PQFormat t => ByteString
pqFormat @t20
      , forall t. PQFormat t => ByteString
pqFormat @t21, forall t. PQFormat t => ByteString
pqFormat @t22, forall t. PQFormat t => ByteString
pqFormat @t23, forall t. PQFormat t => ByteString
pqFormat @t24
      , forall t. PQFormat t => ByteString
pqFormat @t25, forall t. PQFormat t => ByteString
pqFormat @t26, forall t. PQFormat t => ByteString
pqFormat @t27, forall t. PQFormat t => ByteString
pqFormat @t28
      , forall t. PQFormat t => ByteString
pqFormat @t29, forall t. PQFormat t => ByteString
pqFormat @t30, forall t. PQFormat t => ByteString
pqFormat @t31, forall t. PQFormat t => ByteString
pqFormat @t32
      , forall t. PQFormat t => ByteString
pqFormat @t33, forall t. PQFormat t => ByteString
pqFormat @t34
      ]
    pqVariables :: Int
pqVariables = Int
34

instance (
    PQFormat t1, PQFormat t2, PQFormat t3, PQFormat t4, PQFormat t5, PQFormat t6
  , PQFormat t7, PQFormat t8, PQFormat t9, PQFormat t10, PQFormat t11, PQFormat t12
  , PQFormat t13, PQFormat t14, PQFormat t15, PQFormat t16, PQFormat t17, PQFormat t18
  , PQFormat t19, PQFormat t20, PQFormat t21, PQFormat t22, PQFormat t23, PQFormat t24
  , PQFormat t25, PQFormat t26, PQFormat t27, PQFormat t28, PQFormat t29, PQFormat t30
  , PQFormat t31, PQFormat t32, PQFormat t33, PQFormat t34, PQFormat t35
  ) => PQFormat (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14, t15, t16, t17, t18, t19, t20, t21,  t22, t23, t24, t25, t26, t27, t28, t29, t30, t31, t32, t33, t34, t35) where
    pqFormat :: ByteString
pqFormat = [ByteString] -> ByteString
BS.concat [
        forall t. PQFormat t => ByteString
pqFormat @t1, forall t. PQFormat t => ByteString
pqFormat @t2, forall t. PQFormat t => ByteString
pqFormat @t3, forall t. PQFormat t => ByteString
pqFormat @t4
      , forall t. PQFormat t => ByteString
pqFormat @t5, forall t. PQFormat t => ByteString
pqFormat @t6, forall t. PQFormat t => ByteString
pqFormat @t7, forall t. PQFormat t => ByteString
pqFormat @t8
      , forall t. PQFormat t => ByteString
pqFormat @t9, forall t. PQFormat t => ByteString
pqFormat @t10, forall t. PQFormat t => ByteString
pqFormat @t11, forall t. PQFormat t => ByteString
pqFormat @t12
      , forall t. PQFormat t => ByteString
pqFormat @t13, forall t. PQFormat t => ByteString
pqFormat @t14, forall t. PQFormat t => ByteString
pqFormat @t15, forall t. PQFormat t => ByteString
pqFormat @t16
      , forall t. PQFormat t => ByteString
pqFormat @t17, forall t. PQFormat t => ByteString
pqFormat @t18, forall t. PQFormat t => ByteString
pqFormat @t19, forall t. PQFormat t => ByteString
pqFormat @t20
      , forall t. PQFormat t => ByteString
pqFormat @t21, forall t. PQFormat t => ByteString
pqFormat @t22, forall t. PQFormat t => ByteString
pqFormat @t23, forall t. PQFormat t => ByteString
pqFormat @t24
      , forall t. PQFormat t => ByteString
pqFormat @t25, forall t. PQFormat t => ByteString
pqFormat @t26, forall t. PQFormat t => ByteString
pqFormat @t27, forall t. PQFormat t => ByteString
pqFormat @t28
      , forall t. PQFormat t => ByteString
pqFormat @t29, forall t. PQFormat t => ByteString
pqFormat @t30, forall t. PQFormat t => ByteString
pqFormat @t31, forall t. PQFormat t => ByteString
pqFormat @t32
      , forall t. PQFormat t => ByteString
pqFormat @t33, forall t. PQFormat t => ByteString
pqFormat @t34, forall t. PQFormat t => ByteString
pqFormat @t35
      ]
    pqVariables :: Int
pqVariables = Int
35

instance (
    PQFormat t1, PQFormat t2, PQFormat t3, PQFormat t4, PQFormat t5, PQFormat t6
  , PQFormat t7, PQFormat t8, PQFormat t9, PQFormat t10, PQFormat t11, PQFormat t12
  , PQFormat t13, PQFormat t14, PQFormat t15, PQFormat t16, PQFormat t17, PQFormat t18
  , PQFormat t19, PQFormat t20, PQFormat t21, PQFormat t22, PQFormat t23, PQFormat t24
  , PQFormat t25, PQFormat t26, PQFormat t27, PQFormat t28, PQFormat t29, PQFormat t30
  , PQFormat t31, PQFormat t32, PQFormat t33, PQFormat t34, PQFormat t35, PQFormat t36
  ) => PQFormat (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14, t15, t16, t17, t18, t19, t20, t21,  t22, t23, t24, t25, t26, t27, t28, t29, t30, t31, t32, t33, t34, t35, t36) where
    pqFormat :: ByteString
pqFormat = [ByteString] -> ByteString
BS.concat [
        forall t. PQFormat t => ByteString
pqFormat @t1, forall t. PQFormat t => ByteString
pqFormat @t2, forall t. PQFormat t => ByteString
pqFormat @t3, forall t. PQFormat t => ByteString
pqFormat @t4
      , forall t. PQFormat t => ByteString
pqFormat @t5, forall t. PQFormat t => ByteString
pqFormat @t6, forall t. PQFormat t => ByteString
pqFormat @t7, forall t. PQFormat t => ByteString
pqFormat @t8
      , forall t. PQFormat t => ByteString
pqFormat @t9, forall t. PQFormat t => ByteString
pqFormat @t10, forall t. PQFormat t => ByteString
pqFormat @t11, forall t. PQFormat t => ByteString
pqFormat @t12
      , forall t. PQFormat t => ByteString
pqFormat @t13, forall t. PQFormat t => ByteString
pqFormat @t14, forall t. PQFormat t => ByteString
pqFormat @t15, forall t. PQFormat t => ByteString
pqFormat @t16
      , forall t. PQFormat t => ByteString
pqFormat @t17, forall t. PQFormat t => ByteString
pqFormat @t18, forall t. PQFormat t => ByteString
pqFormat @t19, forall t. PQFormat t => ByteString
pqFormat @t20
      , forall t. PQFormat t => ByteString
pqFormat @t21, forall t. PQFormat t => ByteString
pqFormat @t22, forall t. PQFormat t => ByteString
pqFormat @t23, forall t. PQFormat t => ByteString
pqFormat @t24
      , forall t. PQFormat t => ByteString
pqFormat @t25, forall t. PQFormat t => ByteString
pqFormat @t26, forall t. PQFormat t => ByteString
pqFormat @t27, forall t. PQFormat t => ByteString
pqFormat @t28
      , forall t. PQFormat t => ByteString
pqFormat @t29, forall t. PQFormat t => ByteString
pqFormat @t30, forall t. PQFormat t => ByteString
pqFormat @t31, forall t. PQFormat t => ByteString
pqFormat @t32
      , forall t. PQFormat t => ByteString
pqFormat @t33, forall t. PQFormat t => ByteString
pqFormat @t34, forall t. PQFormat t => ByteString
pqFormat @t35, forall t. PQFormat t => ByteString
pqFormat @t36
      ]
    pqVariables :: Int
pqVariables = Int
36

instance (
    PQFormat t1, PQFormat t2, PQFormat t3, PQFormat t4, PQFormat t5, PQFormat t6
  , PQFormat t7, PQFormat t8, PQFormat t9, PQFormat t10, PQFormat t11, PQFormat t12
  , PQFormat t13, PQFormat t14, PQFormat t15, PQFormat t16, PQFormat t17, PQFormat t18
  , PQFormat t19, PQFormat t20, PQFormat t21, PQFormat t22, PQFormat t23, PQFormat t24
  , PQFormat t25, PQFormat t26, PQFormat t27, PQFormat t28, PQFormat t29, PQFormat t30
  , PQFormat t31, PQFormat t32, PQFormat t33, PQFormat t34, PQFormat t35, PQFormat t36
  , PQFormat t37
  ) => PQFormat (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14, t15, t16, t17, t18, t19, t20, t21,  t22, t23, t24, t25, t26, t27, t28, t29, t30, t31, t32, t33, t34, t35, t36, t37) where
    pqFormat :: ByteString
pqFormat = [ByteString] -> ByteString
BS.concat [
        forall t. PQFormat t => ByteString
pqFormat @t1, forall t. PQFormat t => ByteString
pqFormat @t2, forall t. PQFormat t => ByteString
pqFormat @t3, forall t. PQFormat t => ByteString
pqFormat @t4
      , forall t. PQFormat t => ByteString
pqFormat @t5, forall t. PQFormat t => ByteString
pqFormat @t6, forall t. PQFormat t => ByteString
pqFormat @t7, forall t. PQFormat t => ByteString
pqFormat @t8
      , forall t. PQFormat t => ByteString
pqFormat @t9, forall t. PQFormat t => ByteString
pqFormat @t10, forall t. PQFormat t => ByteString
pqFormat @t11, forall t. PQFormat t => ByteString
pqFormat @t12
      , forall t. PQFormat t => ByteString
pqFormat @t13, forall t. PQFormat t => ByteString
pqFormat @t14, forall t. PQFormat t => ByteString
pqFormat @t15, forall t. PQFormat t => ByteString
pqFormat @t16
      , forall t. PQFormat t => ByteString
pqFormat @t17, forall t. PQFormat t => ByteString
pqFormat @t18, forall t. PQFormat t => ByteString
pqFormat @t19, forall t. PQFormat t => ByteString
pqFormat @t20
      , forall t. PQFormat t => ByteString
pqFormat @t21, forall t. PQFormat t => ByteString
pqFormat @t22, forall t. PQFormat t => ByteString
pqFormat @t23, forall t. PQFormat t => ByteString
pqFormat @t24
      , forall t. PQFormat t => ByteString
pqFormat @t25, forall t. PQFormat t => ByteString
pqFormat @t26, forall t. PQFormat t => ByteString
pqFormat @t27, forall t. PQFormat t => ByteString
pqFormat @t28
      , forall t. PQFormat t => ByteString
pqFormat @t29, forall t. PQFormat t => ByteString
pqFormat @t30, forall t. PQFormat t => ByteString
pqFormat @t31, forall t. PQFormat t => ByteString
pqFormat @t32
      , forall t. PQFormat t => ByteString
pqFormat @t33, forall t. PQFormat t => ByteString
pqFormat @t34, forall t. PQFormat t => ByteString
pqFormat @t35, forall t. PQFormat t => ByteString
pqFormat @t36
      , forall t. PQFormat t => ByteString
pqFormat @t37
      ]
    pqVariables :: Int
pqVariables = Int
37

instance (
    PQFormat t1, PQFormat t2, PQFormat t3, PQFormat t4, PQFormat t5, PQFormat t6
  , PQFormat t7, PQFormat t8, PQFormat t9, PQFormat t10, PQFormat t11, PQFormat t12
  , PQFormat t13, PQFormat t14, PQFormat t15, PQFormat t16, PQFormat t17, PQFormat t18
  , PQFormat t19, PQFormat t20, PQFormat t21, PQFormat t22, PQFormat t23, PQFormat t24
  , PQFormat t25, PQFormat t26, PQFormat t27, PQFormat t28, PQFormat t29, PQFormat t30
  , PQFormat t31, PQFormat t32, PQFormat t33, PQFormat t34, PQFormat t35, PQFormat t36
  , PQFormat t37, PQFormat t38
  ) => PQFormat (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14, t15, t16, t17, t18, t19, t20, t21,  t22, t23, t24, t25, t26, t27, t28, t29, t30, t31, t32, t33, t34, t35, t36, t37, t38) where
    pqFormat :: ByteString
pqFormat = [ByteString] -> ByteString
BS.concat [
        forall t. PQFormat t => ByteString
pqFormat @t1, forall t. PQFormat t => ByteString
pqFormat @t2, forall t. PQFormat t => ByteString
pqFormat @t3, forall t. PQFormat t => ByteString
pqFormat @t4
      , forall t. PQFormat t => ByteString
pqFormat @t5, forall t. PQFormat t => ByteString
pqFormat @t6, forall t. PQFormat t => ByteString
pqFormat @t7, forall t. PQFormat t => ByteString
pqFormat @t8
      , forall t. PQFormat t => ByteString
pqFormat @t9, forall t. PQFormat t => ByteString
pqFormat @t10, forall t. PQFormat t => ByteString
pqFormat @t11, forall t. PQFormat t => ByteString
pqFormat @t12
      , forall t. PQFormat t => ByteString
pqFormat @t13, forall t. PQFormat t => ByteString
pqFormat @t14, forall t. PQFormat t => ByteString
pqFormat @t15, forall t. PQFormat t => ByteString
pqFormat @t16
      , forall t. PQFormat t => ByteString
pqFormat @t17, forall t. PQFormat t => ByteString
pqFormat @t18, forall t. PQFormat t => ByteString
pqFormat @t19, forall t. PQFormat t => ByteString
pqFormat @t20
      , forall t. PQFormat t => ByteString
pqFormat @t21, forall t. PQFormat t => ByteString
pqFormat @t22, forall t. PQFormat t => ByteString
pqFormat @t23, forall t. PQFormat t => ByteString
pqFormat @t24
      , forall t. PQFormat t => ByteString
pqFormat @t25, forall t. PQFormat t => ByteString
pqFormat @t26, forall t. PQFormat t => ByteString
pqFormat @t27, forall t. PQFormat t => ByteString
pqFormat @t28
      , forall t. PQFormat t => ByteString
pqFormat @t29, forall t. PQFormat t => ByteString
pqFormat @t30, forall t. PQFormat t => ByteString
pqFormat @t31, forall t. PQFormat t => ByteString
pqFormat @t32
      , forall t. PQFormat t => ByteString
pqFormat @t33, forall t. PQFormat t => ByteString
pqFormat @t34, forall t. PQFormat t => ByteString
pqFormat @t35, forall t. PQFormat t => ByteString
pqFormat @t36
      , forall t. PQFormat t => ByteString
pqFormat @t37, forall t. PQFormat t => ByteString
pqFormat @t38
      ]
    pqVariables :: Int
pqVariables = Int
38

instance (
    PQFormat t1, PQFormat t2, PQFormat t3, PQFormat t4, PQFormat t5, PQFormat t6
  , PQFormat t7, PQFormat t8, PQFormat t9, PQFormat t10, PQFormat t11, PQFormat t12
  , PQFormat t13, PQFormat t14, PQFormat t15, PQFormat t16, PQFormat t17, PQFormat t18
  , PQFormat t19, PQFormat t20, PQFormat t21, PQFormat t22, PQFormat t23, PQFormat t24
  , PQFormat t25, PQFormat t26, PQFormat t27, PQFormat t28, PQFormat t29, PQFormat t30
  , PQFormat t31, PQFormat t32, PQFormat t33, PQFormat t34, PQFormat t35, PQFormat t36
  , PQFormat t37, PQFormat t38, PQFormat t39
  ) => PQFormat (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14, t15, t16, t17, t18, t19, t20, t21,  t22, t23, t24, t25, t26, t27, t28, t29, t30, t31, t32, t33, t34, t35, t36, t37, t38, t39) where
    pqFormat :: ByteString
pqFormat = [ByteString] -> ByteString
BS.concat [
        forall t. PQFormat t => ByteString
pqFormat @t1, forall t. PQFormat t => ByteString
pqFormat @t2, forall t. PQFormat t => ByteString
pqFormat @t3, forall t. PQFormat t => ByteString
pqFormat @t4
      , forall t. PQFormat t => ByteString
pqFormat @t5, forall t. PQFormat t => ByteString
pqFormat @t6, forall t. PQFormat t => ByteString
pqFormat @t7, forall t. PQFormat t => ByteString
pqFormat @t8
      , forall t. PQFormat t => ByteString
pqFormat @t9, forall t. PQFormat t => ByteString
pqFormat @t10, forall t. PQFormat t => ByteString
pqFormat @t11, forall t. PQFormat t => ByteString
pqFormat @t12
      , forall t. PQFormat t => ByteString
pqFormat @t13, forall t. PQFormat t => ByteString
pqFormat @t14, forall t. PQFormat t => ByteString
pqFormat @t15, forall t. PQFormat t => ByteString
pqFormat @t16
      , forall t. PQFormat t => ByteString
pqFormat @t17, forall t. PQFormat t => ByteString
pqFormat @t18, forall t. PQFormat t => ByteString
pqFormat @t19, forall t. PQFormat t => ByteString
pqFormat @t20
      , forall t. PQFormat t => ByteString
pqFormat @t21, forall t. PQFormat t => ByteString
pqFormat @t22, forall t. PQFormat t => ByteString
pqFormat @t23, forall t. PQFormat t => ByteString
pqFormat @t24
      , forall t. PQFormat t => ByteString
pqFormat @t25, forall t. PQFormat t => ByteString
pqFormat @t26, forall t. PQFormat t => ByteString
pqFormat @t27, forall t. PQFormat t => ByteString
pqFormat @t28
      , forall t. PQFormat t => ByteString
pqFormat @t29, forall t. PQFormat t => ByteString
pqFormat @t30, forall t. PQFormat t => ByteString
pqFormat @t31, forall t. PQFormat t => ByteString
pqFormat @t32
      , forall t. PQFormat t => ByteString
pqFormat @t33, forall t. PQFormat t => ByteString
pqFormat @t34, forall t. PQFormat t => ByteString
pqFormat @t35, forall t. PQFormat t => ByteString
pqFormat @t36
      , forall t. PQFormat t => ByteString
pqFormat @t37, forall t. PQFormat t => ByteString
pqFormat @t38, forall t. PQFormat t => ByteString
pqFormat @t39
      ]
    pqVariables :: Int
pqVariables = Int
39

instance (
    PQFormat t1, PQFormat t2, PQFormat t3, PQFormat t4, PQFormat t5, PQFormat t6
  , PQFormat t7, PQFormat t8, PQFormat t9, PQFormat t10, PQFormat t11, PQFormat t12
  , PQFormat t13, PQFormat t14, PQFormat t15, PQFormat t16, PQFormat t17, PQFormat t18
  , PQFormat t19, PQFormat t20, PQFormat t21, PQFormat t22, PQFormat t23, PQFormat t24
  , PQFormat t25, PQFormat t26, PQFormat t27, PQFormat t28, PQFormat t29, PQFormat t30
  , PQFormat t31, PQFormat t32, PQFormat t33, PQFormat t34, PQFormat t35, PQFormat t36
  , PQFormat t37, PQFormat t38, PQFormat t39, PQFormat t40
  ) => PQFormat (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14, t15, t16, t17, t18, t19, t20, t21,  t22, t23, t24, t25, t26, t27, t28, t29, t30, t31, t32, t33, t34, t35, t36, t37, t38, t39, t40) where
    pqFormat :: ByteString
pqFormat = [ByteString] -> ByteString
BS.concat [
        forall t. PQFormat t => ByteString
pqFormat @t1, forall t. PQFormat t => ByteString
pqFormat @t2, forall t. PQFormat t => ByteString
pqFormat @t3, forall t. PQFormat t => ByteString
pqFormat @t4
      , forall t. PQFormat t => ByteString
pqFormat @t5, forall t. PQFormat t => ByteString
pqFormat @t6, forall t. PQFormat t => ByteString
pqFormat @t7, forall t. PQFormat t => ByteString
pqFormat @t8
      , forall t. PQFormat t => ByteString
pqFormat @t9, forall t. PQFormat t => ByteString
pqFormat @t10, forall t. PQFormat t => ByteString
pqFormat @t11, forall t. PQFormat t => ByteString
pqFormat @t12
      , forall t. PQFormat t => ByteString
pqFormat @t13, forall t. PQFormat t => ByteString
pqFormat @t14, forall t. PQFormat t => ByteString
pqFormat @t15, forall t. PQFormat t => ByteString
pqFormat @t16
      , forall t. PQFormat t => ByteString
pqFormat @t17, forall t. PQFormat t => ByteString
pqFormat @t18, forall t. PQFormat t => ByteString
pqFormat @t19, forall t. PQFormat t => ByteString
pqFormat @t20
      , forall t. PQFormat t => ByteString
pqFormat @t21, forall t. PQFormat t => ByteString
pqFormat @t22, forall t. PQFormat t => ByteString
pqFormat @t23, forall t. PQFormat t => ByteString
pqFormat @t24
      , forall t. PQFormat t => ByteString
pqFormat @t25, forall t. PQFormat t => ByteString
pqFormat @t26, forall t. PQFormat t => ByteString
pqFormat @t27, forall t. PQFormat t => ByteString
pqFormat @t28
      , forall t. PQFormat t => ByteString
pqFormat @t29, forall t. PQFormat t => ByteString
pqFormat @t30, forall t. PQFormat t => ByteString
pqFormat @t31, forall t. PQFormat t => ByteString
pqFormat @t32
      , forall t. PQFormat t => ByteString
pqFormat @t33, forall t. PQFormat t => ByteString
pqFormat @t34, forall t. PQFormat t => ByteString
pqFormat @t35, forall t. PQFormat t => ByteString
pqFormat @t36
      , forall t. PQFormat t => ByteString
pqFormat @t37, forall t. PQFormat t => ByteString
pqFormat @t38, forall t. PQFormat t => ByteString
pqFormat @t39, forall t. PQFormat t => ByteString
pqFormat @t40
      ]
    pqVariables :: Int
pqVariables = Int
40

instance (
    PQFormat t1, PQFormat t2, PQFormat t3, PQFormat t4, PQFormat t5, PQFormat t6
  , PQFormat t7, PQFormat t8, PQFormat t9, PQFormat t10, PQFormat t11, PQFormat t12
  , PQFormat t13, PQFormat t14, PQFormat t15, PQFormat t16, PQFormat t17, PQFormat t18
  , PQFormat t19, PQFormat t20, PQFormat t21, PQFormat t22, PQFormat t23, PQFormat t24
  , PQFormat t25, PQFormat t26, PQFormat t27, PQFormat t28, PQFormat t29, PQFormat t30
  , PQFormat t31, PQFormat t32, PQFormat t33, PQFormat t34, PQFormat t35, PQFormat t36
  , PQFormat t37, PQFormat t38, PQFormat t39, PQFormat t40, PQFormat t41
  ) => PQFormat (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14, t15, t16, t17, t18, t19, t20, t21,  t22, t23, t24, t25, t26, t27, t28, t29, t30, t31, t32, t33, t34, t35, t36, t37, t38, t39, t40, t41) where
    pqFormat :: ByteString
pqFormat = [ByteString] -> ByteString
BS.concat [
        forall t. PQFormat t => ByteString
pqFormat @t1, forall t. PQFormat t => ByteString
pqFormat @t2, forall t. PQFormat t => ByteString
pqFormat @t3, forall t. PQFormat t => ByteString
pqFormat @t4
      , forall t. PQFormat t => ByteString
pqFormat @t5, forall t. PQFormat t => ByteString
pqFormat @t6, forall t. PQFormat t => ByteString
pqFormat @t7, forall t. PQFormat t => ByteString
pqFormat @t8
      , forall t. PQFormat t => ByteString
pqFormat @t9, forall t. PQFormat t => ByteString
pqFormat @t10, forall t. PQFormat t => ByteString
pqFormat @t11, forall t. PQFormat t => ByteString
pqFormat @t12
      , forall t. PQFormat t => ByteString
pqFormat @t13, forall t. PQFormat t => ByteString
pqFormat @t14, forall t. PQFormat t => ByteString
pqFormat @t15, forall t. PQFormat t => ByteString
pqFormat @t16
      , forall t. PQFormat t => ByteString
pqFormat @t17, forall t. PQFormat t => ByteString
pqFormat @t18, forall t. PQFormat t => ByteString
pqFormat @t19, forall t. PQFormat t => ByteString
pqFormat @t20
      , forall t. PQFormat t => ByteString
pqFormat @t21, forall t. PQFormat t => ByteString
pqFormat @t22, forall t. PQFormat t => ByteString
pqFormat @t23, forall t. PQFormat t => ByteString
pqFormat @t24
      , forall t. PQFormat t => ByteString
pqFormat @t25, forall t. PQFormat t => ByteString
pqFormat @t26, forall t. PQFormat t => ByteString
pqFormat @t27, forall t. PQFormat t => ByteString
pqFormat @t28
      , forall t. PQFormat t => ByteString
pqFormat @t29, forall t. PQFormat t => ByteString
pqFormat @t30, forall t. PQFormat t => ByteString
pqFormat @t31, forall t. PQFormat t => ByteString
pqFormat @t32
      , forall t. PQFormat t => ByteString
pqFormat @t33, forall t. PQFormat t => ByteString
pqFormat @t34, forall t. PQFormat t => ByteString
pqFormat @t35, forall t. PQFormat t => ByteString
pqFormat @t36
      , forall t. PQFormat t => ByteString
pqFormat @t37, forall t. PQFormat t => ByteString
pqFormat @t38, forall t. PQFormat t => ByteString
pqFormat @t39, forall t. PQFormat t => ByteString
pqFormat @t40
      , forall t. PQFormat t => ByteString
pqFormat @t41
      ]
    pqVariables :: Int
pqVariables = Int
41

instance (
    PQFormat t1, PQFormat t2, PQFormat t3, PQFormat t4, PQFormat t5, PQFormat t6
  , PQFormat t7, PQFormat t8, PQFormat t9, PQFormat t10, PQFormat t11, PQFormat t12
  , PQFormat t13, PQFormat t14, PQFormat t15, PQFormat t16, PQFormat t17, PQFormat t18
  , PQFormat t19, PQFormat t20, PQFormat t21, PQFormat t22, PQFormat t23, PQFormat t24
  , PQFormat t25, PQFormat t26, PQFormat t27, PQFormat t28, PQFormat t29, PQFormat t30
  , PQFormat t31, PQFormat t32, PQFormat t33, PQFormat t34, PQFormat t35, PQFormat t36
  , PQFormat t37, PQFormat t38, PQFormat t39, PQFormat t40, PQFormat t41, PQFormat t42
  ) => PQFormat (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14, t15, t16, t17, t18, t19, t20, t21,  t22, t23, t24, t25, t26, t27, t28, t29, t30, t31, t32, t33, t34, t35, t36, t37, t38, t39, t40, t41, t42) where
    pqFormat :: ByteString
pqFormat = [ByteString] -> ByteString
BS.concat [
        forall t. PQFormat t => ByteString
pqFormat @t1, forall t. PQFormat t => ByteString
pqFormat @t2, forall t. PQFormat t => ByteString
pqFormat @t3, forall t. PQFormat t => ByteString
pqFormat @t4
      , forall t. PQFormat t => ByteString
pqFormat @t5, forall t. PQFormat t => ByteString
pqFormat @t6, forall t. PQFormat t => ByteString
pqFormat @t7, forall t. PQFormat t => ByteString
pqFormat @t8
      , forall t. PQFormat t => ByteString
pqFormat @t9, forall t. PQFormat t => ByteString
pqFormat @t10, forall t. PQFormat t => ByteString
pqFormat @t11, forall t. PQFormat t => ByteString
pqFormat @t12
      , forall t. PQFormat t => ByteString
pqFormat @t13, forall t. PQFormat t => ByteString
pqFormat @t14, forall t. PQFormat t => ByteString
pqFormat @t15, forall t. PQFormat t => ByteString
pqFormat @t16
      , forall t. PQFormat t => ByteString
pqFormat @t17, forall t. PQFormat t => ByteString
pqFormat @t18, forall t. PQFormat t => ByteString
pqFormat @t19, forall t. PQFormat t => ByteString
pqFormat @t20
      , forall t. PQFormat t => ByteString
pqFormat @t21, forall t. PQFormat t => ByteString
pqFormat @t22, forall t. PQFormat t => ByteString
pqFormat @t23, forall t. PQFormat t => ByteString
pqFormat @t24
      , forall t. PQFormat t => ByteString
pqFormat @t25, forall t. PQFormat t => ByteString
pqFormat @t26, forall t. PQFormat t => ByteString
pqFormat @t27, forall t. PQFormat t => ByteString
pqFormat @t28
      , forall t. PQFormat t => ByteString
pqFormat @t29, forall t. PQFormat t => ByteString
pqFormat @t30, forall t. PQFormat t => ByteString
pqFormat @t31, forall t. PQFormat t => ByteString
pqFormat @t32
      , forall t. PQFormat t => ByteString
pqFormat @t33, forall t. PQFormat t => ByteString
pqFormat @t34, forall t. PQFormat t => ByteString
pqFormat @t35, forall t. PQFormat t => ByteString
pqFormat @t36
      , forall t. PQFormat t => ByteString
pqFormat @t37, forall t. PQFormat t => ByteString
pqFormat @t38, forall t. PQFormat t => ByteString
pqFormat @t39, forall t. PQFormat t => ByteString
pqFormat @t40
      , forall t. PQFormat t => ByteString
pqFormat @t41, forall t. PQFormat t => ByteString
pqFormat @t42
      ]
    pqVariables :: Int
pqVariables = Int
42

instance (
    PQFormat t1, PQFormat t2, PQFormat t3, PQFormat t4, PQFormat t5, PQFormat t6
  , PQFormat t7, PQFormat t8, PQFormat t9, PQFormat t10, PQFormat t11, PQFormat t12
  , PQFormat t13, PQFormat t14, PQFormat t15, PQFormat t16, PQFormat t17, PQFormat t18
  , PQFormat t19, PQFormat t20, PQFormat t21, PQFormat t22, PQFormat t23, PQFormat t24
  , PQFormat t25, PQFormat t26, PQFormat t27, PQFormat t28, PQFormat t29, PQFormat t30
  , PQFormat t31, PQFormat t32, PQFormat t33, PQFormat t34, PQFormat t35, PQFormat t36
  , PQFormat t37, PQFormat t38, PQFormat t39, PQFormat t40, PQFormat t41, PQFormat t42
  , PQFormat t43
  ) => PQFormat (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14, t15, t16, t17, t18, t19, t20, t21,  t22, t23, t24, t25, t26, t27, t28, t29, t30, t31, t32, t33, t34, t35, t36, t37, t38, t39, t40, t41, t42, t43) where
    pqFormat :: ByteString
pqFormat = [ByteString] -> ByteString
BS.concat [
        forall t. PQFormat t => ByteString
pqFormat @t1, forall t. PQFormat t => ByteString
pqFormat @t2, forall t. PQFormat t => ByteString
pqFormat @t3, forall t. PQFormat t => ByteString
pqFormat @t4
      , forall t. PQFormat t => ByteString
pqFormat @t5, forall t. PQFormat t => ByteString
pqFormat @t6, forall t. PQFormat t => ByteString
pqFormat @t7, forall t. PQFormat t => ByteString
pqFormat @t8
      , forall t. PQFormat t => ByteString
pqFormat @t9, forall t. PQFormat t => ByteString
pqFormat @t10, forall t. PQFormat t => ByteString
pqFormat @t11, forall t. PQFormat t => ByteString
pqFormat @t12
      , forall t. PQFormat t => ByteString
pqFormat @t13, forall t. PQFormat t => ByteString
pqFormat @t14, forall t. PQFormat t => ByteString
pqFormat @t15, forall t. PQFormat t => ByteString
pqFormat @t16
      , forall t. PQFormat t => ByteString
pqFormat @t17, forall t. PQFormat t => ByteString
pqFormat @t18, forall t. PQFormat t => ByteString
pqFormat @t19, forall t. PQFormat t => ByteString
pqFormat @t20
      , forall t. PQFormat t => ByteString
pqFormat @t21, forall t. PQFormat t => ByteString
pqFormat @t22, forall t. PQFormat t => ByteString
pqFormat @t23, forall t. PQFormat t => ByteString
pqFormat @t24
      , forall t. PQFormat t => ByteString
pqFormat @t25, forall t. PQFormat t => ByteString
pqFormat @t26, forall t. PQFormat t => ByteString
pqFormat @t27, forall t. PQFormat t => ByteString
pqFormat @t28
      , forall t. PQFormat t => ByteString
pqFormat @t29, forall t. PQFormat t => ByteString
pqFormat @t30, forall t. PQFormat t => ByteString
pqFormat @t31, forall t. PQFormat t => ByteString
pqFormat @t32
      , forall t. PQFormat t => ByteString
pqFormat @t33, forall t. PQFormat t => ByteString
pqFormat @t34, forall t. PQFormat t => ByteString
pqFormat @t35, forall t. PQFormat t => ByteString
pqFormat @t36
      , forall t. PQFormat t => ByteString
pqFormat @t37, forall t. PQFormat t => ByteString
pqFormat @t38, forall t. PQFormat t => ByteString
pqFormat @t39, forall t. PQFormat t => ByteString
pqFormat @t40
      , forall t. PQFormat t => ByteString
pqFormat @t41, forall t. PQFormat t => ByteString
pqFormat @t42, forall t. PQFormat t => ByteString
pqFormat @t43
      ]
    pqVariables :: Int
pqVariables = Int
43

instance (
    PQFormat t1, PQFormat t2, PQFormat t3, PQFormat t4, PQFormat t5, PQFormat t6
  , PQFormat t7, PQFormat t8, PQFormat t9, PQFormat t10, PQFormat t11, PQFormat t12
  , PQFormat t13, PQFormat t14, PQFormat t15, PQFormat t16, PQFormat t17, PQFormat t18
  , PQFormat t19, PQFormat t20, PQFormat t21, PQFormat t22, PQFormat t23, PQFormat t24
  , PQFormat t25, PQFormat t26, PQFormat t27, PQFormat t28, PQFormat t29, PQFormat t30
  , PQFormat t31, PQFormat t32, PQFormat t33, PQFormat t34, PQFormat t35, PQFormat t36
  , PQFormat t37, PQFormat t38, PQFormat t39, PQFormat t40, PQFormat t41, PQFormat t42
  , PQFormat t43, PQFormat t44
  ) => PQFormat (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14, t15, t16, t17, t18, t19, t20, t21,  t22, t23, t24, t25, t26, t27, t28, t29, t30, t31, t32, t33, t34, t35, t36, t37, t38, t39, t40, t41, t42, t43, t44) where
    pqFormat :: ByteString
pqFormat = [ByteString] -> ByteString
BS.concat [
        forall t. PQFormat t => ByteString
pqFormat @t1, forall t. PQFormat t => ByteString
pqFormat @t2, forall t. PQFormat t => ByteString
pqFormat @t3, forall t. PQFormat t => ByteString
pqFormat @t4
      , forall t. PQFormat t => ByteString
pqFormat @t5, forall t. PQFormat t => ByteString
pqFormat @t6, forall t. PQFormat t => ByteString
pqFormat @t7, forall t. PQFormat t => ByteString
pqFormat @t8
      , forall t. PQFormat t => ByteString
pqFormat @t9, forall t. PQFormat t => ByteString
pqFormat @t10, forall t. PQFormat t => ByteString
pqFormat @t11, forall t. PQFormat t => ByteString
pqFormat @t12
      , forall t. PQFormat t => ByteString
pqFormat @t13, forall t. PQFormat t => ByteString
pqFormat @t14, forall t. PQFormat t => ByteString
pqFormat @t15, forall t. PQFormat t => ByteString
pqFormat @t16
      , forall t. PQFormat t => ByteString
pqFormat @t17, forall t. PQFormat t => ByteString
pqFormat @t18, forall t. PQFormat t => ByteString
pqFormat @t19, forall t. PQFormat t => ByteString
pqFormat @t20
      , forall t. PQFormat t => ByteString
pqFormat @t21, forall t. PQFormat t => ByteString
pqFormat @t22, forall t. PQFormat t => ByteString
pqFormat @t23, forall t. PQFormat t => ByteString
pqFormat @t24
      , forall t. PQFormat t => ByteString
pqFormat @t25, forall t. PQFormat t => ByteString
pqFormat @t26, forall t. PQFormat t => ByteString
pqFormat @t27, forall t. PQFormat t => ByteString
pqFormat @t28
      , forall t. PQFormat t => ByteString
pqFormat @t29, forall t. PQFormat t => ByteString
pqFormat @t30, forall t. PQFormat t => ByteString
pqFormat @t31, forall t. PQFormat t => ByteString
pqFormat @t32
      , forall t. PQFormat t => ByteString
pqFormat @t33, forall t. PQFormat t => ByteString
pqFormat @t34, forall t. PQFormat t => ByteString
pqFormat @t35, forall t. PQFormat t => ByteString
pqFormat @t36
      , forall t. PQFormat t => ByteString
pqFormat @t37, forall t. PQFormat t => ByteString
pqFormat @t38, forall t. PQFormat t => ByteString
pqFormat @t39, forall t. PQFormat t => ByteString
pqFormat @t40
      , forall t. PQFormat t => ByteString
pqFormat @t41, forall t. PQFormat t => ByteString
pqFormat @t42, forall t. PQFormat t => ByteString
pqFormat @t43, forall t. PQFormat t => ByteString
pqFormat @t44
      ]
    pqVariables :: Int
pqVariables = Int
44

instance (
    PQFormat t1, PQFormat t2, PQFormat t3, PQFormat t4, PQFormat t5, PQFormat t6
  , PQFormat t7, PQFormat t8, PQFormat t9, PQFormat t10, PQFormat t11, PQFormat t12
  , PQFormat t13, PQFormat t14, PQFormat t15, PQFormat t16, PQFormat t17, PQFormat t18
  , PQFormat t19, PQFormat t20, PQFormat t21, PQFormat t22, PQFormat t23, PQFormat t24
  , PQFormat t25, PQFormat t26, PQFormat t27, PQFormat t28, PQFormat t29, PQFormat t30
  , PQFormat t31, PQFormat t32, PQFormat t33, PQFormat t34, PQFormat t35, PQFormat t36
  , PQFormat t37, PQFormat t38, PQFormat t39, PQFormat t40, PQFormat t41, PQFormat t42
  , PQFormat t43, PQFormat t44, PQFormat t45
  ) => PQFormat (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14, t15, t16, t17, t18, t19, t20, t21,  t22, t23, t24, t25, t26, t27, t28, t29, t30, t31, t32, t33, t34, t35, t36, t37, t38, t39, t40, t41, t42, t43, t44, t45) where
    pqFormat :: ByteString
pqFormat = [ByteString] -> ByteString
BS.concat [
        forall t. PQFormat t => ByteString
pqFormat @t1, forall t. PQFormat t => ByteString
pqFormat @t2, forall t. PQFormat t => ByteString
pqFormat @t3, forall t. PQFormat t => ByteString
pqFormat @t4
      , forall t. PQFormat t => ByteString
pqFormat @t5, forall t. PQFormat t => ByteString
pqFormat @t6, forall t. PQFormat t => ByteString
pqFormat @t7, forall t. PQFormat t => ByteString
pqFormat @t8
      , forall t. PQFormat t => ByteString
pqFormat @t9, forall t. PQFormat t => ByteString
pqFormat @t10, forall t. PQFormat t => ByteString
pqFormat @t11, forall t. PQFormat t => ByteString
pqFormat @t12
      , forall t. PQFormat t => ByteString
pqFormat @t13, forall t. PQFormat t => ByteString
pqFormat @t14, forall t. PQFormat t => ByteString
pqFormat @t15, forall t. PQFormat t => ByteString
pqFormat @t16
      , forall t. PQFormat t => ByteString
pqFormat @t17, forall t. PQFormat t => ByteString
pqFormat @t18, forall t. PQFormat t => ByteString
pqFormat @t19, forall t. PQFormat t => ByteString
pqFormat @t20
      , forall t. PQFormat t => ByteString
pqFormat @t21, forall t. PQFormat t => ByteString
pqFormat @t22, forall t. PQFormat t => ByteString
pqFormat @t23, forall t. PQFormat t => ByteString
pqFormat @t24
      , forall t. PQFormat t => ByteString
pqFormat @t25, forall t. PQFormat t => ByteString
pqFormat @t26, forall t. PQFormat t => ByteString
pqFormat @t27, forall t. PQFormat t => ByteString
pqFormat @t28
      , forall t. PQFormat t => ByteString
pqFormat @t29, forall t. PQFormat t => ByteString
pqFormat @t30, forall t. PQFormat t => ByteString
pqFormat @t31, forall t. PQFormat t => ByteString
pqFormat @t32
      , forall t. PQFormat t => ByteString
pqFormat @t33, forall t. PQFormat t => ByteString
pqFormat @t34, forall t. PQFormat t => ByteString
pqFormat @t35, forall t. PQFormat t => ByteString
pqFormat @t36
      , forall t. PQFormat t => ByteString
pqFormat @t37, forall t. PQFormat t => ByteString
pqFormat @t38, forall t. PQFormat t => ByteString
pqFormat @t39, forall t. PQFormat t => ByteString
pqFormat @t40
      , forall t. PQFormat t => ByteString
pqFormat @t41, forall t. PQFormat t => ByteString
pqFormat @t42, forall t. PQFormat t => ByteString
pqFormat @t43, forall t. PQFormat t => ByteString
pqFormat @t44
      , forall t. PQFormat t => ByteString
pqFormat @t45
      ]
    pqVariables :: Int
pqVariables = Int
45

instance (
    PQFormat t1, PQFormat t2, PQFormat t3, PQFormat t4, PQFormat t5, PQFormat t6
  , PQFormat t7, PQFormat t8, PQFormat t9, PQFormat t10, PQFormat t11, PQFormat t12
  , PQFormat t13, PQFormat t14, PQFormat t15, PQFormat t16, PQFormat t17, PQFormat t18
  , PQFormat t19, PQFormat t20, PQFormat t21, PQFormat t22, PQFormat t23, PQFormat t24
  , PQFormat t25, PQFormat t26, PQFormat t27, PQFormat t28, PQFormat t29, PQFormat t30
  , PQFormat t31, PQFormat t32, PQFormat t33, PQFormat t34, PQFormat t35, PQFormat t36
  , PQFormat t37, PQFormat t38, PQFormat t39, PQFormat t40, PQFormat t41, PQFormat t42
  , PQFormat t43, PQFormat t44, PQFormat t45, PQFormat t46
  ) => PQFormat (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14, t15, t16, t17, t18, t19, t20, t21,  t22, t23, t24, t25, t26, t27, t28, t29, t30, t31, t32, t33, t34, t35, t36, t37, t38, t39, t40, t41, t42, t43, t44, t45, t46) where
    pqFormat :: ByteString
pqFormat = [ByteString] -> ByteString
BS.concat [
        forall t. PQFormat t => ByteString
pqFormat @t1, forall t. PQFormat t => ByteString
pqFormat @t2, forall t. PQFormat t => ByteString
pqFormat @t3, forall t. PQFormat t => ByteString
pqFormat @t4
      , forall t. PQFormat t => ByteString
pqFormat @t5, forall t. PQFormat t => ByteString
pqFormat @t6, forall t. PQFormat t => ByteString
pqFormat @t7, forall t. PQFormat t => ByteString
pqFormat @t8
      , forall t. PQFormat t => ByteString
pqFormat @t9, forall t. PQFormat t => ByteString
pqFormat @t10, forall t. PQFormat t => ByteString
pqFormat @t11, forall t. PQFormat t => ByteString
pqFormat @t12
      , forall t. PQFormat t => ByteString
pqFormat @t13, forall t. PQFormat t => ByteString
pqFormat @t14, forall t. PQFormat t => ByteString
pqFormat @t15, forall t. PQFormat t => ByteString
pqFormat @t16
      , forall t. PQFormat t => ByteString
pqFormat @t17, forall t. PQFormat t => ByteString
pqFormat @t18, forall t. PQFormat t => ByteString
pqFormat @t19, forall t. PQFormat t => ByteString
pqFormat @t20
      , forall t. PQFormat t => ByteString
pqFormat @t21, forall t. PQFormat t => ByteString
pqFormat @t22, forall t. PQFormat t => ByteString
pqFormat @t23, forall t. PQFormat t => ByteString
pqFormat @t24
      , forall t. PQFormat t => ByteString
pqFormat @t25, forall t. PQFormat t => ByteString
pqFormat @t26, forall t. PQFormat t => ByteString
pqFormat @t27, forall t. PQFormat t => ByteString
pqFormat @t28
      , forall t. PQFormat t => ByteString
pqFormat @t29, forall t. PQFormat t => ByteString
pqFormat @t30, forall t. PQFormat t => ByteString
pqFormat @t31, forall t. PQFormat t => ByteString
pqFormat @t32
      , forall t. PQFormat t => ByteString
pqFormat @t33, forall t. PQFormat t => ByteString
pqFormat @t34, forall t. PQFormat t => ByteString
pqFormat @t35, forall t. PQFormat t => ByteString
pqFormat @t36
      , forall t. PQFormat t => ByteString
pqFormat @t37, forall t. PQFormat t => ByteString
pqFormat @t38, forall t. PQFormat t => ByteString
pqFormat @t39, forall t. PQFormat t => ByteString
pqFormat @t40
      , forall t. PQFormat t => ByteString
pqFormat @t41, forall t. PQFormat t => ByteString
pqFormat @t42, forall t. PQFormat t => ByteString
pqFormat @t43, forall t. PQFormat t => ByteString
pqFormat @t44
      , forall t. PQFormat t => ByteString
pqFormat @t45, forall t. PQFormat t => ByteString
pqFormat @t46
      ]
    pqVariables :: Int
pqVariables = Int
46

instance (
    PQFormat t1, PQFormat t2, PQFormat t3, PQFormat t4, PQFormat t5, PQFormat t6
  , PQFormat t7, PQFormat t8, PQFormat t9, PQFormat t10, PQFormat t11, PQFormat t12
  , PQFormat t13, PQFormat t14, PQFormat t15, PQFormat t16, PQFormat t17, PQFormat t18
  , PQFormat t19, PQFormat t20, PQFormat t21, PQFormat t22, PQFormat t23, PQFormat t24
  , PQFormat t25, PQFormat t26, PQFormat t27, PQFormat t28, PQFormat t29, PQFormat t30
  , PQFormat t31, PQFormat t32, PQFormat t33, PQFormat t34, PQFormat t35, PQFormat t36
  , PQFormat t37, PQFormat t38, PQFormat t39, PQFormat t40, PQFormat t41, PQFormat t42
  , PQFormat t43, PQFormat t44, PQFormat t45, PQFormat t46, PQFormat t47
  ) => PQFormat (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14, t15, t16, t17, t18, t19, t20, t21,  t22, t23, t24, t25, t26, t27, t28, t29, t30, t31, t32, t33, t34, t35, t36, t37, t38, t39, t40, t41, t42, t43, t44, t45, t46, t47) where
    pqFormat :: ByteString
pqFormat = [ByteString] -> ByteString
BS.concat [
        forall t. PQFormat t => ByteString
pqFormat @t1, forall t. PQFormat t => ByteString
pqFormat @t2, forall t. PQFormat t => ByteString
pqFormat @t3, forall t. PQFormat t => ByteString
pqFormat @t4
      , forall t. PQFormat t => ByteString
pqFormat @t5, forall t. PQFormat t => ByteString
pqFormat @t6, forall t. PQFormat t => ByteString
pqFormat @t7, forall t. PQFormat t => ByteString
pqFormat @t8
      , forall t. PQFormat t => ByteString
pqFormat @t9, forall t. PQFormat t => ByteString
pqFormat @t10, forall t. PQFormat t => ByteString
pqFormat @t11, forall t. PQFormat t => ByteString
pqFormat @t12
      , forall t. PQFormat t => ByteString
pqFormat @t13, forall t. PQFormat t => ByteString
pqFormat @t14, forall t. PQFormat t => ByteString
pqFormat @t15, forall t. PQFormat t => ByteString
pqFormat @t16
      , forall t. PQFormat t => ByteString
pqFormat @t17, forall t. PQFormat t => ByteString
pqFormat @t18, forall t. PQFormat t => ByteString
pqFormat @t19, forall t. PQFormat t => ByteString
pqFormat @t20
      , forall t. PQFormat t => ByteString
pqFormat @t21, forall t. PQFormat t => ByteString
pqFormat @t22, forall t. PQFormat t => ByteString
pqFormat @t23, forall t. PQFormat t => ByteString
pqFormat @t24
      , forall t. PQFormat t => ByteString
pqFormat @t25, forall t. PQFormat t => ByteString
pqFormat @t26, forall t. PQFormat t => ByteString
pqFormat @t27, forall t. PQFormat t => ByteString
pqFormat @t28
      , forall t. PQFormat t => ByteString
pqFormat @t29, forall t. PQFormat t => ByteString
pqFormat @t30, forall t. PQFormat t => ByteString
pqFormat @t31, forall t. PQFormat t => ByteString
pqFormat @t32
      , forall t. PQFormat t => ByteString
pqFormat @t33, forall t. PQFormat t => ByteString
pqFormat @t34, forall t. PQFormat t => ByteString
pqFormat @t35, forall t. PQFormat t => ByteString
pqFormat @t36
      , forall t. PQFormat t => ByteString
pqFormat @t37, forall t. PQFormat t => ByteString
pqFormat @t38, forall t. PQFormat t => ByteString
pqFormat @t39, forall t. PQFormat t => ByteString
pqFormat @t40
      , forall t. PQFormat t => ByteString
pqFormat @t41, forall t. PQFormat t => ByteString
pqFormat @t42, forall t. PQFormat t => ByteString
pqFormat @t43, forall t. PQFormat t => ByteString
pqFormat @t44
      , forall t. PQFormat t => ByteString
pqFormat @t45, forall t. PQFormat t => ByteString
pqFormat @t46, forall t. PQFormat t => ByteString
pqFormat @t47
      ]
    pqVariables :: Int
pqVariables = Int
47

instance (
    PQFormat t1, PQFormat t2, PQFormat t3, PQFormat t4, PQFormat t5, PQFormat t6
  , PQFormat t7, PQFormat t8, PQFormat t9, PQFormat t10, PQFormat t11, PQFormat t12
  , PQFormat t13, PQFormat t14, PQFormat t15, PQFormat t16, PQFormat t17, PQFormat t18
  , PQFormat t19, PQFormat t20, PQFormat t21, PQFormat t22, PQFormat t23, PQFormat t24
  , PQFormat t25, PQFormat t26, PQFormat t27, PQFormat t28, PQFormat t29, PQFormat t30
  , PQFormat t31, PQFormat t32, PQFormat t33, PQFormat t34, PQFormat t35, PQFormat t36
  , PQFormat t37, PQFormat t38, PQFormat t39, PQFormat t40, PQFormat t41, PQFormat t42
  , PQFormat t43, PQFormat t44, PQFormat t45, PQFormat t46, PQFormat t47, PQFormat t48
  ) => PQFormat (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14, t15, t16, t17, t18, t19, t20, t21,  t22, t23, t24, t25, t26, t27, t28, t29, t30, t31, t32, t33, t34, t35, t36, t37, t38, t39, t40, t41, t42, t43, t44, t45, t46, t47, t48) where
    pqFormat :: ByteString
pqFormat = [ByteString] -> ByteString
BS.concat [
        forall t. PQFormat t => ByteString
pqFormat @t1, forall t. PQFormat t => ByteString
pqFormat @t2, forall t. PQFormat t => ByteString
pqFormat @t3, forall t. PQFormat t => ByteString
pqFormat @t4
      , forall t. PQFormat t => ByteString
pqFormat @t5, forall t. PQFormat t => ByteString
pqFormat @t6, forall t. PQFormat t => ByteString
pqFormat @t7, forall t. PQFormat t => ByteString
pqFormat @t8
      , forall t. PQFormat t => ByteString
pqFormat @t9, forall t. PQFormat t => ByteString
pqFormat @t10, forall t. PQFormat t => ByteString
pqFormat @t11, forall t. PQFormat t => ByteString
pqFormat @t12
      , forall t. PQFormat t => ByteString
pqFormat @t13, forall t. PQFormat t => ByteString
pqFormat @t14, forall t. PQFormat t => ByteString
pqFormat @t15, forall t. PQFormat t => ByteString
pqFormat @t16
      , forall t. PQFormat t => ByteString
pqFormat @t17, forall t. PQFormat t => ByteString
pqFormat @t18, forall t. PQFormat t => ByteString
pqFormat @t19, forall t. PQFormat t => ByteString
pqFormat @t20
      , forall t. PQFormat t => ByteString
pqFormat @t21, forall t. PQFormat t => ByteString
pqFormat @t22, forall t. PQFormat t => ByteString
pqFormat @t23, forall t. PQFormat t => ByteString
pqFormat @t24
      , forall t. PQFormat t => ByteString
pqFormat @t25, forall t. PQFormat t => ByteString
pqFormat @t26, forall t. PQFormat t => ByteString
pqFormat @t27, forall t. PQFormat t => ByteString
pqFormat @t28
      , forall t. PQFormat t => ByteString
pqFormat @t29, forall t. PQFormat t => ByteString
pqFormat @t30, forall t. PQFormat t => ByteString
pqFormat @t31, forall t. PQFormat t => ByteString
pqFormat @t32
      , forall t. PQFormat t => ByteString
pqFormat @t33, forall t. PQFormat t => ByteString
pqFormat @t34, forall t. PQFormat t => ByteString
pqFormat @t35, forall t. PQFormat t => ByteString
pqFormat @t36
      , forall t. PQFormat t => ByteString
pqFormat @t37, forall t. PQFormat t => ByteString
pqFormat @t38, forall t. PQFormat t => ByteString
pqFormat @t39, forall t. PQFormat t => ByteString
pqFormat @t40
      , forall t. PQFormat t => ByteString
pqFormat @t41, forall t. PQFormat t => ByteString
pqFormat @t42, forall t. PQFormat t => ByteString
pqFormat @t43, forall t. PQFormat t => ByteString
pqFormat @t44
      , forall t. PQFormat t => ByteString
pqFormat @t45, forall t. PQFormat t => ByteString
pqFormat @t46, forall t. PQFormat t => ByteString
pqFormat @t47, forall t. PQFormat t => ByteString
pqFormat @t48
      ]
    pqVariables :: Int
pqVariables = Int
48

instance (
    PQFormat t1, PQFormat t2, PQFormat t3, PQFormat t4, PQFormat t5, PQFormat t6
  , PQFormat t7, PQFormat t8, PQFormat t9, PQFormat t10, PQFormat t11, PQFormat t12
  , PQFormat t13, PQFormat t14, PQFormat t15, PQFormat t16, PQFormat t17, PQFormat t18
  , PQFormat t19, PQFormat t20, PQFormat t21, PQFormat t22, PQFormat t23, PQFormat t24
  , PQFormat t25, PQFormat t26, PQFormat t27, PQFormat t28, PQFormat t29, PQFormat t30
  , PQFormat t31, PQFormat t32, PQFormat t33, PQFormat t34, PQFormat t35, PQFormat t36
  , PQFormat t37, PQFormat t38, PQFormat t39, PQFormat t40, PQFormat t41, PQFormat t42
  , PQFormat t43, PQFormat t44, PQFormat t45, PQFormat t46, PQFormat t47, PQFormat t48
  , PQFormat t49
  ) => PQFormat (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14, t15, t16, t17, t18, t19, t20, t21,  t22, t23, t24, t25, t26, t27, t28, t29, t30, t31, t32, t33, t34, t35, t36, t37, t38, t39, t40, t41, t42, t43, t44, t45, t46, t47, t48, t49) where
    pqFormat :: ByteString
pqFormat = [ByteString] -> ByteString
BS.concat [
        forall t. PQFormat t => ByteString
pqFormat @t1, forall t. PQFormat t => ByteString
pqFormat @t2, forall t. PQFormat t => ByteString
pqFormat @t3, forall t. PQFormat t => ByteString
pqFormat @t4
      , forall t. PQFormat t => ByteString
pqFormat @t5, forall t. PQFormat t => ByteString
pqFormat @t6, forall t. PQFormat t => ByteString
pqFormat @t7, forall t. PQFormat t => ByteString
pqFormat @t8
      , forall t. PQFormat t => ByteString
pqFormat @t9, forall t. PQFormat t => ByteString
pqFormat @t10, forall t. PQFormat t => ByteString
pqFormat @t11, forall t. PQFormat t => ByteString
pqFormat @t12
      , forall t. PQFormat t => ByteString
pqFormat @t13, forall t. PQFormat t => ByteString
pqFormat @t14, forall t. PQFormat t => ByteString
pqFormat @t15, forall t. PQFormat t => ByteString
pqFormat @t16
      , forall t. PQFormat t => ByteString
pqFormat @t17, forall t. PQFormat t => ByteString
pqFormat @t18, forall t. PQFormat t => ByteString
pqFormat @t19, forall t. PQFormat t => ByteString
pqFormat @t20
      , forall t. PQFormat t => ByteString
pqFormat @t21, forall t. PQFormat t => ByteString
pqFormat @t22, forall t. PQFormat t => ByteString
pqFormat @t23, forall t. PQFormat t => ByteString
pqFormat @t24
      , forall t. PQFormat t => ByteString
pqFormat @t25, forall t. PQFormat t => ByteString
pqFormat @t26, forall t. PQFormat t => ByteString
pqFormat @t27, forall t. PQFormat t => ByteString
pqFormat @t28
      , forall t. PQFormat t => ByteString
pqFormat @t29, forall t. PQFormat t => ByteString
pqFormat @t30, forall t. PQFormat t => ByteString
pqFormat @t31, forall t. PQFormat t => ByteString
pqFormat @t32
      , forall t. PQFormat t => ByteString
pqFormat @t33, forall t. PQFormat t => ByteString
pqFormat @t34, forall t. PQFormat t => ByteString
pqFormat @t35, forall t. PQFormat t => ByteString
pqFormat @t36
      , forall t. PQFormat t => ByteString
pqFormat @t37, forall t. PQFormat t => ByteString
pqFormat @t38, forall t. PQFormat t => ByteString
pqFormat @t39, forall t. PQFormat t => ByteString
pqFormat @t40
      , forall t. PQFormat t => ByteString
pqFormat @t41, forall t. PQFormat t => ByteString
pqFormat @t42, forall t. PQFormat t => ByteString
pqFormat @t43, forall t. PQFormat t => ByteString
pqFormat @t44
      , forall t. PQFormat t => ByteString
pqFormat @t45, forall t. PQFormat t => ByteString
pqFormat @t46, forall t. PQFormat t => ByteString
pqFormat @t47, forall t. PQFormat t => ByteString
pqFormat @t48
      , forall t. PQFormat t => ByteString
pqFormat @t49
      ]
    pqVariables :: Int
pqVariables = Int
49

instance (
    PQFormat t1, PQFormat t2, PQFormat t3, PQFormat t4, PQFormat t5, PQFormat t6
  , PQFormat t7, PQFormat t8, PQFormat t9, PQFormat t10, PQFormat t11, PQFormat t12
  , PQFormat t13, PQFormat t14, PQFormat t15, PQFormat t16, PQFormat t17, PQFormat t18
  , PQFormat t19, PQFormat t20, PQFormat t21, PQFormat t22, PQFormat t23, PQFormat t24
  , PQFormat t25, PQFormat t26, PQFormat t27, PQFormat t28, PQFormat t29, PQFormat t30
  , PQFormat t31, PQFormat t32, PQFormat t33, PQFormat t34, PQFormat t35, PQFormat t36
  , PQFormat t37, PQFormat t38, PQFormat t39, PQFormat t40, PQFormat t41, PQFormat t42
  , PQFormat t43, PQFormat t44, PQFormat t45, PQFormat t46, PQFormat t47, PQFormat t48
  , PQFormat t49, PQFormat t50
  ) => PQFormat (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14, t15, t16, t17, t18, t19, t20, t21,  t22, t23, t24, t25, t26, t27, t28, t29, t30, t31, t32, t33, t34, t35, t36, t37, t38, t39, t40, t41, t42, t43, t44, t45, t46, t47, t48, t49, t50) where
    pqFormat :: ByteString
pqFormat = [ByteString] -> ByteString
BS.concat [
        forall t. PQFormat t => ByteString
pqFormat @t1, forall t. PQFormat t => ByteString
pqFormat @t2, forall t. PQFormat t => ByteString
pqFormat @t3, forall t. PQFormat t => ByteString
pqFormat @t4
      , forall t. PQFormat t => ByteString
pqFormat @t5, forall t. PQFormat t => ByteString
pqFormat @t6, forall t. PQFormat t => ByteString
pqFormat @t7, forall t. PQFormat t => ByteString
pqFormat @t8
      , forall t. PQFormat t => ByteString
pqFormat @t9, forall t. PQFormat t => ByteString
pqFormat @t10, forall t. PQFormat t => ByteString
pqFormat @t11, forall t. PQFormat t => ByteString
pqFormat @t12
      , forall t. PQFormat t => ByteString
pqFormat @t13, forall t. PQFormat t => ByteString
pqFormat @t14, forall t. PQFormat t => ByteString
pqFormat @t15, forall t. PQFormat t => ByteString
pqFormat @t16
      , forall t. PQFormat t => ByteString
pqFormat @t17, forall t. PQFormat t => ByteString
pqFormat @t18, forall t. PQFormat t => ByteString
pqFormat @t19, forall t. PQFormat t => ByteString
pqFormat @t20
      , forall t. PQFormat t => ByteString
pqFormat @t21, forall t. PQFormat t => ByteString
pqFormat @t22, forall t. PQFormat t => ByteString
pqFormat @t23, forall t. PQFormat t => ByteString
pqFormat @t24
      , forall t. PQFormat t => ByteString
pqFormat @t25, forall t. PQFormat t => ByteString
pqFormat @t26, forall t. PQFormat t => ByteString
pqFormat @t27, forall t. PQFormat t => ByteString
pqFormat @t28
      , forall t. PQFormat t => ByteString
pqFormat @t29, forall t. PQFormat t => ByteString
pqFormat @t30, forall t. PQFormat t => ByteString
pqFormat @t31, forall t. PQFormat t => ByteString
pqFormat @t32
      , forall t. PQFormat t => ByteString
pqFormat @t33, forall t. PQFormat t => ByteString
pqFormat @t34, forall t. PQFormat t => ByteString
pqFormat @t35, forall t. PQFormat t => ByteString
pqFormat @t36
      , forall t. PQFormat t => ByteString
pqFormat @t37, forall t. PQFormat t => ByteString
pqFormat @t38, forall t. PQFormat t => ByteString
pqFormat @t39, forall t. PQFormat t => ByteString
pqFormat @t40
      , forall t. PQFormat t => ByteString
pqFormat @t41, forall t. PQFormat t => ByteString
pqFormat @t42, forall t. PQFormat t => ByteString
pqFormat @t43, forall t. PQFormat t => ByteString
pqFormat @t44
      , forall t. PQFormat t => ByteString
pqFormat @t45, forall t. PQFormat t => ByteString
pqFormat @t46, forall t. PQFormat t => ByteString
pqFormat @t47, forall t. PQFormat t => ByteString
pqFormat @t48
      , forall t. PQFormat t => ByteString
pqFormat @t49, forall t. PQFormat t => ByteString
pqFormat @t50
      ]
    pqVariables :: Int
pqVariables = Int
50