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

tlsConfig passed via launcherConfig #359

Merged
merged 3 commits into from
Apr 1, 2020
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
67 changes: 21 additions & 46 deletions cardano-launcher/app/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -8,15 +8,11 @@ module Main where
import Cardano.Prelude hiding (option)
import qualified Prelude

import Control.Exception.Safe (throwM)

-- Yes, we should use these seldomly but here it seems quite acceptable.
import Data.IORef (newIORef, readIORef, writeIORef)
import Data.Text.Lazy.Builder (fromString, fromText)

import Distribution.System (OS (Windows), buildOS)

import System.FilePath ((</>))
import System.Environment (setEnv)
import System.Exit (exitWith)
import System.IO.Silently (hSilence)
Expand All @@ -29,28 +25,27 @@ import Options.Applicative (Parser, ParserInfo, auto, execParser,
fullDesc, header, help, helper, info,
long, metavar, option, optional, progDesc)

import qualified Cardano.BM.Configuration.Model as CM
import Cardano.BM.Data.Output
import Cardano.BM.Data.Rotation
import Cardano.BM.Setup (withTrace)
import qualified Cardano.BM.Trace as Trace
import Cardano.BM.Tracing

import Cardano.Shell.Application (checkIfApplicationIsRunning)
import Cardano.Shell.CLI (LauncherOptionPath, getDefaultConfigPath,
getLauncherOptions, launcherArgsParser)
import Cardano.Shell.Configuration (ConfigurationOptions (..),
LauncherOptions (..),
import Cardano.Shell.Configuration (LauncherOptions (..),
DaedalusBin (..), getUpdaterData,
getDPath,
setWorkingDirectory)
import Cardano.Shell.Launcher (LoggingDependencies (..), TLSError,
TLSPath (..), WalletRunner (..),
generateTlsCertificates, runLauncher,
walletRunnerProcess)
import Cardano.Shell.Launcher.Types (nullLogging)
import Cardano.Shell.Update.Lib (UpdaterData (..),
runDefaultUpdateProcess)
import Cardano.X509.Configuration (TLSConfiguration)
import Control.Exception.Safe (throwM)

import System.FilePath ((</>))

--------------------------------------------------------------------------------
-- Main
Expand All @@ -77,7 +72,7 @@ main = silence $ do

-- This function either stubs out the wallet exit code or
-- returns the "real" function.
let walletExecutionFunction =
let walletExectionFunction =
Copy link
Contributor

Choose a reason for hiding this comment

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

why do you want to rename this function?

Copy link
Contributor Author

Choose a reason for hiding this comment

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

it's a revert of the entire commit that's failing to work on windows. Fully agree that the other name is better, but I don't have the time or expertise to fix the failures we were getting on windows with this commit. I did a bisect and found this was the culprit.

WalletRunner $ \daedalusBin walletArguments -> do
-- Check if we have any exit codes remaining.
stubExitCodes <- readIORef walletTestExitCodesMVar
Expand Down Expand Up @@ -109,37 +104,8 @@ main = silence $ do
-- Otherwise run the real deal, the real function.
runDefaultUpdateProcess filePath arguments

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

logConfig <- defaultConfigStdout
let logfilepath = lologsPrefix launcherOptions </> "launcher"

-- We configure the logging to be on stdout and in the file as well.
CM.setSetupScribes logConfig
[ScribeDefinition {
scName = toS logfilepath,
scFormat = ScText,
scKind = FileSK,
scPrivacy = ScPublic,
scRotation = Just $ RotationParameters
{ rpLogLimitBytes = 10000000
, rpMaxAgeHours = 24
, rpKeepFilesNum = 3
}
}]

CM.setDefaultScribes logConfig
[ "StdoutSK::text"
, "FileSK::" <> toS logfilepath
]

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

launcherOptions <- do
eLauncherOptions <- getLauncherOptions loggingDependencies (launcherConfigPath launcherCLI)
case eLauncherOptions of
Left err -> do
logErrorMessage baseTrace $
"Error occured while parsing configuration file: " <> show err
throwM $ LauncherOptionsError (show err)
Right lo -> pure lo

let lockFile = loStateDir launcherOptions </> "daedalus_lockfile"
Trace.logNotice baseTrace $ "Locking file so that multiple applications won't run at same time"
-- Check if it's locked or not. Will throw an exception if the
Expand All @@ -172,8 +147,8 @@ main = silence $ do
throwM . WorkingDirectoryDoesNotExist $ workingDir

-- Configuration from the launcher options.
let mConfigurationOptions :: Maybe ConfigurationOptions
mConfigurationOptions = loConfiguration launcherOptions
let mTlsConfig :: Maybe TLSConfiguration
mTlsConfig = loTlsConfig launcherOptions

let daedalusBin :: DaedalusBin
daedalusBin = getDPath launcherOptions
Expand All @@ -187,14 +162,14 @@ main = silence $ do
mTlsPath = TLSPath <$> loTlsPath launcherOptions

-- If the path doesn't exist, then TLS has been disabled!
case (mTlsPath, mConfigurationOptions) of
(Just tlsPath, Just configurationOptions) -> do
case (mTlsPath, mTlsConfig) of
(Just tlsPath, Just tlsConfig) -> do
-- | If we need to, we first check if there are certificates so we don't have
-- to generate them. Since the function is called `generate...`, that's what
-- it does, it generates the certificates.
eTLSGeneration <- generateTlsCertificates
loggingDependencies
configurationOptions
tlsConfig
tlsPath

case eTLSGeneration of
Expand All @@ -208,7 +183,7 @@ main = silence $ do
-- Finally, run the launcher once everything is set up!
exitCode <- runLauncher
loggingDependencies
walletExecutionFunction
walletExectionFunction
daedalusBin
updaterExecutionFunction
updaterData
Expand Down
2 changes: 1 addition & 1 deletion cardano-launcher/cardano-launcher.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -74,6 +74,7 @@ executable cardano-launcher
base >=4.7 && <5
, cardano-prelude
, cardano-launcher
, cardano-sl-x509
-- formatting
, filepath
, formatting
Expand All @@ -89,7 +90,6 @@ executable cardano-launcher
, optparse-applicative
-- directory
, directory
, filepath

if os(windows)
ghc-options: -optl-mwindows
Expand Down
7 changes: 4 additions & 3 deletions cardano-launcher/src/Cardano/Shell/Configuration.hs
Original file line number Diff line number Diff line change
Expand Up @@ -20,6 +20,7 @@ import Data.Yaml (FromJSON (..), withObject, (.:), (.:?))
import System.Directory (doesDirectoryExist, setCurrentDirectory)

import Cardano.Shell.Update.Lib (UpdaterData (..))
import Cardano.X509.Configuration (TLSConfiguration)

--------------------------------------------------------------------------------
-- Configuration
Expand All @@ -43,14 +44,14 @@ newtype DaedalusBin = DaedalusBin
data LauncherOptions = LauncherOptions
{ loConfiguration :: !(Maybe ConfigurationOptions)
, loTlsPath :: !(Maybe FilePath)
, loTlsConfig :: !(Maybe TLSConfiguration)
, loUpdaterPath :: !FilePath
, loUpdaterArgs :: ![Text]
, loUpdateArchive :: !FilePath
, loDaedalusBin :: !FilePath
, loWorkingDirectory :: !FilePath
, loStateDir :: !FilePath
-- On WIN it should set this directory as current.
, lologsPrefix :: !FilePath
} deriving (Show, Generic)

instance FromJSON LauncherOptions where
Expand All @@ -62,20 +63,20 @@ instance FromJSON LauncherOptions where
updateArchive <- o .: "updateArchive"
configuration <- o .:? "configuration"
tlsPath <- o .:? "tlsPath"
tlsConfig <- o .:? "tlsConfig"
workingDir <- o .: "workingDir"
stateDir <- o .: "stateDir"
logsPrefix <- o .: "logsPrefix"

pure $ LauncherOptions
configuration
tlsPath
tlsConfig
updaterPath
updaterArgs
updateArchive
daedalusBin
workingDir
stateDir
logsPrefix

-- | Configuration yaml file location and the key to use. The file should
-- parse to a MultiConfiguration and the 'cfoKey' should be one of the keys
Expand Down
38 changes: 9 additions & 29 deletions cardano-launcher/src/Cardano/Shell/Launcher.hs
Original file line number Diff line number Diff line change
Expand Up @@ -30,24 +30,20 @@ import Prelude (Show (..))
import qualified System.Process as Process
import Turtle (system)

import Cardano.Shell.Configuration (ConfigurationOptions (..),
WalletArguments (..),
import Cardano.Shell.Configuration (WalletArguments (..),
DaedalusBin (..))
import Cardano.Shell.Launcher.Types (LoggingDependencies (..))
import Cardano.Shell.Update.Lib (RemoveArchiveAfterInstall (..),
RunUpdateFunc, UpdaterData (..),
runUpdater)
import Cardano.X509.Configuration (ConfigurationKey (..),
DirConfiguration (..), certChecks,
import Cardano.X509.Configuration (DirConfiguration (..), certChecks,
certFilename, certOutDir,
decodeConfigFile,
TLSConfiguration,
fromConfiguration, genCertificate)
import Control.Exception.Safe (onException)
import Data.X509.Extra (genRSA256KeyPair, validateCertificate,
writeCertificate, writeCredentials)
import Data.X509.Validation (FailedReason)
import System.Directory (createDirectoryIfMissing, doesDirectoryExist,
doesFileExist)
import System.Directory (createDirectoryIfMissing)
import System.FilePath ((</>))

--------------------------------------------------------------------------------
Expand Down Expand Up @@ -297,21 +293,18 @@ runLauncher loggingDependencies walletRunner daedalusBin runUpdateFunc updaterDa
-- This just covers the generation of the TLS certificates and nothing else.
generateTlsCertificates
:: LoggingDependencies
-> ConfigurationOptions
-> TLSConfiguration
-> TLSPath
-> IO (Either TLSError ())
generateTlsCertificates externalDependencies' configurationOptions (TLSPath tlsPath) = runExceptT $ do
doesCertConfigExist <- liftIO $ doesFileExist (cfoFilePath configurationOptions)
doesTLSPathExist <- liftIO $ doesDirectoryExist tlsPath
unless doesCertConfigExist $ throwError . CertConfigNotFound . cfoFilePath $ configurationOptions
unless doesTLSPathExist $ throwError . TLSDirectoryNotFound $ tlsPath
generateTlsCertificates externalDependencies' tlsConfig (TLSPath tlsPath) = runExceptT $ do

let tlsServer = tlsPath </> "server"
let tlsClient = tlsPath </> "client"

-- Create the directories.
liftIO $ do
logInfo externalDependencies' $ "Generating the certificates!"
createDirectoryIfMissing True tlsPath
createDirectoryIfMissing True tlsServer
createDirectoryIfMissing True tlsClient

Expand All @@ -322,24 +315,14 @@ generateTlsCertificates externalDependencies' configurationOptions (TLSPath tlsP
-- `cardano-sl`.
generateCertificates :: FilePath -> FilePath -> ExceptT TLSError IO ()
generateCertificates tlsServer' tlsClient = do

let configFile = cfoFilePath configurationOptions
-- Configuration key within the config file
let configKey :: ConfigurationKey
configKey = ConfigurationKey . textToFilePath . cfoKey $ configurationOptions

let outDirectories :: DirConfiguration -- ^ Output directories configuration
outDirectories = DirConfiguration
{ outDirServer = tlsServer'
, outDirClients = tlsClient
, outDirCA = Nothing -- TODO(KS): AFAIK, we don't output the CA.
, outDirCA = Nothing
}

-- TLS configuration
tlsConfig <- decodeConfigFile configKey configFile `onException`
(throwError . InvalidKey . cfoKey $ configurationOptions)

-- From configuraiton
-- From configuration
(caDesc, descs) <-
liftIO $ fromConfiguration tlsConfig outDirectories genRSA256KeyPair <$> genRSA256KeyPair

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

-- | Error that can be thrown when generating TSL certificates
data TLSError =
Expand Down
Loading