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

[CBR-306] Akegalj/co 319/swagger account index #3086

3 changes: 2 additions & 1 deletion wallet-new/cardano-sl-wallet-new.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -39,9 +39,10 @@ library
Cardano.Wallet.API.V1
Cardano.Wallet.API.V1.Accounts
Cardano.Wallet.API.V1.Addresses
Cardano.Wallet.API.V1.Errors
Cardano.Wallet.API.V1.Generic
Cardano.Wallet.API.V1.Errors
Cardano.Wallet.API.V1.Handlers
Cardano.Wallet.API.V1.Headers
Cardano.Wallet.API.V1.Info
Cardano.Wallet.API.V1.LegacyHandlers
Cardano.Wallet.API.V1.LegacyHandlers.Accounts
Expand Down
8 changes: 4 additions & 4 deletions wallet-new/integration/TransactionSpecs.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,14 +5,14 @@ module TransactionSpecs (transactionSpecs) where

import Universum hiding (log)

import Cardano.Wallet.API.V1.Errors hiding (describe)
import Cardano.Wallet.Client.Http
import Control.Concurrent (threadDelay)
import Control.Lens
import qualified Pos.Core as Core
import Test.Hspec

import Control.Concurrent (threadDelay)
import Text.Show.Pretty (ppShow)

import qualified Pos.Core as Core

import Util

{-# ANN module ("HLint: ignore Reduce duplication" :: Text) #-}
Expand Down
2 changes: 1 addition & 1 deletion wallet-new/integration/WalletSpecs.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,8 +5,8 @@ module WalletSpecs (walletSpecs) where

import Universum

import Cardano.Wallet.API.V1.Types (WalletError (WalletAlreadyExists))
import Cardano.Wallet.Client.Http
import Cardano.Wallet.API.V1.Errors (WalletError (WalletAlreadyExists))
import Control.Lens
import Test.Hspec

Expand Down
68 changes: 54 additions & 14 deletions wallet-new/src/Cardano/Wallet/API/Response.hs
Original file line number Diff line number Diff line change
@@ -1,10 +1,12 @@
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedLists #-}
module Cardano.Wallet.API.Response (
Metadata (..)
, ResponseStatus(..)
, WalletResponse(..)
, JSONValidationError(..)
-- * Generating responses for collections
, respondWith
-- * Generating responses for single resources
Expand All @@ -13,33 +15,37 @@ module Cardano.Wallet.API.Response (
) where

import Prelude
import Universum (Buildable, decodeUtf8, toText, (<>))
import Universum (Buildable, Exception, Text, decodeUtf8, toText, (<>))

import Cardano.Wallet.API.Indices (Indexable', IxSet')
import Cardano.Wallet.API.Request (RequestParams (..))
import Cardano.Wallet.API.Request.Filter (FilterOperations (..))
import Cardano.Wallet.API.Request.Pagination (Page (..), PaginationMetadata (..),
PaginationParams (..), PerPage (..))
import Cardano.Wallet.API.Request.Sort (SortOperations (..))
import Cardano.Wallet.API.Response.Filter.IxSet as FilterBackend
import Cardano.Wallet.API.Response.JSend (ResponseStatus (..))
import Cardano.Wallet.API.Response.Sort.IxSet as SortBackend
import Cardano.Wallet.API.V1.Errors (ToServantError (..))
import Cardano.Wallet.API.V1.Generic (gparseJsend, gtoJsend)
import Control.Lens
import Data.Aeson
import Data.Aeson.Encode.Pretty (encodePretty)
import Data.Aeson.TH
import qualified Data.Char as Char
import Data.Swagger as S
import qualified Data.Text.Buildable
import Data.Typeable
import Formatting (bprint, build, (%))
import Generics.SOP.TH (deriveGeneric)
import GHC.Generics (Generic)
import qualified Serokell.Aeson.Options as Serokell
import Servant (err400)
import Servant.API.ContentTypes (Accept (..), JSON, MimeRender (..), MimeUnrender (..),
OctetStream)
import Test.QuickCheck

import Cardano.Wallet.API.Indices (Indexable', IxSet')
import Cardano.Wallet.API.Request (RequestParams (..))
import Cardano.Wallet.API.Request.Filter (FilterOperations (..))
import Cardano.Wallet.API.Request.Pagination (Page (..), PaginationMetadata (..),
PaginationParams (..), PerPage (..))
import Cardano.Wallet.API.Request.Sort (SortOperations (..))
import Cardano.Wallet.API.Response.Filter.IxSet as FilterBackend
import Cardano.Wallet.API.Response.Sort.IxSet as SortBackend
import Cardano.Wallet.API.V1.Errors (WalletError (JSONValidationFailed))
import qualified Data.Char as Char
import qualified Data.Text.Buildable
import qualified Serokell.Aeson.Options as Serokell


-- | Extra information associated with an HTTP response.
data Metadata = Metadata
Expand Down Expand Up @@ -136,7 +142,7 @@ respondWith :: (Monad m, Indexable' a)
-> m (WalletResponse [a])
respondWith RequestParams{..} fops sorts generator = do
(theData, paginationMetadata) <- paginate rpPaginationParams . sortData sorts . applyFilters fops <$> generator
return $ WalletResponse {
return WalletResponse {
wrData = theData
, wrStatus = SuccessStatus
, wrMeta = Metadata paginationMetadata
Expand Down Expand Up @@ -182,3 +188,37 @@ instance Accept ValidJSON where

instance ToJSON a => MimeRender ValidJSON a where
mimeRender _ = mimeRender (Proxy @ JSON)


--
-- Error from parsing / validating JSON inputs
--

Copy link
Contributor Author

@akegalj akegalj Jun 25, 2018

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

@KtorZ I see you have made MigrationFailed an instance of Expcetion , but JSONValidationError doesn't have the same instance. Is there a reason for the separation?

Copy link
Contributor

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Hmmm. No. That's an oversight πŸ‘

newtype JSONValidationError
= JSONValidationFailed Text
deriving (Show, Eq)

deriveGeneric ''JSONValidationError

instance ToJSON JSONValidationError where
toJSON = gtoJsend ErrorStatus

instance FromJSON JSONValidationError where
parseJSON = gparseJsend

instance Exception JSONValidationError

instance Arbitrary JSONValidationError where
arbitrary = oneof
[ pure $ JSONValidationFailed "JSON validation failed."
]

instance Buildable JSONValidationError where
build = \case
JSONValidationFailed _ ->
bprint "Couldn't decode a JSON input."

instance ToServantError JSONValidationError where
declareServantError = \case
JSONValidationFailed _ ->
err400
Loading