{-# LANGUAGE
    BangPatterns,
    CPP,
    DefaultSignatures,
    FlexibleContexts,
    FlexibleInstances,
    KindSignatures,
    MultiParamTypeClasses,
    OverloadedStrings,
    Rank2Types,
    ScopedTypeVariables,
    TypeOperators,
    UndecidableInstances
    #-}

#if __GLASGOW_HASKELL__ >= 800
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE PolyKinds #-}
#endif

#if !MIN_VERSION_bytestring(0,10,4)
# define MIN_VERSION_text_short(a,b,c) 0
#endif

#if !defined(MIN_VERSION_text_short)
# error **INVARIANT BROKEN** Detected invalid combination of `text-short` and `bytestring` versions. Please verify the `pre-bytestring-0.10-4` flag-logic in the .cabal file wasn't elided.
#endif

module Data.Csv.Conversion
    (
    -- * Type conversion
      Only(..)
    , FromRecord(..)
    , FromNamedRecord(..)
    , ToNamedRecord(..)
    , DefaultOrdered(..)
    , FromField(..)
    , ToRecord(..)
    , ToField(..)

    -- ** Generic type conversion
    , genericParseRecord
    , genericToRecord
    , genericParseNamedRecord
    , genericToNamedRecord
    , genericHeaderOrder

    -- *** Generic type conversion options
    , Options
    , defaultOptions
    , fieldLabelModifier

    -- *** Generic type conversion class names
    , GFromRecord
    , GToRecord
    , GFromNamedRecord
    , GToNamedRecordHeader

    -- * Parser
    , Parser
    , runParser

    -- * Accessors
    , index
    , (.!)
    , unsafeIndex
    , lookup
    , (.:)
    , namedField
    , (.=)
    , record
    , namedRecord
    , header
    ) where

import Control.Applicative (Alternative, (<|>), empty, Const(..))
import Control.Monad (MonadPlus, mplus, mzero)
import qualified Control.Monad.Fail as Fail
import Data.Attoparsec.ByteString.Char8 (double)
import qualified Data.Attoparsec.ByteString.Char8 as A8
import qualified Data.ByteString as B
import qualified Data.ByteString.Char8 as B8
import qualified Data.ByteString.Lazy as L
#if MIN_VERSION_bytestring(0,10,4)
import qualified Data.ByteString.Short as SBS
#endif
import Data.Functor.Identity
import Data.List (intercalate)
import Data.Hashable (Hashable)
import qualified Data.HashMap.Lazy as HM
import Data.Int (Int8, Int16, Int32, Int64)
import qualified Data.IntMap as IM
import qualified Data.Map as M
import Data.Scientific (Scientific)
import Data.Semigroup as Semi (Semigroup, (<>))
import qualified Data.Text as T
import qualified Data.Text.Encoding as T
import qualified Data.Text.Lazy as LT
import qualified Data.Text.Lazy.Encoding as LT
#if MIN_VERSION_text_short(0,1,0)
import qualified Data.Text.Short as T.S
#endif
import Data.Tuple.Only (Only(..))
import Data.Vector (Vector, (!))
import qualified Data.Vector as V
import qualified Data.Vector.Unboxed as U
import Data.Word (Word8, Word16, Word32, Word64)
import GHC.Float (double2Float)
import GHC.Generics
import Numeric.Natural
import Prelude hiding (lookup, takeWhile)

import Data.Csv.Conversion.Internal
import Data.Csv.Types

#if !MIN_VERSION_base(4,8,0)
import Control.Applicative (Applicative, (<$>), (<*>), (<*), (*>), pure)
import Data.Monoid (Monoid, mappend, mempty)
import Data.Traversable (traverse)
import Data.Word (Word)
#endif

------------------------------------------------------------------------
-- bytestring compatibility

toStrict   :: L.ByteString -> B.ByteString
fromStrict :: B.ByteString -> L.ByteString
#if MIN_VERSION_bytestring(0,10,0)
toStrict :: ByteString -> ByteString
toStrict   = ByteString -> ByteString
L.toStrict
fromStrict :: ByteString -> ByteString
fromStrict = ByteString -> ByteString
L.fromStrict
#else
toStrict   = B.concat . L.toChunks
fromStrict = L.fromChunks . (:[])
#endif
{-# INLINE toStrict #-}
{-# INLINE fromStrict #-}

------------------------------------------------------------------------
-- Type conversion

------------------------------------------------------------------------
-- Index-based conversion

-- | Options to customise how to generically encode\/decode your
--   datatype to\/from CSV.
--
--   @since 0.5.1.0
newtype Options = Options
  { Options -> String -> String
fieldLabelModifier :: String -> String
    -- ^ How to convert Haskell field labels to CSV fields.
    --
    --   @since 0.5.1.0
  }

instance Show Options where
  show :: Options -> String
show (Options String -> String
fld) =
    String
"Options {"
      String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
","
         [ String
"fieldLabelModifier =~ " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> String
forall a. Show a => a -> String
show String
sampleField String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" -> " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> String
forall a. Show a => a -> String
show (String -> String
fld String
sampleField)
         ]
      String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"}"
    where
      sampleField :: String
sampleField = String
"_column_A"

-- | Default conversion options.
--
--   @
--   Options
--   { 'fieldLabelModifier' = id
--   }
--   @
--
--   @since 0.5.1.0
defaultOptions :: Options
defaultOptions :: Options
defaultOptions = Options :: (String -> String) -> Options
Options
  { fieldLabelModifier :: String -> String
fieldLabelModifier = String -> String
forall a. a -> a
id
  }

-- | A type that can be converted from a single CSV record, with the
-- possibility of failure.
--
-- When writing an instance, use 'empty', 'mzero', or 'fail' to make a
-- conversion fail, e.g. if a 'Record' has the wrong number of
-- columns.
--
-- Given this example data:
--
-- > John,56
-- > Jane,55
--
-- here's an example type and instance:
--
-- > data Person = Person { name :: !Text, age :: !Int }
-- >
-- > instance FromRecord Person where
-- >     parseRecord v
-- >         | length v == 2 = Person <$>
-- >                           v .! 0 <*>
-- >                           v .! 1
-- >         | otherwise     = mzero
class FromRecord a where
    parseRecord :: Record -> Parser a

    default parseRecord :: (Generic a, GFromRecord (Rep a)) => Record -> Parser a
    parseRecord = Options -> Record -> Parser a
forall a.
(Generic a, GFromRecord (Rep a)) =>
Options -> Record -> Parser a
genericParseRecord Options
defaultOptions

-- | A configurable CSV record parser.  This function applied to
--   'defaultOptions' is used as the default for 'parseRecord' when the
--   type is an instance of 'Generic'.
--
--   @since 0.5.1.0
genericParseRecord :: (Generic a, GFromRecord (Rep a)) => Options -> Record -> Parser a
genericParseRecord :: Options -> Record -> Parser a
genericParseRecord Options
opts Record
r = Rep a Any -> a
forall a x. Generic a => Rep a x -> a
to (Rep a Any -> a) -> Parser (Rep a Any) -> Parser a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Options -> Record -> Parser (Rep a Any)
forall k (f :: k -> *) (p :: k).
GFromRecord f =>
Options -> Record -> Parser (f p)
gparseRecord Options
opts Record
r

-- | A type that can be converted to a single CSV record.
--
-- An example type and instance:
--
-- > data Person = Person { name :: !Text, age :: !Int }
-- >
-- > instance ToRecord Person where
-- >     toRecord (Person name age) = record [
-- >         toField name, toField age]
--
-- Outputs data on this form:
--
-- > John,56
-- > Jane,55
class ToRecord a where
    -- | Convert a value to a record.
    toRecord :: a -> Record

    default toRecord :: (Generic a, GToRecord (Rep a) Field) => a -> Record
    toRecord = Options -> a -> Record
forall a.
(Generic a, GToRecord (Rep a) ByteString) =>
Options -> a -> Record
genericToRecord Options
defaultOptions

-- | A configurable CSV record creator.  This function applied to
--   'defaultOptions' is used as the default for 'toRecord' when the
--   type is an instance of 'Generic'.
--
--   @since 0.5.1.0
genericToRecord :: (Generic a, GToRecord (Rep a) Field) => Options -> a -> Record
genericToRecord :: Options -> a -> Record
genericToRecord Options
opts = [ByteString] -> Record
forall a. [a] -> Vector a
V.fromList ([ByteString] -> Record) -> (a -> [ByteString]) -> a -> Record
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Options -> Rep a Any -> [ByteString]
forall k (a :: k -> *) f (p :: k).
GToRecord a f =>
Options -> a p -> [f]
gtoRecord Options
opts (Rep a Any -> [ByteString])
-> (a -> Rep a Any) -> a -> [ByteString]
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 FromField a => FromRecord (Only a) where
    parseRecord :: Record -> Parser (Only a)
parseRecord Record
v
        | Int
n Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
1    = a -> Only a
forall a. a -> Only a
Only (a -> Only a) -> Parser a -> Parser (Only a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Record -> Int -> Parser a
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
0
        | Bool
otherwise = Int -> Record -> Parser (Only a)
forall a. Int -> Record -> Parser a
lengthMismatch Int
1 Record
v
          where
            n :: Int
n = Record -> Int
forall a. Vector a -> Int
V.length Record
v

-- TODO: Check if we want all toRecord conversions to be stricter.

instance ToField a => ToRecord (Only a) where
    toRecord :: Only a -> Record
toRecord = ByteString -> Record
forall a. a -> Vector a
V.singleton (ByteString -> Record)
-> (Only a -> ByteString) -> Only a -> Record
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> ByteString
forall a. ToField a => a -> ByteString
toField (a -> ByteString) -> (Only a -> a) -> Only a -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Only a -> a
forall a. Only a -> a
fromOnly

instance (FromField a, FromField b) => FromRecord (a, b) where
    parseRecord :: Record -> Parser (a, b)
parseRecord Record
v
        | Int
n Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
2    = (,) (a -> b -> (a, b)) -> Parser a -> Parser (b -> (a, b))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Record -> Int -> Parser a
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
0
                          Parser (b -> (a, b)) -> Parser b -> Parser (a, b)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Record -> Int -> Parser b
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
1
        | Bool
otherwise = Int -> Record -> Parser (a, b)
forall a. Int -> Record -> Parser a
lengthMismatch Int
2 Record
v
          where
            n :: Int
n = Record -> Int
forall a. Vector a -> Int
V.length Record
v

instance (ToField a, ToField b) => ToRecord (a, b) where
    toRecord :: (a, b) -> Record
toRecord (a
a, b
b) = [ByteString] -> Record
forall a. [a] -> Vector a
V.fromList [a -> ByteString
forall a. ToField a => a -> ByteString
toField a
a, b -> ByteString
forall a. ToField a => a -> ByteString
toField b
b]

instance (FromField a, FromField b, FromField c) => FromRecord (a, b, c) where
    parseRecord :: Record -> Parser (a, b, c)
parseRecord Record
v
        | Int
n Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
3    = (,,) (a -> b -> c -> (a, b, c))
-> Parser a -> Parser (b -> c -> (a, b, c))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Record -> Int -> Parser a
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
0
                           Parser (b -> c -> (a, b, c)) -> Parser b -> Parser (c -> (a, b, c))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Record -> Int -> Parser b
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
1
                           Parser (c -> (a, b, c)) -> Parser c -> Parser (a, b, c)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Record -> Int -> Parser c
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
2
        | Bool
otherwise = Int -> Record -> Parser (a, b, c)
forall a. Int -> Record -> Parser a
lengthMismatch Int
3 Record
v
          where
            n :: Int
n = Record -> Int
forall a. Vector a -> Int
V.length Record
v

instance (ToField a, ToField b, ToField c) =>
         ToRecord (a, b, c) where
    toRecord :: (a, b, c) -> Record
toRecord (a
a, b
b, c
c) = [ByteString] -> Record
forall a. [a] -> Vector a
V.fromList [a -> ByteString
forall a. ToField a => a -> ByteString
toField a
a, b -> ByteString
forall a. ToField a => a -> ByteString
toField b
b, c -> ByteString
forall a. ToField a => a -> ByteString
toField c
c]

instance (FromField a, FromField b, FromField c, FromField d) =>
         FromRecord (a, b, c, d) where
    parseRecord :: Record -> Parser (a, b, c, d)
parseRecord Record
v
        | Int
n Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
4    = (,,,) (a -> b -> c -> d -> (a, b, c, d))
-> Parser a -> Parser (b -> c -> d -> (a, b, c, d))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Record -> Int -> Parser a
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
0
                            Parser (b -> c -> d -> (a, b, c, d))
-> Parser b -> Parser (c -> d -> (a, b, c, d))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Record -> Int -> Parser b
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
1
                            Parser (c -> d -> (a, b, c, d))
-> Parser c -> Parser (d -> (a, b, c, d))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Record -> Int -> Parser c
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
2
                            Parser (d -> (a, b, c, d)) -> Parser d -> Parser (a, b, c, d)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Record -> Int -> Parser d
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
3
        | Bool
otherwise = Int -> Record -> Parser (a, b, c, d)
forall a. Int -> Record -> Parser a
lengthMismatch Int
4 Record
v
          where
            n :: Int
n = Record -> Int
forall a. Vector a -> Int
V.length Record
v

instance (ToField a, ToField b, ToField c, ToField d) =>
         ToRecord (a, b, c, d) where
    toRecord :: (a, b, c, d) -> Record
toRecord (a
a, b
b, c
c, d
d) = [ByteString] -> Record
forall a. [a] -> Vector a
V.fromList [
        a -> ByteString
forall a. ToField a => a -> ByteString
toField a
a, b -> ByteString
forall a. ToField a => a -> ByteString
toField b
b, c -> ByteString
forall a. ToField a => a -> ByteString
toField c
c, d -> ByteString
forall a. ToField a => a -> ByteString
toField d
d]

instance (FromField a, FromField b, FromField c, FromField d, FromField e) =>
         FromRecord (a, b, c, d, e) where
    parseRecord :: Record -> Parser (a, b, c, d, e)
parseRecord Record
v
        | Int
n Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
5    = (,,,,) (a -> b -> c -> d -> e -> (a, b, c, d, e))
-> Parser a -> Parser (b -> c -> d -> e -> (a, b, c, d, e))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Record -> Int -> Parser a
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
0
                             Parser (b -> c -> d -> e -> (a, b, c, d, e))
-> Parser b -> Parser (c -> d -> e -> (a, b, c, d, e))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Record -> Int -> Parser b
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
1
                             Parser (c -> d -> e -> (a, b, c, d, e))
-> Parser c -> Parser (d -> e -> (a, b, c, d, e))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Record -> Int -> Parser c
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
2
                             Parser (d -> e -> (a, b, c, d, e))
-> Parser d -> Parser (e -> (a, b, c, d, e))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Record -> Int -> Parser d
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
3
                             Parser (e -> (a, b, c, d, e)) -> Parser e -> Parser (a, b, c, d, e)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Record -> Int -> Parser e
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
4
        | Bool
otherwise = Int -> Record -> Parser (a, b, c, d, e)
forall a. Int -> Record -> Parser a
lengthMismatch Int
5 Record
v
          where
            n :: Int
n = Record -> Int
forall a. Vector a -> Int
V.length Record
v

instance (ToField a, ToField b, ToField c, ToField d, ToField e) =>
         ToRecord (a, b, c, d, e) where
    toRecord :: (a, b, c, d, e) -> Record
toRecord (a
a, b
b, c
c, d
d, e
e) = [ByteString] -> Record
forall a. [a] -> Vector a
V.fromList [
        a -> ByteString
forall a. ToField a => a -> ByteString
toField a
a, b -> ByteString
forall a. ToField a => a -> ByteString
toField b
b, c -> ByteString
forall a. ToField a => a -> ByteString
toField c
c, d -> ByteString
forall a. ToField a => a -> ByteString
toField d
d, e -> ByteString
forall a. ToField a => a -> ByteString
toField e
e]

instance (FromField a, FromField b, FromField c, FromField d, FromField e,
          FromField f) =>
         FromRecord (a, b, c, d, e, f) where
    parseRecord :: Record -> Parser (a, b, c, d, e, f)
parseRecord Record
v
        | Int
n Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
6    = (,,,,,) (a -> b -> c -> d -> e -> f -> (a, b, c, d, e, f))
-> Parser a -> Parser (b -> c -> d -> e -> f -> (a, b, c, d, e, f))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Record -> Int -> Parser a
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
0
                              Parser (b -> c -> d -> e -> f -> (a, b, c, d, e, f))
-> Parser b -> Parser (c -> d -> e -> f -> (a, b, c, d, e, f))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Record -> Int -> Parser b
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
1
                              Parser (c -> d -> e -> f -> (a, b, c, d, e, f))
-> Parser c -> Parser (d -> e -> f -> (a, b, c, d, e, f))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Record -> Int -> Parser c
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
2
                              Parser (d -> e -> f -> (a, b, c, d, e, f))
-> Parser d -> Parser (e -> f -> (a, b, c, d, e, f))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Record -> Int -> Parser d
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
3
                              Parser (e -> f -> (a, b, c, d, e, f))
-> Parser e -> Parser (f -> (a, b, c, d, e, f))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Record -> Int -> Parser e
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
4
                              Parser (f -> (a, b, c, d, e, f))
-> Parser f -> Parser (a, b, c, d, e, f)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Record -> Int -> Parser f
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
5
        | Bool
otherwise = Int -> Record -> Parser (a, b, c, d, e, f)
forall a. Int -> Record -> Parser a
lengthMismatch Int
6 Record
v
          where
            n :: Int
n = Record -> Int
forall a. Vector a -> Int
V.length Record
v

instance (ToField a, ToField b, ToField c, ToField d, ToField e, ToField f) =>
         ToRecord (a, b, c, d, e, f) where
    toRecord :: (a, b, c, d, e, f) -> Record
toRecord (a
a, b
b, c
c, d
d, e
e, f
f) = [ByteString] -> Record
forall a. [a] -> Vector a
V.fromList [
        a -> ByteString
forall a. ToField a => a -> ByteString
toField a
a, b -> ByteString
forall a. ToField a => a -> ByteString
toField b
b, c -> ByteString
forall a. ToField a => a -> ByteString
toField c
c, d -> ByteString
forall a. ToField a => a -> ByteString
toField d
d, e -> ByteString
forall a. ToField a => a -> ByteString
toField e
e, f -> ByteString
forall a. ToField a => a -> ByteString
toField f
f]

instance (FromField a, FromField b, FromField c, FromField d, FromField e,
          FromField f, FromField g) =>
         FromRecord (a, b, c, d, e, f, g) where
    parseRecord :: Record -> Parser (a, b, c, d, e, f, g)
parseRecord Record
v
        | Int
n Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
7    = (,,,,,,) (a -> b -> c -> d -> e -> f -> g -> (a, b, c, d, e, f, g))
-> Parser a
-> Parser (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
<$> Record -> Int -> Parser a
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
0
                               Parser (b -> c -> d -> e -> f -> g -> (a, b, c, d, e, f, g))
-> Parser b
-> Parser (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
<*> Record -> Int -> Parser b
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
1
                               Parser (c -> d -> e -> f -> g -> (a, b, c, d, e, f, g))
-> Parser c -> Parser (d -> e -> f -> g -> (a, b, c, d, e, f, g))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Record -> Int -> Parser c
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
2
                               Parser (d -> e -> f -> g -> (a, b, c, d, e, f, g))
-> Parser d -> Parser (e -> f -> g -> (a, b, c, d, e, f, g))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Record -> Int -> Parser d
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
3
                               Parser (e -> f -> g -> (a, b, c, d, e, f, g))
-> Parser e -> Parser (f -> g -> (a, b, c, d, e, f, g))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Record -> Int -> Parser e
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
4
                               Parser (f -> g -> (a, b, c, d, e, f, g))
-> Parser f -> Parser (g -> (a, b, c, d, e, f, g))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Record -> Int -> Parser f
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
5
                               Parser (g -> (a, b, c, d, e, f, g))
-> Parser g -> Parser (a, b, c, d, e, f, g)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Record -> Int -> Parser g
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
6
        | Bool
otherwise = Int -> Record -> Parser (a, b, c, d, e, f, g)
forall a. Int -> Record -> Parser a
lengthMismatch Int
7 Record
v
          where
            n :: Int
n = Record -> Int
forall a. Vector a -> Int
V.length Record
v

instance (ToField a, ToField b, ToField c, ToField d, ToField e, ToField f,
          ToField g) =>
         ToRecord (a, b, c, d, e, f, g) where
    toRecord :: (a, b, c, d, e, f, g) -> Record
toRecord (a
a, b
b, c
c, d
d, e
e, f
f, g
g) = [ByteString] -> Record
forall a. [a] -> Vector a
V.fromList [
        a -> ByteString
forall a. ToField a => a -> ByteString
toField a
a, b -> ByteString
forall a. ToField a => a -> ByteString
toField b
b, c -> ByteString
forall a. ToField a => a -> ByteString
toField c
c, d -> ByteString
forall a. ToField a => a -> ByteString
toField d
d, e -> ByteString
forall a. ToField a => a -> ByteString
toField e
e, f -> ByteString
forall a. ToField a => a -> ByteString
toField f
f,
        g -> ByteString
forall a. ToField a => a -> ByteString
toField g
g]

instance (FromField a, FromField b, FromField c, FromField d, FromField e,
          FromField f, FromField g, FromField h) =>
         FromRecord (a, b, c, d, e, f, g, h) where
    parseRecord :: Record -> Parser (a, b, c, d, e, f, g, h)
parseRecord Record
v
        | Int
n Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
8    = (,,,,,,,) (a -> b -> c -> d -> e -> f -> g -> h -> (a, b, c, d, e, f, g, h))
-> Parser a
-> Parser
     (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
<$> Record -> Int -> Parser a
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
0
                                Parser
  (b -> c -> d -> e -> f -> g -> h -> (a, b, c, d, e, f, g, h))
-> Parser b
-> Parser (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
<*> Record -> Int -> Parser b
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
1
                                Parser (c -> d -> e -> f -> g -> h -> (a, b, c, d, e, f, g, h))
-> Parser c
-> Parser (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
<*> Record -> Int -> Parser c
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
2
                                Parser (d -> e -> f -> g -> h -> (a, b, c, d, e, f, g, h))
-> Parser d
-> Parser (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
<*> Record -> Int -> Parser d
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
3
                                Parser (e -> f -> g -> h -> (a, b, c, d, e, f, g, h))
-> Parser e -> Parser (f -> g -> h -> (a, b, c, d, e, f, g, h))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Record -> Int -> Parser e
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
4
                                Parser (f -> g -> h -> (a, b, c, d, e, f, g, h))
-> Parser f -> Parser (g -> h -> (a, b, c, d, e, f, g, h))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Record -> Int -> Parser f
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
5
                                Parser (g -> h -> (a, b, c, d, e, f, g, h))
-> Parser g -> Parser (h -> (a, b, c, d, e, f, g, h))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Record -> Int -> Parser g
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
6
                                Parser (h -> (a, b, c, d, e, f, g, h))
-> Parser h -> Parser (a, b, c, d, e, f, g, h)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Record -> Int -> Parser h
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
7
        | Bool
otherwise = Int -> Record -> Parser (a, b, c, d, e, f, g, h)
forall a. Int -> Record -> Parser a
lengthMismatch Int
8 Record
v
          where
            n :: Int
n = Record -> Int
forall a. Vector a -> Int
V.length Record
v

instance (ToField a, ToField b, ToField c, ToField d, ToField e, ToField f,
          ToField g, ToField h) =>
         ToRecord (a, b, c, d, e, f, g, h) where
    toRecord :: (a, b, c, d, e, f, g, h) -> Record
toRecord (a
a, b
b, c
c, d
d, e
e, f
f, g
g, h
h) = [ByteString] -> Record
forall a. [a] -> Vector a
V.fromList [
        a -> ByteString
forall a. ToField a => a -> ByteString
toField a
a, b -> ByteString
forall a. ToField a => a -> ByteString
toField b
b, c -> ByteString
forall a. ToField a => a -> ByteString
toField c
c, d -> ByteString
forall a. ToField a => a -> ByteString
toField d
d, e -> ByteString
forall a. ToField a => a -> ByteString
toField e
e, f -> ByteString
forall a. ToField a => a -> ByteString
toField f
f,
        g -> ByteString
forall a. ToField a => a -> ByteString
toField g
g, h -> ByteString
forall a. ToField a => a -> ByteString
toField h
h]

instance (FromField a, FromField b, FromField c, FromField d, FromField e,
          FromField f, FromField g, FromField h, FromField i) =>
         FromRecord (a, b, c, d, e, f, g, h, i) where
    parseRecord :: Record -> Parser (a, b, c, d, e, f, g, h, i)
parseRecord Record
v
        | Int
n Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
9    = (,,,,,,,,) (a
 -> b
 -> c
 -> d
 -> e
 -> f
 -> g
 -> h
 -> i
 -> (a, b, c, d, e, f, g, h, i))
-> Parser a
-> Parser
     (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
<$> Record -> Int -> Parser a
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
0
                                 Parser
  (b
   -> c -> d -> e -> f -> g -> h -> i -> (a, b, c, d, e, f, g, h, i))
-> Parser b
-> Parser
     (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
<*> Record -> Int -> Parser b
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
1
                                 Parser
  (c -> d -> e -> f -> g -> h -> i -> (a, b, c, d, e, f, g, h, i))
-> Parser c
-> Parser
     (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
<*> Record -> Int -> Parser c
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
2
                                 Parser (d -> e -> f -> g -> h -> i -> (a, b, c, d, e, f, g, h, i))
-> Parser d
-> Parser (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
<*> Record -> Int -> Parser d
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
3
                                 Parser (e -> f -> g -> h -> i -> (a, b, c, d, e, f, g, h, i))
-> Parser e
-> Parser (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
<*> Record -> Int -> Parser e
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
4
                                 Parser (f -> g -> h -> i -> (a, b, c, d, e, f, g, h, i))
-> Parser f -> Parser (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
<*> Record -> Int -> Parser f
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
5
                                 Parser (g -> h -> i -> (a, b, c, d, e, f, g, h, i))
-> Parser g -> Parser (h -> i -> (a, b, c, d, e, f, g, h, i))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Record -> Int -> Parser g
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
6
                                 Parser (h -> i -> (a, b, c, d, e, f, g, h, i))
-> Parser h -> Parser (i -> (a, b, c, d, e, f, g, h, i))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Record -> Int -> Parser h
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
7
                                 Parser (i -> (a, b, c, d, e, f, g, h, i))
-> Parser i -> Parser (a, b, c, d, e, f, g, h, i)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Record -> Int -> Parser i
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
8
        | Bool
otherwise = Int -> Record -> Parser (a, b, c, d, e, f, g, h, i)
forall a. Int -> Record -> Parser a
lengthMismatch Int
9 Record
v
          where
            n :: Int
n = Record -> Int
forall a. Vector a -> Int
V.length Record
v

instance (ToField a, ToField b, ToField c, ToField d, ToField e, ToField f,
          ToField g, ToField h, ToField i) =>
         ToRecord (a, b, c, d, e, f, g, h, i) where
    toRecord :: (a, b, c, d, e, f, g, h, i) -> Record
toRecord (a
a, b
b, c
c, d
d, e
e, f
f, g
g, h
h, i
i) = [ByteString] -> Record
forall a. [a] -> Vector a
V.fromList [
        a -> ByteString
forall a. ToField a => a -> ByteString
toField a
a, b -> ByteString
forall a. ToField a => a -> ByteString
toField b
b, c -> ByteString
forall a. ToField a => a -> ByteString
toField c
c, d -> ByteString
forall a. ToField a => a -> ByteString
toField d
d, e -> ByteString
forall a. ToField a => a -> ByteString
toField e
e, f -> ByteString
forall a. ToField a => a -> ByteString
toField f
f,
        g -> ByteString
forall a. ToField a => a -> ByteString
toField g
g, h -> ByteString
forall a. ToField a => a -> ByteString
toField h
h, i -> ByteString
forall a. ToField a => a -> ByteString
toField i
i]

instance (FromField a, FromField b, FromField c, FromField d, FromField e,
          FromField f, FromField g, FromField h, FromField i, FromField j) =>
         FromRecord (a, b, c, d, e, f, g, h, i, j) where
    parseRecord :: Record -> Parser (a, b, c, d, e, f, g, h, i, j)
parseRecord Record
v
        | Int
n Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
10    = (,,,,,,,,,) (a
 -> b
 -> c
 -> d
 -> e
 -> f
 -> g
 -> h
 -> i
 -> j
 -> (a, b, c, d, e, f, g, h, i, j))
-> Parser a
-> Parser
     (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
<$> Record -> Int -> Parser a
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
0
                                   Parser
  (b
   -> c
   -> d
   -> e
   -> f
   -> g
   -> h
   -> i
   -> j
   -> (a, b, c, d, e, f, g, h, i, j))
-> Parser b
-> Parser
     (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
<*> Record -> Int -> Parser b
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
1
                                   Parser
  (c
   -> d
   -> e
   -> f
   -> g
   -> h
   -> i
   -> j
   -> (a, b, c, d, e, f, g, h, i, j))
-> Parser c
-> Parser
     (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
<*> Record -> Int -> Parser c
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
2
                                   Parser
  (d -> e -> f -> g -> h -> i -> j -> (a, b, c, d, e, f, g, h, i, j))
-> Parser d
-> Parser
     (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
<*> Record -> Int -> Parser d
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
3
                                   Parser
  (e -> f -> g -> h -> i -> j -> (a, b, c, d, e, f, g, h, i, j))
-> Parser e
-> Parser (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
<*> Record -> Int -> Parser e
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
4
                                   Parser (f -> g -> h -> i -> j -> (a, b, c, d, e, f, g, h, i, j))
-> Parser f
-> Parser (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
<*> Record -> Int -> Parser f
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
5
                                   Parser (g -> h -> i -> j -> (a, b, c, d, e, f, g, h, i, j))
-> Parser g
-> Parser (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
<*> Record -> Int -> Parser g
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
6
                                   Parser (h -> i -> j -> (a, b, c, d, e, f, g, h, i, j))
-> Parser h -> Parser (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
<*> Record -> Int -> Parser h
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
7
                                   Parser (i -> j -> (a, b, c, d, e, f, g, h, i, j))
-> Parser i -> Parser (j -> (a, b, c, d, e, f, g, h, i, j))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Record -> Int -> Parser i
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
8
                                   Parser (j -> (a, b, c, d, e, f, g, h, i, j))
-> Parser j -> Parser (a, b, c, d, e, f, g, h, i, j)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Record -> Int -> Parser j
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
9
        | Bool
otherwise = Int -> Record -> Parser (a, b, c, d, e, f, g, h, i, j)
forall a. Int -> Record -> Parser a
lengthMismatch Int
10 Record
v
          where
            n :: Int
n = Record -> Int
forall a. Vector a -> Int
V.length Record
v

instance (ToField a, ToField b, ToField c, ToField d, ToField e, ToField f,
          ToField g, ToField h, ToField i, ToField j) =>
         ToRecord (a, b, c, d, e, f, g, h, i, j) where
    toRecord :: (a, b, c, d, e, f, g, h, i, j) -> Record
toRecord (a
a, b
b, c
c, d
d, e
e, f
f, g
g, h
h, i
i, j
j) = [ByteString] -> Record
forall a. [a] -> Vector a
V.fromList [
        a -> ByteString
forall a. ToField a => a -> ByteString
toField a
a, b -> ByteString
forall a. ToField a => a -> ByteString
toField b
b, c -> ByteString
forall a. ToField a => a -> ByteString
toField c
c, d -> ByteString
forall a. ToField a => a -> ByteString
toField d
d, e -> ByteString
forall a. ToField a => a -> ByteString
toField e
e, f -> ByteString
forall a. ToField a => a -> ByteString
toField f
f,
        g -> ByteString
forall a. ToField a => a -> ByteString
toField g
g, h -> ByteString
forall a. ToField a => a -> ByteString
toField h
h, i -> ByteString
forall a. ToField a => a -> ByteString
toField i
i, j -> ByteString
forall a. ToField a => a -> ByteString
toField j
j]

instance (FromField a, FromField b, FromField c, FromField d, FromField e,
          FromField f, FromField g, FromField h, FromField i, FromField j,
          FromField k) =>
         FromRecord (a, b, c, d, e, f, g, h, i, j, k) where
    parseRecord :: Record -> Parser (a, b, c, d, e, f, g, h, i, j, k)
parseRecord Record
v
        | Int
n Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
11    = (,,,,,,,,,,) (a
 -> b
 -> c
 -> d
 -> e
 -> f
 -> g
 -> h
 -> i
 -> j
 -> k
 -> (a, b, c, d, e, f, g, h, i, j, k))
-> Parser a
-> Parser
     (b
      -> c
      -> d
      -> e
      -> f
      -> g
      -> h
      -> i
      -> j
      -> k
      -> (a, b, c, d, e, f, g, h, i, j, k))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Record -> Int -> Parser a
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
0
                                    Parser
  (b
   -> c
   -> d
   -> e
   -> f
   -> g
   -> h
   -> i
   -> j
   -> k
   -> (a, b, c, d, e, f, g, h, i, j, k))
-> Parser b
-> Parser
     (c
      -> d
      -> e
      -> f
      -> g
      -> h
      -> i
      -> j
      -> k
      -> (a, b, c, d, e, f, g, h, i, j, k))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Record -> Int -> Parser b
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
1
                                    Parser
  (c
   -> d
   -> e
   -> f
   -> g
   -> h
   -> i
   -> j
   -> k
   -> (a, b, c, d, e, f, g, h, i, j, k))
-> Parser c
-> Parser
     (d
      -> e
      -> f
      -> g
      -> h
      -> i
      -> j
      -> k
      -> (a, b, c, d, e, f, g, h, i, j, k))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Record -> Int -> Parser c
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
2
                                    Parser
  (d
   -> e
   -> f
   -> g
   -> h
   -> i
   -> j
   -> k
   -> (a, b, c, d, e, f, g, h, i, j, k))
-> Parser d
-> Parser
     (e
      -> f -> g -> h -> i -> j -> k -> (a, b, c, d, e, f, g, h, i, j, k))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Record -> Int -> Parser d
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
3
                                    Parser
  (e
   -> f -> g -> h -> i -> j -> k -> (a, b, c, d, e, f, g, h, i, j, k))
-> Parser e
-> Parser
     (f -> g -> h -> i -> j -> k -> (a, b, c, d, e, f, g, h, i, j, k))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Record -> Int -> Parser e
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
4
                                    Parser
  (f -> g -> h -> i -> j -> k -> (a, b, c, d, e, f, g, h, i, j, k))
-> Parser f
-> Parser
     (g -> h -> i -> j -> k -> (a, b, c, d, e, f, g, h, i, j, k))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Record -> Int -> Parser f
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
5
                                    Parser (g -> h -> i -> j -> k -> (a, b, c, d, e, f, g, h, i, j, k))
-> Parser g
-> Parser (h -> i -> j -> k -> (a, b, c, d, e, f, g, h, i, j, k))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Record -> Int -> Parser g
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
6
                                    Parser (h -> i -> j -> k -> (a, b, c, d, e, f, g, h, i, j, k))
-> Parser h
-> Parser (i -> j -> k -> (a, b, c, d, e, f, g, h, i, j, k))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Record -> Int -> Parser h
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
7
                                    Parser (i -> j -> k -> (a, b, c, d, e, f, g, h, i, j, k))
-> Parser i -> Parser (j -> k -> (a, b, c, d, e, f, g, h, i, j, k))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Record -> Int -> Parser i
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
8
                                    Parser (j -> k -> (a, b, c, d, e, f, g, h, i, j, k))
-> Parser j -> Parser (k -> (a, b, c, d, e, f, g, h, i, j, k))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Record -> Int -> Parser j
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
9
                                    Parser (k -> (a, b, c, d, e, f, g, h, i, j, k))
-> Parser k -> Parser (a, b, c, d, e, f, g, h, i, j, k)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Record -> Int -> Parser k
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
10
        | Bool
otherwise = Int -> Record -> Parser (a, b, c, d, e, f, g, h, i, j, k)
forall a. Int -> Record -> Parser a
lengthMismatch Int
11 Record
v
          where
            n :: Int
n = Record -> Int
forall a. Vector a -> Int
V.length Record
v

instance (ToField a, ToField b, ToField c, ToField d, ToField e, ToField f,
          ToField g, ToField h, ToField i, ToField j, ToField k) =>
         ToRecord (a, b, c, d, e, f, g, h, i, j, k) where
    toRecord :: (a, b, c, d, e, f, g, h, i, j, k) -> Record
toRecord (a
a, b
b, c
c, d
d, e
e, f
f, g
g, h
h, i
i, j
j, k
k) = [ByteString] -> Record
forall a. [a] -> Vector a
V.fromList [
        a -> ByteString
forall a. ToField a => a -> ByteString
toField a
a, b -> ByteString
forall a. ToField a => a -> ByteString
toField b
b, c -> ByteString
forall a. ToField a => a -> ByteString
toField c
c, d -> ByteString
forall a. ToField a => a -> ByteString
toField d
d, e -> ByteString
forall a. ToField a => a -> ByteString
toField e
e, f -> ByteString
forall a. ToField a => a -> ByteString
toField f
f,
        g -> ByteString
forall a. ToField a => a -> ByteString
toField g
g, h -> ByteString
forall a. ToField a => a -> ByteString
toField h
h, i -> ByteString
forall a. ToField a => a -> ByteString
toField i
i, j -> ByteString
forall a. ToField a => a -> ByteString
toField j
j, k -> ByteString
forall a. ToField a => a -> ByteString
toField k
k]

instance (FromField a, FromField b, FromField c, FromField d, FromField e,
          FromField f, FromField g, FromField h, FromField i, FromField j,
          FromField k, FromField l) =>
         FromRecord (a, b, c, d, e, f, g, h, i, j, k, l) where
    parseRecord :: Record -> Parser (a, b, c, d, e, f, g, h, i, j, k, l)
parseRecord Record
v
        | Int
n Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
12    = (,,,,,,,,,,,) (a
 -> b
 -> c
 -> d
 -> e
 -> f
 -> g
 -> h
 -> i
 -> j
 -> k
 -> l
 -> (a, b, c, d, e, f, g, h, i, j, k, l))
-> Parser a
-> Parser
     (b
      -> c
      -> d
      -> e
      -> f
      -> g
      -> h
      -> i
      -> j
      -> k
      -> l
      -> (a, b, c, d, e, f, g, h, i, j, k, l))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Record -> Int -> Parser a
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
0
                                     Parser
  (b
   -> c
   -> d
   -> e
   -> f
   -> g
   -> h
   -> i
   -> j
   -> k
   -> l
   -> (a, b, c, d, e, f, g, h, i, j, k, l))
-> Parser b
-> Parser
     (c
      -> d
      -> e
      -> f
      -> g
      -> h
      -> i
      -> j
      -> k
      -> l
      -> (a, b, c, d, e, f, g, h, i, j, k, l))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Record -> Int -> Parser b
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
1
                                     Parser
  (c
   -> d
   -> e
   -> f
   -> g
   -> h
   -> i
   -> j
   -> k
   -> l
   -> (a, b, c, d, e, f, g, h, i, j, k, l))
-> Parser c
-> Parser
     (d
      -> e
      -> f
      -> g
      -> h
      -> i
      -> j
      -> k
      -> l
      -> (a, b, c, d, e, f, g, h, i, j, k, l))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Record -> Int -> Parser c
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
2
                                     Parser
  (d
   -> e
   -> f
   -> g
   -> h
   -> i
   -> j
   -> k
   -> l
   -> (a, b, c, d, e, f, g, h, i, j, k, l))
-> Parser d
-> Parser
     (e
      -> f
      -> g
      -> h
      -> i
      -> j
      -> k
      -> l
      -> (a, b, c, d, e, f, g, h, i, j, k, l))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Record -> Int -> Parser d
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
3
                                     Parser
  (e
   -> f
   -> g
   -> h
   -> i
   -> j
   -> k
   -> l
   -> (a, b, c, d, e, f, g, h, i, j, k, l))
-> Parser e
-> Parser
     (f
      -> g
      -> h
      -> i
      -> j
      -> k
      -> l
      -> (a, b, c, d, e, f, g, h, i, j, k, l))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Record -> Int -> Parser e
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
4
                                     Parser
  (f
   -> g
   -> h
   -> i
   -> j
   -> k
   -> l
   -> (a, b, c, d, e, f, g, h, i, j, k, l))
-> Parser f
-> Parser
     (g
      -> h -> i -> j -> k -> l -> (a, b, c, d, e, f, g, h, i, j, k, l))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Record -> Int -> Parser f
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
5
                                     Parser
  (g
   -> h -> i -> j -> k -> l -> (a, b, c, d, e, f, g, h, i, j, k, l))
-> Parser g
-> Parser
     (h -> i -> j -> k -> l -> (a, b, c, d, e, f, g, h, i, j, k, l))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Record -> Int -> Parser g
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
6
                                     Parser
  (h -> i -> j -> k -> l -> (a, b, c, d, e, f, g, h, i, j, k, l))
-> Parser h
-> Parser
     (i -> j -> k -> l -> (a, b, c, d, e, f, g, h, i, j, k, l))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Record -> Int -> Parser h
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
7
                                     Parser (i -> j -> k -> l -> (a, b, c, d, e, f, g, h, i, j, k, l))
-> Parser i
-> Parser (j -> k -> l -> (a, b, c, d, e, f, g, h, i, j, k, l))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Record -> Int -> Parser i
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
8
                                     Parser (j -> k -> l -> (a, b, c, d, e, f, g, h, i, j, k, l))
-> Parser j
-> Parser (k -> l -> (a, b, c, d, e, f, g, h, i, j, k, l))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Record -> Int -> Parser j
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
9
                                     Parser (k -> l -> (a, b, c, d, e, f, g, h, i, j, k, l))
-> Parser k -> Parser (l -> (a, b, c, d, e, f, g, h, i, j, k, l))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Record -> Int -> Parser k
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
10
                                     Parser (l -> (a, b, c, d, e, f, g, h, i, j, k, l))
-> Parser l -> Parser (a, b, c, d, e, f, g, h, i, j, k, l)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Record -> Int -> Parser l
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
11
        | Bool
otherwise = Int -> Record -> Parser (a, b, c, d, e, f, g, h, i, j, k, l)
forall a. Int -> Record -> Parser a
lengthMismatch Int
12 Record
v
          where
            n :: Int
n = Record -> Int
forall a. Vector a -> Int
V.length Record
v

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) =>
         ToRecord (a, b, c, d, e, f, g, h, i, j, k, l) where
    toRecord :: (a, b, c, d, e, f, g, h, i, j, k, l) -> Record
toRecord (a
a, b
b, c
c, d
d, e
e, f
f, g
g, h
h, i
i, j
j, k
k, l
l) = [ByteString] -> Record
forall a. [a] -> Vector a
V.fromList [
        a -> ByteString
forall a. ToField a => a -> ByteString
toField a
a, b -> ByteString
forall a. ToField a => a -> ByteString
toField b
b, c -> ByteString
forall a. ToField a => a -> ByteString
toField c
c, d -> ByteString
forall a. ToField a => a -> ByteString
toField d
d, e -> ByteString
forall a. ToField a => a -> ByteString
toField e
e, f -> ByteString
forall a. ToField a => a -> ByteString
toField f
f,
        g -> ByteString
forall a. ToField a => a -> ByteString
toField g
g, h -> ByteString
forall a. ToField a => a -> ByteString
toField h
h, i -> ByteString
forall a. ToField a => a -> ByteString
toField i
i, j -> ByteString
forall a. ToField a => a -> ByteString
toField j
j, k -> ByteString
forall a. ToField a => a -> ByteString
toField k
k, l -> ByteString
forall a. ToField a => a -> ByteString
toField l
l]

instance (FromField a, FromField b, FromField c, FromField d, FromField e,
          FromField f, FromField g, FromField h, FromField i, FromField j,
          FromField k, FromField l, FromField m) =>
         FromRecord (a, b, c, d, e, f, g, h, i, j, k, l, m) where
    parseRecord :: Record -> Parser (a, b, c, d, e, f, g, h, i, j, k, l, m)
parseRecord Record
v
        | Int
n Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
13    = (,,,,,,,,,,,,) (a
 -> b
 -> c
 -> d
 -> e
 -> f
 -> g
 -> h
 -> i
 -> j
 -> k
 -> l
 -> m
 -> (a, b, c, d, e, f, g, h, i, j, k, l, m))
-> Parser a
-> Parser
     (b
      -> c
      -> d
      -> e
      -> f
      -> g
      -> h
      -> i
      -> j
      -> k
      -> l
      -> m
      -> (a, b, c, d, e, f, g, h, i, j, k, l, m))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Record -> Int -> Parser a
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
0
                                      Parser
  (b
   -> c
   -> d
   -> e
   -> f
   -> g
   -> h
   -> i
   -> j
   -> k
   -> l
   -> m
   -> (a, b, c, d, e, f, g, h, i, j, k, l, m))
-> Parser b
-> Parser
     (c
      -> d
      -> e
      -> f
      -> g
      -> h
      -> i
      -> j
      -> k
      -> l
      -> m
      -> (a, b, c, d, e, f, g, h, i, j, k, l, m))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Record -> Int -> Parser b
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
1
                                      Parser
  (c
   -> d
   -> e
   -> f
   -> g
   -> h
   -> i
   -> j
   -> k
   -> l
   -> m
   -> (a, b, c, d, e, f, g, h, i, j, k, l, m))
-> Parser c
-> Parser
     (d
      -> e
      -> f
      -> g
      -> h
      -> i
      -> j
      -> k
      -> l
      -> m
      -> (a, b, c, d, e, f, g, h, i, j, k, l, m))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Record -> Int -> Parser c
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
2
                                      Parser
  (d
   -> e
   -> f
   -> g
   -> h
   -> i
   -> j
   -> k
   -> l
   -> m
   -> (a, b, c, d, e, f, g, h, i, j, k, l, m))
-> Parser d
-> Parser
     (e
      -> f
      -> g
      -> h
      -> i
      -> j
      -> k
      -> l
      -> m
      -> (a, b, c, d, e, f, g, h, i, j, k, l, m))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Record -> Int -> Parser d
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
3
                                      Parser
  (e
   -> f
   -> g
   -> h
   -> i
   -> j
   -> k
   -> l
   -> m
   -> (a, b, c, d, e, f, g, h, i, j, k, l, m))
-> Parser e
-> Parser
     (f
      -> g
      -> h
      -> i
      -> j
      -> k
      -> l
      -> m
      -> (a, b, c, d, e, f, g, h, i, j, k, l, m))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Record -> Int -> Parser e
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
4
                                      Parser
  (f
   -> g
   -> h
   -> i
   -> j
   -> k
   -> l
   -> m
   -> (a, b, c, d, e, f, g, h, i, j, k, l, m))
-> Parser f
-> Parser
     (g
      -> h
      -> i
      -> j
      -> k
      -> l
      -> m
      -> (a, b, c, d, e, f, g, h, i, j, k, l, m))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Record -> Int -> Parser f
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
5
                                      Parser
  (g
   -> h
   -> i
   -> j
   -> k
   -> l
   -> m
   -> (a, b, c, d, e, f, g, h, i, j, k, l, m))
-> Parser g
-> Parser
     (h
      -> i
      -> j
      -> k
      -> l
      -> m
      -> (a, b, c, d, e, f, g, h, i, j, k, l, m))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Record -> Int -> Parser g
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
6
                                      Parser
  (h
   -> i
   -> j
   -> k
   -> l
   -> m
   -> (a, b, c, d, e, f, g, h, i, j, k, l, m))
-> Parser h
-> Parser
     (i -> j -> k -> l -> m -> (a, b, c, d, e, f, g, h, i, j, k, l, m))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Record -> Int -> Parser h
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
7
                                      Parser
  (i -> j -> k -> l -> m -> (a, b, c, d, e, f, g, h, i, j, k, l, m))
-> Parser i
-> Parser
     (j -> k -> l -> m -> (a, b, c, d, e, f, g, h, i, j, k, l, m))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Record -> Int -> Parser i
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
8
                                      Parser
  (j -> k -> l -> m -> (a, b, c, d, e, f, g, h, i, j, k, l, m))
-> Parser j
-> Parser (k -> l -> m -> (a, b, c, d, e, f, g, h, i, j, k, l, m))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Record -> Int -> Parser j
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
9
                                      Parser (k -> l -> m -> (a, b, c, d, e, f, g, h, i, j, k, l, m))
-> Parser k
-> Parser (l -> m -> (a, b, c, d, e, f, g, h, i, j, k, l, m))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Record -> Int -> Parser k
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
10
                                      Parser (l -> m -> (a, b, c, d, e, f, g, h, i, j, k, l, m))
-> Parser l
-> Parser (m -> (a, b, c, d, e, f, g, h, i, j, k, l, m))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Record -> Int -> Parser l
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
11
                                      Parser (m -> (a, b, c, d, e, f, g, h, i, j, k, l, m))
-> Parser m -> Parser (a, b, c, d, e, f, g, h, i, j, k, l, m)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Record -> Int -> Parser m
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
12
        | Bool
otherwise = Int -> Record -> Parser (a, b, c, d, e, f, g, h, i, j, k, l, m)
forall a. Int -> Record -> Parser a
lengthMismatch Int
13 Record
v
          where
            n :: Int
n = Record -> Int
forall a. Vector a -> Int
V.length Record
v

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) =>
         ToRecord (a, b, c, d, e, f, g, h, i, j, k, l, m) where
    toRecord :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Record
toRecord (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) = [ByteString] -> Record
forall a. [a] -> Vector a
V.fromList [
        a -> ByteString
forall a. ToField a => a -> ByteString
toField a
a, b -> ByteString
forall a. ToField a => a -> ByteString
toField b
b, c -> ByteString
forall a. ToField a => a -> ByteString
toField c
c, d -> ByteString
forall a. ToField a => a -> ByteString
toField d
d, e -> ByteString
forall a. ToField a => a -> ByteString
toField e
e, f -> ByteString
forall a. ToField a => a -> ByteString
toField f
f,
        g -> ByteString
forall a. ToField a => a -> ByteString
toField g
g, h -> ByteString
forall a. ToField a => a -> ByteString
toField h
h, i -> ByteString
forall a. ToField a => a -> ByteString
toField i
i, j -> ByteString
forall a. ToField a => a -> ByteString
toField j
j, k -> ByteString
forall a. ToField a => a -> ByteString
toField k
k, l -> ByteString
forall a. ToField a => a -> ByteString
toField l
l,
        m -> ByteString
forall a. ToField a => a -> ByteString
toField m
m]

instance (FromField a, FromField b, FromField c, FromField d, FromField e,
          FromField f, FromField g, FromField h, FromField i, FromField j,
          FromField k, FromField l, FromField m, FromField n) =>
         FromRecord (a, b, c, d, e, f, g, h, i, j, k, l, m, n) where
    parseRecord :: Record -> Parser (a, b, c, d, e, f, g, h, i, j, k, l, m, n)
parseRecord Record
v
        | Int
n Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
14    = (,,,,,,,,,,,,,) (a
 -> b
 -> c
 -> d
 -> e
 -> f
 -> g
 -> h
 -> i
 -> j
 -> k
 -> l
 -> m
 -> n
 -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n))
-> Parser a
-> Parser
     (b
      -> c
      -> d
      -> e
      -> f
      -> g
      -> h
      -> i
      -> j
      -> k
      -> l
      -> m
      -> n
      -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Record -> Int -> Parser a
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
0
                                       Parser
  (b
   -> c
   -> d
   -> e
   -> f
   -> g
   -> h
   -> i
   -> j
   -> k
   -> l
   -> m
   -> n
   -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n))
-> Parser b
-> Parser
     (c
      -> d
      -> e
      -> f
      -> g
      -> h
      -> i
      -> j
      -> k
      -> l
      -> m
      -> n
      -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Record -> Int -> Parser b
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
1
                                       Parser
  (c
   -> d
   -> e
   -> f
   -> g
   -> h
   -> i
   -> j
   -> k
   -> l
   -> m
   -> n
   -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n))
-> Parser c
-> Parser
     (d
      -> e
      -> f
      -> g
      -> h
      -> i
      -> j
      -> k
      -> l
      -> m
      -> n
      -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Record -> Int -> Parser c
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
2
                                       Parser
  (d
   -> e
   -> f
   -> g
   -> h
   -> i
   -> j
   -> k
   -> l
   -> m
   -> n
   -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n))
-> Parser d
-> Parser
     (e
      -> f
      -> g
      -> h
      -> i
      -> j
      -> k
      -> l
      -> m
      -> n
      -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Record -> Int -> Parser d
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
3
                                       Parser
  (e
   -> f
   -> g
   -> h
   -> i
   -> j
   -> k
   -> l
   -> m
   -> n
   -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n))
-> Parser e
-> Parser
     (f
      -> g
      -> h
      -> i
      -> j
      -> k
      -> l
      -> m
      -> n
      -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Record -> Int -> Parser e
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
4
                                       Parser
  (f
   -> g
   -> h
   -> i
   -> j
   -> k
   -> l
   -> m
   -> n
   -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n))
-> Parser f
-> Parser
     (g
      -> h
      -> i
      -> j
      -> k
      -> l
      -> m
      -> n
      -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Record -> Int -> Parser f
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
5
                                       Parser
  (g
   -> h
   -> i
   -> j
   -> k
   -> l
   -> m
   -> n
   -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n))
-> Parser g
-> Parser
     (h
      -> i
      -> j
      -> k
      -> l
      -> m
      -> n
      -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Record -> Int -> Parser g
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
6
                                       Parser
  (h
   -> i
   -> j
   -> k
   -> l
   -> m
   -> n
   -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n))
-> Parser h
-> Parser
     (i
      -> j
      -> k
      -> l
      -> m
      -> n
      -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Record -> Int -> Parser h
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
7
                                       Parser
  (i
   -> j
   -> k
   -> l
   -> m
   -> n
   -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n))
-> Parser i
-> Parser
     (j
      -> k -> l -> m -> n -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Record -> Int -> Parser i
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
8
                                       Parser
  (j
   -> k -> l -> m -> n -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n))
-> Parser j
-> Parser
     (k -> l -> m -> n -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Record -> Int -> Parser j
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
9
                                       Parser
  (k -> l -> m -> n -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n))
-> Parser k
-> Parser
     (l -> m -> n -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Record -> Int -> Parser k
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
10
                                       Parser (l -> m -> n -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n))
-> Parser l
-> Parser (m -> n -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Record -> Int -> Parser l
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
11
                                       Parser (m -> n -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n))
-> Parser m
-> Parser (n -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Record -> Int -> Parser m
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
12
                                       Parser (n -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n))
-> Parser n -> Parser (a, b, c, d, e, f, g, h, i, j, k, l, m, n)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Record -> Int -> Parser n
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
13
        | Bool
otherwise = Int -> Record -> Parser (a, b, c, d, e, f, g, h, i, j, k, l, m, n)
forall a. Int -> Record -> Parser a
lengthMismatch Int
14 Record
v
          where
            n :: Int
n = Record -> Int
forall a. Vector a -> Int
V.length Record
v

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) =>
         ToRecord (a, b, c, d, e, f, g, h, i, j, k, l, m, n) where
    toRecord :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Record
toRecord (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) = [ByteString] -> Record
forall a. [a] -> Vector a
V.fromList [
        a -> ByteString
forall a. ToField a => a -> ByteString
toField a
a, b -> ByteString
forall a. ToField a => a -> ByteString
toField b
b, c -> ByteString
forall a. ToField a => a -> ByteString
toField c
c, d -> ByteString
forall a. ToField a => a -> ByteString
toField d
d, e -> ByteString
forall a. ToField a => a -> ByteString
toField e
e, f -> ByteString
forall a. ToField a => a -> ByteString
toField f
f,
        g -> ByteString
forall a. ToField a => a -> ByteString
toField g
g, h -> ByteString
forall a. ToField a => a -> ByteString
toField h
h, i -> ByteString
forall a. ToField a => a -> ByteString
toField i
i, j -> ByteString
forall a. ToField a => a -> ByteString
toField j
j, k -> ByteString
forall a. ToField a => a -> ByteString
toField k
k, l -> ByteString
forall a. ToField a => a -> ByteString
toField l
l,
        m -> ByteString
forall a. ToField a => a -> ByteString
toField m
m, n -> ByteString
forall a. ToField a => a -> ByteString
toField n
n]

instance (FromField a, FromField b, FromField c, FromField d, FromField e,
          FromField f, FromField g, FromField h, FromField i, FromField j,
          FromField k, FromField l, FromField m, FromField n, FromField o) =>
         FromRecord (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) where
    parseRecord :: Record -> Parser (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)
parseRecord Record
v
        | Int
n Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
15    = (,,,,,,,,,,,,,,) (a
 -> b
 -> c
 -> d
 -> e
 -> f
 -> g
 -> h
 -> i
 -> j
 -> k
 -> l
 -> m
 -> n
 -> o
 -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o))
-> Parser a
-> Parser
     (b
      -> c
      -> d
      -> e
      -> f
      -> g
      -> h
      -> i
      -> j
      -> k
      -> l
      -> m
      -> n
      -> o
      -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Record -> Int -> Parser a
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
0
                                        Parser
  (b
   -> c
   -> d
   -> e
   -> f
   -> g
   -> h
   -> i
   -> j
   -> k
   -> l
   -> m
   -> n
   -> o
   -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o))
-> Parser b
-> Parser
     (c
      -> d
      -> e
      -> f
      -> g
      -> h
      -> i
      -> j
      -> k
      -> l
      -> m
      -> n
      -> o
      -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Record -> Int -> Parser b
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
1
                                        Parser
  (c
   -> d
   -> e
   -> f
   -> g
   -> h
   -> i
   -> j
   -> k
   -> l
   -> m
   -> n
   -> o
   -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o))
-> Parser c
-> Parser
     (d
      -> e
      -> f
      -> g
      -> h
      -> i
      -> j
      -> k
      -> l
      -> m
      -> n
      -> o
      -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Record -> Int -> Parser c
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
2
                                        Parser
  (d
   -> e
   -> f
   -> g
   -> h
   -> i
   -> j
   -> k
   -> l
   -> m
   -> n
   -> o
   -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o))
-> Parser d
-> Parser
     (e
      -> f
      -> g
      -> h
      -> i
      -> j
      -> k
      -> l
      -> m
      -> n
      -> o
      -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Record -> Int -> Parser d
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
3
                                        Parser
  (e
   -> f
   -> g
   -> h
   -> i
   -> j
   -> k
   -> l
   -> m
   -> n
   -> o
   -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o))
-> Parser e
-> Parser
     (f
      -> g
      -> h
      -> i
      -> j
      -> k
      -> l
      -> m
      -> n
      -> o
      -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Record -> Int -> Parser e
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
4
                                        Parser
  (f
   -> g
   -> h
   -> i
   -> j
   -> k
   -> l
   -> m
   -> n
   -> o
   -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o))
-> Parser f
-> Parser
     (g
      -> h
      -> i
      -> j
      -> k
      -> l
      -> m
      -> n
      -> o
      -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Record -> Int -> Parser f
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
5
                                        Parser
  (g
   -> h
   -> i
   -> j
   -> k
   -> l
   -> m
   -> n
   -> o
   -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o))
-> Parser g
-> Parser
     (h
      -> i
      -> j
      -> k
      -> l
      -> m
      -> n
      -> o
      -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Record -> Int -> Parser g
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
6
                                        Parser
  (h
   -> i
   -> j
   -> k
   -> l
   -> m
   -> n
   -> o
   -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o))
-> Parser h
-> Parser
     (i
      -> j
      -> k
      -> l
      -> m
      -> n
      -> o
      -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Record -> Int -> Parser h
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
7
                                        Parser
  (i
   -> j
   -> k
   -> l
   -> m
   -> n
   -> o
   -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o))
-> Parser i
-> Parser
     (j
      -> k
      -> l
      -> m
      -> n
      -> o
      -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Record -> Int -> Parser i
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
8
                                        Parser
  (j
   -> k
   -> l
   -> m
   -> n
   -> o
   -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o))
-> Parser j
-> Parser
     (k
      -> l
      -> m
      -> n
      -> o
      -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Record -> Int -> Parser j
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
9
                                        Parser
  (k
   -> l
   -> m
   -> n
   -> o
   -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o))
-> Parser k
-> Parser
     (l -> m -> n -> o -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Record -> Int -> Parser k
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
10
                                        Parser
  (l -> m -> n -> o -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o))
-> Parser l
-> Parser
     (m -> n -> o -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Record -> Int -> Parser l
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
11
                                        Parser
  (m -> n -> o -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o))
-> Parser m
-> Parser (n -> o -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Record -> Int -> Parser m
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
12
                                        Parser (n -> o -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o))
-> Parser n
-> Parser (o -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Record -> Int -> Parser n
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
13
                                        Parser (o -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o))
-> Parser o -> Parser (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Record -> Int -> Parser o
forall a. FromField a => Record -> Int -> Parser a
unsafeIndex Record
v Int
14
        | Bool
otherwise = Int
-> Record -> Parser (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)
forall a. Int -> Record -> Parser a
lengthMismatch Int
15 Record
v
          where
            n :: Int
n = Record -> Int
forall a. Vector a -> Int
V.length Record
v

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) =>
         ToRecord (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) where
    toRecord :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Record
toRecord (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) = [ByteString] -> Record
forall a. [a] -> Vector a
V.fromList [
        a -> ByteString
forall a. ToField a => a -> ByteString
toField a
a, b -> ByteString
forall a. ToField a => a -> ByteString
toField b
b, c -> ByteString
forall a. ToField a => a -> ByteString
toField c
c, d -> ByteString
forall a. ToField a => a -> ByteString
toField d
d, e -> ByteString
forall a. ToField a => a -> ByteString
toField e
e, f -> ByteString
forall a. ToField a => a -> ByteString
toField f
f,
        g -> ByteString
forall a. ToField a => a -> ByteString
toField g
g, h -> ByteString
forall a. ToField a => a -> ByteString
toField h
h, i -> ByteString
forall a. ToField a => a -> ByteString
toField i
i, j -> ByteString
forall a. ToField a => a -> ByteString
toField j
j, k -> ByteString
forall a. ToField a => a -> ByteString
toField k
k, l -> ByteString
forall a. ToField a => a -> ByteString
toField l
l,
        m -> ByteString
forall a. ToField a => a -> ByteString
toField m
m, n -> ByteString
forall a. ToField a => a -> ByteString
toField n
n, o -> ByteString
forall a. ToField a => a -> ByteString
toField o
o]

lengthMismatch :: Int -> Record -> Parser a
lengthMismatch :: Int -> Record -> Parser a
lengthMismatch Int
expected Record
v =
    String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Parser a) -> String -> Parser a
forall a b. (a -> b) -> a -> b
$ String
"cannot unpack array of length " String -> String -> String
forall a. [a] -> [a] -> [a]
++
    Int -> String
forall a. Show a => a -> String
show Int
n String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" into a " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
desired String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
". Input record: " String -> String -> String
forall a. [a] -> [a] -> [a]
++
    Record -> String
forall a. Show a => a -> String
show Record
v
  where
    n :: Int
n = Record -> Int
forall a. Vector a -> Int
V.length Record
v
    desired :: String
desired | Int
expected Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
1 = String
"Only"
            | Int
expected Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
2 = String
"pair"
            | Bool
otherwise     = Int -> String
forall a. Show a => a -> String
show Int
expected String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"-tuple"

instance FromField a => FromRecord [a] where
    parseRecord :: Record -> Parser [a]
parseRecord = (ByteString -> Parser a) -> [ByteString] -> Parser [a]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse ByteString -> Parser a
forall a. FromField a => ByteString -> Parser a
parseField ([ByteString] -> Parser [a])
-> (Record -> [ByteString]) -> Record -> Parser [a]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Record -> [ByteString]
forall a. Vector a -> [a]
V.toList

instance ToField a => ToRecord [a] where
    toRecord :: [a] -> Record
toRecord = [ByteString] -> Record
forall a. [a] -> Vector a
V.fromList ([ByteString] -> Record) -> ([a] -> [ByteString]) -> [a] -> Record
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> ByteString) -> [a] -> [ByteString]
forall a b. (a -> b) -> [a] -> [b]
map a -> ByteString
forall a. ToField a => a -> ByteString
toField

instance FromField a => FromRecord (V.Vector a) where
    parseRecord :: Record -> Parser (Vector a)
parseRecord = (ByteString -> Parser a) -> Record -> Parser (Vector a)
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse ByteString -> Parser a
forall a. FromField a => ByteString -> Parser a
parseField

instance ToField a => ToRecord (Vector a) where
    toRecord :: Vector a -> Record
toRecord = (a -> ByteString) -> Vector a -> Record
forall a b. (a -> b) -> Vector a -> Vector b
V.map a -> ByteString
forall a. ToField a => a -> ByteString
toField

instance (FromField a, U.Unbox a) => FromRecord (U.Vector a) where
    parseRecord :: Record -> Parser (Vector a)
parseRecord = (Vector a -> Vector a) -> Parser (Vector a) -> Parser (Vector a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Vector a -> Vector a
forall (v :: * -> *) a (w :: * -> *).
(Vector v a, Vector w a) =>
v a -> w a
U.convert (Parser (Vector a) -> Parser (Vector a))
-> (Record -> Parser (Vector a)) -> Record -> Parser (Vector a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ByteString -> Parser a) -> Record -> Parser (Vector a)
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse ByteString -> Parser a
forall a. FromField a => ByteString -> Parser a
parseField

instance (ToField a, U.Unbox a) => ToRecord (U.Vector a) where
    toRecord :: Vector a -> Record
toRecord = (a -> ByteString) -> Vector a -> Record
forall a b. (a -> b) -> Vector a -> Vector b
V.map a -> ByteString
forall a. ToField a => a -> ByteString
toField (Vector a -> Record)
-> (Vector a -> Vector a) -> Vector a -> Record
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Vector a -> Vector a
forall (v :: * -> *) a (w :: * -> *).
(Vector v a, Vector w a) =>
v a -> w a
U.convert

------------------------------------------------------------------------
-- Name-based conversion

-- | A type that can be converted from a single CSV record, with the
-- possibility of failure.
--
-- When writing an instance, use 'empty', 'mzero', or 'fail' to make a
-- conversion fail, e.g. if a 'Record' has the wrong number of
-- columns.
--
-- Given this example data:
--
-- > name,age
-- > John,56
-- > Jane,55
--
-- here's an example type and instance:
--
-- > {-# LANGUAGE OverloadedStrings #-}
-- >
-- > data Person = Person { name :: !Text, age :: !Int }
-- >
-- > instance FromNamedRecord Person where
-- >     parseNamedRecord m = Person <$>
-- >                          m .: "name" <*>
-- >                          m .: "age"
--
-- Note the use of the @OverloadedStrings@ language extension which
-- enables 'B8.ByteString' values to be written as string literals.
class FromNamedRecord a where
    parseNamedRecord :: NamedRecord -> Parser a

    default parseNamedRecord :: (Generic a, GFromNamedRecord (Rep a)) => NamedRecord -> Parser a
    parseNamedRecord = Options -> NamedRecord -> Parser a
forall a.
(Generic a, GFromNamedRecord (Rep a)) =>
Options -> NamedRecord -> Parser a
genericParseNamedRecord Options
defaultOptions

-- | A configurable CSV named record parser.  This function applied to
--   'defaultOptions' is used as the default for 'parseNamedRecord'
--   when the type is an instance of 'Generic'.
--
--   @since 0.5.1.0
genericParseNamedRecord :: (Generic a, GFromNamedRecord (Rep a)) => Options -> NamedRecord -> Parser a
genericParseNamedRecord :: Options -> NamedRecord -> Parser a
genericParseNamedRecord Options
opts NamedRecord
r = Rep a Any -> a
forall a x. Generic a => Rep a x -> a
to (Rep a Any -> a) -> Parser (Rep a Any) -> Parser a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Options -> NamedRecord -> Parser (Rep a Any)
forall k (f :: k -> *) (p :: k).
GFromNamedRecord f =>
Options -> NamedRecord -> Parser (f p)
gparseNamedRecord Options
opts NamedRecord
r

-- | A type that can be converted to a single CSV record.
--
-- An example type and instance:
--
-- > data Person = Person { name :: !Text, age :: !Int }
-- >
-- > instance ToNamedRecord Person where
-- >     toNamedRecord (Person name age) = namedRecord [
-- >         "name" .= name, "age" .= age]
class ToNamedRecord a where
    -- | Convert a value to a named record.
    toNamedRecord :: a -> NamedRecord

    default toNamedRecord ::
        (Generic a, GToRecord (Rep a) (B.ByteString, B.ByteString)) =>
        a -> NamedRecord
    toNamedRecord = Options -> a -> NamedRecord
forall a.
(Generic a, GToRecord (Rep a) (ByteString, ByteString)) =>
Options -> a -> NamedRecord
genericToNamedRecord Options
defaultOptions

-- | A configurable CSV named record creator.  This function applied
--   to 'defaultOptions' is used as the default for 'toNamedRecord' when
--   the type is an instance of 'Generic'.
--
--   @since 0.5.1.0
genericToNamedRecord :: (Generic a, GToRecord (Rep a) (B.ByteString, B.ByteString))
                        => Options -> a -> NamedRecord
genericToNamedRecord :: Options -> a -> NamedRecord
genericToNamedRecord Options
opts = [(ByteString, ByteString)] -> NamedRecord
namedRecord ([(ByteString, ByteString)] -> NamedRecord)
-> (a -> [(ByteString, ByteString)]) -> a -> NamedRecord
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Options -> Rep a Any -> [(ByteString, ByteString)]
forall k (a :: k -> *) f (p :: k).
GToRecord a f =>
Options -> a p -> [f]
gtoRecord Options
opts (Rep a Any -> [(ByteString, ByteString)])
-> (a -> Rep a Any) -> a -> [(ByteString, ByteString)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Rep a Any
forall a x. Generic a => a -> Rep a x
from

-- | A type that has a default field order when converted to CSV. This
-- class lets you specify how to get the headers to use for a record
-- type that's an instance of 'ToNamedRecord'.
--
-- To derive an instance, the type is required to only have one
-- constructor and that constructor must have named fields (also known
-- as selectors) for all fields.
--
-- Right: @data Foo = Foo { foo :: !Int }@
--
-- Wrong: @data Bar = Bar Int@
--
-- If you try to derive an instance using GHC generics and your type
-- doesn't have named fields, you will get an error along the lines
-- of:
--
-- > <interactive>:9:10:
-- >     No instance for (DefaultOrdered (M1 S NoSelector (K1 R Char) ()))
-- >       arising from a use of ‘Data.Csv.Conversion.$gdmheader’
-- >     In the expression: Data.Csv.Conversion.$gdmheader
-- >     In an equation for ‘header’:
-- >         header = Data.Csv.Conversion.$gdmheader
-- >     In the instance declaration for ‘DefaultOrdered Foo’
--
class DefaultOrdered a where
    -- | The header order for this record. Should include the names
    -- used in the 'NamedRecord' returned by 'toNamedRecord'. Pass
    -- 'undefined' as the argument, together with a type annotation
    -- e.g. @'headerOrder' ('undefined' :: MyRecord)@.
    headerOrder :: a -> Header  -- TODO: Add Generic implementation

    default headerOrder ::
        (Generic a, GToNamedRecordHeader (Rep a)) =>
        a -> Header
    headerOrder = Options -> a -> Record
forall a.
(Generic a, GToNamedRecordHeader (Rep a)) =>
Options -> a -> Record
genericHeaderOrder Options
defaultOptions

-- | A configurable CSV header record generator.  This function
--   applied to 'defaultOptions' is used as the default for
--   'headerOrder' when the type is an instance of 'Generic'.
--
--   @since 0.5.1.0
genericHeaderOrder :: (Generic a, GToNamedRecordHeader (Rep a))
                      => Options -> a -> Header
genericHeaderOrder :: Options -> a -> Record
genericHeaderOrder Options
opts = [ByteString] -> Record
forall a. [a] -> Vector a
V.fromList([ByteString] -> Record) -> (a -> [ByteString]) -> a -> Record
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Options -> Rep a Any -> [ByteString]
forall k (a :: k -> *) (p :: k).
GToNamedRecordHeader a =>
Options -> a p -> [ByteString]
gtoNamedRecordHeader Options
opts (Rep a Any -> [ByteString])
-> (a -> Rep a Any) -> a -> [ByteString]
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 (FromField a, FromField b, Ord a) => FromNamedRecord (M.Map a b) where
    parseNamedRecord :: NamedRecord -> Parser (Map a b)
parseNamedRecord NamedRecord
m = [(a, b)] -> Map a b
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList ([(a, b)] -> Map a b) -> Parser [(a, b)] -> Parser (Map a b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
                         (((ByteString, ByteString) -> Parser (a, b))
-> [(ByteString, ByteString)] -> Parser [(a, b)]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse (ByteString, ByteString) -> Parser (a, b)
forall a b.
(FromField a, FromField b) =>
(ByteString, ByteString) -> Parser (a, b)
parseBoth ([(ByteString, ByteString)] -> Parser [(a, b)])
-> [(ByteString, ByteString)] -> Parser [(a, b)]
forall a b. (a -> b) -> a -> b
$ NamedRecord -> [(ByteString, ByteString)]
forall k v. HashMap k v -> [(k, v)]
HM.toList NamedRecord
m)

instance (ToField a, ToField b, Ord a) => ToNamedRecord (M.Map a b) where
    toNamedRecord :: Map a b -> NamedRecord
toNamedRecord = [(ByteString, ByteString)] -> NamedRecord
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HM.fromList ([(ByteString, ByteString)] -> NamedRecord)
-> (Map a b -> [(ByteString, ByteString)])
-> Map a b
-> NamedRecord
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((a, b) -> (ByteString, ByteString))
-> [(a, b)] -> [(ByteString, ByteString)]
forall a b. (a -> b) -> [a] -> [b]
map (\ (a
k, b
v) -> (a -> ByteString
forall a. ToField a => a -> ByteString
toField a
k, b -> ByteString
forall a. ToField a => a -> ByteString
toField b
v)) ([(a, b)] -> [(ByteString, ByteString)])
-> (Map a b -> [(a, b)]) -> Map a b -> [(ByteString, ByteString)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Map a b -> [(a, b)]
forall k a. Map k a -> [(k, a)]
M.toList

instance (Eq a, FromField a, FromField b, Hashable a) => FromNamedRecord (HM.HashMap a b) where
    parseNamedRecord :: NamedRecord -> Parser (HashMap a b)
parseNamedRecord NamedRecord
m = [(a, b)] -> HashMap a b
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HM.fromList ([(a, b)] -> HashMap a b)
-> Parser [(a, b)] -> Parser (HashMap a b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
                         (((ByteString, ByteString) -> Parser (a, b))
-> [(ByteString, ByteString)] -> Parser [(a, b)]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse (ByteString, ByteString) -> Parser (a, b)
forall a b.
(FromField a, FromField b) =>
(ByteString, ByteString) -> Parser (a, b)
parseBoth ([(ByteString, ByteString)] -> Parser [(a, b)])
-> [(ByteString, ByteString)] -> Parser [(a, b)]
forall a b. (a -> b) -> a -> b
$ NamedRecord -> [(ByteString, ByteString)]
forall k v. HashMap k v -> [(k, v)]
HM.toList NamedRecord
m)

instance (Eq a, ToField a, ToField b, Hashable a) => ToNamedRecord (HM.HashMap a b) where
    toNamedRecord :: HashMap a b -> NamedRecord
toNamedRecord = [(ByteString, ByteString)] -> NamedRecord
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HM.fromList ([(ByteString, ByteString)] -> NamedRecord)
-> (HashMap a b -> [(ByteString, ByteString)])
-> HashMap a b
-> NamedRecord
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((a, b) -> (ByteString, ByteString))
-> [(a, b)] -> [(ByteString, ByteString)]
forall a b. (a -> b) -> [a] -> [b]
map (\ (a
k, b
v) -> (a -> ByteString
forall a. ToField a => a -> ByteString
toField a
k, b -> ByteString
forall a. ToField a => a -> ByteString
toField b
v)) ([(a, b)] -> [(ByteString, ByteString)])
-> (HashMap a b -> [(a, b)])
-> HashMap a b
-> [(ByteString, ByteString)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HashMap a b -> [(a, b)]
forall k v. HashMap k v -> [(k, v)]
HM.toList

parseBoth :: (FromField a, FromField b) => (Field, Field) -> Parser (a, b)
parseBoth :: (ByteString, ByteString) -> Parser (a, b)
parseBoth (ByteString
k, ByteString
v) = (,) (a -> b -> (a, b)) -> Parser a -> Parser (b -> (a, b))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Parser a
forall a. FromField a => ByteString -> Parser a
parseField ByteString
k Parser (b -> (a, b)) -> Parser b -> Parser (a, b)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ByteString -> Parser b
forall a. FromField a => ByteString -> Parser a
parseField ByteString
v

------------------------------------------------------------------------
-- Individual field conversion

-- | A type that can be converted from a single CSV field, with the
-- possibility of failure.
--
-- When writing an instance, use 'empty', 'mzero', or 'fail' to make a
-- conversion fail, e.g. if a 'Field' can't be converted to the given
-- type.
--
-- Example type and instance:
--
-- > {-# LANGUAGE OverloadedStrings #-}
-- >
-- > data Color = Red | Green | Blue
-- >
-- > instance FromField Color where
-- >     parseField s
-- >         | s == "R"  = pure Red
-- >         | s == "G"  = pure Green
-- >         | s == "B"  = pure Blue
-- >         | otherwise = mzero
class FromField a where
    parseField :: Field -> Parser a

-- | A type that can be converted to a single CSV field.
--
-- Example type and instance:
--
-- > {-# LANGUAGE OverloadedStrings #-}
-- >
-- > data Color = Red | Green | Blue
-- >
-- > instance ToField Color where
-- >     toField Red   = "R"
-- >     toField Green = "G"
-- >     toField Blue  = "B"
class ToField a where
    toField :: a -> Field

-- | 'Nothing' if the 'Field' is 'B.empty', 'Just' otherwise.
instance FromField a => FromField (Maybe a) where
    parseField :: ByteString -> Parser (Maybe a)
parseField ByteString
s
        | ByteString -> Bool
B.null ByteString
s  = Maybe a -> Parser (Maybe a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe a
forall a. Maybe a
Nothing
        | Bool
otherwise = a -> Maybe a
forall a. a -> Maybe a
Just (a -> Maybe a) -> Parser a -> Parser (Maybe a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Parser a
forall a. FromField a => ByteString -> Parser a
parseField ByteString
s
    {-# INLINE parseField #-}

-- | 'Nothing' is encoded as an 'B.empty' field.
instance ToField a => ToField (Maybe a) where
    toField :: Maybe a -> ByteString
toField = ByteString -> (a -> ByteString) -> Maybe a -> ByteString
forall b a. b -> (a -> b) -> Maybe a -> b
maybe ByteString
B.empty a -> ByteString
forall a. ToField a => a -> ByteString
toField
    {-# INLINE toField #-}

-- | @'Left' field@ if conversion failed, 'Right' otherwise.
instance FromField a => FromField (Either Field a) where
    parseField :: ByteString -> Parser (Either ByteString a)
parseField ByteString
s = case Parser a -> Either String a
forall a. Parser a -> Either String a
runParser (ByteString -> Parser a
forall a. FromField a => ByteString -> Parser a
parseField ByteString
s) of
        Left String
_  -> Either ByteString a -> Parser (Either ByteString a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either ByteString a -> Parser (Either ByteString a))
-> Either ByteString a -> Parser (Either ByteString a)
forall a b. (a -> b) -> a -> b
$ ByteString -> Either ByteString a
forall a b. a -> Either a b
Left ByteString
s
        Right a
a -> Either ByteString a -> Parser (Either ByteString a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either ByteString a -> Parser (Either ByteString a))
-> Either ByteString a -> Parser (Either ByteString a)
forall a b. (a -> b) -> a -> b
$ a -> Either ByteString a
forall a b. b -> Either a b
Right a
a
    {-# INLINE parseField #-}

-- | Ignores the 'Field'. Always succeeds.
instance FromField () where
    parseField :: ByteString -> Parser ()
parseField ByteString
_ = () -> Parser ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
    {-# INLINE parseField #-}

-- | @since 0.5.2.0
instance FromField a => FromField (Identity a) where
    parseField :: ByteString -> Parser (Identity a)
parseField = (a -> Identity a) -> Parser a -> Parser (Identity a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> Identity a
forall a. a -> Identity a
Identity (Parser a -> Parser (Identity a))
-> (ByteString -> Parser a) -> ByteString -> Parser (Identity a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Parser a
forall a. FromField a => ByteString -> Parser a
parseField
    {-# INLINE parseField #-}

-- | @since 0.5.2.0
instance ToField a => ToField (Identity a) where
    toField :: Identity a -> ByteString
toField = a -> ByteString
forall a. ToField a => a -> ByteString
toField (a -> ByteString) -> (Identity a -> a) -> Identity a -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Identity a -> a
forall a. Identity a -> a
runIdentity
    {-# INLINE toField #-}

-- | @since 0.5.2.0
instance FromField a => FromField (Const a b) where
    parseField :: ByteString -> Parser (Const a b)
parseField = (a -> Const a b) -> Parser a -> Parser (Const a b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> Const a b
forall k a (b :: k). a -> Const a b
Const (Parser a -> Parser (Const a b))
-> (ByteString -> Parser a) -> ByteString -> Parser (Const a b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Parser a
forall a. FromField a => ByteString -> Parser a
parseField
    {-# INLINE parseField #-}

-- | @since 0.5.2.0
instance ToField a => ToField (Const a b) where
    toField :: Const a b -> ByteString
toField = a -> ByteString
forall a. ToField a => a -> ByteString
toField (a -> ByteString) -> (Const a b -> a) -> Const a b -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Const a b -> a
forall a k (b :: k). Const a b -> a
getConst
    {-# INLINE toField #-}

-- | Assumes UTF-8 encoding.
instance FromField Char where
    parseField :: ByteString -> Parser Char
parseField ByteString
s =
        case ByteString -> Either UnicodeException Text
T.decodeUtf8' ByteString
s of
          Left UnicodeException
e -> String -> Parser Char
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Parser Char) -> String -> Parser Char
forall a b. (a -> b) -> a -> b
$ UnicodeException -> String
forall a. Show a => a -> String
show UnicodeException
e
          Right Text
t
            | Text -> Int -> Ordering
T.compareLength Text
t Int
1 Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
== Ordering
EQ -> Char -> Parser Char
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Text -> Char
T.head Text
t)
            | Bool
otherwise -> String -> ByteString -> Maybe String -> Parser Char
forall a. String -> ByteString -> Maybe String -> Parser a
typeError String
"Char" ByteString
s Maybe String
forall a. Maybe a
Nothing
    {-# INLINE parseField #-}

-- | Uses UTF-8 encoding.
instance ToField Char where
    toField :: Char -> ByteString
toField = ByteString -> ByteString
forall a. ToField a => a -> ByteString
toField (ByteString -> ByteString)
-> (Char -> ByteString) -> Char -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ByteString
T.encodeUtf8 (Text -> ByteString) -> (Char -> Text) -> Char -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Text
T.singleton
    {-# INLINE toField #-}

-- | Accepts the same syntax as 'rational'. Ignores whitespace.
--
-- @since 0.5.1.0
instance FromField Scientific where
  parseField :: ByteString -> Parser Scientific
parseField ByteString
s = case Parser Scientific -> ByteString -> Either String Scientific
forall a. Parser a -> ByteString -> Either String a
parseOnly (Parser ()
ws Parser () -> Parser Scientific -> Parser Scientific
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser Scientific
A8.scientific Parser Scientific -> Parser () -> Parser Scientific
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Parser ()
ws) ByteString
s of
                   Left String
err -> String -> ByteString -> Maybe String -> Parser Scientific
forall a. String -> ByteString -> Maybe String -> Parser a
typeError String
"Scientific" ByteString
s (String -> Maybe String
forall a. a -> Maybe a
Just String
err)
                   Right Scientific
n  -> Scientific -> Parser Scientific
forall (f :: * -> *) a. Applicative f => a -> f a
pure Scientific
n
  {-# INLINE parseField #-}

-- | Uses decimal notation or scientific notation, depending on the number.
--
-- @since 0.5.1.0
instance ToField Scientific where
  toField :: Scientific -> ByteString
toField = Scientific -> ByteString
scientific
  {-# INLINE toField #-}

-- | Accepts same syntax as 'rational'. Ignores whitespace.
instance FromField Double where
    parseField :: ByteString -> Parser Double
parseField = ByteString -> Parser Double
parseDouble
    {-# INLINE parseField #-}

-- | Uses decimal notation or scientific notation, depending on the
-- number.
instance ToField Double where
    toField :: Double -> ByteString
toField = Double -> ByteString
forall a. RealFloat a => a -> ByteString
realFloat
    {-# INLINE toField #-}

-- | Accepts same syntax as 'rational'. Ignores whitespace.
instance FromField Float where
    parseField :: ByteString -> Parser Float
parseField ByteString
s = Double -> Float
double2Float (Double -> Float) -> Parser Double -> Parser Float
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Parser Double
parseDouble ByteString
s
    {-# INLINE parseField #-}

-- | Uses decimal notation or scientific notation, depending on the
-- number.
instance ToField Float where
    toField :: Float -> ByteString
toField = Float -> ByteString
forall a. RealFloat a => a -> ByteString
realFloat
    {-# INLINE toField #-}

parseDouble :: B.ByteString -> Parser Double
parseDouble :: ByteString -> Parser Double
parseDouble ByteString
s = case Parser Double -> ByteString -> Either String Double
forall a. Parser a -> ByteString -> Either String a
parseOnly (Parser ()
ws Parser () -> Parser Double -> Parser Double
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser Double
double Parser Double -> Parser () -> Parser Double
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Parser ()
ws) ByteString
s of
    Left String
err -> String -> ByteString -> Maybe String -> Parser Double
forall a. String -> ByteString -> Maybe String -> Parser a
typeError String
"Double" ByteString
s (String -> Maybe String
forall a. a -> Maybe a
Just String
err)
    Right Double
n  -> Double -> Parser Double
forall (f :: * -> *) a. Applicative f => a -> f a
pure Double
n
{-# INLINE parseDouble #-}

-- | Accepts a signed decimal number. Ignores whitespace.
instance FromField Int where
    parseField :: ByteString -> Parser Int
parseField = String -> ByteString -> Parser Int
forall a. (Integral a, Num a) => String -> ByteString -> Parser a
parseSigned String
"Int"
    {-# INLINE parseField #-}

-- | Uses decimal encoding with optional sign.
instance ToField Int where
    toField :: Int -> ByteString
toField = Int -> ByteString
forall a. Integral a => a -> ByteString
decimal
    {-# INLINE toField #-}

-- | Accepts a signed decimal number. Ignores whitespace.
instance FromField Integer where
    parseField :: ByteString -> Parser Integer
parseField = String -> ByteString -> Parser Integer
forall a. (Integral a, Num a) => String -> ByteString -> Parser a
parseSigned String
"Integer"
    {-# INLINE parseField #-}

-- | Uses decimal encoding with optional sign.
instance ToField Integer where
    toField :: Integer -> ByteString
toField = Integer -> ByteString
forall a. Integral a => a -> ByteString
decimal
    {-# INLINE toField #-}

-- | Accepts a signed decimal number. Ignores whitespace.
instance FromField Int8 where
    parseField :: ByteString -> Parser Int8
parseField = String -> ByteString -> Parser Int8
forall a. (Integral a, Num a) => String -> ByteString -> Parser a
parseSigned String
"Int8"
    {-# INLINE parseField #-}

-- | Uses decimal encoding with optional sign.
instance ToField Int8 where
    toField :: Int8 -> ByteString
toField = Int8 -> ByteString
forall a. Integral a => a -> ByteString
decimal
    {-# INLINE toField #-}

-- | Accepts a signed decimal number. Ignores whitespace.
instance FromField Int16 where
    parseField :: ByteString -> Parser Int16
parseField = String -> ByteString -> Parser Int16
forall a. (Integral a, Num a) => String -> ByteString -> Parser a
parseSigned String
"Int16"
    {-# INLINE parseField #-}

-- | Uses decimal encoding with optional sign.
instance ToField Int16 where
    toField :: Int16 -> ByteString
toField = Int16 -> ByteString
forall a. Integral a => a -> ByteString
decimal
    {-# INLINE toField #-}

-- | Accepts a signed decimal number. Ignores whitespace.
instance FromField Int32 where
    parseField :: ByteString -> Parser Int32
parseField = String -> ByteString -> Parser Int32
forall a. (Integral a, Num a) => String -> ByteString -> Parser a
parseSigned String
"Int32"
    {-# INLINE parseField #-}

-- | Uses decimal encoding with optional sign.
instance ToField Int32 where
    toField :: Int32 -> ByteString
toField = Int32 -> ByteString
forall a. Integral a => a -> ByteString
decimal
    {-# INLINE toField #-}

-- | Accepts a signed decimal number. Ignores whitespace.
instance FromField Int64 where
    parseField :: ByteString -> Parser Int64
parseField = String -> ByteString -> Parser Int64
forall a. (Integral a, Num a) => String -> ByteString -> Parser a
parseSigned String
"Int64"
    {-# INLINE parseField #-}

-- | Uses decimal encoding with optional sign.
instance ToField Int64 where
    toField :: Int64 -> ByteString
toField = Int64 -> ByteString
forall a. Integral a => a -> ByteString
decimal
    {-# INLINE toField #-}

-- | Accepts an unsigned decimal number. Ignores whitespace.
instance FromField Word where
    parseField :: ByteString -> Parser Word
parseField = String -> ByteString -> Parser Word
forall a. Integral a => String -> ByteString -> Parser a
parseUnsigned String
"Word"
    {-# INLINE parseField #-}

-- | Uses decimal encoding.
instance ToField Word where
    toField :: Word -> ByteString
toField = Word -> ByteString
forall a. Integral a => a -> ByteString
decimal
    {-# INLINE toField #-}

-- | Accepts an unsigned decimal number. Ignores whitespace.
--
-- @since 0.5.1.0
instance FromField Natural where
    parseField :: ByteString -> Parser Natural
parseField = String -> ByteString -> Parser Natural
forall a. Integral a => String -> ByteString -> Parser a
parseUnsigned String
"Natural"
    {-# INLINE parseField #-}

-- | Uses decimal encoding.
--
-- @since 0.5.1.0
instance ToField Natural where
    toField :: Natural -> ByteString
toField = Natural -> ByteString
forall a. Integral a => a -> ByteString
decimal
    {-# INLINE toField #-}

-- | Accepts an unsigned decimal number. Ignores whitespace.
instance FromField Word8 where
    parseField :: ByteString -> Parser Word8
parseField = String -> ByteString -> Parser Word8
forall a. Integral a => String -> ByteString -> Parser a
parseUnsigned String
"Word8"
    {-# INLINE parseField #-}

-- | Uses decimal encoding.
instance ToField Word8 where
    toField :: Word8 -> ByteString
toField = Word8 -> ByteString
forall a. Integral a => a -> ByteString
decimal
    {-# INLINE toField #-}

-- | Accepts an unsigned decimal number. Ignores whitespace.
instance FromField Word16 where
    parseField :: ByteString -> Parser Word16
parseField = String -> ByteString -> Parser Word16
forall a. Integral a => String -> ByteString -> Parser a
parseUnsigned String
"Word16"
    {-# INLINE parseField #-}

-- | Uses decimal encoding.
instance ToField Word16 where
    toField :: Word16 -> ByteString
toField = Word16 -> ByteString
forall a. Integral a => a -> ByteString
decimal
    {-# INLINE toField #-}

-- | Accepts an unsigned decimal number. Ignores whitespace.
instance FromField Word32 where
    parseField :: ByteString -> Parser Word32
parseField = String -> ByteString -> Parser Word32
forall a. Integral a => String -> ByteString -> Parser a
parseUnsigned String
"Word32"
    {-# INLINE parseField #-}

-- | Uses decimal encoding.
instance ToField Word32 where
    toField :: Word32 -> ByteString
toField = Word32 -> ByteString
forall a. Integral a => a -> ByteString
decimal
    {-# INLINE toField #-}

-- | Accepts an unsigned decimal number. Ignores whitespace.
instance FromField Word64 where
    parseField :: ByteString -> Parser Word64
parseField = String -> ByteString -> Parser Word64
forall a. Integral a => String -> ByteString -> Parser a
parseUnsigned String
"Word64"
    {-# INLINE parseField #-}

-- | Uses decimal encoding.
instance ToField Word64 where
    toField :: Word64 -> ByteString
toField = Word64 -> ByteString
forall a. Integral a => a -> ByteString
decimal
    {-# INLINE toField #-}

instance FromField B.ByteString where
    parseField :: ByteString -> Parser ByteString
parseField = ByteString -> Parser ByteString
forall (f :: * -> *) a. Applicative f => a -> f a
pure
    {-# INLINE parseField #-}

instance ToField B.ByteString where
    toField :: ByteString -> ByteString
toField = ByteString -> ByteString
forall a. a -> a
id
    {-# INLINE toField #-}

instance FromField L.ByteString where
    parseField :: ByteString -> Parser ByteString
parseField = ByteString -> Parser ByteString
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ByteString -> Parser ByteString)
-> (ByteString -> ByteString) -> ByteString -> Parser ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ByteString
fromStrict
    {-# INLINE parseField #-}

instance ToField L.ByteString where
    toField :: ByteString -> ByteString
toField = ByteString -> ByteString
toStrict
    {-# INLINE toField #-}

#if MIN_VERSION_bytestring(0,10,4)
instance FromField SBS.ShortByteString where
    parseField :: ByteString -> Parser ShortByteString
parseField = ShortByteString -> Parser ShortByteString
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ShortByteString -> Parser ShortByteString)
-> (ByteString -> ShortByteString)
-> ByteString
-> Parser ShortByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ShortByteString
SBS.toShort
    {-# INLINE parseField #-}

instance ToField SBS.ShortByteString where
    toField :: ShortByteString -> ByteString
toField = ShortByteString -> ByteString
SBS.fromShort
    {-# INLINE toField #-}
#endif

#if MIN_VERSION_text_short(0,1,0)
-- | Assumes UTF-8 encoding. Fails on invalid byte sequences.
--
-- @since 0.5.0.0
instance FromField T.S.ShortText where
    parseField :: ByteString -> Parser ShortText
parseField = Parser ShortText
-> (ShortText -> Parser ShortText)
-> Maybe ShortText
-> Parser ShortText
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (String -> Parser ShortText
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Invalid UTF-8 stream") ShortText -> Parser ShortText
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe ShortText -> Parser ShortText)
-> (ByteString -> Maybe ShortText)
-> ByteString
-> Parser ShortText
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Maybe ShortText
T.S.fromByteString
    {-# INLINE parseField #-}

-- | Uses UTF-8 encoding.
--
-- @since 0.5.0.0
instance ToField T.S.ShortText where
    toField :: ShortText -> ByteString
toField = ShortText -> ByteString
T.S.toByteString
    {-# INLINE toField #-}
#endif

-- | Assumes UTF-8 encoding. Fails on invalid byte sequences.
instance FromField T.Text where
    parseField :: ByteString -> Parser Text
parseField = (UnicodeException -> Parser Text)
-> (Text -> Parser Text)
-> Either UnicodeException Text
-> Parser Text
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (String -> Parser Text
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Parser Text)
-> (UnicodeException -> String) -> UnicodeException -> Parser Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UnicodeException -> String
forall a. Show a => a -> String
show) Text -> Parser Text
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either UnicodeException Text -> Parser Text)
-> (ByteString -> Either UnicodeException Text)
-> ByteString
-> Parser Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Either UnicodeException Text
T.decodeUtf8'
    {-# INLINE parseField #-}

-- | Uses UTF-8 encoding.
instance ToField T.Text where
    toField :: Text -> ByteString
toField = ByteString -> ByteString
forall a. ToField a => a -> ByteString
toField (ByteString -> ByteString)
-> (Text -> ByteString) -> Text -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ByteString
T.encodeUtf8
    {-# INLINE toField #-}

-- | Assumes UTF-8 encoding. Fails on invalid byte sequences.
instance FromField LT.Text where
    parseField :: ByteString -> Parser Text
parseField = (UnicodeException -> Parser Text)
-> (Text -> Parser Text)
-> Either UnicodeException Text
-> Parser Text
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (String -> Parser Text
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Parser Text)
-> (UnicodeException -> String) -> UnicodeException -> Parser Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UnicodeException -> String
forall a. Show a => a -> String
show) (Text -> Parser Text
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Text -> Parser Text) -> (Text -> Text) -> Text -> Parser Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
LT.fromStrict) (Either UnicodeException Text -> Parser Text)
-> (ByteString -> Either UnicodeException Text)
-> ByteString
-> Parser Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Either UnicodeException Text
T.decodeUtf8'
    {-# INLINE parseField #-}

-- | Uses UTF-8 encoding.
instance ToField LT.Text where
    toField :: Text -> ByteString
toField = ByteString -> ByteString
forall a. ToField a => a -> ByteString
toField (ByteString -> ByteString)
-> (Text -> ByteString) -> Text -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ByteString
toStrict (ByteString -> ByteString)
-> (Text -> ByteString) -> Text -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ByteString
LT.encodeUtf8
    {-# INLINE toField #-}

-- | Assumes UTF-8 encoding. Fails on invalid byte sequences.
instance FromField [Char] where
    parseField :: ByteString -> Parser String
parseField = (Text -> String) -> Parser Text -> Parser String
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> String
T.unpack (Parser Text -> Parser String)
-> (ByteString -> Parser Text) -> ByteString -> Parser String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Parser Text
forall a. FromField a => ByteString -> Parser a
parseField
    {-# INLINE parseField #-}

-- | Uses UTF-8 encoding.
instance ToField [Char] where
    toField :: String -> ByteString
toField = Text -> ByteString
forall a. ToField a => a -> ByteString
toField (Text -> ByteString) -> (String -> Text) -> String -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
T.pack
    {-# INLINE toField #-}

parseSigned :: (Integral a, Num a) => String -> B.ByteString -> Parser a
parseSigned :: String -> ByteString -> Parser a
parseSigned String
typ ByteString
s = case Parser a -> ByteString -> Either String a
forall a. Parser a -> ByteString -> Either String a
parseOnly (Parser ()
ws Parser () -> Parser a -> Parser a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser a -> Parser a
forall a. Num a => Parser a -> Parser a
A8.signed Parser a
forall a. Integral a => Parser a
A8.decimal Parser a -> Parser () -> Parser a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Parser ()
ws) ByteString
s of
    Left String
err -> String -> ByteString -> Maybe String -> Parser a
forall a. String -> ByteString -> Maybe String -> Parser a
typeError String
typ ByteString
s (String -> Maybe String
forall a. a -> Maybe a
Just String
err)
    Right a
n  -> a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure a
n
{-# INLINE parseSigned #-}

parseUnsigned :: Integral a => String -> B.ByteString -> Parser a
parseUnsigned :: String -> ByteString -> Parser a
parseUnsigned String
typ ByteString
s = case Parser a -> ByteString -> Either String a
forall a. Parser a -> ByteString -> Either String a
parseOnly (Parser ()
ws Parser () -> Parser a -> Parser a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser a
forall a. Integral a => Parser a
A8.decimal Parser a -> Parser () -> Parser a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Parser ()
ws) ByteString
s of
    Left String
err -> String -> ByteString -> Maybe String -> Parser a
forall a. String -> ByteString -> Maybe String -> Parser a
typeError String
typ ByteString
s (String -> Maybe String
forall a. a -> Maybe a
Just String
err)
    Right a
n  -> a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure a
n
{-# INLINE parseUnsigned #-}

ws :: A8.Parser ()
ws :: Parser ()
ws = (Char -> Bool) -> Parser ()
A8.skipWhile (\Char
c -> Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
' ' Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'\t')



------------------------------------------------------------------------
-- Custom version of attoparsec @parseOnly@ function which fails if
-- there is leftover content after parsing a field.
parseOnly :: A8.Parser a -> B.ByteString -> Either String a
parseOnly :: Parser a -> ByteString -> Either String a
parseOnly Parser a
parser ByteString
input = IResult ByteString a -> Either String a
forall b. IResult ByteString b -> Either String b
go (Parser a -> ByteString -> IResult ByteString a
forall a. Parser a -> ByteString -> Result a
A8.parse Parser a
parser ByteString
input) where
  go :: IResult ByteString b -> Either String b
go (A8.Fail ByteString
_ [String]
_ String
err) = String -> Either String b
forall a b. a -> Either a b
Left String
err
  go (A8.Partial ByteString -> IResult ByteString b
f)    = IResult ByteString b -> Either String b
forall b. IResult ByteString b -> Either String b
go2 (ByteString -> IResult ByteString b
f ByteString
B.empty)
  go (A8.Done ByteString
leftover b
result)
    | ByteString -> Bool
B.null ByteString
leftover = b -> Either String b
forall a b. b -> Either a b
Right b
result
    | Bool
otherwise = String -> Either String b
forall a b. a -> Either a b
Left (String
"incomplete field parse, leftover: "
                        String -> String -> String
forall a. [a] -> [a] -> [a]
++ [Word8] -> String
forall a. Show a => a -> String
show (ByteString -> [Word8]
B.unpack ByteString
leftover))

  go2 :: IResult ByteString b -> Either String b
go2 (A8.Fail ByteString
_ [String]
_ String
err) = String -> Either String b
forall a b. a -> Either a b
Left String
err
  go2 (A8.Partial ByteString -> IResult ByteString b
_)    = String -> Either String b
forall a. HasCallStack => String -> a
error String
"parseOnly: impossible error!"
  go2 (A8.Done ByteString
leftover b
result)
    | ByteString -> Bool
B.null ByteString
leftover = b -> Either String b
forall a b. b -> Either a b
Right b
result
    | Bool
otherwise = String -> Either String b
forall a b. a -> Either a b
Left (String
"incomplete field parse, leftover: "
                        String -> String -> String
forall a. [a] -> [a] -> [a]
++ [Word8] -> String
forall a. Show a => a -> String
show (ByteString -> [Word8]
B.unpack ByteString
leftover))
{-# INLINE parseOnly #-}

typeError :: String -> B.ByteString -> Maybe String -> Parser a
typeError :: String -> ByteString -> Maybe String -> Parser a
typeError String
typ ByteString
s Maybe String
mmsg =
    String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Parser a) -> String -> Parser a
forall a b. (a -> b) -> a -> b
$ String
"expected " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
typ String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
", got " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> String
forall a. Show a => a -> String
show (ByteString -> String
B8.unpack ByteString
s) String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
cause
  where
    cause :: String
cause = case Maybe String
mmsg of
        Just String
msg -> String
" (" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
msg String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
")"
        Maybe String
Nothing  -> String
""

------------------------------------------------------------------------
-- Constructors and accessors

-- | Retrieve the /n/th field in the given record. The result is
-- 'empty' if the value cannot be converted to the desired type.
-- Raises an exception if the index is out of bounds.
--
-- 'index' is a simple convenience function that is equivalent to
-- @'parseField' (v '!' idx)@. If you're certain that the index is not
-- out of bounds, using 'unsafeIndex' is somewhat faster.
index :: FromField a => Record -> Int -> Parser a
index :: Record -> Int -> Parser a
index Record
v Int
idx = ByteString -> Parser a
forall a. FromField a => ByteString -> Parser a
parseField (Record
v Record -> Int -> ByteString
forall a. Vector a -> Int -> a
! Int
idx)
{-# INLINE index #-}

-- | Alias for 'index'.
(.!) :: FromField a => Record -> Int -> Parser a
.! :: Record -> Int -> Parser a
(.!) = Record -> Int -> Parser a
forall a. FromField a => Record -> Int -> Parser a
index
{-# INLINE (.!) #-}
infixl 9 .!

-- | Like 'index' but without bounds checking.
unsafeIndex :: FromField a => Record -> Int -> Parser a
unsafeIndex :: Record -> Int -> Parser a
unsafeIndex Record
v Int
idx = ByteString -> Parser a
forall a. FromField a => ByteString -> Parser a
parseField (Record -> Int -> ByteString
forall a. Vector a -> Int -> a
V.unsafeIndex Record
v Int
idx)
{-# INLINE unsafeIndex #-}

-- | Retrieve a field in the given record by name.  The result is
-- 'empty' if the field is missing or if the value cannot be converted
-- to the desired type.
lookup :: FromField a => NamedRecord -> B.ByteString -> Parser a
lookup :: NamedRecord -> ByteString -> Parser a
lookup NamedRecord
m ByteString
name = Parser a
-> (ByteString -> Parser a) -> Maybe ByteString -> Parser a
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
err) ByteString -> Parser a
forall a (m :: * -> *).
(FromField a, MonadFail m) =>
ByteString -> m a
parseField' (Maybe ByteString -> Parser a) -> Maybe ByteString -> Parser a
forall a b. (a -> b) -> a -> b
$ ByteString -> NamedRecord -> Maybe ByteString
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
HM.lookup ByteString
name NamedRecord
m
  where err :: String
err = String
"no field named " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> String
forall a. Show a => a -> String
show (ByteString -> String
B8.unpack ByteString
name)
        parseField' :: ByteString -> m a
parseField' ByteString
fld = case Parser a -> Either String a
forall a. Parser a -> Either String a
runParser (ByteString -> Parser a
forall a. FromField a => ByteString -> Parser a
parseField ByteString
fld) of
          Left String
e -> String -> m a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> m a) -> String -> m a
forall a b. (a -> b) -> a -> b
$ String
"in named field " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> String
forall a. Show a => a -> String
show (ByteString -> String
B8.unpack ByteString
name) String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
": " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
e
          Right a
res -> a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure a
res
{-# INLINE lookup #-}

-- | Alias for 'lookup'.
(.:) :: FromField a => NamedRecord -> B.ByteString -> Parser a
.: :: NamedRecord -> ByteString -> Parser a
(.:) = NamedRecord -> ByteString -> Parser a
forall a. FromField a => NamedRecord -> ByteString -> Parser a
lookup
{-# INLINE (.:) #-}

-- | Construct a pair from a name and a value.  For use with
-- 'namedRecord'.
namedField :: ToField a => B.ByteString -> a -> (B.ByteString, B.ByteString)
namedField :: ByteString -> a -> (ByteString, ByteString)
namedField ByteString
name a
val = (ByteString
name, a -> ByteString
forall a. ToField a => a -> ByteString
toField a
val)
{-# INLINE namedField #-}

-- | Alias for 'namedField'.
(.=) :: ToField a => B.ByteString -> a -> (B.ByteString, B.ByteString)
.= :: ByteString -> a -> (ByteString, ByteString)
(.=) = ByteString -> a -> (ByteString, ByteString)
forall a. ToField a => ByteString -> a -> (ByteString, ByteString)
namedField
{-# INLINE (.=) #-}

-- | Construct a record from a list of 'B.ByteString's.  Use 'toField'
-- to convert values to 'B.ByteString's for use with 'record'.
record :: [B.ByteString] -> Record
record :: [ByteString] -> Record
record = [ByteString] -> Record
forall a. [a] -> Vector a
V.fromList

-- | Construct a named record from a list of name-value 'B.ByteString'
-- pairs.  Use '.=' to construct such a pair from a name and a value.
namedRecord :: [(B.ByteString, B.ByteString)] -> NamedRecord
namedRecord :: [(ByteString, ByteString)] -> NamedRecord
namedRecord = [(ByteString, ByteString)] -> NamedRecord
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HM.fromList

-- | Construct a header from a list of 'B.ByteString's.
header :: [B.ByteString] -> Header
header :: [ByteString] -> Record
header = [ByteString] -> Record
forall a. [a] -> Vector a
V.fromList

------------------------------------------------------------------------
-- Parser for converting records to data types

-- | Failure continuation.
type Failure f r   = String -> f r
-- | Success continuation.
type Success a f r = a -> f r

-- | Conversion of a field to a value might fail e.g. if the field is
-- malformed. This possibility is captured by the 'Parser' type, which
-- lets you compose several field conversions together in such a way
-- that if any of them fail, the whole record conversion fails.
newtype Parser a = Parser {
      Parser a
-> forall (f :: * -> *) r. Failure f r -> Success a f r -> f r
unParser :: forall (f :: * -> *) (r :: *).
                  Failure f r
               -> Success a f r
               -> f r
    }

instance Monad Parser where
    Parser a
m >>= :: Parser a -> (a -> Parser b) -> Parser b
>>= a -> Parser b
g = (forall (f :: * -> *) r. Failure f r -> Success b f r -> f r)
-> Parser b
forall a.
(forall (f :: * -> *) r. Failure f r -> Success a f r -> f r)
-> Parser a
Parser ((forall (f :: * -> *) r. Failure f r -> Success b f r -> f r)
 -> Parser b)
-> (forall (f :: * -> *) r. Failure f r -> Success b f r -> f r)
-> Parser b
forall a b. (a -> b) -> a -> b
$ \Failure f r
kf Success b f r
ks -> let ks' :: a -> f r
ks' a
a = Parser b -> Failure f r -> Success b f r -> f r
forall a.
Parser a
-> forall (f :: * -> *) r. Failure f r -> Success a f r -> f r
unParser (a -> Parser b
g a
a) Failure f r
kf Success b f r
ks
                                 in Parser a -> Failure f r -> (a -> f r) -> f r
forall a.
Parser a
-> forall (f :: * -> *) r. Failure f r -> Success a f r -> f r
unParser Parser a
m Failure f r
kf a -> f r
ks'
    {-# INLINE (>>=) #-}
    >> :: Parser a -> Parser b -> Parser b
(>>) = Parser a -> Parser b -> Parser b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
(*>)
    {-# INLINE (>>) #-}
    return :: a -> Parser a
return = a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
    {-# INLINE return #-}

#if !MIN_VERSION_base(4,13,0)
    fail = Fail.fail
    {-# INLINE fail #-}
#endif

-- | @since 0.5.0.0
instance Fail.MonadFail Parser where
    fail :: String -> Parser a
fail String
msg = (forall (f :: * -> *) r. Failure f r -> Success a f r -> f r)
-> Parser a
forall a.
(forall (f :: * -> *) r. Failure f r -> Success a f r -> f r)
-> Parser a
Parser ((forall (f :: * -> *) r. Failure f r -> Success a f r -> f r)
 -> Parser a)
-> (forall (f :: * -> *) r. Failure f r -> Success a f r -> f r)
-> Parser a
forall a b. (a -> b) -> a -> b
$ \Failure f r
kf Success a f r
_ks -> Failure f r
kf String
msg
    {-# INLINE fail #-}

instance Functor Parser where
    fmap :: (a -> b) -> Parser a -> Parser b
fmap a -> b
f Parser a
m = (forall (f :: * -> *) r. Failure f r -> Success b f r -> f r)
-> Parser b
forall a.
(forall (f :: * -> *) r. Failure f r -> Success a f r -> f r)
-> Parser a
Parser ((forall (f :: * -> *) r. Failure f r -> Success b f r -> f r)
 -> Parser b)
-> (forall (f :: * -> *) r. Failure f r -> Success b f r -> f r)
-> Parser b
forall a b. (a -> b) -> a -> b
$ \Failure f r
kf Success b f r
ks -> let ks' :: a -> f r
ks' a
a = Success b f r
ks (a -> b
f a
a)
                                  in Parser a -> Failure f r -> (a -> f r) -> f r
forall a.
Parser a
-> forall (f :: * -> *) r. Failure f r -> Success a f r -> f r
unParser Parser a
m Failure f r
kf a -> f r
ks'
    {-# INLINE fmap #-}

instance Applicative Parser where
    pure :: a -> Parser a
pure a
a = (forall (f :: * -> *) r. Failure f r -> Success a f r -> f r)
-> Parser a
forall a.
(forall (f :: * -> *) r. Failure f r -> Success a f r -> f r)
-> Parser a
Parser ((forall (f :: * -> *) r. Failure f r -> Success a f r -> f r)
 -> Parser a)
-> (forall (f :: * -> *) r. Failure f r -> Success a f r -> f r)
-> Parser a
forall a b. (a -> b) -> a -> b
$ \Failure f r
_kf Success a f r
ks -> Success a f r
ks a
a
    {-# INLINE pure #-}
    <*> :: Parser (a -> b) -> Parser a -> Parser b
(<*>) = Parser (a -> b) -> Parser a -> Parser b
forall a b. Parser (a -> b) -> Parser a -> Parser b
apP
    {-# INLINE (<*>) #-}

instance Alternative Parser where
    empty :: Parser a
empty = String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"empty"
    {-# INLINE empty #-}
    <|> :: Parser a -> Parser a -> Parser a
(<|>) = Parser a -> Parser a -> Parser a
forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
mplus
    {-# INLINE (<|>) #-}

instance MonadPlus Parser where
    mzero :: Parser a
mzero = String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"mzero"
    {-# INLINE mzero #-}
    mplus :: Parser a -> Parser a -> Parser a
mplus Parser a
a Parser a
b = (forall (f :: * -> *) r. Failure f r -> Success a f r -> f r)
-> Parser a
forall a.
(forall (f :: * -> *) r. Failure f r -> Success a f r -> f r)
-> Parser a
Parser ((forall (f :: * -> *) r. Failure f r -> Success a f r -> f r)
 -> Parser a)
-> (forall (f :: * -> *) r. Failure f r -> Success a f r -> f r)
-> Parser a
forall a b. (a -> b) -> a -> b
$ \Failure f r
kf Success a f r
ks -> let kf' :: p -> f r
kf' p
_ = Parser a -> Failure f r -> Success a f r -> f r
forall a.
Parser a
-> forall (f :: * -> *) r. Failure f r -> Success a f r -> f r
unParser Parser a
b Failure f r
kf Success a f r
ks
                                   in Parser a -> Failure f r -> Success a f r -> f r
forall a.
Parser a
-> forall (f :: * -> *) r. Failure f r -> Success a f r -> f r
unParser Parser a
a Failure f r
forall p. p -> f r
kf' Success a f r
ks
    {-# INLINE mplus #-}

-- | @since 0.5.0.0
instance Semi.Semigroup (Parser a) where
    <> :: Parser a -> Parser a -> Parser a
(<>) = Parser a -> Parser a -> Parser a
forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
mplus
    {-# INLINE (<>) #-}

instance Monoid (Parser a) where
    mempty :: Parser a
mempty  = String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"mempty"
    {-# INLINE mempty #-}
    mappend :: Parser a -> Parser a -> Parser a
mappend = Parser a -> Parser a -> Parser a
forall a. Semigroup a => a -> a -> a
(Semi.<>)
    {-# INLINE mappend #-}

apP :: Parser (a -> b) -> Parser a -> Parser b
apP :: Parser (a -> b) -> Parser a -> Parser b
apP Parser (a -> b)
d Parser a
e = do
  a -> b
b <- Parser (a -> b)
d
  a
a <- Parser a
e
  b -> Parser b
forall (f :: * -> *) a. Applicative f => a -> f a
pure (a -> b
b a
a)
{-# INLINE apP #-}

-- | Run a 'Parser', returning either @'Left' errMsg@ or @'Right'
-- result@. Forces the value in the 'Left' or 'Right' constructors to
-- weak head normal form.
--
-- You most likely won't need to use this function directly, but it's
-- included for completeness.
runParser :: Parser a -> Either String a
runParser :: Parser a -> Either String a
runParser Parser a
p = Parser a
-> Failure (Either String) a
-> Success a (Either String) a
-> Either String a
forall a.
Parser a
-> forall (f :: * -> *) r. Failure f r -> Success a f r -> f r
unParser Parser a
p Failure (Either String) a
forall a b. a -> Either a b
left Success a (Either String) a
forall b a. b -> Either a b
right
  where
    left :: a -> Either a b
left !a
errMsg = a -> Either a b
forall a b. a -> Either a b
Left a
errMsg
    right :: b -> Either a b
right !b
x = b -> Either a b
forall a b. b -> Either a b
Right b
x
{-# INLINE runParser #-}

------------------------------------------------------------------------
-- Generics

class GFromRecord f where
    gparseRecord :: Options -> Record -> Parser (f p)

instance GFromRecordSum f Record => GFromRecord (M1 i n f) where
    gparseRecord :: Options -> Record -> Parser (M1 i n f p)
gparseRecord Options
opts Record
v =
        case Int
-> IntMap (Record -> Parser (f p))
-> Maybe (Record -> Parser (f p))
forall a. Int -> IntMap a -> Maybe a
IM.lookup Int
n (Options -> IntMap (Record -> Parser (f p))
forall k (f :: k -> *) r (p :: k).
GFromRecordSum f r =>
Options -> IntMap (r -> Parser (f p))
gparseRecordSum Options
opts) of
            Maybe (Record -> Parser (f p))
Nothing -> Int -> Record -> Parser (M1 i n f p)
forall a. Int -> Record -> Parser a
lengthMismatch Int
n Record
v
            Just Record -> Parser (f p)
p -> f p -> M1 i n f p
forall k i (c :: Meta) (f :: k -> *) (p :: k). f p -> M1 i c f p
M1 (f p -> M1 i n f p) -> Parser (f p) -> Parser (M1 i n f p)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Record -> Parser (f p)
p Record
v
      where
        n :: Int
n = Record -> Int
forall a. Vector a -> Int
V.length Record
v

class GFromNamedRecord f where
    gparseNamedRecord :: Options -> NamedRecord -> Parser (f p)

instance GFromRecordSum f NamedRecord => GFromNamedRecord (M1 i n f) where
    gparseNamedRecord :: Options -> NamedRecord -> Parser (M1 i n f p)
gparseNamedRecord Options
opts NamedRecord
v =
        ((NamedRecord -> Parser (f p))
 -> Parser (M1 i n f p) -> Parser (M1 i n f p))
-> Parser (M1 i n f p)
-> [NamedRecord -> Parser (f p)]
-> Parser (M1 i n f p)
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (\NamedRecord -> Parser (f p)
f Parser (M1 i n f p)
p -> Parser (M1 i n f p)
p Parser (M1 i n f p) -> Parser (M1 i n f p) -> Parser (M1 i n f p)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> f p -> M1 i n f p
forall k i (c :: Meta) (f :: k -> *) (p :: k). f p -> M1 i c f p
M1 (f p -> M1 i n f p) -> Parser (f p) -> Parser (M1 i n f p)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> NamedRecord -> Parser (f p)
f NamedRecord
v) Parser (M1 i n f p)
forall (f :: * -> *) a. Alternative f => f a
empty (IntMap (NamedRecord -> Parser (f p))
-> [NamedRecord -> Parser (f p)]
forall a. IntMap a -> [a]
IM.elems (Options -> IntMap (NamedRecord -> Parser (f p))
forall k (f :: k -> *) r (p :: k).
GFromRecordSum f r =>
Options -> IntMap (r -> Parser (f p))
gparseRecordSum Options
opts))

class GFromRecordSum f r where
    gparseRecordSum :: Options -> IM.IntMap (r -> Parser (f p))

instance (GFromRecordSum a r, GFromRecordSum b r) => GFromRecordSum (a :+: b) r where
    gparseRecordSum :: Options -> IntMap (r -> Parser ((:+:) a b p))
gparseRecordSum Options
opts =
        ((r -> Parser ((:+:) a b p))
 -> (r -> Parser ((:+:) a b p)) -> r -> Parser ((:+:) a b p))
-> IntMap (r -> Parser ((:+:) a b p))
-> IntMap (r -> Parser ((:+:) a b p))
-> IntMap (r -> Parser ((:+:) a b p))
forall a. (a -> a -> a) -> IntMap a -> IntMap a -> IntMap a
IM.unionWith (\r -> Parser ((:+:) a b p)
a r -> Parser ((:+:) a b p)
b r
r -> r -> Parser ((:+:) a b p)
a r
r Parser ((:+:) a b p)
-> Parser ((:+:) a b p) -> Parser ((:+:) a b p)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> r -> Parser ((:+:) a b p)
b r
r)
            ((Parser (a p) -> Parser ((:+:) a b p))
-> (r -> Parser (a p)) -> r -> Parser ((:+:) a b p)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (a p -> (:+:) a b p
forall k (f :: k -> *) (g :: k -> *) (p :: k). f p -> (:+:) f g p
L1 (a p -> (:+:) a b p) -> Parser (a p) -> Parser ((:+:) a b p)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>) ((r -> Parser (a p)) -> r -> Parser ((:+:) a b p))
-> IntMap (r -> Parser (a p)) -> IntMap (r -> Parser ((:+:) a b p))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Options -> IntMap (r -> Parser (a p))
forall k (f :: k -> *) r (p :: k).
GFromRecordSum f r =>
Options -> IntMap (r -> Parser (f p))
gparseRecordSum Options
opts)
            ((Parser (b p) -> Parser ((:+:) a b p))
-> (r -> Parser (b p)) -> r -> Parser ((:+:) a b p)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (b p -> (:+:) a b p
forall k (f :: k -> *) (g :: k -> *) (p :: k). g p -> (:+:) f g p
R1 (b p -> (:+:) a b p) -> Parser (b p) -> Parser ((:+:) a b p)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>) ((r -> Parser (b p)) -> r -> Parser ((:+:) a b p))
-> IntMap (r -> Parser (b p)) -> IntMap (r -> Parser ((:+:) a b p))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Options -> IntMap (r -> Parser (b p))
forall k (f :: k -> *) r (p :: k).
GFromRecordSum f r =>
Options -> IntMap (r -> Parser (f p))
gparseRecordSum Options
opts)

instance GFromRecordProd f r => GFromRecordSum (M1 i n f) r where
    gparseRecordSum :: Options -> IntMap (r -> Parser (M1 i n f p))
gparseRecordSum Options
opts = Int
-> (r -> Parser (M1 i n f p)) -> IntMap (r -> Parser (M1 i n f p))
forall a. Int -> a -> IntMap a
IM.singleton Int
n ((Parser (f p) -> Parser (M1 i n f p))
-> (r -> Parser (f p)) -> r -> Parser (M1 i n f p)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (f p -> M1 i n f p
forall k i (c :: Meta) (f :: k -> *) (p :: k). f p -> M1 i c f p
M1 (f p -> M1 i n f p) -> Parser (f p) -> Parser (M1 i n f p)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>) r -> Parser (f p)
forall (p :: k). r -> Parser (f p)
f)
      where
        (Int
n, r -> Parser (f p)
f) = Options -> Int -> (Int, r -> Parser (f p))
forall k (f :: k -> *) r (p :: k).
GFromRecordProd f r =>
Options -> Int -> (Int, r -> Parser (f p))
gparseRecordProd Options
opts Int
0

class GFromRecordProd f r where
    gparseRecordProd :: Options -> Int -> (Int, r -> Parser (f p))

instance GFromRecordProd U1 r where
    gparseRecordProd :: Options -> Int -> (Int, r -> Parser (U1 p))
gparseRecordProd Options
_ Int
n = (Int
n, Parser (U1 p) -> r -> Parser (U1 p)
forall a b. a -> b -> a
const (U1 p -> Parser (U1 p)
forall (f :: * -> *) a. Applicative f => a -> f a
pure U1 p
forall k (p :: k). U1 p
U1))

instance (GFromRecordProd a r, GFromRecordProd b r) => GFromRecordProd (a :*: b) r where
    gparseRecordProd :: Options -> Int -> (Int, r -> Parser ((:*:) a b p))
gparseRecordProd Options
opts Int
n0 = (Int
n2, r -> Parser ((:*:) a b p)
f)
      where
        f :: r -> Parser ((:*:) a b p)
f r
r = a p -> b p -> (:*:) a b p
forall k (f :: k -> *) (g :: k -> *) (p :: k).
f p -> g p -> (:*:) f g p
(:*:) (a p -> b p -> (:*:) a b p)
-> Parser (a p) -> Parser (b p -> (:*:) a b p)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> r -> Parser (a p)
forall (p :: k). r -> Parser (a p)
fa r
r Parser (b p -> (:*:) a b p) -> Parser (b p) -> Parser ((:*:) a b p)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> r -> Parser (b p)
forall (p :: k). r -> Parser (b p)
fb r
r
        (Int
n1, r -> Parser (a p)
fa) = Options -> Int -> (Int, r -> Parser (a p))
forall k (f :: k -> *) r (p :: k).
GFromRecordProd f r =>
Options -> Int -> (Int, r -> Parser (f p))
gparseRecordProd Options
opts Int
n0
        (Int
n2, r -> Parser (b p)
fb) = Options -> Int -> (Int, r -> Parser (b p))
forall k (f :: k -> *) r (p :: k).
GFromRecordProd f r =>
Options -> Int -> (Int, r -> Parser (f p))
gparseRecordProd Options
opts Int
n1

instance GFromRecordProd f Record => GFromRecordProd (M1 i n f) Record where
    gparseRecordProd :: Options -> Int -> (Int, Record -> Parser (M1 i n f p))
gparseRecordProd Options
opts Int
n = (Parser (f p) -> Parser (M1 i n f p))
-> (Record -> Parser (f p)) -> Record -> Parser (M1 i n f p)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (f p -> M1 i n f p
forall k i (c :: Meta) (f :: k -> *) (p :: k). f p -> M1 i c f p
M1 (f p -> M1 i n f p) -> Parser (f p) -> Parser (M1 i n f p)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>) ((Record -> Parser (f p)) -> Record -> Parser (M1 i n f p))
-> (Int, Record -> Parser (f p))
-> (Int, Record -> Parser (M1 i n f p))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Options -> Int -> (Int, Record -> Parser (f p))
forall k (f :: k -> *) r (p :: k).
GFromRecordProd f r =>
Options -> Int -> (Int, r -> Parser (f p))
gparseRecordProd Options
opts Int
n

instance FromField a => GFromRecordProd (K1 i a) Record where
    gparseRecordProd :: Options -> Int -> (Int, Record -> Parser (K1 i a p))
gparseRecordProd Options
_ Int
n = (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1, \Record
v -> a -> K1 i a p
forall k i c (p :: k). c -> K1 i c p
K1 (a -> K1 i a p) -> Parser a -> Parser (K1 i a p)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Parser a
forall a. FromField a => ByteString -> Parser a
parseField (Record -> Int -> ByteString
forall a. Vector a -> Int -> a
V.unsafeIndex Record
v Int
n))

data Proxy s (f :: * -> *) a = Proxy

instance (FromField a, Selector s) => GFromRecordProd (M1 S s (K1 i a)) NamedRecord where
    gparseRecordProd :: Options -> Int -> (Int, NamedRecord -> Parser (M1 S s (K1 i a) p))
gparseRecordProd Options
opts Int
n = (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1, \NamedRecord
v -> (K1 i a p -> M1 S s (K1 i a) p
forall k i (c :: Meta) (f :: k -> *) (p :: k). f p -> M1 i c f p
M1 (K1 i a p -> M1 S s (K1 i a) p)
-> (a -> K1 i a p) -> a -> M1 S s (K1 i a) p
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> K1 i a p
forall k i c (p :: k). c -> K1 i c p
K1) (a -> M1 S s (K1 i a) p) -> Parser a -> Parser (M1 S s (K1 i a) p)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> NamedRecord
v NamedRecord -> ByteString -> Parser a
forall a. FromField a => NamedRecord -> ByteString -> Parser a
.: ByteString
name)
      where
        name :: ByteString
name = Text -> ByteString
T.encodeUtf8 (String -> Text
T.pack (Options -> String -> String
fieldLabelModifier Options
opts (Proxy s Any a -> String
forall k (s :: k) k1 (t :: k -> (k1 -> *) -> k1 -> *)
       (f :: k1 -> *) (a :: k1).
Selector s =>
t s f a -> String
selName (forall k k (s :: k) (f :: * -> *) (a :: k). Proxy s f a
forall (f :: * -> *). Proxy s f a
Proxy :: Proxy s f a))))


class GToRecord a f where
    gtoRecord :: Options -> a p -> [f]

instance GToRecord U1 f where
    gtoRecord :: Options -> U1 p -> [f]
gtoRecord Options
_ U1 p
U1 = []

instance (GToRecord a f, GToRecord b f) => GToRecord (a :*: b) f where
    gtoRecord :: Options -> (:*:) a b p -> [f]
gtoRecord Options
opts (a p
a :*: b p
b) = Options -> a p -> [f]
forall k (a :: k -> *) f (p :: k).
GToRecord a f =>
Options -> a p -> [f]
gtoRecord Options
opts a p
a [f] -> [f] -> [f]
forall a. [a] -> [a] -> [a]
++ Options -> b p -> [f]
forall k (a :: k -> *) f (p :: k).
GToRecord a f =>
Options -> a p -> [f]
gtoRecord Options
opts b p
b

instance (GToRecord a f, GToRecord b f) => GToRecord (a :+: b) f where
    gtoRecord :: Options -> (:+:) a b p -> [f]
gtoRecord Options
opts (L1 a p
a) = Options -> a p -> [f]
forall k (a :: k -> *) f (p :: k).
GToRecord a f =>
Options -> a p -> [f]
gtoRecord Options
opts a p
a
    gtoRecord Options
opts (R1 b p
b) = Options -> b p -> [f]
forall k (a :: k -> *) f (p :: k).
GToRecord a f =>
Options -> a p -> [f]
gtoRecord Options
opts b p
b

instance GToRecord a f => GToRecord (M1 D c a) f where
    gtoRecord :: Options -> M1 D c a p -> [f]
gtoRecord Options
opts (M1 a p
a) = Options -> a p -> [f]
forall k (a :: k -> *) f (p :: k).
GToRecord a f =>
Options -> a p -> [f]
gtoRecord Options
opts a p
a

instance GToRecord a f => GToRecord (M1 C c a) f where
    gtoRecord :: Options -> M1 C c a p -> [f]
gtoRecord Options
opts (M1 a p
a) = Options -> a p -> [f]
forall k (a :: k -> *) f (p :: k).
GToRecord a f =>
Options -> a p -> [f]
gtoRecord Options
opts a p
a

instance GToRecord a Field => GToRecord (M1 S c a) Field where
    gtoRecord :: Options -> M1 S c a p -> [ByteString]
gtoRecord Options
opts (M1 a p
a) = Options -> a p -> [ByteString]
forall k (a :: k -> *) f (p :: k).
GToRecord a f =>
Options -> a p -> [f]
gtoRecord Options
opts a p
a

instance ToField a => GToRecord (K1 i a) Field where
    gtoRecord :: Options -> K1 i a p -> [ByteString]
gtoRecord Options
_ (K1 a
a) = [a -> ByteString
forall a. ToField a => a -> ByteString
toField a
a]

instance (ToField a, Selector s) => GToRecord (M1 S s (K1 i a)) (B.ByteString, B.ByteString) where
    gtoRecord :: Options -> M1 S s (K1 i a) p -> [(ByteString, ByteString)]
gtoRecord Options
opts m :: M1 S s (K1 i a) p
m@(M1 (K1 a
a)) = [ByteString
name ByteString -> ByteString -> (ByteString, ByteString)
forall a. ToField a => ByteString -> a -> (ByteString, ByteString)
.= a -> ByteString
forall a. ToField a => a -> ByteString
toField a
a]
      where
        name :: ByteString
name = Text -> ByteString
T.encodeUtf8 (String -> Text
T.pack (Options -> String -> String
fieldLabelModifier Options
opts (M1 S s (K1 i a) p -> String
forall k (s :: k) k1 (t :: k -> (k1 -> *) -> k1 -> *)
       (f :: k1 -> *) (a :: k1).
Selector s =>
t s f a -> String
selName M1 S s (K1 i a) p
m)))

-- We statically fail on sum types and product types without selectors
-- (field names).

class GToNamedRecordHeader a
  where
    gtoNamedRecordHeader :: Options -> a p -> [Name]

instance GToNamedRecordHeader U1
  where
    gtoNamedRecordHeader :: Options -> U1 p -> [ByteString]
gtoNamedRecordHeader Options
_ U1 p
_ = []

instance (GToNamedRecordHeader a, GToNamedRecordHeader b) =>
         GToNamedRecordHeader (a :*: b)
  where
    gtoNamedRecordHeader :: Options -> (:*:) a b p -> [ByteString]
gtoNamedRecordHeader Options
opts (:*:) a b p
_ = Options -> a Any -> [ByteString]
forall k (a :: k -> *) (p :: k).
GToNamedRecordHeader a =>
Options -> a p -> [ByteString]
gtoNamedRecordHeader Options
opts (forall (p :: k). a p
forall a. HasCallStack => a
undefined :: a p) [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++
                                  Options -> b Any -> [ByteString]
forall k (a :: k -> *) (p :: k).
GToNamedRecordHeader a =>
Options -> a p -> [ByteString]
gtoNamedRecordHeader Options
opts (forall (p :: k). b p
forall a. HasCallStack => a
undefined :: b p)

instance GToNamedRecordHeader a => GToNamedRecordHeader (M1 D c a)
  where
    gtoNamedRecordHeader :: Options -> M1 D c a p -> [ByteString]
gtoNamedRecordHeader Options
opts M1 D c a p
_ = Options -> a Any -> [ByteString]
forall k (a :: k -> *) (p :: k).
GToNamedRecordHeader a =>
Options -> a p -> [ByteString]
gtoNamedRecordHeader Options
opts (forall (p :: k). a p
forall a. HasCallStack => a
undefined :: a p)

instance GToNamedRecordHeader a => GToNamedRecordHeader (M1 C c a)
  where
    gtoNamedRecordHeader :: Options -> M1 C c a p -> [ByteString]
gtoNamedRecordHeader Options
opts M1 C c a p
_ = Options -> a Any -> [ByteString]
forall k (a :: k -> *) (p :: k).
GToNamedRecordHeader a =>
Options -> a p -> [ByteString]
gtoNamedRecordHeader Options
opts (forall (p :: k). a p
forall a. HasCallStack => a
undefined :: a p)

-- | Instance to ensure that you cannot derive DefaultOrdered for
-- constructors without selectors.
#if MIN_VERSION_base(4,9,0)
instance DefaultOrdered (M1 S ('MetaSel 'Nothing srcpk srcstr decstr) a ())
         => GToNamedRecordHeader (M1 S ('MetaSel 'Nothing srcpk srcstr decstr) a)
#else
instance DefaultOrdered (M1 S NoSelector a ()) => GToNamedRecordHeader (M1 S NoSelector a)
#endif
  where
    gtoNamedRecordHeader :: Options
-> M1 S ('MetaSel 'Nothing srcpk srcstr decstr) a p -> [ByteString]
gtoNamedRecordHeader Options
_ M1 S ('MetaSel 'Nothing srcpk srcstr decstr) a p
_ =
        String -> [ByteString]
forall a. HasCallStack => String -> a
error String
"You cannot derive DefaultOrdered for constructors without selectors."

instance Selector s => GToNamedRecordHeader (M1 S s a)
  where
    gtoNamedRecordHeader :: Options -> M1 S s a p -> [ByteString]
gtoNamedRecordHeader Options
opts M1 S s a p
m
        | String -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
name = String -> [ByteString]
forall a. HasCallStack => String -> a
error String
"Cannot derive DefaultOrdered for constructors without selectors"
        | Bool
otherwise = [String -> ByteString
B8.pack (Options -> String -> String
fieldLabelModifier Options
opts (M1 S s a p -> String
forall k (s :: k) k1 (t :: k -> (k1 -> *) -> k1 -> *)
       (f :: k1 -> *) (a :: k1).
Selector s =>
t s f a -> String
selName M1 S s a p
m))]
      where name :: String
name = M1 S s a p -> String
forall k (s :: k) k1 (t :: k -> (k1 -> *) -> k1 -> *)
       (f :: k1 -> *) (a :: k1).
Selector s =>
t s f a -> String
selName M1 S s a p
m