@@ -8,6 +8,7 @@ module VVA.API.SyncAiResponseType where
88
99import GHC.Generics (Generic )
1010import Data.Text (Text )
11+ import qualified Data.Text (stripPrefix )
1112import Data.Aeson
1213import qualified Data.Aeson.Types as Aeson
1314import Data.Aeson.Types (Parser )
@@ -51,71 +52,91 @@ instance ToJSON SearchAiResponse where
5152
5253data DRepData = DRepData
5354 { drepId :: Text
54- , motivations :: Text
55- , givenName :: Text
56- , objectives :: Text
57- , status :: Text
55+ -- Missing:
56+ -- , dRepHash :: Text
57+ -- , view :: Text
58+ -- , isScriptBased :: Bool
5859 , url :: Maybe Text
59- , votingPower :: Double
60- , imageUrl :: Maybe TextOrValue
61- -- , imageHash :: Maybe TextOrValue
60+ -- Missing:
61+ -- , dataHash :: Maybe Text
62+ -- , deposit :: Integer
63+ , votingPower :: Double -- We might need to multiply this by 1e6 to get the actual voting power + Int
64+ , status :: Text
65+ -- Missing:
66+ -- , type :: DRepType
67+ -- , latestTxHash :: Maybe Text
68+ -- , latestRegistrationDate :: UTCTime
69+ -- , metadataError :: Maybe Text
6270 , paymentAddress :: Maybe TextOrValue
71+ , givenName :: Maybe Text
72+ , objectives :: Maybe Text
73+ , motivations :: Maybe Text
6374 , qualifications :: Maybe TextOrValue
75+ , imageUrl :: Maybe TextOrValue
76+ , imageHash :: Maybe TextOrValue
6477 , linkReferences :: [Reference ]
6578 , identityReferences :: [Reference ]
6679 } deriving (Show , Generic , ToSchema , ToJSON )
6780
6881instance FromJSON DRepData where
6982 parseJSON = withObject " DRepData" $ \ v -> do
70- drepId <- v .: " drepId"
83+ -- dRep data:
84+ -- drepId <- v .: "drepId"
7185 motivations <- v .: " motivations"
7286 givenName <- v .: " name"
7387 objectives <- v .: " objectives"
7488 status <- v .: " status"
7589 url <- v .:? " url"
7690 votingPower <- (v .: " votingPower" <|> (v .: " metrics" >>= (.: " votingPower" )))
7791
78- imageUrl <- v .:? " image" >>= \ img ->
79- case img of
80- Just _ -> pure img
81- Nothing -> do
82- m <- v .:? " metadata"
83- m1 <- m .::? " json_metadata"
84- m2 <- m1 .::? " body"
85- m3 <- m2 .::? " image"
86- m4 <- m3 .::? " contentUrl"
87- traverse parseJSON m4
92+ --
93+ mMeta <- v .:? " metadata"
94+ mJsonMeta <- mMeta .::? " json_metadata"
95+ mBody <- mJsonMeta .::? " body"
8896
89-
90- paymentAddress <- v .:? " paymentAddress" >>= \ pa ->
91- case pa of
92- Just _ -> pure pa
93- Nothing -> do
94- m <- v .:? " metadata"
95- m1 <- m .::? " json_metadata"
96- m2 <- m1 .::? " body"
97- m3 <- m2 .::? " paymentAddress"
98- traverse parseJSON m3
99-
100- qualifications <- v .:? " qualifications" >>= \ q ->
101- case q of
102- Just _ -> pure q
103- Nothing -> do
104- m <- v .:? " metadata"
105- m1 <- m .::? " json_metadata"
106- m2 <- m1 .::? " body"
107- m3 <- m2 .::? " qualifications"
108- traverse parseJSON m3
109-
110- references <- v .:? " references" >>= \ r ->
111- case r of
112- Just _ -> pure r
97+ drepId <- v .:? " drepId" >>= \ did ->
98+ case did of
99+ Just _ -> pure did
113100 Nothing -> do
114101 m <- v .:? " metadata"
115- m1 <- m .::? " json_metadata"
116- m2 <- m1 .::? " body"
117- m3 <- m2 .::? " references"
118- traverse parseJSON m3
102+ m1 <- m .::? " hex"
103+ traverse parseJSON m1
104+
105+ imageUrl <- do
106+ m <- v .:? " metadata"
107+ m1 <- m .::? " json_metadata"
108+ m2 <- m1 .::? " body"
109+ m3 <- m2 .::? " image"
110+ m4 <- m3 .::? " contentUrl"
111+ traverse parseJSON m4
112+
113+ imageHash <- do
114+ m <- v .:? " metadata"
115+ m1 <- m .::? " json_metadata"
116+ m2 <- m1 .::? " body"
117+ m3 <- m2 .::? " imageHash"
118+ traverse parseJSON m3
119+
120+ paymentAddress <- do
121+ m <- v .:? " metadata"
122+ m1 <- m .::? " json_metadata"
123+ m2 <- m1 .::? " body"
124+ m3 <- m2 .::? " paymentAddress"
125+ traverse parseJSON m3
126+
127+ qualifications <- do
128+ m <- v .:? " metadata"
129+ m1 <- m .::? " json_metadata"
130+ m2 <- m1 .::? " body"
131+ m3 <- m2 .::? " qualifications"
132+ traverse parseJSON m3
133+
134+ references <- do
135+ m <- v .:? " metadata"
136+ m1 <- m .::? " json_metadata"
137+ m2 <- m1 .::? " body"
138+ m3 <- m2 .::? " references"
139+ traverse parseJSON m3
119140
120141 -- Split references by @type
121142 let (linkRefs, identityRefs) = case references of
@@ -127,7 +148,7 @@ instance FromJSON DRepData where
127148
128149 pure $ DRepData
129150 drepId motivations givenName objectives status url votingPower
130- imageUrl paymentAddress qualifications linkRefs identityRefs
151+ imageUrl imageHash paymentAddress qualifications linkRefs identityRefs
131152
132153data Reference = Reference
133154 { refType :: Maybe Text -- "@type"
0 commit comments