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

Commit 5627705

Browse files
iohk-bors[bot]KtorZ
andcommitted
Merge #4050 #4051
4050: Internal Endpoints Disclaimer r=KtorZ a=KtorZ ## Description <!--- A brief description of this PR and the problem is trying to solve --> As a follow-up from the discussion in cardano-foundation/cardano-wallet#151 (comment), we will add a proper disclaimer in the documentation about the internal endpoints. ## Linked issue <!--- Put here the relevant issue from YouTrack --> cardano-foundation/cardano-wallet#228 4051: Disable node monitoring API by default r=KtorZ a=KtorZ ## Description <!--- A brief description of this PR and the problem is trying to solve --> Instead of using default arguments pointing to files that may or may not be present. It's better to simply not have it by default, and activate it only when needed ## Linked issue <!--- Put here the relevant issue from YouTrack --> Co-authored-by: KtorZ <[email protected]>
3 parents 0bb4e77 + c6cf5be + cd8b177 commit 5627705

File tree

12 files changed

+90
-58
lines changed

12 files changed

+90
-58
lines changed

lib/src/Pos/Client/CLI/NodeOptions.hs

+12-19
Original file line numberDiff line numberDiff line change
@@ -25,15 +25,14 @@ import Data.Version (showVersion)
2525
import NeatInterpolation (text)
2626
import Options.Applicative (Parser, auto, execParser, footerDoc,
2727
fullDesc, header, help, helper, info, infoOption, long,
28-
metavar, option, progDesc, showDefault, strOption, switch,
29-
value)
28+
metavar, option, progDesc, strOption, switch, value)
3029
import Text.PrettyPrint.ANSI.Leijen (Doc)
3130

3231
import Paths_cardano_sl (version)
3332

3433
import Pos.Client.CLI.Options (CommonArgs (..), commonArgsParser,
3534
optionalJSONPath, templateParser)
36-
import Pos.Core.NetworkAddress (NetworkAddress, addrParser, localhost)
35+
import Pos.Core.NetworkAddress (NetworkAddress, addrParser)
3736
import Pos.Infra.HealthCheck.Route53 (route53HealthCheckOption)
3837
import Pos.Infra.InjectFail (FInjectsSpec, parseFInjectsSpec)
3938
import Pos.Infra.Network.CLI (NetworkConfigOpts, networkConfigOption)
@@ -162,7 +161,7 @@ nodeArgsParser = NodeArgs <$> behaviorParser
162161
metavar "FILE" <>
163162
help "Path to the behavior config"
164163

165-
data NodeWithApiArgs = NodeWithApiArgs CommonNodeArgs NodeArgs NodeApiArgs
164+
data NodeWithApiArgs = NodeWithApiArgs CommonNodeArgs NodeArgs (Maybe NodeApiArgs)
166165

167166
nodeWithApiArgsParser :: Parser NodeWithApiArgs
168167
nodeWithApiArgsParser =
@@ -171,22 +170,19 @@ nodeWithApiArgsParser =
171170
<*> nodeArgsParser
172171
<*> nodeApiArgsParser
173172

174-
nodeApiArgsParser :: Parser NodeApiArgs
175-
nodeApiArgsParser =
176-
NodeApiArgs
177-
<$> addressParser "node-api-address" (localhost, 8080)
178-
<*> tlsParamsParser
179-
<*> debugModeParser
180-
<*> addressParser "node-doc-address" (localhost, 8180)
173+
nodeApiArgsParser :: Parser (Maybe NodeApiArgs)
174+
nodeApiArgsParser = optional $ NodeApiArgs
175+
<$> addressParser "node-api-address"
176+
<*> tlsParamsParser
177+
<*> debugModeParser
178+
<*> addressParser "node-doc-address"
181179
where
182-
addressParser flagName defValue =
180+
addressParser :: String -> Parser NetworkAddress
181+
addressParser flagName =
183182
option (fromParsec addrParser) $
184183
long flagName
185184
<> metavar "IP:PORT"
186-
<> help helpMsg
187-
<> showDefault
188-
<> value defValue
189-
helpMsg = "IP and port for backend node API."
185+
<> help "IP and port for backend node API."
190186
debugModeParser :: Parser Bool
191187
debugModeParser =
192188
switch (long "wallet-debug" <>
@@ -216,23 +212,20 @@ tlsParamsParser = constructTlsParams <$> certPathParser
216212
"tlscert"
217213
"FILEPATH"
218214
"Path to file with TLS certificate"
219-
<> value "scripts/tls-files/server.crt"
220215
)
221216

