Skip to content
This repository was archived by the owner on Aug 18, 2020. It is now read-only.

Commit 70a86f7

Browse files
committed
Merge pull request #3707 [remove wallet orphan instances] into CO-372/TheGreatCleanup
2 parents 95387ef + cdc4649 commit 70a86f7

File tree

12 files changed

+52
-112
lines changed

12 files changed

+52
-112
lines changed

wallet-new/cardano-sl-wallet-new.cabal

-4
Original file line numberDiff line numberDiff line change
@@ -115,10 +115,6 @@ library
115115
Cardano.Wallet.Kernel.Util.StrictNonEmpty
116116
Cardano.Wallet.Kernel.Util.StrictStateT
117117
Cardano.Wallet.Kernel.Wallets
118-
Cardano.Wallet.Orphans
119-
Cardano.Wallet.Orphans.Aeson
120-
Cardano.Wallet.Orphans.Arbitrary
121-
Cardano.Wallet.Orphans.Bi
122118
Cardano.Wallet.Server
123119
Cardano.Wallet.Server.CLI
124120
Cardano.Wallet.Server.Middlewares

wallet-new/src/Cardano/Wallet/API/V1/Swagger/Example.hs

+1-2
Original file line numberDiff line numberDiff line change
@@ -8,7 +8,6 @@ import Data.Swagger (Definitions, NamedSchema (..), Schema,
88
import Data.Swagger.Declare (Declare)
99
import Data.Typeable (typeOf)
1010

11-
import Cardano.Wallet.Orphans.Arbitrary ()
1211
import Test.QuickCheck (Arbitrary (..), listOf1)
1312
import Test.QuickCheck.Gen (Gen (..), resize)
1413
import Test.QuickCheck.Random (mkQCGen)
@@ -21,7 +20,7 @@ class Arbitrary a => Example a where
2120
example = arbitrary
2221

2322
instance Example ()
24-
instance Example a => Example (NonEmpty a)
23+
instance (Example a, Arbitrary (NonEmpty a) ) => Example (NonEmpty a)
2524

2625
-- NOTE: we don't want to see empty list examples in our swagger doc :)
2726
instance Example a => Example [a] where

wallet-new/src/Cardano/Wallet/API/V1/Types.hs

+39-11
Original file line numberDiff line numberDiff line change
@@ -11,7 +11,7 @@
1111
{-# LANGUAGE StandaloneDeriving #-}
1212
{-# LANGUAGE StrictData #-}
1313
{-# LANGUAGE TemplateHaskell #-}
14-
14+
{-# LANGUAGE ViewPatterns #-}
1515
-- The hlint parser fails on the `pattern` function, so we disable the
1616
-- language extension here.
1717
{-# LANGUAGE NoPatternSynonyms #-}
@@ -163,8 +163,9 @@ import Data.Swagger.Internal.TypeShape (GenericHasSimpleShape,
163163
GenericShape)
164164
import Data.Text (Text, dropEnd, toLower)
165165
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+
(%))
168169
import qualified Formatting.Buildable
169170
import Generics.SOP.TH (deriveGeneric)
170171
import GHC.Generics (Generic, Rep)
@@ -188,7 +189,6 @@ import Cardano.Wallet.API.V1.Generic (jsendErrorGenericParseJSON,
188189
jsendErrorGenericToJSON)
189190
import Cardano.Wallet.API.V1.Swagger.Example (Example, example,
190191
genExample)
191-
import Cardano.Wallet.Orphans.Aeson ()
192192
import Cardano.Wallet.Types.UtxoStatistics
193193
import Cardano.Wallet.Util (mkJsonKey, showApiUtcTime)
194194

@@ -197,7 +197,6 @@ import qualified Pos.Binary.Class as Bi
197197
import qualified Pos.Chain.Txp as Txp
198198
import qualified Pos.Chain.Update as Core
199199
import qualified Pos.Client.Txp.Util as Core
200-
import Pos.Core (addressF)
201200
import qualified Pos.Core as Core
202201
import Pos.Crypto (PublicKey (..), decodeHash, hashHexF)
203202
import qualified Pos.Crypto.Signing as Core
@@ -208,7 +207,9 @@ import Pos.Infra.Util.LogSafe (BuildableSafeGen (..), SecureLog (..),
208207
buildSafe, buildSafeList, buildSafeMaybe,
209208
deriveSafeBuildable, plainOrSecureF)
210209
import Pos.Util.Servant (Flaggable (..))
210+
import Test.Pos.Chain.Update.Arbitrary ()
211211
import Test.Pos.Core.Arbitrary ()
212+
import Text.ParserCombinators.ReadP (readP_to_S)
212213

213214
-- | Declare generic schema, while documenting properties
214215
-- For instance:
@@ -314,7 +315,7 @@ instance Bounded a => Bounded (V1 a) where
314315
minBound = V1 $ minBound @a
315316
maxBound = V1 $ maxBound @a
316317

317-
instance Buildable a => Buildable (V1 a) where
318+
instance {-# OVERLAPPABLE #-} Buildable a => Buildable (V1 a) where
318319
build (V1 x) = bprint build x
319320

320321
instance Buildable (SecureLog a) => Buildable (SecureLog (V1 a)) where
@@ -323,7 +324,6 @@ instance Buildable (SecureLog a) => Buildable (SecureLog (V1 a)) where
323324
instance (Buildable a, Buildable b) => Buildable (a, b) where
324325
build (a, b) = bprint ("("%build%", "%build%")") a b
325326

326-
327327
--
328328
-- Benign instances
329329
--
@@ -382,8 +382,17 @@ instance ToSchema (V1 Core.Coin) where
382382
& type_ .~ SwaggerNumber
383383
& maximum_ .~ Just (fromIntegral Core.maxCoinVal)
384384

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+
385394
instance ToJSON (V1 Core.Address) where
386-
toJSON (V1 c) = String $ sformat addressF c
395+
toJSON (V1 c) = String $ sformat Core.addressF c
387396

388397
instance FromJSON (V1 Core.Address) where
389398
parseJSON (String a) = case Core.decodeTextAddress a of
@@ -2356,17 +2365,36 @@ instance BuildableSafeGen SlotDuration where
23562365
data NodeSettings = NodeSettings {
23572366
setSlotDuration :: !SlotDuration
23582367
, setSoftwareInfo :: !(V1 Core.SoftwareVersion)
2359-
, setProjectVersion :: !Version
2368+
, setProjectVersion :: !(V1 Version)
23602369
, setGitRevision :: !Text
23612370
} deriving (Show, Eq, Generic)
23622371

23632372
#if !(MIN_VERSION_swagger2(2,2,2))
23642373
-- See note [Version Orphan]
2365-
instance ToSchema Version where
2374+
instance ToSchema (V1 Version) where
23662375
declareNamedSchema _ =
2367-
pure $ NamedSchema (Just "Version") $ mempty
2376+
pure $ NamedSchema (Just "V1Version") $ mempty
23682377
& type_ .~ SwaggerString
23692378

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+
23702398
-- Note [Version Orphan]
23712399
-- I have opened a PR to add an instance of 'Version' to the swagger2
23722400
-- library. When the PR is merged, we can delete the instance here and remove the warning from the file.

wallet-new/src/Cardano/Wallet/Kernel/DB/Util/AcidState.hs

-1
Original file line numberDiff line numberDiff line change
@@ -47,7 +47,6 @@ import Cardano.Wallet.Kernel.DB.Util.IxSet (HasPrimKey, Indexable,
4747
import qualified Cardano.Wallet.Kernel.DB.Util.IxSet as IxSet
4848
import qualified Cardano.Wallet.Kernel.DB.Util.Zoomable as Z
4949
import Cardano.Wallet.Kernel.Util.StrictStateT
50-
import Cardano.Wallet.Orphans ()
5150
import UTxO.Util (mustBeRight)
5251

5352
{-------------------------------------------------------------------------------

wallet-new/src/Cardano/Wallet/Orphans.hs

-19
This file was deleted.

wallet-new/src/Cardano/Wallet/Orphans/Aeson.hs

-11
This file was deleted.

wallet-new/src/Cardano/Wallet/Orphans/Arbitrary.hs

-52
This file was deleted.

wallet-new/src/Cardano/Wallet/Orphans/Bi.hs

-3
This file was deleted.

wallet-new/src/Cardano/Wallet/WalletLayer/Kernel/Settings.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -22,7 +22,7 @@ getNodeSettings w = liftIO $
2222
V1.NodeSettings
2323
<$> (mkSlotDuration <$> Node.getNextEpochSlotDuration node)
2424
<*> (V1 <$> Node.curSoftwareVersion node)
25-
<*> pure version
25+
<*> pure (V1 version)
2626
<*> (mkGitRevision <$> Node.compileInfo node)
2727
where
2828
mkSlotDuration :: Millisecond -> V1.SlotDuration

wallet-new/test/Cardano/Wallet/WalletLayer/QuickCheck.hs

-1
Original file line numberDiff line numberDiff line change
@@ -9,7 +9,6 @@ module Cardano.Wallet.WalletLayer.QuickCheck
99
import Universum
1010

1111
import Cardano.Wallet.Kernel.Diffusion (WalletDiffusion (..))
12-
import Cardano.Wallet.Orphans.Arbitrary ()
1312
import Cardano.Wallet.WalletLayer (ActiveWalletLayer (..),
1413
DeleteAccountError (..), DeleteExternalWalletError (..),
1514
DeleteWalletError (..), GetAccountError (..),

wallet-new/test/MarshallingSpec.hs

+3-2
Original file line numberDiff line numberDiff line change
@@ -9,11 +9,12 @@ import Universum
99
import Control.Lens (from, to)
1010
import Data.Aeson
1111
import qualified Data.ByteString as BS
12-
import Data.SafeCopy hiding (Migrate)
12+
import Data.SafeCopy hiding (Migrate, Version)
1313
import Data.Serialize (runGet, runPut)
1414
import Data.Time (UTCTime (..), fromGregorian)
1515
import Data.Time.Clock.POSIX (POSIXTime)
1616
import Data.Typeable (typeRep)
17+
import Data.Version (Version)
1718
import Pos.Client.Txp.Util (InputSelectionPolicy)
1819
import Pos.Core.NetworkMagic (NetworkMagic (..))
1920
import qualified Pos.Crypto as Crypto
@@ -45,7 +46,6 @@ import Cardano.Wallet.API.V1.Types
4546
import Cardano.Wallet.Kernel.DB.HdWallet (HdRoot)
4647
import Cardano.Wallet.Kernel.DB.InDb (InDb (..))
4748
import qualified Cardano.Wallet.Kernel.Util.Strict as Strict
48-
import Cardano.Wallet.Orphans ()
4949
import qualified Cardano.Wallet.Util as Util
5050

5151
-- | Tests whether or not some instances (JSON, Bi, etc) roundtrips.
@@ -87,6 +87,7 @@ spec = parallel $ describe "Marshalling & Unmarshalling" $ do
8787
aesonRoundtripProp @SyncThroughput Proxy
8888
aesonRoundtripProp @AccountIndex Proxy
8989
aesonRoundtripProp @(V1 AddressOwnership) Proxy
90+
aesonRoundtripProp @(V1 Version) Proxy
9091

9192
-- HttpApiData roundtrips
9293
httpApiDataRoundtripProp @AccountIndex Proxy

wallet-new/test/SwaggerSpec.hs

+8-5
Original file line numberDiff line numberDiff line change
@@ -9,7 +9,6 @@ import qualified Prelude
99
import qualified Data.HashMap.Strict.InsOrd as IOMap
1010
import Data.String.Conv
1111
import Data.Swagger
12-
import Pos.Wallet.Aeson.ClientTypes ()
1312
import Servant
1413
import Servant.Swagger.Test ()
1514
import Test.Hspec
@@ -21,17 +20,15 @@ import Cardano.Wallet.API.Response (ValidJSON)
2120
import qualified Cardano.Wallet.API.V1 as V1
2221
import Cardano.Wallet.API.V1.Swagger ()
2322
import qualified Cardano.Wallet.API.V1.Swagger as Swagger
24-
import Cardano.Wallet.Orphans.Aeson ()
25-
import Cardano.Wallet.Orphans.Arbitrary ()
2623
import Pos.Chain.Update (ApplicationName (..), SoftwareVersion (..))
2724
import Pos.Util.CompileInfo (CompileTimeInfo (CompileTimeInfo),
2825
gitRev)
2926

3027
-- for vendored code
31-
import Data.Aeson (ToJSON)
28+
import Data.Aeson (ToJSON (..))
3229
import Servant.Swagger.Internal.Test (props)
3330
import Servant.Swagger.Internal.TypeLevel (BodyTypes, Every, TMap)
34-
import Test.QuickCheck (Arbitrary)
31+
import Test.QuickCheck (Arbitrary, arbitrary)
3532

3633
-- Syntethic instances and orphans to be able to use `validateEveryToJSON`.
3734
-- In the future, hopefully, we will never need these.
@@ -52,6 +49,12 @@ instance ToSchema NoContent where
5249
& type_ .~ SwaggerArray
5350
& maxLength .~ Just 0
5451

52+
instance Arbitrary NoContent where
53+
arbitrary = pure NoContent
54+
55+
instance ToJSON NoContent where
56+
toJSON NoContent = toJSON ()
57+
5558
spec :: Spec
5659
spec = modifyMaxSuccess (const 10) $ do
5760
describe "Swagger Integration" $ do

0 commit comments

Comments
 (0)