#if __GLASGOW_HASKELL__ >= 706
#endif
#include "incoherent-compat.h"
#include "overlapping-compat.h"
module Data.Aeson.Types.FromJSON
(
FromJSON(..)
, FromJSON1(..)
, parseJSON1
, FromJSON2(..)
, parseJSON2
, GFromJSON(..)
, FromArgs(..)
, genericParseJSON
, genericLiftParseJSON
, FromJSONKey(..)
, FromJSONKeyFunction(..)
, fromJSONKeyCoerce
, coerceFromJSONKeyFunction
, mapFromJSONKeyFunction
, listParser
, withObject
, withText
, withArray
, withNumber
, withScientific
, withBool
, withEmbeddedJSON
, fromJSON
, ifromJSON
, typeMismatch
, parseField
, parseFieldMaybe
, parseFieldMaybe'
, explicitParseField
, explicitParseFieldMaybe
, explicitParseFieldMaybe'
, (.:)
, (.:?)
, (.:!)
, (.!=)
, parseOptionalFieldWith
) where
import Prelude ()
import Prelude.Compat
import Control.Applicative ((<|>), Const(..))
import Control.Monad ((<=<), zipWithM)
import Data.Aeson.Internal.Functions (mapKey)
import Data.Aeson.Parser.Internal (eitherDecodeWith, jsonEOF)
import Data.Aeson.Types.Generic
import Data.Aeson.Types.Internal
import Data.Attoparsec.Number (Number(..))
import Data.Bits (unsafeShiftR)
import Data.Fixed (Fixed, HasResolution)
import Data.Functor.Compose (Compose(..))
import Data.Functor.Identity (Identity(..))
import Data.Functor.Product (Product(..))
import Data.Functor.Sum (Sum(..))
import Data.Hashable (Hashable(..))
import Data.Int (Int16, Int32, Int64, Int8)
import Data.List.NonEmpty (NonEmpty(..))
import Data.Maybe (fromMaybe)
import Data.Monoid ((<>))
import Data.Proxy (Proxy(..))
import Data.Ratio ((%), Ratio)
import Data.Scientific (Scientific)
import Data.Tagged (Tagged(..))
import Data.Text (Text, pack, unpack)
import Data.Time (Day, DiffTime, LocalTime, NominalDiffTime, TimeOfDay, UTCTime, ZonedTime)
import Data.Time.Format (parseTime)
import Data.Time.Locale.Compat (defaultTimeLocale)
import Data.Traversable as Tr (sequence)
import Data.Vector (Vector)
import Data.Version (Version, parseVersion)
import Data.Word (Word16, Word32, Word64, Word8)
import Foreign.Storable (Storable)
import Foreign.C.Types (CTime (..))
import GHC.Generics
import Numeric.Natural (Natural)
import Text.ParserCombinators.ReadP (readP_to_S)
import Unsafe.Coerce (unsafeCoerce)
import qualified Data.Aeson.Compat as Compat
import qualified Data.Aeson.Parser.Time as Time
import qualified Data.Attoparsec.ByteString.Char8 as A (endOfInput, parseOnly, scientific)
import qualified Data.DList as DList
import qualified Data.HashMap.Strict as H
import qualified Data.HashSet as HashSet
import qualified Data.IntMap as IntMap
import qualified Data.IntSet as IntSet
import qualified Data.Map as M
import qualified Data.Monoid as Monoid
import qualified Data.Scientific as Scientific
import qualified Data.Semigroup as Semigroup
import qualified Data.Sequence as Seq
import qualified Data.Set as Set
import qualified Data.Text as T
import qualified Data.Text.Encoding as T
import qualified Data.Text.Lazy as LT
import qualified Data.Tree as Tree
import qualified Data.UUID.Types as UUID
import qualified Data.Vector as V
import qualified Data.Vector.Generic as VG
import qualified Data.Vector.Primitive as VP
import qualified Data.Vector.Storable as VS
import qualified Data.Vector.Unboxed as VU
#ifndef HAS_COERCIBLE
#define HAS_COERCIBLE (__GLASGOW_HASKELL__ >= 707)
#endif
#if HAS_COERCIBLE
import Data.Coerce (Coercible, coerce)
coerce' :: Coercible a b => a -> b
coerce' = coerce
#else
coerce' :: a -> b
coerce' = unsafeCoerce
#endif
parseIndexedJSON :: (Value -> Parser a) -> Int -> Value -> Parser a
parseIndexedJSON p idx value = p value <?> Index idx
parseIndexedJSONPair :: (Value -> Parser a) -> (Value -> Parser b) -> Int -> Value -> Parser (a, b)
parseIndexedJSONPair keyParser valParser idx value = p value <?> Index idx
where
p = withArray "(k,v)" $ \ab ->
let n = V.length ab
in if n == 2
then (,) <$> parseJSONElemAtIndex keyParser 0 ab
<*> parseJSONElemAtIndex valParser 1 ab
else fail $ "cannot unpack array of length " ++
show n ++ " into a pair"
parseJSONElemAtIndex :: (Value -> Parser a) -> Int -> V.Vector Value -> Parser a
parseJSONElemAtIndex p idx ary = p (V.unsafeIndex ary idx) <?> Index idx
scientificToNumber :: Scientific -> Number
scientificToNumber s
| e < 0 = D $ Scientific.toRealFloat s
| otherwise = I $ c * 10 ^ e
where
e = Scientific.base10Exponent s
c = Scientific.coefficient s
parseRealFloat :: RealFloat a => String -> Value -> Parser a
parseRealFloat _ (Number s) = pure $ Scientific.toRealFloat s
parseRealFloat _ Null = pure (0/0)
parseRealFloat expected v = typeMismatch expected v
parseIntegralFromScientific :: forall a. Integral a => String -> Scientific -> Parser a
parseIntegralFromScientific expected s =
case Scientific.floatingOrInteger s :: Either Double a of
Right x -> pure x
Left _ -> fail $ "expected " ++ expected ++ ", encountered floating number " ++ show s
parseIntegral :: Integral a => String -> Value -> Parser a
parseIntegral expected =
withScientific expected $ parseIntegralFromScientific expected
parseBoundedIntegralFromScientific :: (Bounded a, Integral a) => String -> Scientific -> Parser a
parseBoundedIntegralFromScientific expected s = maybe
(fail $ expected ++ " is either floating or will cause over or underflow: " ++ show s)
pure
(Scientific.toBoundedInteger s)
parseBoundedIntegral :: (Bounded a, Integral a) => String -> Value -> Parser a
parseBoundedIntegral expected =
withScientific expected $ parseBoundedIntegralFromScientific expected
parseScientificText :: Text -> Parser Scientific
parseScientificText
= either fail pure
. A.parseOnly (A.scientific <* A.endOfInput)
. T.encodeUtf8
parseIntegralText :: Integral a => String -> Text -> Parser a
parseIntegralText expected t =
parseScientificText t >>= parseIntegralFromScientific expected
parseBoundedIntegralText :: (Bounded a, Integral a) => String -> Text -> Parser a
parseBoundedIntegralText expected t =
parseScientificText t >>= parseBoundedIntegralFromScientific expected
parseOptionalFieldWith :: (Value -> Parser (Maybe a))
-> Object -> Text -> Parser (Maybe a)
parseOptionalFieldWith pj obj key =
case H.lookup key obj of
Nothing -> pure Nothing
Just v -> pj v <?> Key key
class GFromJSON arity f where
gParseJSON :: Options -> FromArgs arity a -> Value -> Parser (f a)
data FromArgs arity a where
NoFromArgs :: FromArgs Zero a
From1Args :: (Value -> Parser a) -> (Value -> Parser [a]) -> FromArgs One a
genericParseJSON :: (Generic a, GFromJSON Zero (Rep a))
=> Options -> Value -> Parser a
genericParseJSON opts = fmap to . gParseJSON opts NoFromArgs
genericLiftParseJSON :: (Generic1 f, GFromJSON One (Rep1 f))
=> Options -> (Value -> Parser a) -> (Value -> Parser [a])
-> Value -> Parser (f a)
genericLiftParseJSON opts pj pjl = fmap to1 . gParseJSON opts (From1Args pj pjl)
class FromJSON a where
parseJSON :: Value -> Parser a
default parseJSON :: (Generic a, GFromJSON Zero (Rep a)) => Value -> Parser a
parseJSON = genericParseJSON defaultOptions
parseJSONList :: Value -> Parser [a]
parseJSONList (Array a)
= zipWithM (parseIndexedJSON parseJSON) [0..]
. V.toList
$ a
parseJSONList v = typeMismatch "[a]" v
class FromJSONKey a where
fromJSONKey :: FromJSONKeyFunction a
default fromJSONKey :: FromJSON a => FromJSONKeyFunction a
fromJSONKey = FromJSONKeyValue parseJSON
fromJSONKeyList :: FromJSONKeyFunction [a]
default fromJSONKeyList :: FromJSON a => FromJSONKeyFunction [a]
fromJSONKeyList = FromJSONKeyValue parseJSON
data CoerceText a where
#if HAS_COERCIBLE
CoerceText :: Coercible Text a => CoerceText a
#else
CoerceText :: CoerceText a
#endif
data FromJSONKeyFunction a
= FromJSONKeyCoerce !(CoerceText a)
| FromJSONKeyText !(Text -> a)
| FromJSONKeyTextParser !(Text -> Parser a)
| FromJSONKeyValue !(Value -> Parser a)
instance Functor FromJSONKeyFunction where
fmap h (FromJSONKeyCoerce CoerceText) = FromJSONKeyText (h . coerce')
fmap h (FromJSONKeyText f) = FromJSONKeyText (h . f)
fmap h (FromJSONKeyTextParser f) = FromJSONKeyTextParser (fmap h . f)
fmap h (FromJSONKeyValue f) = FromJSONKeyValue (fmap h . f)
fromJSONKeyCoerce ::
#if HAS_COERCIBLE
Coercible Text a =>
#endif
FromJSONKeyFunction a
fromJSONKeyCoerce = FromJSONKeyCoerce CoerceText
coerceFromJSONKeyFunction ::
#if HAS_COERCIBLE
Coercible a b =>
#endif
FromJSONKeyFunction a -> FromJSONKeyFunction b
#if HAS_COERCIBLE
coerceFromJSONKeyFunction = coerce
#else
coerceFromJSONKeyFunction (FromJSONKeyCoerce CoerceText) = FromJSONKeyCoerce CoerceText
coerceFromJSONKeyFunction (FromJSONKeyText f) = FromJSONKeyText (coerce' . f)
coerceFromJSONKeyFunction (FromJSONKeyTextParser f) = FromJSONKeyTextParser (fmap coerce' . f)
coerceFromJSONKeyFunction (FromJSONKeyValue f) = FromJSONKeyValue (fmap coerce' . f)
#endif
#if HAS_COERCIBLE
#endif
mapFromJSONKeyFunction :: (a -> b) -> FromJSONKeyFunction a -> FromJSONKeyFunction b
mapFromJSONKeyFunction = fmap
typeMismatch :: String
-> Value
-> Parser a
typeMismatch expected actual =
fail $ "expected " ++ expected ++ ", encountered " ++ name
where
name = case actual of
Object _ -> "Object"
Array _ -> "Array"
String _ -> "String"
Number _ -> "Number"
Bool _ -> "Boolean"
Null -> "Null"
class FromJSON1 f where
liftParseJSON :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser (f a)
default liftParseJSON :: (Generic1 f, GFromJSON One (Rep1 f))
=> (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser (f a)
liftParseJSON = genericLiftParseJSON defaultOptions
liftParseJSONList :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser [f a]
liftParseJSONList f g v = listParser (liftParseJSON f g) v
parseJSON1 :: (FromJSON1 f, FromJSON a) => Value -> Parser (f a)
parseJSON1 = liftParseJSON parseJSON parseJSONList
class FromJSON2 f where
liftParseJSON2
:: (Value -> Parser a)
-> (Value -> Parser [a])
-> (Value -> Parser b)
-> (Value -> Parser [b])
-> Value -> Parser (f a b)
liftParseJSONList2
:: (Value -> Parser a)
-> (Value -> Parser [a])
-> (Value -> Parser b)
-> (Value -> Parser [b])
-> Value -> Parser [f a b]
liftParseJSONList2 fa ga fb gb v = case v of
Array vals -> fmap V.toList (V.mapM (liftParseJSON2 fa ga fb gb) vals)
_ -> typeMismatch "[a]" v
parseJSON2 :: (FromJSON2 f, FromJSON a, FromJSON b) => Value -> Parser (f a b)
parseJSON2 = liftParseJSON2 parseJSON parseJSONList parseJSON parseJSONList
listParser :: (Value -> Parser a) -> Value -> Parser [a]
listParser f (Array xs) = fmap V.toList (V.mapM f xs)
listParser _ v = typeMismatch "[a]" v
instance FromJSON1 [] where
liftParseJSON _ p' = p'
instance (FromJSON a) => FromJSON [a] where
parseJSON = parseJSON1
withObject :: String -> (Object -> Parser a) -> Value -> Parser a
withObject _ f (Object obj) = f obj
withObject expected _ v = typeMismatch expected v
withText :: String -> (Text -> Parser a) -> Value -> Parser a
withText _ f (String txt) = f txt
withText expected _ v = typeMismatch expected v
withArray :: String -> (Array -> Parser a) -> Value -> Parser a
withArray _ f (Array arr) = f arr
withArray expected _ v = typeMismatch expected v
withNumber :: String -> (Number -> Parser a) -> Value -> Parser a
withNumber expected f = withScientific expected (f . scientificToNumber)
withScientific :: String -> (Scientific -> Parser a) -> Value -> Parser a
withScientific _ f (Number scientific) = f scientific
withScientific expected _ v = typeMismatch expected v
withBool :: String -> (Bool -> Parser a) -> Value -> Parser a
withBool _ f (Bool arr) = f arr
withBool expected _ v = typeMismatch expected v
withEmbeddedJSON :: String -> (Value -> Parser a) -> Value -> Parser a
withEmbeddedJSON _ innerParser (String txt) =
either fail innerParser $ eitherDecode (Compat.fromStrict $ T.encodeUtf8 txt)
where
eitherDecode = eitherFormatError . eitherDecodeWith jsonEOF ifromJSON
eitherFormatError = either (Left . uncurry formatError) Right
withEmbeddedJSON name _ v = typeMismatch name v
fromJSON :: (FromJSON a) => Value -> Result a
fromJSON = parse parseJSON
ifromJSON :: (FromJSON a) => Value -> IResult a
ifromJSON = iparse parseJSON
(.:) :: (FromJSON a) => Object -> Text -> Parser a
(.:) = explicitParseField parseJSON
(.:?) :: (FromJSON a) => Object -> Text -> Parser (Maybe a)
(.:?) = explicitParseFieldMaybe parseJSON
(.:!) :: (FromJSON a) => Object -> Text -> Parser (Maybe a)
(.:!) = explicitParseFieldMaybe' parseJSON
parseField :: (FromJSON a) => Object -> Text -> Parser a
parseField = (.:)
parseFieldMaybe :: (FromJSON a) => Object -> Text -> Parser (Maybe a)
parseFieldMaybe = (.:?)
parseFieldMaybe' :: (FromJSON a) => Object -> Text -> Parser (Maybe a)
parseFieldMaybe' = (.:!)
explicitParseField :: (Value -> Parser a) -> Object -> Text -> Parser a
explicitParseField p obj key = case H.lookup key obj of
Nothing -> fail $ "key " ++ show key ++ " not present"
Just v -> p v <?> Key key
explicitParseFieldMaybe :: (Value -> Parser a) -> Object -> Text -> Parser (Maybe a)
explicitParseFieldMaybe p obj key = case H.lookup key obj of
Nothing -> pure Nothing
Just v -> liftParseJSON p (listParser p) v <?> Key key
explicitParseFieldMaybe' :: (Value -> Parser a) -> Object -> Text -> Parser (Maybe a)
explicitParseFieldMaybe' p obj key = case H.lookup key obj of
Nothing -> pure Nothing
Just v -> Just <$> p v <?> Key key
(.!=) :: Parser (Maybe a) -> a -> Parser a
pmval .!= val = fromMaybe val <$> pmval
instance OVERLAPPABLE_ (GFromJSON arity a) => GFromJSON arity (M1 i c a) where
gParseJSON opts fargs = fmap M1 . gParseJSON opts fargs
instance (FromJSON a) => GFromJSON arity (K1 i a) where
gParseJSON _opts _ = fmap K1 . parseJSON
instance GFromJSON One Par1 where
gParseJSON _opts (From1Args pj _) = fmap Par1 . pj
instance (FromJSON1 f) => GFromJSON One (Rec1 f) where
gParseJSON _opts (From1Args pj pjl) = fmap Rec1 . liftParseJSON pj pjl
instance GFromJSON arity U1 where
gParseJSON _opts _ v
| isEmptyArray v = pure U1
| otherwise = typeMismatch "unit constructor (U1)" v
instance ( ConsFromJSON arity a
, AllNullary (C1 c a) allNullary
, ParseSum arity (C1 c a) allNullary
) => GFromJSON arity (D1 d (C1 c a)) where
gParseJSON opts fargs
| tagSingleConstructors opts
= fmap M1
. (unTagged :: Tagged allNullary (Parser (C1 c a p)) -> Parser (C1 c a p))
. parseSum opts fargs
| otherwise = fmap M1 . fmap M1 . consParseJSON opts fargs
instance (ConsFromJSON arity a) => GFromJSON arity (C1 c a) where
gParseJSON opts fargs = fmap M1 . consParseJSON opts fargs
instance ( FromProduct arity a, FromProduct arity b
, ProductSize a, ProductSize b
) => GFromJSON arity (a :*: b) where
gParseJSON opts fargs = withArray "product (:*:)" $ \arr ->
let lenArray = V.length arr
lenProduct = (unTagged2 :: Tagged2 (a :*: b) Int -> Int)
productSize in
if lenArray == lenProduct
then parseProduct opts fargs arr 0 lenProduct
else fail $ "When expecting a product of " ++ show lenProduct ++
" values, encountered an Array of " ++ show lenArray ++
" elements instead"
instance ( AllNullary (a :+: b) allNullary
, ParseSum arity (a :+: b) allNullary
) => GFromJSON arity (a :+: b) where
gParseJSON opts fargs =
(unTagged :: Tagged allNullary (Parser ((a :+: b) d)) ->
Parser ((a :+: b) d))
. parseSum opts fargs
instance (FromJSON1 f, GFromJSON One g) => GFromJSON One (f :.: g) where
gParseJSON opts fargs =
let gpj = gParseJSON opts fargs in
fmap Comp1 . liftParseJSON gpj (listParser gpj)
class ParseSum arity f allNullary where
parseSum :: Options -> FromArgs arity a
-> Value -> Tagged allNullary (Parser (f a))
instance ( SumFromString f
, FromPair arity f
, FromTaggedObject arity f
, FromUntaggedValue arity f
) => ParseSum arity f True where
parseSum opts fargs
| allNullaryToStringTag opts = Tagged . parseAllNullarySum opts
| otherwise = Tagged . parseNonAllNullarySum opts fargs
instance ( FromPair arity f
, FromTaggedObject arity f
, FromUntaggedValue arity f
) => ParseSum arity f False where
parseSum opts fargs = Tagged . parseNonAllNullarySum opts fargs
parseAllNullarySum :: SumFromString f => Options -> Value -> Parser (f a)
parseAllNullarySum opts = withText "Text" $ \key ->
maybe (notFound key) return $
parseSumFromString opts key
class SumFromString f where
parseSumFromString :: Options -> Text -> Maybe (f a)
instance (SumFromString a, SumFromString b) => SumFromString (a :+: b) where
parseSumFromString opts key = (L1 <$> parseSumFromString opts key) <|>
(R1 <$> parseSumFromString opts key)
instance (Constructor c) => SumFromString (C1 c U1) where
parseSumFromString opts key | key == name = Just $ M1 U1
| otherwise = Nothing
where
name = pack $ constructorTagModifier opts $
conName (undefined :: t c U1 p)
parseNonAllNullarySum :: ( FromPair arity f
, FromTaggedObject arity f
, FromUntaggedValue arity f
) => Options -> FromArgs arity c
-> Value -> Parser (f c)
parseNonAllNullarySum opts fargs =
case sumEncoding opts of
TaggedObject{..} ->
withObject "Object" $ \obj -> do
tag <- obj .: pack tagFieldName
fromMaybe (notFound tag) $
parseFromTaggedObject opts fargs contentsFieldName obj tag
ObjectWithSingleField ->
withObject "Object" $ \obj ->
case H.toList obj of
[pair@(tag, _)] -> fromMaybe (notFound tag) $
parsePair opts fargs pair
_ -> fail "Object doesn't have a single field"
TwoElemArray ->
withArray "Array" $ \arr ->
if V.length arr == 2
then case V.unsafeIndex arr 0 of
String tag -> fromMaybe (notFound tag) $
parsePair opts fargs (tag, V.unsafeIndex arr 1)
_ -> fail "First element is not a String"
else fail "Array doesn't have 2 elements"
UntaggedValue -> parseUntaggedValue opts fargs
class FromTaggedObject arity f where
parseFromTaggedObject :: Options -> FromArgs arity a
-> String -> Object
-> Text -> Maybe (Parser (f a))
instance ( FromTaggedObject arity a, FromTaggedObject arity b) =>
FromTaggedObject arity (a :+: b) where
parseFromTaggedObject opts fargs contentsFieldName obj tag =
(fmap L1 <$> parseFromTaggedObject opts fargs contentsFieldName obj tag) <|>
(fmap R1 <$> parseFromTaggedObject opts fargs contentsFieldName obj tag)
instance ( FromTaggedObject' arity f
, Constructor c
) => FromTaggedObject arity (C1 c f) where
parseFromTaggedObject opts fargs contentsFieldName obj tag
| tag == name = Just $ M1 <$> parseFromTaggedObject'
opts fargs contentsFieldName obj
| otherwise = Nothing
where
name = pack $ constructorTagModifier opts $
conName (undefined :: t c f p)
class FromTaggedObject' arity f where
parseFromTaggedObject' :: Options -> FromArgs arity a -> String
-> Object -> Parser (f a)
class FromTaggedObject'' arity f isRecord where
parseFromTaggedObject'' :: Options -> FromArgs arity a -> String
-> Object -> Tagged isRecord (Parser (f a))
instance ( IsRecord f isRecord
, FromTaggedObject'' arity f isRecord
) => FromTaggedObject' arity f where
parseFromTaggedObject' opts fargs contentsFieldName =
(unTagged :: Tagged isRecord (Parser (f a)) -> Parser (f a)) .
parseFromTaggedObject'' opts fargs contentsFieldName
instance (FromRecord arity f) => FromTaggedObject'' arity f True where
parseFromTaggedObject'' opts fargs _ =
Tagged . parseRecord opts fargs Nothing
instance (GFromJSON arity f) => FromTaggedObject'' arity f False where
parseFromTaggedObject'' opts fargs contentsFieldName = Tagged .
(gParseJSON opts fargs <=< (.: pack contentsFieldName))
instance OVERLAPPING_ FromTaggedObject'' arity U1 False where
parseFromTaggedObject'' _ _ _ _ = Tagged (pure U1)
class ConsFromJSON arity f where
consParseJSON :: Options -> FromArgs arity a
-> Value -> Parser (f a)
class ConsFromJSON' arity f isRecord where
consParseJSON' :: Options -> FromArgs arity a
-> Maybe Text
-> Value -> Tagged isRecord (Parser (f a))
instance ( IsRecord f isRecord
, ConsFromJSON' arity f isRecord
) => ConsFromJSON arity f where
consParseJSON opts fargs v = let
(v2,lab) = case (unwrapUnaryRecords opts,isUnary (undefined :: f a)) of
(True,True) -> (object [(pack "dummy",v)], Just $ pack "dummy")
_ ->(v,Nothing)
in (unTagged :: Tagged isRecord (Parser (f a)) -> Parser (f a))
$ consParseJSON' opts fargs lab v2
instance (FromRecord arity f) => ConsFromJSON' arity f True where
consParseJSON' opts fargs mlab = Tagged . withObject "record (:*:)"
(parseRecord opts fargs mlab)
instance (GFromJSON arity f) => ConsFromJSON' arity f False where
consParseJSON' opts fargs _ = Tagged . gParseJSON opts fargs
class FromRecord arity f where
parseRecord :: Options -> FromArgs arity a
-> Maybe Text
-> Object -> Parser (f a)
instance ( FromRecord arity a
, FromRecord arity b
) => FromRecord arity (a :*: b) where
parseRecord opts fargs _ obj =
(:*:) <$> parseRecord opts fargs Nothing obj
<*> parseRecord opts fargs Nothing obj
instance OVERLAPPABLE_ (Selector s, GFromJSON arity a) =>
FromRecord arity (S1 s a) where
parseRecord opts fargs lab =
(<?> Key label) . gParseJSON opts fargs <=< (.: label)
where
label = fromMaybe defLabel lab
defLabel = pack . fieldLabelModifier opts $
selName (undefined :: t s a p)
instance INCOHERENT_ (Selector s, FromJSON a) =>
FromRecord arity (S1 s (K1 i (Maybe a))) where
parseRecord _ _ (Just lab) obj = M1 . K1 <$> obj .:? lab
parseRecord opts _ Nothing obj = M1 . K1 <$> obj .:? pack label
where
label = fieldLabelModifier opts $
selName (undefined :: t s (K1 i (Maybe a)) p)
instance INCOHERENT_ (Selector s, FromJSON a) =>
FromRecord arity (S1 s (K1 i (Semigroup.Option a))) where
parseRecord opts fargs lab obj = wrap <$> parseRecord opts fargs lab obj
where
wrap :: S1 s (K1 i (Maybe a)) p -> S1 s (K1 i (Semigroup.Option a)) p
wrap (M1 (K1 a)) = M1 (K1 (Semigroup.Option a))
class FromProduct arity f where
parseProduct :: Options -> FromArgs arity a
-> Array -> Int -> Int
-> Parser (f a)
instance ( FromProduct arity a
, FromProduct arity b
) => FromProduct arity (a :*: b) where
parseProduct opts fargs arr ix len =
(:*:) <$> parseProduct opts fargs arr ix lenL
<*> parseProduct opts fargs arr ixR lenR
where
lenL = len `unsafeShiftR` 1
ixR = ix + lenL
lenR = len lenL
instance (GFromJSON arity a) => FromProduct arity (S1 s a) where
parseProduct opts fargs arr ix _ =
gParseJSON opts fargs $ V.unsafeIndex arr ix
class FromPair arity f where
parsePair :: Options -> FromArgs arity a
-> Pair -> Maybe (Parser (f a))
instance ( FromPair arity a
, FromPair arity b
) => FromPair arity (a :+: b) where
parsePair opts fargs pair = (fmap L1 <$> parsePair opts fargs pair) <|>
(fmap R1 <$> parsePair opts fargs pair)
instance ( Constructor c
, GFromJSON arity a
, ConsFromJSON arity a
) => FromPair arity (C1 c a) where
parsePair opts fargs (tag, value)
| tag == tag' = Just $ gParseJSON opts fargs value
| otherwise = Nothing
where
tag' = pack $ constructorTagModifier opts $
conName (undefined :: t c a p)
class FromUntaggedValue arity f where
parseUntaggedValue :: Options -> FromArgs arity a
-> Value -> Parser (f a)
instance
( FromUntaggedValue arity a
, FromUntaggedValue arity b
) => FromUntaggedValue arity (a :+: b)
where
parseUntaggedValue opts fargs value =
L1 <$> parseUntaggedValue opts fargs value <|>
R1 <$> parseUntaggedValue opts fargs value
instance OVERLAPPABLE_
( GFromJSON arity a
, ConsFromJSON arity a
) => FromUntaggedValue arity (C1 c a)
where
parseUntaggedValue = gParseJSON
instance OVERLAPPING_
( Constructor c )
=> FromUntaggedValue arity (C1 c U1)
where
parseUntaggedValue opts _ (String s)
| s == pack (constructorTagModifier opts (conName (undefined :: t c U1 p))) =
pure $ M1 U1
| otherwise =
fail $ "Invalid tag: " ++ unpack s
parseUntaggedValue _ _ v = typeMismatch (conName (undefined :: t c U1 p)) v
notFound :: Text -> Parser a
notFound key = fail $ "The key \"" ++ unpack key ++ "\" was not found"
instance FromJSON2 Const where
liftParseJSON2 p _ _ _ = fmap Const . p
instance FromJSON a => FromJSON1 (Const a) where
liftParseJSON _ _ = fmap Const . parseJSON
instance FromJSON a => FromJSON (Const a b) where
parseJSON = fmap Const . parseJSON
instance FromJSON1 Maybe where
liftParseJSON _ _ Null = pure Nothing
liftParseJSON p _ a = Just <$> p a
instance (FromJSON a) => FromJSON (Maybe a) where
parseJSON = parseJSON1
instance FromJSON2 Either where
liftParseJSON2 pA _ pB _ (Object (H.toList -> [(key, value)]))
| key == left = Left <$> pA value <?> Key left
| key == right = Right <$> pB value <?> Key right
where
left, right :: Text
left = "Left"
right = "Right"
liftParseJSON2 _ _ _ _ _ = fail $
"expected an object with a single property " ++
"where the property key should be either " ++
"\"Left\" or \"Right\""
instance (FromJSON a) => FromJSON1 (Either a) where
liftParseJSON = liftParseJSON2 parseJSON parseJSONList
instance (FromJSON a, FromJSON b) => FromJSON (Either a b) where
parseJSON = parseJSON2
instance FromJSON Bool where
parseJSON = withBool "Bool" pure
instance FromJSONKey Bool where
fromJSONKey = FromJSONKeyTextParser $ \t -> case t of
"true" -> pure True
"false" -> pure False
_ -> fail $ "Cannot parse key into Bool: " ++ T.unpack t
instance FromJSON Ordering where
parseJSON = withText "Ordering" $ \s ->
case s of
"LT" -> return LT
"EQ" -> return EQ
"GT" -> return GT
_ -> fail "Parsing Ordering value failed: expected \"LT\", \"EQ\", or \"GT\""
instance FromJSON () where
parseJSON = withArray "()" $ \v ->
if V.null v
then pure ()
else fail "Expected an empty array"
instance FromJSON Char where
parseJSON = withText "Char" $ \t ->
if T.compareLength t 1 == EQ
then pure $ T.head t
else fail "Expected a string of length 1"
parseJSONList = withText "String" $ pure . T.unpack
instance FromJSON Double where
parseJSON = parseRealFloat "Double"
instance FromJSONKey Double where
fromJSONKey = FromJSONKeyTextParser $ \t -> case t of
"NaN" -> pure (0/0)
"Infinity" -> pure (1/0)
"-Infinity" -> pure (negate 1/0)
_ -> Scientific.toRealFloat <$> parseScientificText t
instance FromJSON Number where
parseJSON (Number s) = pure $ scientificToNumber s
parseJSON Null = pure (D (0/0))
parseJSON v = typeMismatch "Number" v
instance FromJSON Float where
parseJSON = parseRealFloat "Float"
instance FromJSONKey Float where
fromJSONKey = FromJSONKeyTextParser $ \t -> case t of
"NaN" -> pure (0/0)
"Infinity" -> pure (1/0)
"-Infinity" -> pure (negate 1/0)
_ -> Scientific.toRealFloat <$> parseScientificText t
instance (FromJSON a, Integral a) => FromJSON (Ratio a) where
parseJSON = withObject "Rational" $ \obj ->
(%) <$> obj .: "numerator"
<*> obj .: "denominator"
instance HasResolution a => FromJSON (Fixed a) where
parseJSON = withScientific "Fixed" $ pure . realToFrac
instance FromJSON Int where
parseJSON = parseBoundedIntegral "Int"
instance FromJSONKey Int where
fromJSONKey = FromJSONKeyTextParser $ parseBoundedIntegralText "Int"
instance FromJSON Integer where
parseJSON = parseIntegral "Integer"
instance FromJSONKey Integer where
fromJSONKey = FromJSONKeyTextParser $ parseIntegralText "Integer"
instance FromJSON Natural where
parseJSON value = do
integer :: Integer <- parseIntegral "Natural" value
if integer < 0 then
fail $ "expected Natural, encountered negative number " <> show integer
else
pure $ fromIntegral integer
instance FromJSONKey Natural where
fromJSONKey = FromJSONKeyTextParser $ \text -> do
integer :: Integer <- parseIntegralText "Natural" text
if integer < 0 then
fail $ "expected Natural, encountered negative number " <> show integer
else
pure $ fromIntegral integer
instance FromJSON Int8 where
parseJSON = parseBoundedIntegral "Int8"
instance FromJSONKey Int8 where
fromJSONKey = FromJSONKeyTextParser $ parseBoundedIntegralText "Int8"
instance FromJSON Int16 where
parseJSON = parseBoundedIntegral "Int16"
instance FromJSONKey Int16 where
fromJSONKey = FromJSONKeyTextParser $ parseBoundedIntegralText "Int16"
instance FromJSON Int32 where
parseJSON = parseBoundedIntegral "Int32"
instance FromJSONKey Int32 where
fromJSONKey = FromJSONKeyTextParser $ parseBoundedIntegralText "Int32"
instance FromJSON Int64 where
parseJSON = parseBoundedIntegral "Int64"
instance FromJSONKey Int64 where
fromJSONKey = FromJSONKeyTextParser $ parseBoundedIntegralText "Int64"
instance FromJSON Word where
parseJSON = parseBoundedIntegral "Word"
instance FromJSONKey Word where
fromJSONKey = FromJSONKeyTextParser $ parseBoundedIntegralText "Word"
instance FromJSON Word8 where
parseJSON = parseBoundedIntegral "Word8"
instance FromJSONKey Word8 where
fromJSONKey = FromJSONKeyTextParser $ parseBoundedIntegralText "Word8"
instance FromJSON Word16 where
parseJSON = parseBoundedIntegral "Word16"
instance FromJSONKey Word16 where
fromJSONKey = FromJSONKeyTextParser $ parseBoundedIntegralText "Word16"
instance FromJSON Word32 where
parseJSON = parseBoundedIntegral "Word32"
instance FromJSONKey Word32 where
fromJSONKey = FromJSONKeyTextParser $ parseBoundedIntegralText "Word32"
instance FromJSON Word64 where
parseJSON = parseBoundedIntegral "Word64"
instance FromJSONKey Word64 where
fromJSONKey = FromJSONKeyTextParser $ parseBoundedIntegralText "Word64"
instance FromJSON CTime where
parseJSON = fmap CTime . parseJSON
instance FromJSON Text where
parseJSON = withText "Text" pure
instance FromJSONKey Text where
fromJSONKey = fromJSONKeyCoerce
instance FromJSON LT.Text where
parseJSON = withText "Lazy Text" $ pure . LT.fromStrict
instance FromJSONKey LT.Text where
fromJSONKey = FromJSONKeyText LT.fromStrict
instance FromJSON Version where
parseJSON = withText "Version" parseVersionText
instance FromJSONKey Version where
fromJSONKey = FromJSONKeyTextParser parseVersionText
parseVersionText :: Text -> Parser Version
parseVersionText = go . readP_to_S parseVersion . unpack
where
go [(v,[])] = return v
go (_ : xs) = go xs
go _ = fail "could not parse Version"
instance FromJSON1 NonEmpty where
liftParseJSON p _ = withArray "NonEmpty a" $
(>>= ne) . Tr.sequence . zipWith (parseIndexedJSON p) [0..] . V.toList
where
ne [] = fail "Expected a NonEmpty but got an empty list"
ne (x:xs) = pure (x :| xs)
instance (FromJSON a) => FromJSON (NonEmpty a) where
parseJSON = parseJSON1
instance FromJSON Scientific where
parseJSON = withScientific "Scientific" pure
instance FromJSON1 DList.DList where
liftParseJSON p _ = withArray "DList a" $
fmap DList.fromList .
Tr.sequence . zipWith (parseIndexedJSON p) [0..] . V.toList
instance (FromJSON a) => FromJSON (DList.DList a) where
parseJSON = parseJSON1
instance FromJSON1 Identity where
liftParseJSON p _ a = Identity <$> p a
liftParseJSONList _ p a = fmap Identity <$> p a
instance (FromJSON a) => FromJSON (Identity a) where
parseJSON = parseJSON1
parseJSONList = liftParseJSONList parseJSON parseJSONList
instance (FromJSONKey a) => FromJSONKey (Identity a) where
fromJSONKey = coerceFromJSONKeyFunction (fromJSONKey :: FromJSONKeyFunction a)
fromJSONKeyList = coerceFromJSONKeyFunction (fromJSONKeyList :: FromJSONKeyFunction [a])
instance (FromJSON1 f, FromJSON1 g) => FromJSON1 (Compose f g) where
liftParseJSON p pl a = Compose <$> liftParseJSON g gl a
where
g = liftParseJSON p pl
gl = liftParseJSONList p pl
liftParseJSONList p pl a = map Compose <$> liftParseJSONList g gl a
where
g = liftParseJSON p pl
gl = liftParseJSONList p pl
instance (FromJSON1 f, FromJSON1 g, FromJSON a) => FromJSON (Compose f g a) where
parseJSON = parseJSON1
parseJSONList = liftParseJSONList parseJSON parseJSONList
instance (FromJSON1 f, FromJSON1 g) => FromJSON1 (Product f g) where
liftParseJSON p pl a = uncurry Pair <$> liftParseJSON2 px pxl py pyl a
where
px = liftParseJSON p pl
pxl = liftParseJSONList p pl
py = liftParseJSON p pl
pyl = liftParseJSONList p pl
instance (FromJSON1 f, FromJSON1 g, FromJSON a) => FromJSON (Product f g a) where
parseJSON = parseJSON1
instance (FromJSON1 f, FromJSON1 g) => FromJSON1 (Sum f g) where
liftParseJSON p pl (Object (H.toList -> [(key, value)]))
| key == inl = InL <$> liftParseJSON p pl value <?> Key inl
| key == inr = InR <$> liftParseJSON p pl value <?> Key inl
where
inl, inr :: Text
inl = "InL"
inr = "InR"
liftParseJSON _ _ _ = fail $
"expected an object with a single property " ++
"where the property key should be either " ++
"\"InL\" or \"InR\""
instance (FromJSON1 f, FromJSON1 g, FromJSON a) => FromJSON (Sum f g a) where
parseJSON = parseJSON1
instance FromJSON1 Seq.Seq where
liftParseJSON p _ = withArray "Seq a" $
fmap Seq.fromList .
Tr.sequence . zipWith (parseIndexedJSON p) [0..] . V.toList
instance (FromJSON a) => FromJSON (Seq.Seq a) where
parseJSON = parseJSON1
instance (Ord a, FromJSON a) => FromJSON (Set.Set a) where
parseJSON = fmap Set.fromList . parseJSON
instance FromJSON IntSet.IntSet where
parseJSON = fmap IntSet.fromList . parseJSON
instance FromJSON1 IntMap.IntMap where
liftParseJSON p pl = fmap IntMap.fromList . liftParseJSON p' pl'
where
p' = liftParseJSON2 parseJSON parseJSONList p pl
pl' = liftParseJSONList2 parseJSON parseJSONList p pl
instance FromJSON a => FromJSON (IntMap.IntMap a) where
parseJSON = fmap IntMap.fromList . parseJSON
instance (FromJSONKey k, Ord k) => FromJSON1 (M.Map k) where
liftParseJSON p _ = case fromJSONKey of
FromJSONKeyCoerce _-> withObject "Map k v" $
fmap (H.foldrWithKey (M.insert . unsafeCoerce) M.empty) . H.traverseWithKey (\k v -> p v <?> Key k)
FromJSONKeyText f -> withObject "Map k v" $
fmap (H.foldrWithKey (M.insert . f) M.empty) . H.traverseWithKey (\k v -> p v <?> Key k)
FromJSONKeyTextParser f -> withObject "Map k v" $
H.foldrWithKey (\k v m -> M.insert <$> f k <?> Key k <*> p v <?> Key k <*> m) (pure M.empty)
FromJSONKeyValue f -> withArray "Map k v" $ \arr ->
fmap M.fromList . Tr.sequence .
zipWith (parseIndexedJSONPair f p) [0..] . V.toList $ arr
instance (FromJSONKey k, Ord k, FromJSON v) => FromJSON (M.Map k v) where
parseJSON = parseJSON1
instance FromJSON1 Tree.Tree where
liftParseJSON p pl = go
where
go v = uncurry Tree.Node <$> liftParseJSON2 p pl p' pl' v
p' = liftParseJSON go (listParser go)
pl'= liftParseJSONList go (listParser go)
instance (FromJSON v) => FromJSON (Tree.Tree v) where
parseJSON = parseJSON1
instance FromJSON UUID.UUID where
parseJSON = withText "UUID" $
maybe (fail "Invalid UUID") pure . UUID.fromText
instance FromJSONKey UUID.UUID where
fromJSONKey = FromJSONKeyTextParser $
maybe (fail "Invalid UUID") pure . UUID.fromText
instance FromJSON1 Vector where
liftParseJSON p _ = withArray "Vector a" $
V.mapM (uncurry $ parseIndexedJSON p) . V.indexed
instance (FromJSON a) => FromJSON (Vector a) where
parseJSON = parseJSON1
vectorParseJSON :: (FromJSON a, VG.Vector w a) => String -> Value -> Parser (w a)
vectorParseJSON s = withArray s $ fmap V.convert . V.mapM (uncurry $ parseIndexedJSON parseJSON) . V.indexed
instance (Storable a, FromJSON a) => FromJSON (VS.Vector a) where
parseJSON = vectorParseJSON "Data.Vector.Storable.Vector a"
instance (VP.Prim a, FromJSON a) => FromJSON (VP.Vector a) where
parseJSON = vectorParseJSON "Data.Vector.Primitive.Vector a"
instance (VG.Vector VU.Vector a, FromJSON a) => FromJSON (VU.Vector a) where
parseJSON = vectorParseJSON "Data.Vector.Unboxed.Vector a"
instance (Eq a, Hashable a, FromJSON a) => FromJSON (HashSet.HashSet a) where
parseJSON = fmap HashSet.fromList . parseJSON
instance (FromJSONKey k, Eq k, Hashable k) => FromJSON1 (H.HashMap k) where
liftParseJSON p _ = case fromJSONKey of
FromJSONKeyCoerce _ -> withObject "HashMap ~Text v" $
uc . H.traverseWithKey (\k v -> p v <?> Key k)
FromJSONKeyText f -> withObject "HashMap k v" $
fmap (mapKey f) . H.traverseWithKey (\k v -> p v <?> Key k)
FromJSONKeyTextParser f -> withObject "HashMap k v" $
H.foldrWithKey (\k v m -> H.insert <$> f k <?> Key k <*> p v <?> Key k <*> m) (pure H.empty)
FromJSONKeyValue f -> withArray "Map k v" $ \arr ->
fmap H.fromList . Tr.sequence .
zipWith (parseIndexedJSONPair f p) [0..] . V.toList $ arr
where
uc :: Parser (H.HashMap Text v) -> Parser (H.HashMap k v)
uc = unsafeCoerce
instance (FromJSON v, FromJSONKey k, Eq k, Hashable k) => FromJSON (H.HashMap k v) where
parseJSON = parseJSON1
instance FromJSON Value where
parseJSON = pure
instance FromJSON DotNetTime where
parseJSON = withText "DotNetTime" $ \t ->
let (s,m) = T.splitAt (T.length t 5) t
t' = T.concat [s,".",m]
in case parseTime defaultTimeLocale "/Date(%s%Q)/" (unpack t') of
Just d -> pure (DotNetTime d)
_ -> fail "could not parse .NET time"
instance FromJSON Day where
parseJSON = withText "Day" (Time.run Time.day)
instance FromJSONKey Day where
fromJSONKey = FromJSONKeyTextParser (Time.run Time.day)
instance FromJSON TimeOfDay where
parseJSON = withText "TimeOfDay" (Time.run Time.timeOfDay)
instance FromJSONKey TimeOfDay where
fromJSONKey = FromJSONKeyTextParser (Time.run Time.timeOfDay)
instance FromJSON LocalTime where
parseJSON = withText "LocalTime" (Time.run Time.localTime)
instance FromJSONKey LocalTime where
fromJSONKey = FromJSONKeyTextParser (Time.run Time.localTime)
instance FromJSON ZonedTime where
parseJSON = withText "ZonedTime" (Time.run Time.zonedTime)
instance FromJSONKey ZonedTime where
fromJSONKey = FromJSONKeyTextParser (Time.run Time.zonedTime)
instance FromJSON UTCTime where
parseJSON = withText "UTCTime" (Time.run Time.utcTime)
instance FromJSONKey UTCTime where
fromJSONKey = FromJSONKeyTextParser (Time.run Time.utcTime)
instance FromJSON NominalDiffTime where
parseJSON = withScientific "NominalDiffTime" $ pure . realToFrac
instance FromJSON DiffTime where
parseJSON = withScientific "DiffTime" $ pure . realToFrac
instance FromJSON1 Monoid.Dual where
liftParseJSON p _ = fmap Monoid.Dual . p
instance FromJSON a => FromJSON (Monoid.Dual a) where
parseJSON = parseJSON1
instance FromJSON1 Monoid.First where
liftParseJSON p p' = fmap Monoid.First . liftParseJSON p p'
instance FromJSON a => FromJSON (Monoid.First a) where
parseJSON = parseJSON1
instance FromJSON1 Monoid.Last where
liftParseJSON p p' = fmap Monoid.Last . liftParseJSON p p'
instance FromJSON a => FromJSON (Monoid.Last a) where
parseJSON = parseJSON1
instance FromJSON1 Semigroup.Min where
liftParseJSON p _ a = Semigroup.Min <$> p a
liftParseJSONList _ p a = fmap Semigroup.Min <$> p a
instance (FromJSON a) => FromJSON (Semigroup.Min a) where
parseJSON = parseJSON1
parseJSONList = liftParseJSONList parseJSON parseJSONList
instance FromJSON1 Semigroup.Max where
liftParseJSON p _ a = Semigroup.Max <$> p a
liftParseJSONList _ p a = fmap Semigroup.Max <$> p a
instance (FromJSON a) => FromJSON (Semigroup.Max a) where
parseJSON = parseJSON1
parseJSONList = liftParseJSONList parseJSON parseJSONList
instance FromJSON1 Semigroup.First where
liftParseJSON p _ a = Semigroup.First <$> p a
liftParseJSONList _ p a = fmap Semigroup.First <$> p a
instance (FromJSON a) => FromJSON (Semigroup.First a) where
parseJSON = parseJSON1
parseJSONList = liftParseJSONList parseJSON parseJSONList
instance FromJSON1 Semigroup.Last where
liftParseJSON p _ a = Semigroup.Last <$> p a
liftParseJSONList _ p a = fmap Semigroup.Last <$> p a
instance (FromJSON a) => FromJSON (Semigroup.Last a) where
parseJSON = parseJSON1
parseJSONList = liftParseJSONList parseJSON parseJSONList
instance FromJSON1 Semigroup.WrappedMonoid where
liftParseJSON p _ a = Semigroup.WrapMonoid <$> p a
liftParseJSONList _ p a = fmap Semigroup.WrapMonoid <$> p a
instance (FromJSON a) => FromJSON (Semigroup.WrappedMonoid a) where
parseJSON = parseJSON1
parseJSONList = liftParseJSONList parseJSON parseJSONList
instance FromJSON1 Semigroup.Option where
liftParseJSON p p' = fmap Semigroup.Option . liftParseJSON p p'
instance FromJSON a => FromJSON (Semigroup.Option a) where
parseJSON = parseJSON1
instance FromJSON1 Proxy where
liftParseJSON _ _ Null = pure Proxy
liftParseJSON _ _ v = typeMismatch "Proxy" v
instance FromJSON (Proxy a) where
parseJSON Null = pure Proxy
parseJSON v = typeMismatch "Proxy" v
instance FromJSON2 Tagged where
liftParseJSON2 _ _ p _ = fmap Tagged . p
instance FromJSON1 (Tagged a) where
liftParseJSON p _ = fmap Tagged . p
instance FromJSON b => FromJSON (Tagged a b) where
parseJSON = parseJSON1
instance FromJSONKey b => FromJSONKey (Tagged a b) where
fromJSONKey = coerceFromJSONKeyFunction (fromJSONKey :: FromJSONKeyFunction b)
fromJSONKeyList = (fmap . fmap) Tagged fromJSONKeyList
instance (FromJSON a, FromJSON b) => FromJSONKey (a,b)
instance (FromJSON a, FromJSON b, FromJSON c) => FromJSONKey (a,b,c)
instance (FromJSON a, FromJSON b, FromJSON c, FromJSON d) => FromJSONKey (a,b,c,d)
instance FromJSONKey Char where
fromJSONKey = FromJSONKeyTextParser $ \t ->
if T.length t == 1
then return (T.index t 0)
else typeMismatch "Expected Char but String didn't contain exactly one character" (String t)
fromJSONKeyList = FromJSONKeyText T.unpack
instance (FromJSONKey a, FromJSON a) => FromJSONKey [a] where
fromJSONKey = fromJSONKeyList
instance FromJSON2 (,) where
liftParseJSON2 pA _ pB _ = withArray "(a, b)" $ \t ->
let n = V.length t
in if n == 2
then (,)
<$> parseJSONElemAtIndex pA 0 t
<*> parseJSONElemAtIndex pB 1 t
else fail $ "cannot unpack array of length " ++ show n ++ " into a tuple of length 2"
instance (FromJSON a) => FromJSON1 ((,) a) where
liftParseJSON = liftParseJSON2 parseJSON parseJSONList
instance (FromJSON a, FromJSON b) => FromJSON (a, b) where
parseJSON = parseJSON2
instance (FromJSON a) => FromJSON2 ((,,) a) where
liftParseJSON2 pB _ pC _ = withArray "(a, b, c)" $ \t ->
let n = V.length t
in if n == 3
then (,,)
<$> parseJSONElemAtIndex parseJSON 0 t
<*> parseJSONElemAtIndex pB 1 t
<*> parseJSONElemAtIndex pC 2 t
else fail $ "cannot unpack array of length " ++ show n ++ " into a tuple of length 3"
instance (FromJSON a, FromJSON b) => FromJSON1 ((,,) a b) where
liftParseJSON = liftParseJSON2 parseJSON parseJSONList
instance (FromJSON a, FromJSON b, FromJSON c) => FromJSON (a, b, c) where
parseJSON = parseJSON2
instance (FromJSON a, FromJSON b) => FromJSON2 ((,,,) a b) where
liftParseJSON2 pC _ pD _ = withArray "(a, b, c, d)" $ \t ->
let n = V.length t
in if n == 4
then (,,,)
<$> parseJSONElemAtIndex parseJSON 0 t
<*> parseJSONElemAtIndex parseJSON 1 t
<*> parseJSONElemAtIndex pC 2 t
<*> parseJSONElemAtIndex pD 3 t
else fail $ "cannot unpack array of length " ++ show n ++ " into a tuple of length 4"
instance (FromJSON a, FromJSON b, FromJSON c) => FromJSON1 ((,,,) a b c) where
liftParseJSON = liftParseJSON2 parseJSON parseJSONList
instance (FromJSON a, FromJSON b, FromJSON c, FromJSON d) => FromJSON (a, b, c, d) where
parseJSON = parseJSON2
instance (FromJSON a, FromJSON b, FromJSON c) => FromJSON2 ((,,,,) a b c) where
liftParseJSON2 pD _ pE _ = withArray "(a, b, c, d, e)" $ \t ->
let n = V.length t
in if n == 5
then (,,,,)
<$> parseJSONElemAtIndex parseJSON 0 t
<*> parseJSONElemAtIndex parseJSON 1 t
<*> parseJSONElemAtIndex parseJSON 2 t
<*> parseJSONElemAtIndex pD 3 t
<*> parseJSONElemAtIndex pE 4 t
else fail $ "cannot unpack array of length " ++ show n ++ " into a tuple of length 5"
instance (FromJSON a, FromJSON b, FromJSON c, FromJSON d) => FromJSON1 ((,,,,) a b c d) where
liftParseJSON = liftParseJSON2 parseJSON parseJSONList
instance (FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e) => FromJSON (a, b, c, d, e) where
parseJSON = parseJSON2
instance (FromJSON a, FromJSON b, FromJSON c, FromJSON d) => FromJSON2 ((,,,,,) a b c d) where
liftParseJSON2 pE _ pF _ = withArray "(a, b, c, d, e, f)" $ \t ->
let n = V.length t
in if n == 6
then (,,,,,)
<$> parseJSONElemAtIndex parseJSON 0 t
<*> parseJSONElemAtIndex parseJSON 1 t
<*> parseJSONElemAtIndex parseJSON 2 t
<*> parseJSONElemAtIndex parseJSON 3 t
<*> parseJSONElemAtIndex pE 4 t
<*> parseJSONElemAtIndex pF 5 t
else fail $ "cannot unpack array of length " ++ show n ++ " into a tuple of length 6"
instance (FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e) => FromJSON1 ((,,,,,) a b c d e) where
liftParseJSON = liftParseJSON2 parseJSON parseJSONList
instance (FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f) => FromJSON (a, b, c, d, e, f) where
parseJSON = parseJSON2
instance (FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e) => FromJSON2 ((,,,,,,) a b c d e) where
liftParseJSON2 pF _ pG _ = withArray "(a, b, c, d, e, f, g)" $ \t ->
let n = V.length t
in if n == 7
then (,,,,,,)
<$> parseJSONElemAtIndex parseJSON 0 t
<*> parseJSONElemAtIndex parseJSON 1 t
<*> parseJSONElemAtIndex parseJSON 2 t
<*> parseJSONElemAtIndex parseJSON 3 t
<*> parseJSONElemAtIndex parseJSON 4 t
<*> parseJSONElemAtIndex pF 5 t
<*> parseJSONElemAtIndex pG 6 t
else fail $ "cannot unpack array of length " ++ show n ++ " into a tuple of length 7"
instance (FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f) => FromJSON1 ((,,,,,,) a b c d e f) where
liftParseJSON = liftParseJSON2 parseJSON parseJSONList
instance (FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g) => FromJSON (a, b, c, d, e, f, g) where
parseJSON = parseJSON2
instance (FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f) => FromJSON2 ((,,,,,,,) a b c d e f) where
liftParseJSON2 pG _ pH _ = withArray "(a, b, c, d, e, f, g, h)" $ \t ->
let n = V.length t
in if n == 8
then (,,,,,,,)
<$> parseJSONElemAtIndex parseJSON 0 t
<*> parseJSONElemAtIndex parseJSON 1 t
<*> parseJSONElemAtIndex parseJSON 2 t
<*> parseJSONElemAtIndex parseJSON 3 t
<*> parseJSONElemAtIndex parseJSON 4 t
<*> parseJSONElemAtIndex parseJSON 5 t
<*> parseJSONElemAtIndex pG 6 t
<*> parseJSONElemAtIndex pH 7 t
else fail $ "cannot unpack array of length " ++ show n ++ " into a tuple of length 8"
instance (FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g) => FromJSON1 ((,,,,,,,) a b c d e f g) where
liftParseJSON = liftParseJSON2 parseJSON parseJSONList
instance (FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h) => FromJSON (a, b, c, d, e, f, g, h) where
parseJSON = parseJSON2
instance (FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g) => FromJSON2 ((,,,,,,,,) a b c d e f g) where
liftParseJSON2 pH _ pI _ = withArray "(a, b, c, d, e, f, g, h, i)" $ \t ->
let n = V.length t
in if n == 9
then (,,,,,,,,)
<$> parseJSONElemAtIndex parseJSON 0 t
<*> parseJSONElemAtIndex parseJSON 1 t
<*> parseJSONElemAtIndex parseJSON 2 t
<*> parseJSONElemAtIndex parseJSON 3 t
<*> parseJSONElemAtIndex parseJSON 4 t
<*> parseJSONElemAtIndex parseJSON 5 t
<*> parseJSONElemAtIndex parseJSON 6 t
<*> parseJSONElemAtIndex pH 7 t
<*> parseJSONElemAtIndex pI 8 t
else fail $ "cannot unpack array of length " ++ show n ++ " into a tuple of length 9"
instance (FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h) => FromJSON1 ((,,,,,,,,) a b c d e f g h) where
liftParseJSON = liftParseJSON2 parseJSON parseJSONList
instance (FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i) => FromJSON (a, b, c, d, e, f, g, h, i) where
parseJSON = parseJSON2
instance (FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h) => FromJSON2 ((,,,,,,,,,) a b c d e f g h) where
liftParseJSON2 pI _ pJ _ = withArray "(a, b, c, d, e, f, g, h, i, j)" $ \t ->
let n = V.length t
in if n == 10
then (,,,,,,,,,)
<$> parseJSONElemAtIndex parseJSON 0 t
<*> parseJSONElemAtIndex parseJSON 1 t
<*> parseJSONElemAtIndex parseJSON 2 t
<*> parseJSONElemAtIndex parseJSON 3 t
<*> parseJSONElemAtIndex parseJSON 4 t
<*> parseJSONElemAtIndex parseJSON 5 t
<*> parseJSONElemAtIndex parseJSON 6 t
<*> parseJSONElemAtIndex parseJSON 7 t
<*> parseJSONElemAtIndex pI 8 t
<*> parseJSONElemAtIndex pJ 9 t
else fail $ "cannot unpack array of length " ++ show n ++ " into a tuple of length 10"
instance (FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i) => FromJSON1 ((,,,,,,,,,) a b c d e f g h i) where
liftParseJSON = liftParseJSON2 parseJSON parseJSONList
instance (FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i, FromJSON j) => FromJSON (a, b, c, d, e, f, g, h, i, j) where
parseJSON = parseJSON2
instance (FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i) => FromJSON2 ((,,,,,,,,,,) a b c d e f g h i) where
liftParseJSON2 pJ _ pK _ = withArray "(a, b, c, d, e, f, g, h, i, j, k)" $ \t ->
let n = V.length t
in if n == 11
then (,,,,,,,,,,)
<$> parseJSONElemAtIndex parseJSON 0 t
<*> parseJSONElemAtIndex parseJSON 1 t
<*> parseJSONElemAtIndex parseJSON 2 t
<*> parseJSONElemAtIndex parseJSON 3 t
<*> parseJSONElemAtIndex parseJSON 4 t
<*> parseJSONElemAtIndex parseJSON 5 t
<*> parseJSONElemAtIndex parseJSON 6 t
<*> parseJSONElemAtIndex parseJSON 7 t
<*> parseJSONElemAtIndex parseJSON 8 t
<*> parseJSONElemAtIndex pJ 9 t
<*> parseJSONElemAtIndex pK 10 t
else fail $ "cannot unpack array of length " ++ show n ++ " into a tuple of length 11"
instance (FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i, FromJSON j) => FromJSON1 ((,,,,,,,,,,) a b c d e f g h i j) where
liftParseJSON = liftParseJSON2 parseJSON parseJSONList
instance (FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i, FromJSON j, FromJSON k) => FromJSON (a, b, c, d, e, f, g, h, i, j, k) where
parseJSON = parseJSON2
instance (FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i, FromJSON j) => FromJSON2 ((,,,,,,,,,,,) a b c d e f g h i j) where
liftParseJSON2 pK _ pL _ = withArray "(a, b, c, d, e, f, g, h, i, j, k, l)" $ \t ->
let n = V.length t
in if n == 12
then (,,,,,,,,,,,)
<$> parseJSONElemAtIndex parseJSON 0 t
<*> parseJSONElemAtIndex parseJSON 1 t
<*> parseJSONElemAtIndex parseJSON 2 t
<*> parseJSONElemAtIndex parseJSON 3 t
<*> parseJSONElemAtIndex parseJSON 4 t
<*> parseJSONElemAtIndex parseJSON 5 t
<*> parseJSONElemAtIndex parseJSON 6 t
<*> parseJSONElemAtIndex parseJSON 7 t
<*> parseJSONElemAtIndex parseJSON 8 t
<*> parseJSONElemAtIndex parseJSON 9 t
<*> parseJSONElemAtIndex pK 10 t
<*> parseJSONElemAtIndex pL 11 t
else fail $ "cannot unpack array of length " ++ show n ++ " into a tuple of length 12"
instance (FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i, FromJSON j, FromJSON k) => FromJSON1 ((,,,,,,,,,,,) a b c d e f g h i j k) where
liftParseJSON = liftParseJSON2 parseJSON parseJSONList
instance (FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i, FromJSON j, FromJSON k, FromJSON l) => FromJSON (a, b, c, d, e, f, g, h, i, j, k, l) where
parseJSON = parseJSON2
instance (FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i, FromJSON j, FromJSON k) => FromJSON2 ((,,,,,,,,,,,,) a b c d e f g h i j k) where
liftParseJSON2 pL _ pM _ = withArray "(a, b, c, d, e, f, g, h, i, j, k, l, m)" $ \t ->
let n = V.length t
in if n == 13
then (,,,,,,,,,,,,)
<$> parseJSONElemAtIndex parseJSON 0 t
<*> parseJSONElemAtIndex parseJSON 1 t
<*> parseJSONElemAtIndex parseJSON 2 t
<*> parseJSONElemAtIndex parseJSON 3 t
<*> parseJSONElemAtIndex parseJSON 4 t
<*> parseJSONElemAtIndex parseJSON 5 t
<*> parseJSONElemAtIndex parseJSON 6 t
<*> parseJSONElemAtIndex parseJSON 7 t
<*> parseJSONElemAtIndex parseJSON 8 t
<*> parseJSONElemAtIndex parseJSON 9 t
<*> parseJSONElemAtIndex parseJSON 10 t
<*> parseJSONElemAtIndex pL 11 t
<*> parseJSONElemAtIndex pM 12 t
else fail $ "cannot unpack array of length " ++ show n ++ " into a tuple of length 13"
instance (FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i, FromJSON j, FromJSON k, FromJSON l) => FromJSON1 ((,,,,,,,,,,,,) a b c d e f g h i j k l) where
liftParseJSON = liftParseJSON2 parseJSON parseJSONList
instance (FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i, FromJSON j, FromJSON k, FromJSON l, FromJSON m) => FromJSON (a, b, c, d, e, f, g, h, i, j, k, l, m) where
parseJSON = parseJSON2
instance (FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i, FromJSON j, FromJSON k, FromJSON l) => FromJSON2 ((,,,,,,,,,,,,,) a b c d e f g h i j k l) where
liftParseJSON2 pM _ pN _ = withArray "(a, b, c, d, e, f, g, h, i, j, k, l, m, n)" $ \t ->
let n = V.length t
in if n == 14
then (,,,,,,,,,,,,,)
<$> parseJSONElemAtIndex parseJSON 0 t
<*> parseJSONElemAtIndex parseJSON 1 t
<*> parseJSONElemAtIndex parseJSON 2 t
<*> parseJSONElemAtIndex parseJSON 3 t
<*> parseJSONElemAtIndex parseJSON 4 t
<*> parseJSONElemAtIndex parseJSON 5 t
<*> parseJSONElemAtIndex parseJSON 6 t
<*> parseJSONElemAtIndex parseJSON 7 t
<*> parseJSONElemAtIndex parseJSON 8 t
<*> parseJSONElemAtIndex parseJSON 9 t
<*> parseJSONElemAtIndex parseJSON 10 t
<*> parseJSONElemAtIndex parseJSON 11 t
<*> parseJSONElemAtIndex pM 12 t
<*> parseJSONElemAtIndex pN 13 t
else fail $ "cannot unpack array of length " ++ show n ++ " into a tuple of length 14"
instance (FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i, FromJSON j, FromJSON k, FromJSON l, FromJSON m) => FromJSON1 ((,,,,,,,,,,,,,) a b c d e f g h i j k l m) where
liftParseJSON = liftParseJSON2 parseJSON parseJSONList
instance (FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i, FromJSON j, FromJSON k, FromJSON l, FromJSON m, FromJSON n) => FromJSON (a, b, c, d, e, f, g, h, i, j, k, l, m, n) where
parseJSON = parseJSON2
instance (FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i, FromJSON j, FromJSON k, FromJSON l, FromJSON m) => FromJSON2 ((,,,,,,,,,,,,,,) a b c d e f g h i j k l m) where
liftParseJSON2 pN _ pO _ = withArray "(a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)" $ \t ->
let n = V.length t
in if n == 15
then (,,,,,,,,,,,,,,)
<$> parseJSONElemAtIndex parseJSON 0 t
<*> parseJSONElemAtIndex parseJSON 1 t
<*> parseJSONElemAtIndex parseJSON 2 t
<*> parseJSONElemAtIndex parseJSON 3 t
<*> parseJSONElemAtIndex parseJSON 4 t
<*> parseJSONElemAtIndex parseJSON 5 t
<*> parseJSONElemAtIndex parseJSON 6 t
<*> parseJSONElemAtIndex parseJSON 7 t
<*> parseJSONElemAtIndex parseJSON 8 t
<*> parseJSONElemAtIndex parseJSON 9 t
<*> parseJSONElemAtIndex parseJSON 10 t
<*> parseJSONElemAtIndex parseJSON 11 t
<*> parseJSONElemAtIndex parseJSON 12 t
<*> parseJSONElemAtIndex pN 13 t
<*> parseJSONElemAtIndex pO 14 t
else fail $ "cannot unpack array of length " ++ show n ++ " into a tuple of length 15"
instance (FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i, FromJSON j, FromJSON k, FromJSON l, FromJSON m, FromJSON n) => FromJSON1 ((,,,,,,,,,,,,,,) a b c d e f g h i j k l m n) where
liftParseJSON = liftParseJSON2 parseJSON parseJSONList
instance (FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i, FromJSON j, FromJSON k, FromJSON l, FromJSON m, FromJSON n, FromJSON o) => FromJSON (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) where
parseJSON = parseJSON2