1
1
{-# LANGUAGE DeriveFunctor #-}
2
2
{-# LANGUAGE DeriveGeneric #-}
3
+ {-# LANGUAGE LambdaCase #-}
3
4
{-# LANGUAGE OverloadedLists #-}
4
5
module Cardano.Wallet.API.Response (
5
6
Metadata (.. )
6
7
, ResponseStatus (.. )
7
8
, WalletResponse (.. )
9
+ , JSONValidationError (.. )
8
10
-- * Generating responses for collections
9
11
, respondWith
10
12
, fromSlice
@@ -18,18 +20,22 @@ module Cardano.Wallet.API.Response (
18
20
) where
19
21
20
22
import Prelude
21
- import Universum (Buildable , decodeUtf8 , toText , (<>) )
23
+ import Universum (Buildable , Exception , Text , decodeUtf8 , toText ,
24
+ (<>) )
22
25
23
- import Cardano.Wallet.API.Response.JSend (ResponseStatus (.. ))
24
- import Cardano.Wallet.API.V1.Swagger.Example (Example , example )
25
26
import Control.Lens
26
- import Data.Aeson
27
+ import Data.Aeson ( FromJSON ( .. ), ToJSON ( .. ), eitherDecode , encode )
27
28
import Data.Aeson.Encode.Pretty (encodePretty )
29
+ import qualified Data.Aeson.Options as Serokell
28
30
import Data.Aeson.TH
31
+ import qualified Data.Char as Char
29
32
import Data.Swagger as S hiding (Example , example )
30
33
import Data.Typeable
31
34
import Formatting (bprint , build , (%) )
35
+ import qualified Formatting.Buildable
36
+ import Generics.SOP.TH (deriveGeneric )
32
37
import GHC.Generics (Generic )
38
+ import Servant (err400 )
33
39
import Servant.API.ContentTypes (Accept (.. ), JSON , MimeRender (.. ),
34
40
MimeUnrender (.. ), OctetStream )
35
41
import Test.QuickCheck
@@ -42,14 +48,13 @@ import Cardano.Wallet.API.Request.Pagination (Page (..),
42
48
PerPage (.. ))
43
49
import Cardano.Wallet.API.Request.Sort (SortOperations (.. ))
44
50
import Cardano.Wallet.API.Response.Filter.IxSet as FilterBackend
51
+ import Cardano.Wallet.API.Response.JSend (HasDiagnostic (.. ),
52
+ ResponseStatus (.. ))
45
53
import Cardano.Wallet.API.Response.Sort.IxSet as SortBackend
46
- import Cardano.Wallet.API.V1.Errors
47
- (WalletError (JSONValidationFailed ))
48
-
49
- import qualified Data.Aeson.Options as Serokell
50
- import qualified Data.Char as Char
51
- import qualified Formatting.Buildable
52
-
54
+ import Cardano.Wallet.API.V1.Errors (ToServantError (.. ))
55
+ import Cardano.Wallet.API.V1.Generic (jsendErrorGenericParseJSON ,
56
+ jsendErrorGenericToJSON )
57
+ import Cardano.Wallet.API.V1.Swagger.Example (Example , example )
53
58
54
59
-- | Extra information associated with an HTTP response.
55
60
data Metadata = Metadata
@@ -166,7 +171,7 @@ respondWith :: (Monad m, Indexable' a)
166
171
-> m (WalletResponse [a ])
167
172
respondWith RequestParams {.. } fops sorts generator = do
168
173
(theData, paginationMetadata) <- paginate rpPaginationParams . sortData sorts . applyFilters fops <$> generator
169
- return $ WalletResponse {
174
+ return WalletResponse {
170
175
wrData = theData
171
176
, wrStatus = SuccessStatus
172
177
, wrMeta = Metadata paginationMetadata
@@ -225,3 +230,40 @@ instance Accept ValidJSON where
225
230
226
231
instance ToJSON a => MimeRender ValidJSON a where
227
232
mimeRender _ = mimeRender (Proxy @ JSON )
233
+
234
+
235
+ --
236
+ -- Error from parsing / validating JSON inputs
237
+ --
238
+
239
+ newtype JSONValidationError
240
+ = JSONValidationFailed Text
241
+ deriving (Eq , Show , Generic )
242
+
243
+ deriveGeneric ''JSONValidationError
244
+
245
+ instance ToJSON JSONValidationError where
246
+ toJSON =
247
+ jsendErrorGenericToJSON
248
+
249
+ instance FromJSON JSONValidationError where
250
+ parseJSON =
251
+ jsendErrorGenericParseJSON
252
+
253
+ instance Exception JSONValidationError
254
+
255
+ instance Arbitrary JSONValidationError where
256
+ arbitrary =
257
+ pure (JSONValidationFailed " JSON validation failed." )
258
+
259
+ instance Buildable JSONValidationError where
260
+ build _ =
261
+ bprint " Couldn't decode a JSON input."
262
+
263
+ instance HasDiagnostic JSONValidationError where
264
+ getDiagnosticKey _ =
265
+ " validationError"
266
+
267
+ instance ToServantError JSONValidationError where
268
+ declareServantError _ =
269
+ err400
0 commit comments