{-# LANGUAGE DefaultSignatures, FlexibleInstances, FlexibleContexts #-}
module Database.PostgreSQL.Simple.ToRow
(
ToRow(..)
) where
import Database.PostgreSQL.Simple.ToField (Action(..), ToField(..))
import Database.PostgreSQL.Simple.Types (Only(..), (:.)(..))
import GHC.Generics
class ToRow a where
toRow :: a -> [Action]
default toRow :: (Generic a, GToRow (Rep a)) => a -> [Action]
toRow = Rep a Any -> [Action]
forall (f :: * -> *) p. GToRow f => f p -> [Action]
gtoRow (Rep a Any -> [Action]) -> (a -> Rep a Any) -> a -> [Action]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Rep a Any
forall a x. Generic a => a -> Rep a x
from
instance ToRow () where
toRow :: () -> [Action]
toRow ()
_ = []
instance (ToField a) => ToRow (Only a) where
toRow :: Only a -> [Action]
toRow (Only a
v) = [a -> Action
forall a. ToField a => a -> Action
toField a
v]
instance (ToField a, ToField b) => ToRow (a,b) where
toRow :: (a, b) -> [Action]
toRow (a
a,b
b) = [a -> Action
forall a. ToField a => a -> Action
toField a
a, b -> Action
forall a. ToField a => a -> Action
toField b
b]
instance (ToField a, ToField b, ToField c) => ToRow (a,b,c) where
toRow :: (a, b, c) -> [Action]
toRow (a
a,b
b,c
c) = [a -> Action
forall a. ToField a => a -> Action
toField a
a, b -> Action
forall a. ToField a => a -> Action
toField b
b, c -> Action
forall a. ToField a => a -> Action
toField c
c]
instance (ToField a, ToField b, ToField c, ToField d) => ToRow (a,b,c,d) where
toRow :: (a, b, c, d) -> [Action]
toRow (a
a,b
b,c
c,d
d) = [a -> Action
forall a. ToField a => a -> Action
toField a
a, b -> Action
forall a. ToField a => a -> Action
toField b
b, c -> Action
forall a. ToField a => a -> Action
toField c
c, d -> Action
forall a. ToField a => a -> Action
toField d
d]
instance (ToField a, ToField b, ToField c, ToField d, ToField e)
=> ToRow (a,b,c,d,e) where
toRow :: (a, b, c, d, e) -> [Action]
toRow (a
a,b
b,c
c,d
d,e
e) =
[a -> Action
forall a. ToField a => a -> Action
toField a
a, b -> Action
forall a. ToField a => a -> Action
toField b
b, c -> Action
forall a. ToField a => a -> Action
toField c
c, d -> Action
forall a. ToField a => a -> Action
toField d
d, e -> Action
forall a. ToField a => a -> Action
toField e
e]
instance (ToField a, ToField b, ToField c, ToField d, ToField e, ToField f)
=> ToRow (a,b,c,d,e,f) where
toRow :: (a, b, c, d, e, f) -> [Action]
toRow (a
a,b
b,c
c,d
d,e
e,f
f) =
[a -> Action
forall a. ToField a => a -> Action
toField a
a, b -> Action
forall a. ToField a => a -> Action
toField b
b, c -> Action
forall a. ToField a => a -> Action
toField c
c, d -> Action
forall a. ToField a => a -> Action
toField d
d, e -> Action
forall a. ToField a => a -> Action
toField e
e, f -> Action
forall a. ToField a => a -> Action
toField f
f]
instance (ToField a, ToField b, ToField c, ToField d, ToField e, ToField f,
ToField g)
=> ToRow (a,b,c,d,e,f,g) where
toRow :: (a, b, c, d, e, f, g) -> [Action]
toRow (a
a,b
b,c
c,d
d,e
e,f
f,g
g) =
[a -> Action
forall a. ToField a => a -> Action
toField a
a, b -> Action
forall a. ToField a => a -> Action
toField b
b, c -> Action
forall a. ToField a => a -> Action
toField c
c, d -> Action
forall a. ToField a => a -> Action
toField d
d, e -> Action
forall a. ToField a => a -> Action
toField e
e, f -> Action
forall a. ToField a => a -> Action
toField f
f,
g -> Action
forall a. ToField a => a -> Action
toField g
g]
instance (ToField a, ToField b, ToField c, ToField d, ToField e, ToField f,
ToField g, ToField h)
=> ToRow (a,b,c,d,e,f,g,h) where
toRow :: (a, b, c, d, e, f, g, h) -> [Action]
toRow (a
a,b
b,c
c,d
d,e
e,f
f,g
g,h
h) =
[a -> Action
forall a. ToField a => a -> Action
toField a
a, b -> Action
forall a. ToField a => a -> Action
toField b
b, c -> Action
forall a. ToField a => a -> Action
toField c
c, d -> Action
forall a. ToField a => a -> Action
toField d
d, e -> Action
forall a. ToField a => a -> Action
toField e
e, f -> Action
forall a. ToField a => a -> Action
toField f
f,
g -> Action
forall a. ToField a => a -> Action
toField g
g, h -> Action
forall a. ToField a => a -> Action
toField h
h]
instance (ToField a, ToField b, ToField c, ToField d, ToField e, ToField f,
ToField g, ToField h, ToField i)
=> ToRow (a,b,c,d,e,f,g,h,i) where
toRow :: (a, b, c, d, e, f, g, h, i) -> [Action]
toRow (a
a,b
b,c
c,d
d,e
e,f
f,g
g,h
h,i
i) =
[a -> Action
forall a. ToField a => a -> Action
toField a
a, b -> Action
forall a. ToField a => a -> Action
toField b
b, c -> Action
forall a. ToField a => a -> Action
toField c
c, d -> Action
forall a. ToField a => a -> Action
toField d
d, e -> Action
forall a. ToField a => a -> Action
toField e
e, f -> Action
forall a. ToField a => a -> Action
toField f
f,
g -> Action
forall a. ToField a => a -> Action
toField g
g, h -> Action
forall a. ToField a => a -> Action
toField h
h, i -> Action
forall a. ToField a => a -> Action
toField i
i]
instance (ToField a, ToField b, ToField c, ToField d, ToField e, ToField f,
ToField g, ToField h, ToField i, ToField j)
=> ToRow (a,b,c,d,e,f,g,h,i,j) where
toRow :: (a, b, c, d, e, f, g, h, i, j) -> [Action]
toRow (a
a,b
b,c
c,d
d,e
e,f
f,g
g,h
h,i
i,j
j) =
[a -> Action
forall a. ToField a => a -> Action
toField a
a, b -> Action
forall a. ToField a => a -> Action
toField b
b, c -> Action
forall a. ToField a => a -> Action
toField c
c, d -> Action
forall a. ToField a => a -> Action
toField d
d, e -> Action
forall a. ToField a => a -> Action
toField e
e, f -> Action
forall a. ToField a => a -> Action
toField f
f,
g -> Action
forall a. ToField a => a -> Action
toField g
g, h -> Action
forall a. ToField a => a -> Action
toField h
h, i -> Action
forall a. ToField a => a -> Action
toField i
i, j -> Action
forall a. ToField a => a -> Action
toField j
j]
instance (ToField a, ToField b, ToField c, ToField d, ToField e, ToField f,
ToField g, ToField h, ToField i, ToField j, ToField k)
=> ToRow (a,b,c,d,e,f,g,h,i,j,k) where
toRow :: (a, b, c, d, e, f, g, h, i, j, k) -> [Action]
toRow (a
a,b
b,c
c,d
d,e
e,f
f,g
g,h
h,i
i,j
j,k
k) =
[a -> Action
forall a. ToField a => a -> Action
toField a
a, b -> Action
forall a. ToField a => a -> Action
toField b
b, c -> Action
forall a. ToField a => a -> Action
toField c
c, d -> Action
forall a. ToField a => a -> Action
toField d
d, e -> Action
forall a. ToField a => a -> Action
toField e
e, f -> Action
forall a. ToField a => a -> Action
toField f
f,
g -> Action
forall a. ToField a => a -> Action
toField g
g, h -> Action
forall a. ToField a => a -> Action
toField h
h, i -> Action
forall a. ToField a => a -> Action
toField i
i, j -> Action
forall a. ToField a => a -> Action
toField j
j, k -> Action
forall a. ToField a => a -> Action
toField k
k]
instance (ToField a, ToField b, ToField c, ToField d, ToField e, ToField f,
ToField g, ToField h, ToField i, ToField j, ToField k, ToField l)
=> ToRow (a,b,c,d,e,f,g,h,i,j,k,l) where
toRow :: (a, b, c, d, e, f, g, h, i, j, k, l) -> [Action]
toRow (a
a,b
b,c
c,d
d,e
e,f
f,g
g,h
h,i
i,j
j,k
k,l
l) =
[a -> Action
forall a. ToField a => a -> Action
toField a
a, b -> Action
forall a. ToField a => a -> Action
toField b
b, c -> Action
forall a. ToField a => a -> Action
toField c
c, d -> Action
forall a. ToField a => a -> Action
toField d
d, e -> Action
forall a. ToField a => a -> Action
toField e
e, f -> Action
forall a. ToField a => a -> Action
toField f
f,
g -> Action
forall a. ToField a => a -> Action
toField g
g, h -> Action
forall a. ToField a => a -> Action
toField h
h, i -> Action
forall a. ToField a => a -> Action
toField i
i, j -> Action
forall a. ToField a => a -> Action
toField j
j, k -> Action
forall a. ToField a => a -> Action
toField k
k, l -> Action
forall a. ToField a => a -> Action
toField l
l]
instance (ToField a, ToField b, ToField c, ToField d, ToField e, ToField f,
ToField g, ToField h, ToField i, ToField j, ToField k, ToField l,
ToField m)
=> ToRow (a,b,c,d,e,f,g,h,i,j,k,l,m) where
toRow :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> [Action]
toRow (a
a,b
b,c
c,d
d,e
e,f
f,g
g,h
h,i
i,j
j,k
k,l
l,m
m) =
[a -> Action
forall a. ToField a => a -> Action
toField a
a, b -> Action
forall a. ToField a => a -> Action
toField b
b, c -> Action
forall a. ToField a => a -> Action
toField c
c, d -> Action
forall a. ToField a => a -> Action
toField d
d, e -> Action
forall a. ToField a => a -> Action
toField e
e, f -> Action
forall a. ToField a => a -> Action
toField f
f,
g -> Action
forall a. ToField a => a -> Action
toField g
g, h -> Action
forall a. ToField a => a -> Action
toField h
h, i -> Action
forall a. ToField a => a -> Action
toField i
i, j -> Action
forall a. ToField a => a -> Action
toField j
j, k -> Action
forall a. ToField a => a -> Action
toField k
k, l -> Action
forall a. ToField a => a -> Action
toField l
l,
m -> Action
forall a. ToField a => a -> Action
toField m
m]
instance (ToField a, ToField b, ToField c, ToField d, ToField e, ToField f,
ToField g, ToField h, ToField i, ToField j, ToField k, ToField l,
ToField m, ToField n)
=> ToRow (a,b,c,d,e,f,g,h,i,j,k,l,m,n) where
toRow :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> [Action]
toRow (a
a,b
b,c
c,d
d,e
e,f
f,g
g,h
h,i
i,j
j,k
k,l
l,m
m,n
n) =
[a -> Action
forall a. ToField a => a -> Action
toField a
a, b -> Action
forall a. ToField a => a -> Action
toField b
b, c -> Action
forall a. ToField a => a -> Action
toField c
c, d -> Action
forall a. ToField a => a -> Action
toField d
d, e -> Action
forall a. ToField a => a -> Action
toField e
e, f -> Action
forall a. ToField a => a -> Action
toField f
f,
g -> Action
forall a. ToField a => a -> Action
toField g
g, h -> Action
forall a. ToField a => a -> Action
toField h
h, i -> Action
forall a. ToField a => a -> Action
toField i
i, j -> Action
forall a. ToField a => a -> Action
toField j
j, k -> Action
forall a. ToField a => a -> Action
toField k
k, l -> Action
forall a. ToField a => a -> Action
toField l
l,
m -> Action
forall a. ToField a => a -> Action
toField m
m, n -> Action
forall a. ToField a => a -> Action
toField n
n]
instance (ToField a, ToField b, ToField c, ToField d, ToField e, ToField f,
ToField g, ToField h, ToField i, ToField j, ToField k, ToField l,
ToField m, ToField n, ToField o)
=> ToRow (a,b,c,d,e,f,g,h,i,j,k,l,m,n,o) where
toRow :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> [Action]
toRow (a
a,b
b,c
c,d
d,e
e,f
f,g
g,h
h,i
i,j
j,k
k,l
l,m
m,n
n,o
o) =
[a -> Action
forall a. ToField a => a -> Action
toField a
a, b -> Action
forall a. ToField a => a -> Action
toField b
b, c -> Action
forall a. ToField a => a -> Action
toField c
c, d -> Action
forall a. ToField a => a -> Action
toField d
d, e -> Action
forall a. ToField a => a -> Action
toField e
e, f -> Action
forall a. ToField a => a -> Action
toField f
f,
g -> Action
forall a. ToField a => a -> Action
toField g
g, h -> Action
forall a. ToField a => a -> Action
toField h
h, i -> Action
forall a. ToField a => a -> Action
toField i
i, j -> Action
forall a. ToField a => a -> Action
toField j
j, k -> Action
forall a. ToField a => a -> Action
toField k
k, l -> Action
forall a. ToField a => a -> Action
toField l
l,
m -> Action
forall a. ToField a => a -> Action
toField m
m, n -> Action
forall a. ToField a => a -> Action
toField n
n, o -> Action
forall a. ToField a => a -> Action
toField o
o]
instance (ToField a, ToField b, ToField c, ToField d, ToField e, ToField f,
ToField g, ToField h, ToField i, ToField j, ToField k, ToField l,
ToField m, ToField n, ToField o, ToField p)
=> ToRow (a,b,c,d,e,f,g,h,i,j,k,l,m,n,o,p) where
toRow :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p) -> [Action]
toRow (a
a,b
b,c
c,d
d,e
e,f
f,g
g,h
h,i
i,j
j,k
k,l
l,m
m,n
n,o
o,p
p) =
[a -> Action
forall a. ToField a => a -> Action
toField a
a, b -> Action
forall a. ToField a => a -> Action
toField b
b, c -> Action
forall a. ToField a => a -> Action
toField c
c, d -> Action
forall a. ToField a => a -> Action
toField d
d, e -> Action
forall a. ToField a => a -> Action
toField e
e, f -> Action
forall a. ToField a => a -> Action
toField f
f,
g -> Action
forall a. ToField a => a -> Action
toField g
g, h -> Action
forall a. ToField a => a -> Action
toField h
h, i -> Action
forall a. ToField a => a -> Action
toField i
i, j -> Action
forall a. ToField a => a -> Action
toField j
j, k -> Action
forall a. ToField a => a -> Action
toField k
k, l -> Action
forall a. ToField a => a -> Action
toField l
l,
m -> Action
forall a. ToField a => a -> Action
toField m
m, n -> Action
forall a. ToField a => a -> Action
toField n
n, o -> Action
forall a. ToField a => a -> Action
toField o
o, p -> Action
forall a. ToField a => a -> Action
toField p
p]
instance (ToField a, ToField b, ToField c, ToField d, ToField e, ToField f,
ToField g, ToField h, ToField i, ToField j, ToField k, ToField l,
ToField m, ToField n, ToField o, ToField p, ToField q)
=> ToRow (a,b,c,d,e,f,g,h,i,j,k,l,m,n,o,p,q) where
toRow :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q) -> [Action]
toRow (a
a,b
b,c
c,d
d,e
e,f
f,g
g,h
h,i
i,j
j,k
k,l
l,m
m,n
n,o
o,p
p,q
q) =
[a -> Action
forall a. ToField a => a -> Action
toField a
a, b -> Action
forall a. ToField a => a -> Action
toField b
b, c -> Action
forall a. ToField a => a -> Action
toField c
c, d -> Action
forall a. ToField a => a -> Action
toField d
d, e -> Action
forall a. ToField a => a -> Action
toField e
e, f -> Action
forall a. ToField a => a -> Action
toField f
f,
g -> Action
forall a. ToField a => a -> Action
toField g
g, h -> Action
forall a. ToField a => a -> Action
toField h
h, i -> Action
forall a. ToField a => a -> Action
toField i
i, j -> Action
forall a. ToField a => a -> Action
toField j
j, k -> Action
forall a. ToField a => a -> Action
toField k
k, l -> Action
forall a. ToField a => a -> Action
toField l
l,
m -> Action
forall a. ToField a => a -> Action
toField m
m, n -> Action
forall a. ToField a => a -> Action
toField n
n, o -> Action
forall a. ToField a => a -> Action
toField o
o, p -> Action
forall a. ToField a => a -> Action
toField p
p, q -> Action
forall a. ToField a => a -> Action
toField q
q]
instance (ToField a, ToField b, ToField c, ToField d, ToField e, ToField f,
ToField g, ToField h, ToField i, ToField j, ToField k, ToField l,
ToField m, ToField n, ToField o, ToField p, ToField q, ToField r)
=> ToRow (a,b,c,d,e,f,g,h,i,j,k,l,m,n,o,p,q,r) where
toRow :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r) -> [Action]
toRow (a
a,b
b,c
c,d
d,e
e,f
f,g
g,h
h,i
i,j
j,k
k,l
l,m
m,n
n,o
o,p
p,q
q,r
r) =
[a -> Action
forall a. ToField a => a -> Action
toField a
a, b -> Action
forall a. ToField a => a -> Action
toField b
b, c -> Action
forall a. ToField a => a -> Action
toField c
c, d -> Action
forall a. ToField a => a -> Action
toField d
d, e -> Action
forall a. ToField a => a -> Action
toField e
e, f -> Action
forall a. ToField a => a -> Action
toField f
f,
g -> Action
forall a. ToField a => a -> Action
toField g
g, h -> Action
forall a. ToField a => a -> Action
toField h
h, i -> Action
forall a. ToField a => a -> Action
toField i
i, j -> Action
forall a. ToField a => a -> Action
toField j
j, k -> Action
forall a. ToField a => a -> Action
toField k
k, l -> Action
forall a. ToField a => a -> Action
toField l
l,
m -> Action
forall a. ToField a => a -> Action
toField m
m, n -> Action
forall a. ToField a => a -> Action
toField n
n, o -> Action
forall a. ToField a => a -> Action
toField o
o, p -> Action
forall a. ToField a => a -> Action
toField p
p, q -> Action
forall a. ToField a => a -> Action
toField q
q, r -> Action
forall a. ToField a => a -> Action
toField r
r]
instance (ToField a, ToField b, ToField c, ToField d, ToField e, ToField f,
ToField g, ToField h, ToField i, ToField j, ToField k, ToField l,
ToField m, ToField n, ToField o, ToField p, ToField q, ToField r,
ToField s)
=> ToRow (a,b,c,d,e,f,g,h,i,j,k,l,m,n,o,p,q,r,s) where
toRow :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s)
-> [Action]
toRow (a
a,b
b,c
c,d
d,e
e,f
f,g
g,h
h,i
i,j
j,k
k,l
l,m
m,n
n,o
o,p
p,q
q,r
r,s
s) =
[a -> Action
forall a. ToField a => a -> Action
toField a
a, b -> Action
forall a. ToField a => a -> Action
toField b
b, c -> Action
forall a. ToField a => a -> Action
toField c
c, d -> Action
forall a. ToField a => a -> Action
toField d
d, e -> Action
forall a. ToField a => a -> Action
toField e
e, f -> Action
forall a. ToField a => a -> Action
toField f
f,
g -> Action
forall a. ToField a => a -> Action
toField g
g, h -> Action
forall a. ToField a => a -> Action
toField h
h, i -> Action
forall a. ToField a => a -> Action
toField i
i, j -> Action
forall a. ToField a => a -> Action
toField j
j, k -> Action
forall a. ToField a => a -> Action
toField k
k, l -> Action
forall a. ToField a => a -> Action
toField l
l,
m -> Action
forall a. ToField a => a -> Action
toField m
m, n -> Action
forall a. ToField a => a -> Action
toField n
n, o -> Action
forall a. ToField a => a -> Action
toField o
o, p -> Action
forall a. ToField a => a -> Action
toField p
p, q -> Action
forall a. ToField a => a -> Action
toField q
q, r -> Action
forall a. ToField a => a -> Action
toField r
r,
s -> Action
forall a. ToField a => a -> Action
toField s
s]
instance (ToField a, ToField b, ToField c, ToField d, ToField e, ToField f,
ToField g, ToField h, ToField i, ToField j, ToField k, ToField l,
ToField m, ToField n, ToField o, ToField p, ToField q, ToField r,
ToField s, ToField t)
=> ToRow (a,b,c,d,e,f,g,h,i,j,k,l,m,n,o,p,q,r,s,t) where
toRow :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t)
-> [Action]
toRow (a
a,b
b,c
c,d
d,e
e,f
f,g
g,h
h,i
i,j
j,k
k,l
l,m
m,n
n,o
o,p
p,q
q,r
r,s
s,t
t) =
[a -> Action
forall a. ToField a => a -> Action
toField a
a, b -> Action
forall a. ToField a => a -> Action
toField b
b, c -> Action
forall a. ToField a => a -> Action
toField c
c, d -> Action
forall a. ToField a => a -> Action
toField d
d, e -> Action
forall a. ToField a => a -> Action
toField e
e, f -> Action
forall a. ToField a => a -> Action
toField f
f,
g -> Action
forall a. ToField a => a -> Action
toField g
g, h -> Action
forall a. ToField a => a -> Action
toField h
h, i -> Action
forall a. ToField a => a -> Action
toField i
i, j -> Action
forall a. ToField a => a -> Action
toField j
j, k -> Action
forall a. ToField a => a -> Action
toField k
k, l -> Action
forall a. ToField a => a -> Action
toField l
l,
m -> Action
forall a. ToField a => a -> Action
toField m
m, n -> Action
forall a. ToField a => a -> Action
toField n
n, o -> Action
forall a. ToField a => a -> Action
toField o
o, p -> Action
forall a. ToField a => a -> Action
toField p
p, q -> Action
forall a. ToField a => a -> Action
toField q
q, r -> Action
forall a. ToField a => a -> Action
toField r
r,
s -> Action
forall a. ToField a => a -> Action
toField s
s, t -> Action
forall a. ToField a => a -> Action
toField t
t]
instance (ToField a) => ToRow [a] where
toRow :: [a] -> [Action]
toRow = (a -> Action) -> [a] -> [Action]
forall a b. (a -> b) -> [a] -> [b]
map a -> Action
forall a. ToField a => a -> Action
toField
instance (ToRow a, ToRow b) => ToRow (a :. b) where
toRow :: (a :. b) -> [Action]
toRow (a
a :. b
b) = a -> [Action]
forall a. ToRow a => a -> [Action]
toRow a
a [Action] -> [Action] -> [Action]
forall a. [a] -> [a] -> [a]
++ b -> [Action]
forall a. ToRow a => a -> [Action]
toRow b
b
class GToRow f where
gtoRow :: f p -> [Action]
instance GToRow f => GToRow (M1 c i f) where
gtoRow :: M1 c i f p -> [Action]
gtoRow (M1 f p
x) = f p -> [Action]
forall (f :: * -> *) p. GToRow f => f p -> [Action]
gtoRow f p
x
instance (GToRow f, GToRow g) => GToRow (f :*: g) where
gtoRow :: (:*:) f g p -> [Action]
gtoRow (f p
f :*: g p
g) = f p -> [Action]
forall (f :: * -> *) p. GToRow f => f p -> [Action]
gtoRow f p
f [Action] -> [Action] -> [Action]
forall a. [a] -> [a] -> [a]
++ g p -> [Action]
forall (f :: * -> *) p. GToRow f => f p -> [Action]
gtoRow g p
g
instance (ToField a) => GToRow (K1 R a) where
gtoRow :: K1 R a p -> [Action]
gtoRow (K1 a
a) = [a -> Action
forall a. ToField a => a -> Action
toField a
a]
instance GToRow U1 where
gtoRow :: U1 p -> [Action]
gtoRow U1 p
_ = []