11
11
{-# LANGUAGE StandaloneDeriving #-}
12
12
{-# LANGUAGE StrictData #-}
13
13
{-# LANGUAGE TemplateHaskell #-}
14
-
14
+ {-# LANGUAGE ViewPatterns #-}
15
15
-- The hlint parser fails on the `pattern` function, so we disable the
16
16
-- language extension here.
17
17
{-# LANGUAGE NoPatternSynonyms #-}
@@ -163,8 +163,9 @@ import Data.Swagger.Internal.TypeShape (GenericHasSimpleShape,
163
163
GenericShape )
164
164
import Data.Text (Text , dropEnd , toLower )
165
165
import qualified Data.Text as T
166
- import Data.Version (Version )
167
- import Formatting (bprint , build , fconst , int , sformat , stext , (%) )
166
+ import Data.Version (Version (.. ), parseVersion , showVersion )
167
+ import Formatting (bprint , build , fconst , int , sformat , shown , stext ,
168
+ (%) )
168
169
import qualified Formatting.Buildable
169
170
import Generics.SOP.TH (deriveGeneric )
170
171
import GHC.Generics (Generic , Rep )
@@ -188,7 +189,6 @@ import Cardano.Wallet.API.V1.Generic (jsendErrorGenericParseJSON,
188
189
jsendErrorGenericToJSON )
189
190
import Cardano.Wallet.API.V1.Swagger.Example (Example , example ,
190
191
genExample )
191
- import Cardano.Wallet.Orphans.Aeson ()
192
192
import Cardano.Wallet.Types.UtxoStatistics
193
193
import Cardano.Wallet.Util (mkJsonKey , showApiUtcTime )
194
194
@@ -197,7 +197,6 @@ import qualified Pos.Binary.Class as Bi
197
197
import qualified Pos.Chain.Txp as Txp
198
198
import qualified Pos.Chain.Update as Core
199
199
import qualified Pos.Client.Txp.Util as Core
200
- import Pos.Core (addressF )
201
200
import qualified Pos.Core as Core
202
201
import Pos.Crypto (PublicKey (.. ), decodeHash , hashHexF )
203
202
import qualified Pos.Crypto.Signing as Core
@@ -208,7 +207,9 @@ import Pos.Infra.Util.LogSafe (BuildableSafeGen (..), SecureLog (..),
208
207
buildSafe , buildSafeList , buildSafeMaybe ,
209
208
deriveSafeBuildable , plainOrSecureF )
210
209
import Pos.Util.Servant (Flaggable (.. ))
210
+ import Test.Pos.Chain.Update.Arbitrary ()
211
211
import Test.Pos.Core.Arbitrary ()
212
+ import Text.ParserCombinators.ReadP (readP_to_S )
212
213
213
214
-- | Declare generic schema, while documenting properties
214
215
-- For instance:
@@ -314,7 +315,7 @@ instance Bounded a => Bounded (V1 a) where
314
315
minBound = V1 $ minBound @ a
315
316
maxBound = V1 $ maxBound @ a
316
317
317
- instance Buildable a => Buildable (V1 a ) where
318
+ instance {-# OVERLAPPABLE #-} Buildable a => Buildable (V1 a ) where
318
319
build (V1 x) = bprint build x
319
320
320
321
instance Buildable (SecureLog a ) => Buildable (SecureLog (V1 a )) where
@@ -323,7 +324,6 @@ instance Buildable (SecureLog a) => Buildable (SecureLog (V1 a)) where
323
324
instance (Buildable a , Buildable b ) => Buildable (a , b ) where
324
325
build (a, b) = bprint (" (" % build% " , " % build% " )" ) a b
325
326
326
-
327
327
--
328
328
-- Benign instances
329
329
--
@@ -382,8 +382,17 @@ instance ToSchema (V1 Core.Coin) where
382
382
& type_ .~ SwaggerNumber
383
383
& maximum_ .~ Just (fromIntegral Core. maxCoinVal)
384
384
385
+ instance ToHttpApiData Core. Coin where
386
+ toQueryParam = pretty . Core. coinToInteger
387
+
388
+ instance FromHttpApiData Core. Coin where
389
+ parseUrlPiece p = do
390
+ c <- Core. Coin <$> parseQueryParam p
391
+ Core. checkCoin c
392
+ pure c
393
+
385
394
instance ToJSON (V1 Core. Address ) where
386
- toJSON (V1 c) = String $ sformat addressF c
395
+ toJSON (V1 c) = String $ sformat Core. addressF c
387
396
388
397
instance FromJSON (V1 Core. Address ) where
389
398
parseJSON (String a) = case Core. decodeTextAddress a of
@@ -2356,17 +2365,36 @@ instance BuildableSafeGen SlotDuration where
2356
2365
data NodeSettings = NodeSettings {
2357
2366
setSlotDuration :: ! SlotDuration
2358
2367
, setSoftwareInfo :: ! (V1 Core. SoftwareVersion )
2359
- , setProjectVersion :: ! Version
2368
+ , setProjectVersion :: ! ( V1 Version )
2360
2369
, setGitRevision :: ! Text
2361
2370
} deriving (Show , Eq , Generic )
2362
2371
2363
2372
#if !(MIN_VERSION_swagger2(2,2,2))
2364
2373
-- See note [Version Orphan]
2365
- instance ToSchema Version where
2374
+ instance ToSchema ( V1 Version ) where
2366
2375
declareNamedSchema _ =
2367
- pure $ NamedSchema (Just " Version " ) $ mempty
2376
+ pure $ NamedSchema (Just " V1Version " ) $ mempty
2368
2377
& type_ .~ SwaggerString
2369
2378
2379
+ instance Buildable (V1 Version ) where
2380
+ build (V1 v) = bprint shown v
2381
+
2382
+ instance Buildable (SecureLog (V1 Version )) where
2383
+ build (SecureLog x) = Formatting.Buildable. build x
2384
+
2385
+ instance ToJSON (V1 Version ) where
2386
+ toJSON (V1 v) = toJSON (showVersion v)
2387
+
2388
+ instance FromJSON (V1 Version ) where
2389
+ parseJSON (String v) = case readP_to_S parseVersion (T. unpack v) of
2390
+ (reverse -> ((ver,_): _)) -> pure (V1 ver)
2391
+ _ -> mempty
2392
+ parseJSON x = typeMismatch " Not a valid Version" x
2393
+
2394
+ instance Arbitrary (V1 Version ) where
2395
+ arbitrary = fmap V1 arbitrary
2396
+
2397
+
2370
2398
-- Note [Version Orphan]
2371
2399
-- I have opened a PR to add an instance of 'Version' to the swagger2
2372
2400
-- library. When the PR is merged, we can delete the instance here and remove the warning from the file.
0 commit comments