222217
keyPathParser :: Parser FilePath
223218
keyPathParser = strOption (templateParser
224219
"tlskey"
225220
"FILEPATH"
226221
"Path to file with TLS key"
227-
<> value "scripts/tls-files/server.key"
228222
)
229223

230224
caPathParser :: Parser FilePath
231225
caPathParser = strOption (templateParser
232226
"tlsca"
233227
"FILEPATH"
234228
"Path to file with TLS certificate authority"
235-
<> value "scripts/tls-files/ca.crt"
236229
)
237230

238231
noClientAuthParser :: Parser Bool

lib/src/Pos/Node/API.hs

+5-4
Original file line numberDiff line numberDiff line change
@@ -19,7 +19,7 @@ import Data.Aeson.Types (toJSONKeyText)
1919
import qualified Data.ByteArray as ByteArray
2020
import qualified Data.Char as C
2121
import qualified Data.Map.Strict as Map
22-
import Data.Swagger hiding (Example, example)
22+
import Data.Swagger hiding (Example, Tag, example)
2323
import qualified Data.Swagger as S
2424
import Data.Swagger.Declare (Declare, look)
2525
import Data.Swagger.Internal.Schema (GToSchema)
@@ -46,7 +46,8 @@ import Pos.Infra.Util.LogSafe (BuildableSafeGen (..), SecureLog (..),
4646
deriveSafeBuildable)
4747
import Pos.Util.Example
4848
import Pos.Util.Servant (APIResponse, CustomQueryFlag, Flaggable (..),
49-
HasCustomQueryFlagDescription (..), Tags, ValidJSON)
49+
HasCustomQueryFlagDescription (..), Tag,
50+
TagDescription (..), ValidJSON)
5051
import Pos.Util.UnitsOfMeasure
5152
import Serokell.Util.Text
5253

@@ -665,13 +666,13 @@ instance BuildableSafeGen NodeSettings where
665666

666667

667668
type SettingsAPI =
668-
Tags '["Settings"]
669+
Tag "Settings" 'NoTagDescription
669670
:> "node-settings"
670671
:> Summary "Retrieves the static settings for this node."
671672
:> Get '[ValidJSON] (APIResponse NodeSettings)
672673

673674
type InfoAPI =
674-
Tags '["Info"]
675+
Tag "Info" 'NoTagDescription
675676
:> "node-info"
676677
:> Summary "Retrieves the dynamic information for this node."
677678
:> CustomQueryFlag "force_ntp_check" ForceNtpCheck

lib/src/Pos/Util/Servant.hs

