{-# LANGUAGE RecordWildCards #-}

------------------------------------------------------------------------------
-- |
-- Module:      Database.SQLite.Simple.FromRow
-- Copyright:   (c) 2011-2012 Leon P Smith
--              (c) 2012-2013 Janne Hellsten
-- License:     BSD3
-- Maintainer:  Janne Hellsten <jjhellst@gmail.com>
-- Portability: portable
--
-- The 'FromRow' typeclass, for converting a row of results
-- returned by a SQL query into a more useful Haskell representation.
--
-- Predefined instances are provided for tuples containing up to ten
-- elements.
------------------------------------------------------------------------------

module Database.SQLite.Simple.FromRow
     ( FromRow(..)
     , RowParser
     , field
     , fieldWith
     , numFieldsRemaining
     ) where

import           Control.Exception (SomeException(..))
import           Control.Monad (replicateM)
import           Control.Monad.Trans.State.Strict
import           Control.Monad.Trans.Reader
import           Control.Monad.Trans.Class

import           Database.SQLite.Simple.FromField
import           Database.SQLite.Simple.Internal
import           Database.SQLite.Simple.Ok
import           Database.SQLite.Simple.Types

-- | A collection type that can be converted from a sequence of fields.
-- Instances are provided for tuples up to 10 elements and lists of any length.
--
-- Note that instances can defined outside of sqlite-simple,  which is
-- often useful.   For example, here's an instance for a user-defined pair:
--
-- @data User = User { name :: String, fileQuota :: Int }
--
-- instance 'FromRow' User where
--     fromRow = User \<$\> 'field' \<*\> 'field'
-- @
--
-- The number of calls to 'field' must match the number of fields returned
-- in a single row of the query result.  Otherwise,  a 'ConversionFailed'
-- exception will be thrown.
--
-- Note the caveats associated with user-defined implementations of
-- 'fromRow'.

class FromRow a where
    fromRow :: RowParser a

fieldWith :: FieldParser a -> RowParser a
fieldWith :: FieldParser a -> RowParser a
fieldWith fieldP :: FieldParser a
fieldP = ReaderT RowParseRO (StateT (Int, [SQLData]) Ok) a -> RowParser a
forall a.
ReaderT RowParseRO (StateT (Int, [SQLData]) Ok) a -> RowParser a
RP (ReaderT RowParseRO (StateT (Int, [SQLData]) Ok) a -> RowParser a)
-> ReaderT RowParseRO (StateT (Int, [SQLData]) Ok) a -> RowParser a
forall a b. (a -> b) -> a -> b
$ do
    Int
ncols <- (RowParseRO -> Int)
-> ReaderT RowParseRO (StateT (Int, [SQLData]) Ok) Int
forall (m :: * -> *) r a. Monad m => (r -> a) -> ReaderT r m a
asks RowParseRO -> Int
nColumns
    (column :: Int
column, remaining :: [SQLData]
remaining) <- StateT (Int, [SQLData]) Ok (Int, [SQLData])
-> ReaderT RowParseRO (StateT (Int, [SQLData]) Ok) (Int, [SQLData])
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift StateT (Int, [SQLData]) Ok (Int, [SQLData])
forall (m :: * -> *) s. Monad m => StateT s m s
get
    StateT (Int, [SQLData]) Ok ()
-> ReaderT RowParseRO (StateT (Int, [SQLData]) Ok) ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ((Int, [SQLData]) -> StateT (Int, [SQLData]) Ok ()
forall (m :: * -> *) s. Monad m => s -> StateT s m ()
put (Int
column Int -> Int -> Int
forall a. Num a => a -> a -> a
+ 1, [SQLData] -> [SQLData]
forall a. [a] -> [a]
tail [SQLData]
remaining))
    if Int
column Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
ncols
    then
      StateT (Int, [SQLData]) Ok a
-> ReaderT RowParseRO (StateT (Int, [SQLData]) Ok) a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (Ok a -> StateT (Int, [SQLData]) Ok a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ([SomeException] -> Ok a
forall a. [SomeException] -> Ok a
Errors [ColumnOutOfBounds -> SomeException
forall e. Exception e => e -> SomeException
SomeException (Int -> ColumnOutOfBounds
ColumnOutOfBounds (Int
columnInt -> Int -> Int
forall a. Num a => a -> a -> a
+1))]))
    else do
      let r :: SQLData
r = [SQLData] -> SQLData
forall a. [a] -> a
head [SQLData]
remaining
          field :: Field
field = SQLData -> Int -> Field
Field SQLData
r Int
column
      StateT (Int, [SQLData]) Ok a
-> ReaderT RowParseRO (StateT (Int, [SQLData]) Ok) a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (Ok a -> StateT (Int, [SQLData]) Ok a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (FieldParser a
fieldP Field
field))

field :: FromField a => RowParser a
field :: RowParser a
field = FieldParser a -> RowParser a
forall a. FieldParser a -> RowParser a
fieldWith FieldParser a
forall a. FromField a => FieldParser a
fromField

numFieldsRemaining :: RowParser Int
numFieldsRemaining :: RowParser Int
numFieldsRemaining = ReaderT RowParseRO (StateT (Int, [SQLData]) Ok) Int
-> RowParser Int
forall a.
ReaderT RowParseRO (StateT (Int, [SQLData]) Ok) a -> RowParser a
RP (ReaderT RowParseRO (StateT (Int, [SQLData]) Ok) Int
 -> RowParser Int)
-> ReaderT RowParseRO (StateT (Int, [SQLData]) Ok) Int
-> RowParser Int
forall a b. (a -> b) -> a -> b
$ do
  Int
ncols <- (RowParseRO -> Int)
-> ReaderT RowParseRO (StateT (Int, [SQLData]) Ok) Int
forall (m :: * -> *) r a. Monad m => (r -> a) -> ReaderT r m a
asks RowParseRO -> Int
nColumns
  (columnIdx :: Int
columnIdx,_) <- StateT (Int, [SQLData]) Ok (Int, [SQLData])
-> ReaderT RowParseRO (StateT (Int, [SQLData]) Ok) (Int, [SQLData])
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift StateT (Int, [SQLData]) Ok (Int, [SQLData])
forall (m :: * -> *) s. Monad m => StateT s m s
get
  Int -> ReaderT RowParseRO (StateT (Int, [SQLData]) Ok) Int
forall (m :: * -> *) a. Monad m => a -> m a
return (Int -> ReaderT RowParseRO (StateT (Int, [SQLData]) Ok) Int)
-> Int -> ReaderT RowParseRO (StateT (Int, [SQLData]) Ok) Int
forall a b. (a -> b) -> a -> b
$! Int
ncols Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
columnIdx

instance (FromField a) => FromRow (Only a) where
    fromRow :: RowParser (Only a)
fromRow = a -> Only a
forall a. a -> Only a
Only (a -> Only a) -> RowParser a -> RowParser (Only a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> RowParser a
forall a. FromField a => RowParser a
field

instance (FromField a, FromField b) => FromRow (a,b) where
    fromRow :: RowParser (a, b)
fromRow = (,) (a -> b -> (a, b)) -> RowParser a -> RowParser (b -> (a, b))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> RowParser a
forall a. FromField a => RowParser a
field RowParser (b -> (a, b)) -> RowParser b -> RowParser (a, b)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> RowParser b
forall a. FromField a => RowParser a
field

instance (FromField a, FromField b, FromField c) => FromRow (a,b,c) where
    fromRow :: RowParser (a, b, c)
fromRow = (,,) (a -> b -> c -> (a, b, c))
-> RowParser a -> RowParser (b -> c -> (a, b, c))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> RowParser a
forall a. FromField a => RowParser a
field RowParser (b -> c -> (a, b, c))
-> RowParser b -> RowParser (c -> (a, b, c))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> RowParser b
forall a. FromField a => RowParser a
field RowParser (c -> (a, b, c)) -> RowParser c -> RowParser (a, b, c)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> RowParser c
forall a. FromField a => RowParser a
field

instance (FromField a, FromField b, FromField c, FromField d) =>
    FromRow (a,b,c,d) where
    fromRow :: RowParser (a, b, c, d)
fromRow = (,,,) (a -> b -> c -> d -> (a, b, c, d))
-> RowParser a -> RowParser (b -> c -> d -> (a, b, c, d))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> RowParser a
forall a. FromField a => RowParser a
field RowParser (b -> c -> d -> (a, b, c, d))
-> RowParser b -> RowParser (c -> d -> (a, b, c, d))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> RowParser b
forall a. FromField a => RowParser a
field RowParser (c -> d -> (a, b, c, d))
-> RowParser c -> RowParser (d -> (a, b, c, d))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> RowParser c
forall a. FromField a => RowParser a
field RowParser (d -> (a, b, c, d))
-> RowParser d -> RowParser (a, b, c, d)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> RowParser d
forall a. FromField a => RowParser a
field

instance (FromField a, FromField b, FromField c, FromField d, FromField e) =>
    FromRow (a,b,c,d,e) where
    fromRow :: RowParser (a, b, c, d, e)
fromRow = (,,,,) (a -> b -> c -> d -> e -> (a, b, c, d, e))
-> RowParser a -> RowParser (b -> c -> d -> e -> (a, b, c, d, e))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> RowParser a
forall a. FromField a => RowParser a
field RowParser (b -> c -> d -> e -> (a, b, c, d, e))
-> RowParser b -> RowParser (c -> d -> e -> (a, b, c, d, e))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> RowParser b
forall a. FromField a => RowParser a
field RowParser (c -> d -> e -> (a, b, c, d, e))
-> RowParser c -> RowParser (d -> e -> (a, b, c, d, e))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> RowParser c
forall a. FromField a => RowParser a
field RowParser (d -> e -> (a, b, c, d, e))
-> RowParser d -> RowParser (e -> (a, b, c, d, e))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> RowParser d
forall a. FromField a => RowParser a
field RowParser (e -> (a, b, c, d, e))
-> RowParser e -> RowParser (a, b, c, d, e)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> RowParser e
forall a. FromField a => RowParser a
field

instance (FromField a, FromField b, FromField c, FromField d, FromField e,
          FromField f) =>
    FromRow (a,b,c,d,e,f) where
    fromRow :: RowParser (a, b, c, d, e, f)
fromRow = (,,,,,) (a -> b -> c -> d -> e -> f -> (a, b, c, d, e, f))
-> RowParser a
-> RowParser (b -> c -> d -> e -> f -> (a, b, c, d, e, f))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> RowParser a
forall a. FromField a => RowParser a
field RowParser (b -> c -> d -> e -> f -> (a, b, c, d, e, f))
-> RowParser b
-> RowParser (c -> d -> e -> f -> (a, b, c, d, e, f))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> RowParser b
forall a. FromField a => RowParser a
field RowParser (c -> d -> e -> f -> (a, b, c, d, e, f))
-> RowParser c -> RowParser (d -> e -> f -> (a, b, c, d, e, f))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> RowParser c
forall a. FromField a => RowParser a
field RowParser (d -> e -> f -> (a, b, c, d, e, f))
-> RowParser d -> RowParser (e -> f -> (a, b, c, d, e, f))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> RowParser d
forall a. FromField a => RowParser a
field RowParser (e -> f -> (a, b, c, d, e, f))
-> RowParser e -> RowParser (f -> (a, b, c, d, e, f))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> RowParser e
forall a. FromField a => RowParser a
field
                      RowParser (f -> (a, b, c, d, e, f))
-> RowParser f -> RowParser (a, b, c, d, e, f)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> RowParser f
forall a. FromField a => RowParser a
field

instance (FromField a, FromField b, FromField c, FromField d, FromField e,
          FromField f, FromField g) =>
    FromRow (a,b,c,d,e,f,g) where
    fromRow :: RowParser (a, b, c, d, e, f, g)
fromRow = (,,,,,,) (a -> b -> c -> d -> e -> f -> g -> (a, b, c, d, e, f, g))
-> RowParser a
-> RowParser (b -> c -> d -> e -> f -> g -> (a, b, c, d, e, f, g))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> RowParser a
forall a. FromField a => RowParser a
field RowParser (b -> c -> d -> e -> f -> g -> (a, b, c, d, e, f, g))
-> RowParser b
-> RowParser (c -> d -> e -> f -> g -> (a, b, c, d, e, f, g))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> RowParser b
forall a. FromField a => RowParser a
field RowParser (c -> d -> e -> f -> g -> (a, b, c, d, e, f, g))
-> RowParser c
-> RowParser (d -> e -> f -> g -> (a, b, c, d, e, f, g))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> RowParser c
forall a. FromField a => RowParser a
field RowParser (d -> e -> f -> g -> (a, b, c, d, e, f, g))
-> RowParser d -> RowParser (e -> f -> g -> (a, b, c, d, e, f, g))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> RowParser d
forall a. FromField a => RowParser a
field RowParser (e -> f -> g -> (a, b, c, d, e, f, g))
-> RowParser e -> RowParser (f -> g -> (a, b, c, d, e, f, g))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> RowParser e
forall a. FromField a => RowParser a
field
                       RowParser (f -> g -> (a, b, c, d, e, f, g))
-> RowParser f -> RowParser (g -> (a, b, c, d, e, f, g))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> RowParser f
forall a. FromField a => RowParser a
field RowParser (g -> (a, b, c, d, e, f, g))
-> RowParser g -> RowParser (a, b, c, d, e, f, g)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> RowParser g
forall a. FromField a => RowParser a
field

instance (FromField a, FromField b, FromField c, FromField d, FromField e,
          FromField f, FromField g, FromField h) =>
    FromRow (a,b,c,d,e,f,g,h) where
    fromRow :: RowParser (a, b, c, d, e, f, g, h)
fromRow = (,,,,,,,) (a -> b -> c -> d -> e -> f -> g -> h -> (a, b, c, d, e, f, g, h))
-> RowParser a
-> RowParser
     (b -> c -> d -> e -> f -> g -> h -> (a, b, c, d, e, f, g, h))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> RowParser a
forall a. FromField a => RowParser a
field RowParser
  (b -> c -> d -> e -> f -> g -> h -> (a, b, c, d, e, f, g, h))
-> RowParser b
-> RowParser
     (c -> d -> e -> f -> g -> h -> (a, b, c, d, e, f, g, h))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> RowParser b
forall a. FromField a => RowParser a
field RowParser (c -> d -> e -> f -> g -> h -> (a, b, c, d, e, f, g, h))
-> RowParser c
-> RowParser (d -> e -> f -> g -> h -> (a, b, c, d, e, f, g, h))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> RowParser c
forall a. FromField a => RowParser a
field RowParser (d -> e -> f -> g -> h -> (a, b, c, d, e, f, g, h))
-> RowParser d
-> RowParser (e -> f -> g -> h -> (a, b, c, d, e, f, g, h))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> RowParser d
forall a. FromField a => RowParser a
field RowParser (e -> f -> g -> h -> (a, b, c, d, e, f, g, h))
-> RowParser e
-> RowParser (f -> g -> h -> (a, b, c, d, e, f, g, h))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> RowParser e
forall a. FromField a => RowParser a
field
                        RowParser (f -> g -> h -> (a, b, c, d, e, f, g, h))
-> RowParser f -> RowParser (g -> h -> (a, b, c, d, e, f, g, h))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> RowParser f
forall a. FromField a => RowParser a
field RowParser (g -> h -> (a, b, c, d, e, f, g, h))
-> RowParser g -> RowParser (h -> (a, b, c, d, e, f, g, h))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> RowParser g
forall a. FromField a => RowParser a
field RowParser (h -> (a, b, c, d, e, f, g, h))
-> RowParser h -> RowParser (a, b, c, d, e, f, g, h)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> RowParser h
forall a. FromField a => RowParser a
field

instance (FromField a, FromField b, FromField c, FromField d, FromField e,
          FromField f, FromField g, FromField h, FromField i) =>
    FromRow (a,b,c,d,e,f,g,h,i) where
    fromRow :: RowParser (a, b, c, d, e, f, g, h, i)
fromRow = (,,,,,,,,) (a
 -> b
 -> c
 -> d
 -> e
 -> f
 -> g
 -> h
 -> i
 -> (a, b, c, d, e, f, g, h, i))
-> RowParser a
-> RowParser
     (b
      -> c -> d -> e -> f -> g -> h -> i -> (a, b, c, d, e, f, g, h, i))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> RowParser a
forall a. FromField a => RowParser a
field RowParser
  (b
   -> c -> d -> e -> f -> g -> h -> i -> (a, b, c, d, e, f, g, h, i))
-> RowParser b
-> RowParser
     (c -> d -> e -> f -> g -> h -> i -> (a, b, c, d, e, f, g, h, i))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> RowParser b
forall a. FromField a => RowParser a
field RowParser
  (c -> d -> e -> f -> g -> h -> i -> (a, b, c, d, e, f, g, h, i))
-> RowParser c
-> RowParser
     (d -> e -> f -> g -> h -> i -> (a, b, c, d, e, f, g, h, i))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> RowParser c
forall a. FromField a => RowParser a
field RowParser
  (d -> e -> f -> g -> h -> i -> (a, b, c, d, e, f, g, h, i))
-> RowParser d
-> RowParser (e -> f -> g -> h -> i -> (a, b, c, d, e, f, g, h, i))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> RowParser d
forall a. FromField a => RowParser a
field RowParser (e -> f -> g -> h -> i -> (a, b, c, d, e, f, g, h, i))
-> RowParser e
-> RowParser (f -> g -> h -> i -> (a, b, c, d, e, f, g, h, i))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> RowParser e
forall a. FromField a => RowParser a
field
                         RowParser (f -> g -> h -> i -> (a, b, c, d, e, f, g, h, i))
-> RowParser f
-> RowParser (g -> h -> i -> (a, b, c, d, e, f, g, h, i))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> RowParser f
forall a. FromField a => RowParser a
field RowParser (g -> h -> i -> (a, b, c, d, e, f, g, h, i))
-> RowParser g -> RowParser (h -> i -> (a, b, c, d, e, f, g, h, i))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> RowParser g
forall a. FromField a => RowParser a
field RowParser (h -> i -> (a, b, c, d, e, f, g, h, i))
-> RowParser h -> RowParser (i -> (a, b, c, d, e, f, g, h, i))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> RowParser h
forall a. FromField a => RowParser a
field RowParser (i -> (a, b, c, d, e, f, g, h, i))
-> RowParser i -> RowParser (a, b, c, d, e, f, g, h, i)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> RowParser i
forall a. FromField a => RowParser a
field

instance (FromField a, FromField b, FromField c, FromField d, FromField e,
          FromField f, FromField g, FromField h, FromField i, FromField j) =>
    FromRow (a,b,c,d,e,f,g,h,i,j) where
    fromRow :: RowParser (a, b, c, d, e, f, g, h, i, j)
fromRow = (,,,,,,,,,) (a
 -> b
 -> c
 -> d
 -> e
 -> f
 -> g
 -> h
 -> i
 -> j
 -> (a, b, c, d, e, f, g, h, i, j))
-> RowParser a
-> RowParser
     (b
      -> c
      -> d
      -> e
      -> f
      -> g
      -> h
      -> i
      -> j
      -> (a, b, c, d, e, f, g, h, i, j))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> RowParser a
forall a. FromField a => RowParser a
field RowParser
  (b
   -> c
   -> d
   -> e
   -> f
   -> g
   -> h
   -> i
   -> j
   -> (a, b, c, d, e, f, g, h, i, j))
-> RowParser b
-> RowParser
     (c
      -> d
      -> e
      -> f
      -> g
      -> h
      -> i
      -> j
      -> (a, b, c, d, e, f, g, h, i, j))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> RowParser b
forall a. FromField a => RowParser a
field RowParser
  (c
   -> d
   -> e
   -> f
   -> g
   -> h
   -> i
   -> j
   -> (a, b, c, d, e, f, g, h, i, j))
-> RowParser c
-> RowParser
     (d -> e -> f -> g -> h -> i -> j -> (a, b, c, d, e, f, g, h, i, j))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> RowParser c
forall a. FromField a => RowParser a
field RowParser
  (d -> e -> f -> g -> h -> i -> j -> (a, b, c, d, e, f, g, h, i, j))
-> RowParser d
-> RowParser
     (e -> f -> g -> h -> i -> j -> (a, b, c, d, e, f, g, h, i, j))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> RowParser d
forall a. FromField a => RowParser a
field RowParser
  (e -> f -> g -> h -> i -> j -> (a, b, c, d, e, f, g, h, i, j))
-> RowParser e
-> RowParser
     (f -> g -> h -> i -> j -> (a, b, c, d, e, f, g, h, i, j))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> RowParser e
forall a. FromField a => RowParser a
field
                          RowParser (f -> g -> h -> i -> j -> (a, b, c, d, e, f, g, h, i, j))
-> RowParser f
-> RowParser (g -> h -> i -> j -> (a, b, c, d, e, f, g, h, i, j))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> RowParser f
forall a. FromField a => RowParser a
field RowParser (g -> h -> i -> j -> (a, b, c, d, e, f, g, h, i, j))
-> RowParser g
-> RowParser (h -> i -> j -> (a, b, c, d, e, f, g, h, i, j))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> RowParser g
forall a. FromField a => RowParser a
field RowParser (h -> i -> j -> (a, b, c, d, e, f, g, h, i, j))
-> RowParser h
-> RowParser (i -> j -> (a, b, c, d, e, f, g, h, i, j))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> RowParser h
forall a. FromField a => RowParser a
field RowParser (i -> j -> (a, b, c, d, e, f, g, h, i, j))
-> RowParser i -> RowParser (j -> (a, b, c, d, e, f, g, h, i, j))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> RowParser i
forall a. FromField a => RowParser a
field RowParser (j -> (a, b, c, d, e, f, g, h, i, j))
-> RowParser j -> RowParser (a, b, c, d, e, f, g, h, i, j)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> RowParser j
forall a. FromField a => RowParser a
field

instance FromField a => FromRow [a] where
    fromRow :: RowParser [a]
fromRow = do
      Int
n <- RowParser Int
numFieldsRemaining
      Int -> RowParser a -> RowParser [a]
forall (m :: * -> *) a. Applicative m => Int -> m a -> m [a]
replicateM Int
n RowParser a
forall a. FromField a => RowParser a
field

instance (FromRow a, FromRow b) => FromRow (a :. b) where
    fromRow :: RowParser (a :. b)
fromRow = a -> b -> a :. b
forall h t. h -> t -> h :. t
(:.) (a -> b -> a :. b) -> RowParser a -> RowParser (b -> a :. b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> RowParser a
forall a. FromRow a => RowParser a
fromRow RowParser (b -> a :. b) -> RowParser b -> RowParser (a :. b)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> RowParser b
forall a. FromRow a => RowParser a
fromRow