@@ -8,15 +8,11 @@ module Main where
8
8
import Cardano.Prelude hiding (option )
9
9
import qualified Prelude
10
10
11
- import Control.Exception.Safe (throwM )
12
-
13
11
-- Yes, we should use these seldomly but here it seems quite acceptable.
14
12
import Data.IORef (newIORef , readIORef , writeIORef )
15
13
import Data.Text.Lazy.Builder (fromString , fromText )
16
14
17
15
import Distribution.System (OS (Windows ), buildOS )
18
-
19
- import System.FilePath ((</>) )
20
16
import System.Environment (setEnv )
21
17
import System.Exit (exitWith )
22
18
import System.IO.Silently (hSilence )
@@ -29,28 +25,27 @@ import Options.Applicative (Parser, ParserInfo, auto, execParser,
29
25
fullDesc , header , help , helper , info ,
30
26
long , metavar , option , optional , progDesc )
31
27
32
- import qualified Cardano.BM.Configuration.Model as CM
33
- import Cardano.BM.Data.Output
34
- import Cardano.BM.Data.Rotation
35
28
import Cardano.BM.Setup (withTrace )
36
29
import qualified Cardano.BM.Trace as Trace
37
30
import Cardano.BM.Tracing
38
31
39
32
import Cardano.Shell.Application (checkIfApplicationIsRunning )
40
33
import Cardano.Shell.CLI (LauncherOptionPath , getDefaultConfigPath ,
41
34
getLauncherOptions , launcherArgsParser )
42
- import Cardano.Shell.Configuration (ConfigurationOptions (.. ),
43
- LauncherOptions (.. ),
35
+ import Cardano.Shell.Configuration (LauncherOptions (.. ),
44
36
DaedalusBin (.. ), getUpdaterData ,
45
37
getDPath ,
46
38
setWorkingDirectory )
47
39
import Cardano.Shell.Launcher (LoggingDependencies (.. ), TLSError ,
48
40
TLSPath (.. ), WalletRunner (.. ),
49
41
generateTlsCertificates , runLauncher ,
50
42
walletRunnerProcess )
51
- import Cardano.Shell.Launcher.Types (nullLogging )
52
43
import Cardano.Shell.Update.Lib (UpdaterData (.. ),
53
44
runDefaultUpdateProcess )
45
+ import Cardano.X509.Configuration (TLSConfiguration )
46
+ import Control.Exception.Safe (throwM )
47
+
48
+ import System.FilePath ((</>) )
54
49
55
50
--------------------------------------------------------------------------------
56
51
-- Main
@@ -77,7 +72,7 @@ main = silence $ do
77
72
78
73
-- This function either stubs out the wallet exit code or
79
74
-- returns the "real" function.
80
- let walletExecutionFunction =
75
+ let walletExectionFunction =
81
76
WalletRunner $ \ daedalusBin walletArguments -> do
82
77
-- Check if we have any exit codes remaining.
83
78
stubExitCodes <- readIORef walletTestExitCodesMVar
@@ -109,37 +104,8 @@ main = silence $ do
109
104
-- Otherwise run the real deal, the real function.
110
105
runDefaultUpdateProcess filePath arguments
111
106
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
121
107
122
108
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
- ]
143
109
144
110
-- A safer way to close the tracing.
145
111
withTrace logConfig " launcher" $ \ baseTrace -> do
@@ -156,6 +122,15 @@ main = silence $ do
156
122
setEnv " LC_ALL" " en_GB.UTF-8"
157
123
setEnv " LANG" " en_GB.UTF-8"
158
124
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
+
159
134
let lockFile = loStateDir launcherOptions </> " daedalus_lockfile"
160
135
Trace. logNotice baseTrace $ " Locking file so that multiple applications won't run at same time"
161
136
-- Check if it's locked or not. Will throw an exception if the
@@ -172,8 +147,8 @@ main = silence $ do
172
147
throwM . WorkingDirectoryDoesNotExist $ workingDir
173
148
174
149
-- Configuration from the launcher options.
175
- let mConfigurationOptions :: Maybe ConfigurationOptions
176
- mConfigurationOptions = loConfiguration launcherOptions
150
+ let mTlsConfig :: Maybe TLSConfiguration
151
+ mTlsConfig = loTlsConfig launcherOptions
177
152
178
153
let daedalusBin :: DaedalusBin
179
154
daedalusBin = getDPath launcherOptions
@@ -187,14 +162,14 @@ main = silence $ do
187
162
mTlsPath = TLSPath <$> loTlsPath launcherOptions
188
163
189
164
-- 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
192
167
-- | If we need to, we first check if there are certificates so we don't have
193
168
-- to generate them. Since the function is called `generate...`, that's what
194
169
-- it does, it generates the certificates.
195
170
eTLSGeneration <- generateTlsCertificates
196
171
loggingDependencies
197
- configurationOptions
172
+ tlsConfig
198
173
tlsPath
199
174
200
175
case eTLSGeneration of
@@ -208,7 +183,7 @@ main = silence $ do
208
183
-- Finally, run the launcher once everything is set up!
209
184
exitCode <- runLauncher
210
185
loggingDependencies
211
- walletExecutionFunction
186
+ walletExectionFunction
212
187
daedalusBin
213
188
updaterExecutionFunction
214
189
updaterData
0 commit comments