+45-16
Original file line numberDiff line numberDiff line change
@@ -69,7 +69,8 @@ module Pos.Util.Servant
6969
, applicationJson
7070
, applyLoggingToHandler
7171
, ValidJSON
72-
, Tags
72+
, Tag
73+
, TagDescription(..)
7374
, mapRouter
7475
, APIResponse(..)
7576
, single
@@ -93,8 +94,14 @@ import Data.Constraint.Forall (Forall, inst)
9394
import Data.Default (Default (..))
9495
import Data.List (lookup)
9596
import Data.Reflection (Reifies (..), reflect)
96-
import qualified Data.Set as Set
97-
import Data.Swagger as S hiding (Example, Header, example, info)
97+
import Data.Swagger (NamedSchema (..), ParamAnySchema (..),
98+
ParamLocation (..), SwaggerType (..), ToSchema (..),
99+
allowEmptyValue, applyTagsFor, declareSchemaRef,
100+
defaultSchemaOptions, default_, description,
101+
genericDeclareNamedSchema, in_, name, operationsOf,
102+
paramSchema, properties, required, schema, toParamSchema,
103+
type_)
104+
import qualified Data.Swagger as S
98105
import qualified Data.Text as T
99106
import Data.Time.Clock.POSIX (getPOSIXTime)
100107
import Data.Typeable (typeOf, typeRep)
@@ -128,7 +135,6 @@ import Pos.Infra.Util.LogSafe (BuildableSafe, SecuredText, buildSafe,
128135
import Pos.Util.Example (Example (..))
129136
import Pos.Util.Jsend (HasDiagnostic (..), ResponseStatus (..),
130137
jsendErrorGenericParseJSON, jsendErrorGenericToJSON)
131-
import Pos.Util.KnownSymbols
132138
import Pos.Util.Pagination
133139
import Pos.Util.Wlog (LoggerName, LoggerNameBox, usingLoggerName)
134140

@@ -894,31 +900,54 @@ instance HasDiagnostic JSONValidationError where
894900

895901
-- | An empty type which can be used to inject Swagger tags at the type level,
896902
-- directly in the Servant API.
897-
data Tags (tags :: [Symbol])
903+
data Tag (tagName :: Symbol) (tagDescription :: TagDescription)
898904

899-
-- | Instance of `HasServer` which erases the `Tags` from its routing,
905+
data TagDescription
906+
= NoTagDescription
907+
| TagDescription Symbol
908+
909+
-- | Instance of `HasServer` which erases the `Tag` from its routing,
900910
-- as the latter is needed only for Swagger.
901-
instance (HasServer subApi context) => HasServer (Tags tags :> subApi) context where
902-
type ServerT (Tags tags :> subApi) m = ServerT subApi m
911+
instance (HasServer subApi context) => HasServer (Tag name desc :> subApi) context where
912+
type ServerT (Tag name desc :> subApi) m = ServerT subApi m
903913
route _ = route (Proxy @subApi)
904914
hoistServerWithContext _ = hoistServerWithContext (Proxy @subApi)
905915

906-
instance (HasClient m subApi) => HasClient m (Tags tags :> subApi) where
907-
type Client m (Tags tags :> subApi) = Client m subApi
916+
instance (HasClient m subApi) => HasClient m (Tag name desc :> subApi) where
917+
type Client m (Tag name desc :> subApi) = Client m subApi
908918
clientWithRoute pm _ = clientWithRoute pm (Proxy @subApi)
909919
hoistClientMonad pm _ f cl =
910920
hoistClientMonad pm (Proxy @subApi) f cl
911921

912922
-- | Similar to 'instance HasServer', just skips 'Tags'.
913923
instance HasLoggingServer config subApi context =>
914-
HasLoggingServer config (Tags tags :> subApi) context where
915-
routeWithLog = mapRouter @(Tags tags :> LoggingApiRec config subApi) route identity
924+
HasLoggingServer config (Tag name desc :> subApi) context where
925+
routeWithLog = mapRouter @(Tag name desc :> LoggingApiRec config subApi) route identity
926+
916927

917-
instance (KnownSymbols tags, HasSwagger subApi) => HasSwagger (Tags tags :> subApi) where
928+
instance
929+
(KnownSymbol name, KnownSymbol desc, HasSwagger subApi)
930+
=> HasSwagger (Tag name ('TagDescription desc) :> subApi) where
931+
toSwagger _ =
932+
let
933+
subApi = toSwagger (Proxy @subApi)
934+
tag = S.Tag
935+
(toText $ symbolVal $ Proxy @name)
936+
(Just $ toText $ symbolVal $ Proxy @desc)
937+
Nothing
938+
in
939+
subApi & applyTagsFor (operationsOf subApi) [tag]
940+
941+
instance (KnownSymbol name, HasSwagger subApi) => HasSwagger (Tag name 'NoTagDescription :> subApi) where
918942
toSwagger _ =
919-
let newTags = map toText (symbolVals (Proxy @tags))
920-
swgr = toSwagger (Proxy @subApi)
921-
in swgr & over (operationsOf swgr . tags) (mappend (Set.fromList newTags))
943+
let
944+
subApi = toSwagger (Proxy @subApi)
945+
tag = S.Tag
946+
(toText $ symbolVal $ Proxy @name)
947+
Nothing
948+
Nothing
949+
in
950+
subApi & applyTagsFor (operationsOf subApi) [tag]
922951

923952
-- | `mapRouter` is helper function used in order to transform one `HasServer`
924953
-- instance to another. It can be used to introduce custom request params type.

node/app/Main.hs

+10-8
Original file line numberDiff line numberDiff line change
@@ -10,20 +10,22 @@ import Pos.Client.CLI (NodeWithApiArgs (..), getNodeApiOptions,
1010
loggingParams)
1111
import Pos.Launcher (actionWithCoreNode, launchNode)
1212
import Pos.Util.CompileInfo (compileInfo, withCompileInfo)
13+
import Pos.Util.Wlog (logInfo)
1314

1415
main :: IO ()
1516
main = withCompileInfo $ do
16-
NodeWithApiArgs cArgs nArgs apiArgs <- getNodeApiOptions
17+
NodeWithApiArgs cArgs nArgs mApiArgs <- getNodeApiOptions
1718
let lArgs = loggingParams "node" cArgs
19+
20+
let nodeServer = case mApiArgs of
21+
Nothing ->
22+
\_ _ _ _ _ _ -> logInfo "Monitoring API is disabled."
23+
Just apiArgs ->
24+
launchNodeServer apiArgs
25+
1826
launchNode nArgs cArgs lArgs
1927
$ \genConfig walConfig txpConfig ntpConfig nodeParams sscParams nodeResources ->
2028
actionWithCoreNode
21-
(launchNodeServer
22-
apiArgs
23-
ntpConfig
24-
nodeResources
25-
updateConfiguration
26-
compileInfo
27-
genConfig)
29+
(nodeServer ntpConfig nodeResources updateConfiguration compileInfo genConfig)
2830
genConfig walConfig txpConfig
2931
ntpConfig nodeParams sscParams nodeResources

wallet/integration/QuickCheckSpecs.hs

+2-2
Original file line numberDiff line numberDiff line change
@@ -16,7 +16,7 @@ import Test.Hspec
1616
import Test.QuickCheck
1717

1818
import Cardano.Wallet.API.Request (FilterBy, SortBy)
19-
import Cardano.Wallet.API.Types (Tags, WithDefaultApiArg)
19+
import Cardano.Wallet.API.Types (Tag, WithDefaultApiArg)
2020
import qualified Cardano.Wallet.API.V1 as V0
2121
import qualified Cardano.Wallet.API.V1 as V1
2222
import Cardano.Wallet.API.V1.Parameters (WalletRequestParams,
@@ -63,7 +63,7 @@ instance HasGenRequest sub => HasGenRequest (SortBy syms res :> sub) where
6363
instance HasGenRequest sub => HasGenRequest (FilterBy syms res :> sub) where
6464
genRequest _ = genRequest (Proxy @sub)
6565

66-
instance HasGenRequest sub => HasGenRequest (Tags tags :> sub) where
66+
instance HasGenRequest sub => HasGenRequest (Tag tag desc :> sub) where
6767
genRequest _ = genRequest (Proxy :: Proxy sub)
6868

6969
instance HasGenRequest (sub :: *) => HasGenRequest (WalletRequestParams :> sub) where

wallet/src/Cardano/Wallet/API/Internal.hs

+8-2
Original file line numberDiff line numberDiff line change
@@ -8,10 +8,16 @@ import Pos.Chain.Update (SoftwareVersion)
88
import Servant
99

1010
import Cardano.Wallet.API.Response (APIResponse, ValidJSON)
11-
import Cardano.Wallet.API.Types (Tags)
11+
import Cardano.Wallet.API.Types
1212
import Cardano.Wallet.API.V1.Types (V1, Wallet, WalletImport)
1313

14-
type API = Tags '["Internal"] :>
14+
type API = Tag "Internal" ('TagDescription
15+
"This section contains endpoints so-called 'Internal'. They are only\
16+
\ expected to be used by advanced users of the API (e.g. Daedalus) with\
17+
\ which there's a privileged communication channel. Backward-compatibility\
18+
\ or existence of these endpoints between versions is not guaranteed and\
19+
\ won't be enforced. Use at your own risks.")
20+
:>
1521
( "next-update"
1622
:> Summary "Version of the next update (404 if none)"
1723
:> Get '[ValidJSON] (APIResponse (V1 SoftwareVersion))

wallet/src/Cardano/Wallet/API/Types.hs

+3-2
Original file line numberDiff line numberDiff line change
@@ -9,7 +9,8 @@ module Cardano.Wallet.API.Types
99
, DHeader
1010
, mapRouter
1111
, WithDefaultApiArg
12-
, Tags
12+
, Tag
13+
, TagDescription(..)
1314
, WalletLoggingConfig
1415
) where
1516

@@ -20,7 +21,7 @@ import Servant
2021
import qualified Servant.Server.Internal as SI
2122

2223
import Pos.Util.Servant (ApiLoggingConfig (..), DHeader, DQueryParam,
23-
Tags, WithDefaultApiArg)
24+
Tag, TagDescription (..), WithDefaultApiArg)
2425

2526
-- | `mapRouter` is helper function used in order to transform one `HasServer`
2627
-- instance to another. It can be used to introduce custom request params type.

wallet/src/Cardano/Wallet/API/V1/Accounts.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -12,7 +12,7 @@ import qualified Pos.Core as Core
1212

1313

1414
type API
15-
= Tags '["Accounts"] :>
15+
= Tag "Accounts" 'NoTagDescription :>
1616
( "wallets" :> CaptureWalletId :> "accounts"
1717
:> CaptureAccountId
1818
:> Summary "Deletes an Account."

wallet/src/Cardano/Wallet/API/V1/Addresses.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -9,7 +9,7 @@ import Cardano.Wallet.API.V1.Parameters
99
import Cardano.Wallet.API.V1.Types
1010

1111

12-
type API = Tags '["Addresses"] :>
12+
type API = Tag "Addresses" 'NoTagDescription :>
1313
( "addresses" :> WalletRequestParams
1414
:> Summary "Returns a list of the addresses."
1515
:> Get '[ValidJSON] (APIResponse [WalletAddress])

wallet/src/Cardano/Wallet/API/V1/Settings.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -6,7 +6,7 @@ import Cardano.Wallet.API.V1.Types
66

77
import Servant
88

9-
type API = Tags '["Settings"] :>
9+
type API = Tag "Settings" 'NoTagDescription :>
1010
( "node-settings" :> Summary "Retrieves the static settings for this node."
1111
:> Get '[ValidJSON] (APIResponse NodeSettings)
1212
)

wallet/src/Cardano/Wallet/API/V1/Transactions.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -10,7 +10,7 @@ import qualified Pos.Core as Core
1010

1111
import Servant
1212

13-
type API = Tags '["Transactions"] :>
13+
type API = Tag "Transactions" 'NoTagDescription :>
1414
( "transactions" :> Summary "Generates a new transaction from the source to one or multiple target addresses."
1515
:> ReqBody '[ValidJSON] Payment
1616
:> Post '[ValidJSON] (APIResponse Transaction)

wallet/src/Cardano/Wallet/API/V1/Wallets.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -9,7 +9,7 @@ import Pos.Core as Core
99

1010
import Servant
1111

12-
type API = Tags '["Wallets"] :>
12+
type API = Tag "Wallets" 'NoTagDescription :>
1313
( "wallets" :> Summary "Creates a new or restores an existing Wallet."
1414
:> ReqBody '[ValidJSON] (New Wallet)
1515
:> PostCreated '[ValidJSON] (APIResponse Wallet)

0 commit comments

Comments
 (0)