10
10
{-# LANGUAGE PolyKinds #-}
11
11
{-# LANGUAGE RecordWildCards #-}
12
12
{-# LANGUAGE ScopedTypeVariables #-}
13
+ {-# LANGUAGE TypeApplications #-}
13
14
{-# LANGUAGE TypeOperators #-}
14
15
{-# LANGUAGE TupleSections #-}
15
16
{-# LANGUAGE UndecidableInstances #-}
@@ -158,6 +159,8 @@ import qualified Data.Primitive.Types as PM
158
159
import qualified Data.Primitive.PrimArray as PM
159
160
160
161
import Data.Coerce (Coercible , coerce )
162
+ import GHC.TypeNats
163
+ import Data.Kind (Type )
161
164
162
165
parseIndexedJSON :: (Value -> Parser a ) -> Int -> Value -> Parser a
163
166
parseIndexedJSON p idx value = p value <?> Index idx
@@ -1010,6 +1013,7 @@ instance ( ConstructorNames f
1010
1013
, FromPair arity f
1011
1014
, FromTaggedObject arity f
1012
1015
, FromUntaggedValue arity f
1016
+ , FromTaggedFlatObject arity f
1013
1017
) => ParseSum arity f True where
1014
1018
parseSum p@ (tname :* opts :* _)
1015
1019
| allNullaryToStringTag opts = Tagged . parseAllNullarySum tname opts
@@ -1019,6 +1023,7 @@ instance ( ConstructorNames f
1019
1023
, FromPair arity f
1020
1024
, FromTaggedObject arity f
1021
1025
, FromUntaggedValue arity f
1026
+ , FromTaggedFlatObject arity f
1022
1027
) => ParseSum arity f False where
1023
1028
parseSum p = Tagged . parseNonAllNullarySum p
1024
1029
@@ -1101,6 +1106,7 @@ parseNonAllNullarySum :: forall f c arity.
1101
1106
( FromPair arity f
1102
1107
, FromTaggedObject arity f
1103
1108
, FromUntaggedValue arity f
1109
+ , FromTaggedFlatObject arity f
1104
1110
, ConstructorNames f
1105
1111
) => TypeName :* Options :* FromArgs arity c
1106
1112
-> Value -> Parser (f c )
@@ -1118,6 +1124,17 @@ parseNonAllNullarySum p@(tname :* opts :* _) =
1118
1124
" , but found tag " ++ show tag
1119
1125
cnames_ = unTagged2 (constructorTags (constructorTagModifier opts) :: Tagged2 f [String ])
1120
1126
1127
+ TaggedFlatObject {.. } ->
1128
+ withObject tname $ \ obj -> do
1129
+ let tagKey = pack tagFieldName
1130
+ badTag tag = failWith_ $ \ cnames ->
1131
+ " expected tag field to be one of " ++ show cnames ++
1132
+ " , but found tag " ++ show tag
1133
+ cnames_ = unTagged2 (constructorTags (constructorTagModifier opts) :: Tagged2 f [String ])
1134
+ tag <- contextType tname . contextTag tagKey cnames_ $ obj .: tagKey
1135
+ fromMaybe (badTag tag <?> Key tagKey) $
1136
+ parseTaggedFlatObject (tag :* p) obj
1137
+
1121
1138
ObjectWithSingleField ->
1122
1139
withObject tname $ \ obj -> case H. toList obj of
1123
1140
[(tag, v)] -> maybe (badTag tag) (<?> Key tag) $
@@ -1401,6 +1418,63 @@ instance ( Constructor c
1401
1418
1402
1419
--------------------------------------------------------------------------------
1403
1420
1421
+ class FromTaggedFlatObject arity f where
1422
+ parseTaggedFlatObject :: Text :* TypeName :* Options :* FromArgs arity a
1423
+ -> Object
1424
+ -> Maybe (Parser (f a ))
1425
+
1426
+ instance ( FromTaggedFlatObject arity f
1427
+ , FromTaggedFlatObject arity g
1428
+ ) => FromTaggedFlatObject arity (f :+: g ) where
1429
+ parseTaggedFlatObject p obj =
1430
+ (fmap L1 <$> parseTaggedFlatObject p obj) <|>
1431
+ (fmap R1 <$> parseTaggedFlatObject p obj)
1432
+
1433
+ instance ( IsRecord f isRecord
1434
+ , FromTaggedFlatObject' arity f isRecord
1435
+ , Constructor c
1436
+ ) => FromTaggedFlatObject arity (C1 c f ) where
1437
+ parseTaggedFlatObject (tag :* p@ (_ :* opts :* _)) obj
1438
+ | tag == tag' = Just $ fmap M1 $ (unTagged @ Type @ isRecord ) $ parseTaggedFlatObject' (cname :* p) obj
1439
+ | otherwise = Nothing
1440
+ where
1441
+ tag' = pack $ constructorTagModifier opts cname
1442
+ cname = conName (undefined :: M1 i c a p )
1443
+
1444
+ class FromTaggedFlatObject' arity f isRecord where
1445
+ parseTaggedFlatObject' :: ConName :* TypeName :* Options :* FromArgs arity a
1446
+ -> Object
1447
+ -> Tagged isRecord (Parser (f a ))
1448
+
1449
+ instance (RecordFromJSON arity f , FieldNames f ) => FromTaggedFlatObject' arity f True where
1450
+ parseTaggedFlatObject' p = Tagged . recordParseJSON (True :* p)
1451
+
1452
+ instance FromTaggedFlatObject' arity U1 False where
1453
+ parseTaggedFlatObject' _ _ = Tagged (pure U1 )
1454
+
1455
+ instance OVERLAPPABLE_ (PositionFromObject 1 arity f ) => FromTaggedFlatObject' arity f False where
1456
+ parseTaggedFlatObject' (_ :* p) obj = Tagged (positionFromObject (Proxy @ 1 ) p obj)
1457
+
1458
+ class KnownNat n => PositionFromObject n arity f where
1459
+ positionFromObject :: Proxy n
1460
+ -> TypeName :* Options :* FromArgs arity a
1461
+ -> Object
1462
+ -> Parser (f a )
1463
+
1464
+ instance (KnownNat n , GFromJSON arity a ) => PositionFromObject n arity (S1 m a ) where
1465
+ positionFromObject _ (_ :* opts :* fargs) obj =
1466
+ explicitParseField (gParseJSON opts fargs) obj $ pack $ show $ natVal $ Proxy @ n
1467
+
1468
+ instance ( PositionFromObject n arity f
1469
+ , PositionFromObject (n + 1 ) arity g
1470
+ ) => PositionFromObject n arity (f :*: g ) where
1471
+ positionFromObject _ p obj =
1472
+ (:*:)
1473
+ <$> positionFromObject (Proxy @ n ) p obj
1474
+ <*> positionFromObject (Proxy @ (n + 1 )) p obj
1475
+
1476
+ --------------------------------------------------------------------------------
1477
+
1404
1478
class FromUntaggedValue arity f where
1405
1479
parseUntaggedValue :: TypeName :* Options :* FromArgs arity a
1406
1480
-> Value
0 commit comments