|
11 | 11 | {-# LANGUAGE TypeFamilies #-}
|
12 | 12 | {-# OPTIONS_GHC -Wall #-}
|
13 | 13 | module Cardano.Faucet.Types.API (
|
14 |
| - WithdrawlRequest(..), wAddress, gRecaptchaResponse |
15 |
| - , WithdrawlResult(..), _WithdrawlError, _WithdrawlSuccess |
| 14 | + WithdrawalRequest(..), wAddress, gRecaptchaResponse |
| 15 | + , WithdrawalResult(..), _WithdrawalError, _WithdrawalSuccess |
16 | 16 | , DepositRequest(..), dWalletId, dAmount
|
17 | 17 | , DepositResult(..)
|
18 | 18 | , GCaptchaResponse(..)
|
19 |
| - , WithdrawlQFull(..) |
| 19 | + , WithdrawalQFull(..) |
20 | 20 | ) where
|
21 | 21 |
|
22 | 22 | import Control.Exception
|
@@ -48,80 +48,80 @@ instance IsString GCaptchaResponse where
|
48 | 48 |
|
49 | 49 | --------------------------------------------------------------------------------
|
50 | 50 | -- | A request to withdraw ADA from the faucet wallet
|
51 |
| -data WithdrawlRequest = WithdrawlRequest { |
| 51 | +data WithdrawalRequest = WithdrawalRequest { |
52 | 52 | -- | The address to send the ADA to
|
53 | 53 | _wAddress :: !(V1 Address)
|
54 | 54 | -- | The "g-recaptcha-response" field sent by the form
|
55 | 55 | , _gRecaptchaResponse :: !GCaptchaResponse
|
56 | 56 | } deriving (Show, Typeable, Generic)
|
57 | 57 |
|
58 |
| -makeLenses ''WithdrawlRequest |
| 58 | +makeLenses ''WithdrawalRequest |
59 | 59 |
|
60 |
| -instance FromJSON WithdrawlRequest where |
61 |
| - parseJSON = withObject "WithdrawlRequest" $ \v -> WithdrawlRequest |
| 60 | +instance FromJSON WithdrawalRequest where |
| 61 | + parseJSON = withObject "WithdrawalRequest" $ \v -> WithdrawalRequest |
62 | 62 | <$> v .: "address"
|
63 | 63 | <*> (GCaptchaResponse <$> v .: "g-recaptcha-response")
|
64 | 64 |
|
65 |
| -instance FromForm WithdrawlRequest where |
66 |
| - fromForm f = WithdrawlRequest |
| 65 | +instance FromForm WithdrawalRequest where |
| 66 | + fromForm f = WithdrawalRequest |
67 | 67 | <$> parseUnique "address" f
|
68 | 68 | <*> (GCaptchaResponse <$> parseUnique "g-recaptcha-response" f)
|
69 | 69 |
|
70 |
| -instance ToSchema WithdrawlRequest where |
| 70 | +instance ToSchema WithdrawalRequest where |
71 | 71 | declareNamedSchema _ = do
|
72 | 72 | addrSchema <- declareSchemaRef (Proxy :: Proxy (V1 Address))
|
73 | 73 | recaptchaSchema <- declareSchemaRef (Proxy :: Proxy Text)
|
74 |
| - return $ NamedSchema (Just "WithdrawlRequest") $ mempty |
| 74 | + return $ NamedSchema (Just "WithdrawalRequest") $ mempty |
75 | 75 | & type_ .~ SwaggerObject
|
76 | 76 | & properties .~ (mempty & at "address" ?~ addrSchema
|
77 | 77 | & at "g-recaptcha-response" ?~ recaptchaSchema)
|
78 | 78 | & required .~ ["address", "g-recaptcha-response"]
|
79 | 79 |
|
80 |
| -instance ToJSON WithdrawlRequest where |
81 |
| - toJSON (WithdrawlRequest w g) = |
| 80 | +instance ToJSON WithdrawalRequest where |
| 81 | + toJSON (WithdrawalRequest w g) = |
82 | 82 | object [ "address" .= w
|
83 | 83 | , "g-recaptcha-response" .= (g ^. _Wrapped)]
|
84 | 84 |
|
85 | 85 |
|
86 | 86 | --------------------------------------------------------------------------------
|
87 |
| -data WithdrawlQFull = WithdrawlQFull deriving (Show, Generic, Exception) |
| 87 | +data WithdrawalQFull = WithdrawalQFull deriving (Show, Generic, Exception) |
88 | 88 |
|
89 |
| -instance ToJSON WithdrawlQFull where |
| 89 | +instance ToJSON WithdrawalQFull where |
90 | 90 | toJSON _ =
|
91 |
| - object [ "error" .= ("Withdrawl queue is full" :: Text) |
| 91 | + object [ "error" .= ("Withdrawal queue is full" :: Text) |
92 | 92 | , "status" .= ("error" :: Text) ]
|
93 | 93 |
|
94 |
| -instance ToSchema WithdrawlQFull where |
| 94 | +instance ToSchema WithdrawalQFull where |
95 | 95 | declareNamedSchema _ = do
|
96 | 96 | strSchema <- declareSchemaRef (Proxy :: Proxy Text)
|
97 |
| - return $ NamedSchema (Just "WithdrawlQFull") $ mempty |
| 97 | + return $ NamedSchema (Just "WithdrawalQFull") $ mempty |
98 | 98 | & type_ .~ SwaggerObject
|
99 | 99 | & properties .~ (mempty
|
100 | 100 | & at "status" ?~ strSchema
|
101 | 101 | & at "error" ?~ strSchema)
|
102 | 102 | & required .~ ["status"]
|
103 | 103 |
|
104 | 104 | --------------------------------------------------------------------------------
|
105 |
| -data WithdrawlResult = |
106 |
| - WithdrawlError Text -- ^ Error with http client error |
107 |
| - | WithdrawlSuccess Transaction -- ^ Success with transaction details |
| 105 | +data WithdrawalResult = |
| 106 | + WithdrawalError Text -- ^ Error with http client error |
| 107 | + | WithdrawalSuccess Transaction -- ^ Success with transaction details |
108 | 108 | deriving (Show, Typeable, Generic)
|
109 | 109 |
|
110 |
| -makePrisms ''WithdrawlResult |
| 110 | +makePrisms ''WithdrawalResult |
111 | 111 |
|
112 |
| -instance ToJSON WithdrawlResult where |
113 |
| - toJSON (WithdrawlSuccess txn) = |
| 112 | +instance ToJSON WithdrawalResult where |
| 113 | + toJSON (WithdrawalSuccess txn) = |
114 | 114 | object ["success" .= txn]
|
115 |
| - toJSON (WithdrawlError err) = |
| 115 | + toJSON (WithdrawalError err) = |
116 | 116 | object ["error" .= err]
|
117 | 117 |
|
118 | 118 | wdDesc :: Text
|
119 | 119 | wdDesc = "An object with either a success field containing the transaction or "
|
120 | 120 | <> "an error field containing the ClientError from the wallet as a string"
|
121 | 121 |
|
122 |
| -instance ToSchema WithdrawlResult where |
| 122 | +instance ToSchema WithdrawalResult where |
123 | 123 | declareNamedSchema = genericDeclareNamedSchema defaultSchemaOptions
|
124 |
| - { constructorTagModifier = map Char.toLower . drop (length ("Withdrawl" :: String)) } |
| 124 | + { constructorTagModifier = map Char.toLower . drop (length ("Withdrawal" :: String)) } |
125 | 125 | & mapped.mapped.schema.description ?~ wdDesc
|
126 | 126 |
|
127 | 127 | --------------------------------------------------------------------------------
|
|
0 commit comments