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

Commit 8387be2

Browse files
disassemblerksaric
andauthored
tlsConfig passed via launcherConfig (#359)
* tlsConfig passed via launcherConfig * Revert "[#345] logging configuration for logging to file (#350)" This reverts commit 975e880. * Temporarily disable the certificate tests. Co-authored-by: ksaric <[email protected]>
1 parent bc3563c commit 8387be2

File tree

6 files changed

+98
-145
lines changed

6 files changed

+98
-145
lines changed

cardano-launcher/app/Main.hs

Lines changed: 21 additions & 46 deletions
Original file line numberDiff line numberDiff line change
@@ -8,15 +8,11 @@ module Main where
88
import Cardano.Prelude hiding (option)
99
import qualified Prelude
1010

11-
import Control.Exception.Safe (throwM)
12-
1311
-- Yes, we should use these seldomly but here it seems quite acceptable.
1412
import Data.IORef (newIORef, readIORef, writeIORef)
1513
import Data.Text.Lazy.Builder (fromString, fromText)
1614

1715
import Distribution.System (OS (Windows), buildOS)
18-
19-
import System.FilePath ((</>))
2016
import System.Environment (setEnv)
2117
import System.Exit (exitWith)
2218
import System.IO.Silently (hSilence)
@@ -29,28 +25,27 @@ import Options.Applicative (Parser, ParserInfo, auto, execParser,
2925
fullDesc, header, help, helper, info,
3026
long, metavar, option, optional, progDesc)
3127

32-
import qualified Cardano.BM.Configuration.Model as CM
33-
import Cardano.BM.Data.Output
34-
import Cardano.BM.Data.Rotation
3528
import Cardano.BM.Setup (withTrace)
3629
import qualified Cardano.BM.Trace as Trace
3730
import Cardano.BM.Tracing
3831

3932
import Cardano.Shell.Application (checkIfApplicationIsRunning)
4033
import Cardano.Shell.CLI (LauncherOptionPath, getDefaultConfigPath,
4134
getLauncherOptions, launcherArgsParser)
42-
import Cardano.Shell.Configuration (ConfigurationOptions (..),
43-
LauncherOptions (..),
35+
import Cardano.Shell.Configuration (LauncherOptions (..),
4436
DaedalusBin (..), getUpdaterData,
4537
getDPath,
4638
setWorkingDirectory)
4739
import Cardano.Shell.Launcher (LoggingDependencies (..), TLSError,
4840
TLSPath (..), WalletRunner (..),
4941
generateTlsCertificates, runLauncher,
5042
walletRunnerProcess)
51-
import Cardano.Shell.Launcher.Types (nullLogging)
5243
import Cardano.Shell.Update.Lib (UpdaterData (..),
5344
runDefaultUpdateProcess)
45+
import Cardano.X509.Configuration (TLSConfiguration)
46+
import Control.Exception.Safe (throwM)
47+
48+
import System.FilePath ((</>))
5449

5550
--------------------------------------------------------------------------------
5651
-- Main
@@ -77,7 +72,7 @@ main = silence $ do
7772

7873
-- This function either stubs out the wallet exit code or
7974
-- returns the "real" function.
80-
let walletExecutionFunction =
75+
let walletExectionFunction =
8176
WalletRunner $ \daedalusBin walletArguments -> do
8277
-- Check if we have any exit codes remaining.
8378
stubExitCodes <- readIORef walletTestExitCodesMVar
@@ -109,37 +104,8 @@ main = silence $ do
109104
-- Otherwise run the real deal, the real function.
110105
runDefaultUpdateProcess filePath arguments
111106

112-
-- We get the launcher options. We don't log them currently because of the cat-mouse deps.
113-
launcherOptions <- do
114-
eLauncherOptions <- getLauncherOptions nullLogging (launcherConfigPath launcherCLI)
115-
case eLauncherOptions of
116-
Left err -> do
117-
putTextLn $
118-
"Error occured while parsing configuration file: " <> show err
119-
throwM $ LauncherOptionsError (show err)
120-
Right lo -> pure lo
121107

122108
logConfig <- defaultConfigStdout
123-
let logfilepath = lologsPrefix launcherOptions </> "launcher"
124-
125-
-- We configure the logging to be on stdout and in the file as well.
126-
CM.setSetupScribes logConfig
127-
[ScribeDefinition {
128-
scName = toS logfilepath,
129-
scFormat = ScText,
130-
scKind = FileSK,
131-
scPrivacy = ScPublic,
132-
scRotation = Just $ RotationParameters
133-
{ rpLogLimitBytes = 10000000
134-
, rpMaxAgeHours = 24
135-
, rpKeepFilesNum = 3
136-
}
137-
}]
138-
139-
CM.setDefaultScribes logConfig
140-
[ "StdoutSK::text"
141-
, "FileSK::" <> toS logfilepath
142-
]
143109

144110
-- A safer way to close the tracing.
145111
withTrace logConfig "launcher" $ \baseTrace -> do
@@ -156,6 +122,15 @@ main = silence $ do
156122
setEnv "LC_ALL" "en_GB.UTF-8"
157123
setEnv "LANG" "en_GB.UTF-8"
158124

125+
launcherOptions <- do
126+
eLauncherOptions <- getLauncherOptions loggingDependencies (launcherConfigPath launcherCLI)
127+
case eLauncherOptions of
128+
Left err -> do
129+
logErrorMessage baseTrace $
130+
"Error occured while parsing configuration file: " <> show err
131+
throwM $ LauncherOptionsError (show err)
132+
Right lo -> pure lo
133+
159134
let lockFile = loStateDir launcherOptions </> "daedalus_lockfile"
160135
Trace.logNotice baseTrace $ "Locking file so that multiple applications won't run at same time"
161136
-- Check if it's locked or not. Will throw an exception if the
@@ -172,8 +147,8 @@ main = silence $ do
172147
throwM . WorkingDirectoryDoesNotExist $ workingDir
173148

174149
-- Configuration from the launcher options.
175-
let mConfigurationOptions :: Maybe ConfigurationOptions
176-
mConfigurationOptions = loConfiguration launcherOptions
150+
let mTlsConfig :: Maybe TLSConfiguration
151+
mTlsConfig = loTlsConfig launcherOptions
177152

178153
let daedalusBin :: DaedalusBin
179154
daedalusBin = getDPath launcherOptions
@@ -187,14 +162,14 @@ main = silence $ do
187162
mTlsPath = TLSPath <$> loTlsPath launcherOptions
188163

189164
-- If the path doesn't exist, then TLS has been disabled!
190-
case (mTlsPath, mConfigurationOptions) of
191-
(Just tlsPath, Just configurationOptions) -> do
165+
case (mTlsPath, mTlsConfig) of
166+
(Just tlsPath, Just tlsConfig) -> do
192167
-- | If we need to, we first check if there are certificates so we don't have
193168
-- to generate them. Since the function is called `generate...`, that's what
194169
-- it does, it generates the certificates.
195170
eTLSGeneration <- generateTlsCertificates
196171
loggingDependencies
197-
configurationOptions
172+
tlsConfig
198173
tlsPath
199174

200175
case eTLSGeneration of
@@ -208,7 +183,7 @@ main = silence $ do
208183
-- Finally, run the launcher once everything is set up!
209184
exitCode <- runLauncher
210185
loggingDependencies
211-
walletExecutionFunction
186+
walletExectionFunction
212187
daedalusBin
213188
updaterExecutionFunction
214189
updaterData

cardano-launcher/cardano-launcher.cabal

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -74,6 +74,7 @@ executable cardano-launcher
7474
base >=4.7 && <5
7575
, cardano-prelude
7676
, cardano-launcher
77+
, cardano-sl-x509
7778
-- formatting
7879
, filepath
7980
, formatting
@@ -89,7 +90,6 @@ executable cardano-launcher
8990
, optparse-applicative
9091
-- directory
9192
, directory
92-
, filepath
9393

9494
if os(windows)
9595
ghc-options: -optl-mwindows

cardano-launcher/src/Cardano/Shell/Configuration.hs

Lines changed: 4 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -20,6 +20,7 @@ import Data.Yaml (FromJSON (..), withObject, (.:), (.:?))
2020
import System.Directory (doesDirectoryExist, setCurrentDirectory)
2121

2222
import Cardano.Shell.Update.Lib (UpdaterData (..))
23+
import Cardano.X509.Configuration (TLSConfiguration)
2324

2425
--------------------------------------------------------------------------------
2526
-- Configuration
@@ -43,14 +44,14 @@ newtype DaedalusBin = DaedalusBin
4344
data LauncherOptions = LauncherOptions
4445
{ loConfiguration :: !(Maybe ConfigurationOptions)
4546
, loTlsPath :: !(Maybe FilePath)
47+
, loTlsConfig :: !(Maybe TLSConfiguration)
4648
, loUpdaterPath :: !FilePath
4749
, loUpdaterArgs :: ![Text]
4850
, loUpdateArchive :: !FilePath
4951
, loDaedalusBin :: !FilePath
5052
, loWorkingDirectory :: !FilePath
5153
, loStateDir :: !FilePath
5254
-- On WIN it should set this directory as current.
53-
, lologsPrefix :: !FilePath
5455
} deriving (Show, Generic)
5556

5657
instance FromJSON LauncherOptions where
@@ -62,20 +63,20 @@ instance FromJSON LauncherOptions where
6263
updateArchive <- o .: "updateArchive"
6364
configuration <- o .:? "configuration"
6465
tlsPath <- o .:? "tlsPath"
66+
tlsConfig <- o .:? "tlsConfig"
6567
workingDir <- o .: "workingDir"
6668
stateDir <- o .: "stateDir"
67-
logsPrefix <- o .: "logsPrefix"
6869

6970
pure $ LauncherOptions
7071
configuration
7172
tlsPath
73+
tlsConfig
7274
updaterPath
7375
updaterArgs
7476
updateArchive
7577
daedalusBin
7678
workingDir
7779
stateDir
78-
logsPrefix
7980

8081
-- | Configuration yaml file location and the key to use. The file should
8182
-- parse to a MultiConfiguration and the 'cfoKey' should be one of the keys

cardano-launcher/src/Cardano/Shell/Launcher.hs

Lines changed: 9 additions & 29 deletions
Original file line numberDiff line numberDiff line change
@@ -30,24 +30,20 @@ import Prelude (Show (..))
3030
import qualified System.Process as Process
3131
import Turtle (system)
3232

33-
import Cardano.Shell.Configuration (ConfigurationOptions (..),
34-
WalletArguments (..),
33+
import Cardano.Shell.Configuration (WalletArguments (..),
3534
DaedalusBin (..))
3635
import Cardano.Shell.Launcher.Types (LoggingDependencies (..))
3736
import Cardano.Shell.Update.Lib (RemoveArchiveAfterInstall (..),
3837
RunUpdateFunc, UpdaterData (..),
3938
runUpdater)
40-
import Cardano.X509.Configuration (ConfigurationKey (..),
41-
DirConfiguration (..), certChecks,
39+
import Cardano.X509.Configuration (DirConfiguration (..), certChecks,
4240
certFilename, certOutDir,
43-
decodeConfigFile,
41+
TLSConfiguration,
4442
fromConfiguration, genCertificate)
45-
import Control.Exception.Safe (onException)
4643
import Data.X509.Extra (genRSA256KeyPair, validateCertificate,
4744
writeCertificate, writeCredentials)
4845
import Data.X509.Validation (FailedReason)
49-
import System.Directory (createDirectoryIfMissing, doesDirectoryExist,
50-
doesFileExist)
46+
import System.Directory (createDirectoryIfMissing)
5147
import System.FilePath ((</>))
5248

5349
--------------------------------------------------------------------------------
@@ -297,21 +293,18 @@ runLauncher loggingDependencies walletRunner daedalusBin runUpdateFunc updaterDa
297293
-- This just covers the generation of the TLS certificates and nothing else.
298294
generateTlsCertificates
299295
:: LoggingDependencies
300-
-> ConfigurationOptions
296+
-> TLSConfiguration
301297
-> TLSPath
302298
-> IO (Either TLSError ())
303-
generateTlsCertificates externalDependencies' configurationOptions (TLSPath tlsPath) = runExceptT $ do
304-
doesCertConfigExist <- liftIO $ doesFileExist (cfoFilePath configurationOptions)
305-
doesTLSPathExist <- liftIO $ doesDirectoryExist tlsPath
306-
unless doesCertConfigExist $ throwError . CertConfigNotFound . cfoFilePath $ configurationOptions
307-
unless doesTLSPathExist $ throwError . TLSDirectoryNotFound $ tlsPath
299+
generateTlsCertificates externalDependencies' tlsConfig (TLSPath tlsPath) = runExceptT $ do
308300

309301
let tlsServer = tlsPath </> "server"
310302
let tlsClient = tlsPath </> "client"
311303

312304
-- Create the directories.
313305
liftIO $ do
314306
logInfo externalDependencies' $ "Generating the certificates!"
307+
createDirectoryIfMissing True tlsPath
315308
createDirectoryIfMissing True tlsServer
316309
createDirectoryIfMissing True tlsClient
317310

@@ -322,24 +315,14 @@ generateTlsCertificates externalDependencies' configurationOptions (TLSPath tlsP
322315
-- `cardano-sl`.
323316
generateCertificates :: FilePath -> FilePath -> ExceptT TLSError IO ()
324317
generateCertificates tlsServer' tlsClient = do
325-
326-
let configFile = cfoFilePath configurationOptions
327-
-- Configuration key within the config file
328-
let configKey :: ConfigurationKey
329-
configKey = ConfigurationKey . textToFilePath . cfoKey $ configurationOptions
330-
331318
let outDirectories :: DirConfiguration -- ^ Output directories configuration
332319
outDirectories = DirConfiguration
333320
{ outDirServer = tlsServer'
334321
, outDirClients = tlsClient
335-
, outDirCA = Nothing -- TODO(KS): AFAIK, we don't output the CA.
322+
, outDirCA = Nothing
336323
}
337324

338-
-- TLS configuration
339-
tlsConfig <- decodeConfigFile configKey configFile `onException`
340-
(throwError . InvalidKey . cfoKey $ configurationOptions)
341-
342-
-- From configuraiton
325+
-- From configuration
343326
(caDesc, descs) <-
344327
liftIO $ fromConfiguration tlsConfig outDirectories genRSA256KeyPair <$> genRSA256KeyPair
345328

@@ -366,9 +349,6 @@ generateTlsCertificates externalDependencies' configurationOptions (TLSPath tlsP
366349
liftIO $ do
367350
writeCredentials (certOutDir desc </> certFilename desc) (key, cert)
368351
writeCertificate (certOutDir desc </> caName) caCert
369-
-- Utility function.
370-
textToFilePath :: Text -> FilePath
371-
textToFilePath = strConv Strict
372352

373353
-- | Error that can be thrown when generating TSL certificates
374354
data TLSError =

0 commit comments

Comments
 (0)