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

Hiroto/update system #231

Merged
merged 13 commits into from
Jul 26, 2019
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
1 change: 1 addition & 0 deletions .gitignore
Original file line number Diff line number Diff line change
Expand Up @@ -4,6 +4,7 @@
dist/*
dist-newstyle/*
.ghc.environment.*
stack.yaml.lock

# From daedalus-bridge
node_modules/*
Expand Down
10 changes: 5 additions & 5 deletions Makefile
Original file line number Diff line number Diff line change
Expand Up @@ -7,20 +7,20 @@ stylish-haskell: ## Apply stylish-haskell on all *.hs files
@find . -type f -name "*.hs" -not -path '.git' -not -path '*.stack-work*' -print0 | xargs -0 stylish-haskell -i

ghci: ## Run repl
@stack ghci $(PROJECT_NAME):lib --haddock-deps --ghci-options=-fobject-code
@stack ghci $(PROJECT_NAME):lib --haddock-deps --ghci-options=-fobject-code --nix

ghcid: ## Run ghcid
@ghcid --command "stack ghci $(PROJECT_NAME):lib --nix -j12 --ghci-options=-fobject-code"

run-test: ## Build & run test
@stack build --fast && \
stack test --fast
@stack build --fast --nix && \
stack test --fast --nix

test-ghci: ## Run repl on test suites
@stack ghci $(PROJECT_NAME):lib $(PROJECT_NAME):test:$(PROJECT_NAME)-test --ghci-options=-fobject-code
@stack ghci $(PROJECT_NAME):lib $(PROJECT_NAME):test:$(PROJECT_NAME)-test --ghci-options=-fobject-code --nix

test-ghcid: ## Run ghcid on test suites
@ghcid --command "stack ghci $(PROJECT_NAME):lib $(PROJECT_NAME):test:$(PROJECT_NAME)-test --ghci-options=-fobject-code"
@ghcid --command "stack ghci --nix $(PROJECT_NAME):lib $(PROJECT_NAME):test:$(PROJECT_NAME)-test --ghci-options=-fobject-code"

test-ghcid-nix: ## Run ghcid on test suites with Nix
#NUM_PROC = $(nproc --all) # Either try to fetch the real num of cores or default to 4
Expand Down
3 changes: 2 additions & 1 deletion app/Launcher/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -18,6 +18,7 @@ import Formatting.Buildable (Buildable (..))

import Control.Exception.Safe (throwM)

-- import Cardano.Shell.Update.Lib (runUpdater, updaterData)
import Cardano.Shell.Configuration.Types (LauncherConfig (..),
WalletArguments (..),
WalletPath (..))
Expand All @@ -37,7 +38,7 @@ import Data.X509.Extra (failIfReasons, genRSA256KeyPair,

main :: IO ()
main = do

let launcherConfig :: LauncherConfig
launcherConfig = LauncherConfig
{ lcfgFilePath = "./configuration/cert-configuration.yaml"
Expand Down
5 changes: 4 additions & 1 deletion cardano-shell.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -31,6 +31,7 @@ library
-- Update system
, CardanoShellSpec
, Cardano.Shell.Update.Types
, Cardano.Shell.Update.Lib
-- Constants
, Cardano.Shell.Constants.PartialTypes
, Cardano.Shell.Constants.Types
Expand All @@ -42,7 +43,6 @@ library
Cardano.Shell.NodeIPC.Lib
, Cardano.Shell.NodeIPC.Message
, Cardano.Shell.NodeIPC.ServerExample

hs-source-dirs:
app
, src
Expand All @@ -69,6 +69,8 @@ library
, text
, transformers
, generic-monoid
if os(windows)
build-depends: Win32

default-language: Haskell2010
default-extensions: NoImplicitPrelude
Expand Down Expand Up @@ -181,6 +183,7 @@ test-suite cardano-shell-test
other-modules:
Paths_cardano_shell
DhallConfigSpec
UpdaterSpec
if !os(windows)
other-modules:
NodeIPCSpec
Expand Down
2 changes: 1 addition & 1 deletion nix/.stack.nix/cardano-shell.nix

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

139 changes: 139 additions & 0 deletions src/Cardano/Shell/Update/Lib.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,139 @@
{-| Update module
-}

{-# LANGUAGE CPP #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE ScopedTypeVariables #-}

module Cardano.Shell.Update.Lib
( UpdaterData(..)
, UpdateError(..)
, RunCmdFunc
, updaterData
, runUpdater
, runUpdater'
) where

import Cardano.Prelude

import qualified Data.Text as T
import Distribution.System (OS (..), buildOS)
import Prelude (String)
import System.Directory (doesFileExist, removeFile)
import System.Environment (getExecutablePath)
import System.Process (proc, waitForProcess, withCreateProcess)
#ifdef mingw32_HOST_OS
import System.Win32.Process (getCurrentProcessId)
#endif

-- | Updater path, args, windows runner path, archive path
data UpdaterData = UpdaterData
Copy link
Contributor

Choose a reason for hiding this comment

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

Maybe you can have UpdaterData for each platform?
Not sure why you have udWindowsPath.

{ udPath :: !FilePath
, udArgs :: ![Text]
, udArchivePath :: !FilePath
}

-- Windows: https://github.com/input-output-hk/daedalus/blob/develop/installers/dhall/win64.dhall#L32-L35
-- MacOS: https://github.com/input-output-hk/daedalus/blob/develop/installers/dhall/macos64.dhall#L31-L34
-- Linux: https://github.com/input-output-hk/daedalus/blob/develop/installers/dhall/linux64.dhall#L29-L32
updaterData :: UpdaterData
updaterData = case buildOS of
Windows -> UpdaterData
"Installer.exe"
[]
"Installer.bat"
OSX -> UpdaterData
"/usr/bin/open"
["-FW"]
"\\${HOME}/Library/Application Support/Daedalus/installer.pkg"
_ -> UpdaterData
"/bin/update-runner"
[]
"\\${XDG_DATA_HOME}/Daedalus/installer.sh"

data UpdateError
= UpdateFailed Int
| UpdaterDoesNotExist
deriving (Eq, Show)

-- | Run the update system
--
-- For UNIX system:
--
-- Check that @udPath@ exists, then run the command @udPath udArgs udArchivePath@
--
-- For Windows:
--
-- Check that @udPath@ exists, but instead of running the command directly, you
-- first have to generate a @.bat@ file which will act as a script.
-- After it being generated, you run that script.
runUpdater :: UpdaterData -> IO (Either UpdateError ExitCode)
runUpdater = runUpdater' runCmd
where
runCmd :: FilePath -> [String] -> FilePath -> IO ExitCode
runCmd path args archive =
withCreateProcess (proc path (args <> [archive]))
$ \_in _out _err ph -> waitForProcess ph

type RunCmdFunc
= FilePath
-> [String]
-> FilePath
-> IO ExitCode

-- | @runUpdater@ but can inject any runCommand function.
-- This is used for testing.
runUpdater' :: RunCmdFunc -> UpdaterData -> IO (Either UpdateError ExitCode)
runUpdater' runCommand ud = do
let path = udPath ud
let args = map toS $ udArgs ud
let archive = (udArchivePath ud)
updaterExists <- doesFileExist path
if updaterExists
then do
exitCode <- case buildOS of
Windows -> do
writeWindowsUpdaterRunner archive
runCommand archive args archive
_ -> runCommand path args archive
case exitCode of
ExitSuccess -> do
whenM (doesFileExist archive) $ removeFile archive
return . Right $ ExitSuccess
ExitFailure code -> return . Left $ UpdateFailed code
else
return . Left $ UpdaterDoesNotExist

-- | Create @.bat@ file on given @FilePath@
--
-- https://github.com/input-output-hk/cardano-sl/blob/develop/tools/src/launcher/Main.hs#L585
--
-- The installer cant write to cardano-launcher.exe while it is running
-- so you must fully stop launcher before you can start the installer.
-- Because of this, we need a @.bat@ file which will run the update procedure and
-- re-launch the launcher.
-- Only Windows has this problem.
writeWindowsUpdaterRunner :: FilePath -> IO ()
Copy link
Contributor

Choose a reason for hiding this comment

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

Please add a comment where you copied this from and why.

writeWindowsUpdaterRunner runnerPath = do
exePath <- getExecutablePath
launcherArgs <- getArgs
#ifdef mingw32_HOST_OS
selfPid <- getCurrentProcessId
#else
let (selfPid :: Integer) = 0 -- This will never be run on non-Windows
#endif
writeFile (toS runnerPath) $ T.unlines
[ "TaskKill /PID "<> show selfPid <>" /F"
-- Run updater
, "%*"
-- Delete updater
, "del %1"
-- Run launcher again
, "start \"cardano launcher\" /b " <> (quote $ toS exePath) <> " "
<> (T.unwords $ map (quote . toS) launcherArgs)
-- Delete the bat file
, "(goto) 2>nul & del \"%~f0\""
]
where
quote :: Text -> Text
quote str = "\"" <> str <> "\""
3 changes: 1 addition & 2 deletions src/Cardano/Shell/Update/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,8 +3,7 @@ module Cardano.Shell.Update.Types where
import Cardano.Prelude

import qualified Data.Map as M

import Test.QuickCheck
import Test.QuickCheck (Gen, choose, frequency, listOf1)
Copy link
Contributor

Choose a reason for hiding this comment

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

Thanks, better.



-- Types we need to check the behaviour.
Expand Down
1 change: 0 additions & 1 deletion stack.yaml
Original file line number Diff line number Diff line change
Expand Up @@ -36,6 +36,5 @@ extra-deps:
- containers-0.5.11.0
- libsystemd-journal-1.4.4


Copy link
Contributor

Choose a reason for hiding this comment

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

👍

nix:
shell-file: stack-shell.nix
2 changes: 2 additions & 0 deletions test/Spec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -20,6 +20,7 @@ import Cardano.Shell.Types (CardanoFeature (..))
import DhallConfigSpec (dhallConfigSpec, mkConfigSpec)
import NodeIPCSMSpec (nodeIPCSMSpec)
import NodeIPCSpec (nodeIPCSpec)
import UpdaterSpec (updaterSpec)

-- | Entry point for tests.
main :: IO ()
Expand All @@ -29,6 +30,7 @@ main = hspec $ do
describe "Cardano configurations" mkConfigSpec
describe "NodeIPC state machine" nodeIPCSMSpec
describe "NodeIPC" nodeIPCSpec
describe "Update system" updaterSpec

-- | A valid concurrency specification.
validConcurrencySpec :: Spec
Expand Down
53 changes: 53 additions & 0 deletions test/UpdaterSpec.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,53 @@
{-# LANGUAGE ScopedTypeVariables #-}

module UpdaterSpec where

import Cardano.Prelude

import Prelude (String)
import Test.Hspec (Spec, describe, it)
import Test.Hspec.QuickCheck (prop)
import Test.QuickCheck (Arbitrary (..), elements)
import Test.QuickCheck.Monadic (assert, monadicIO, run)

import Cardano.Shell.Update.Lib (UpdateError (..), UpdaterData (..),
runUpdater, runUpdater')

updaterSpec :: Spec
updaterSpec = describe "Update system" $ do
it "should be successful" $ monadicIO $ do
eExitCode <- run $ runUpdater testUpdaterData
assert $ eExitCode == (Right ExitSuccess)

it "should return error when updater is not found" $ monadicIO $ do
eExitCode <- run $ runUpdater testUpdaterDataNoPath
assert $ eExitCode == (Left UpdaterDoesNotExist)

prop "should return expected error" $ \(exitNum :: ExitNum) -> monadicIO $ do
eExitCode <- run $ runUpdater' (testRunCmd exitNum) testUpdaterData
assert $ eExitCode == (Left . UpdateFailed . getExitNum $ exitNum)

testUpdaterData :: UpdaterData
testUpdaterData =
UpdaterData
"./test/testUpdater.sh"
[]
""

testUpdaterDataNoPath :: UpdaterData
testUpdaterDataNoPath =
UpdaterData
"This path does not exist"
[]
""

testRunCmd :: ExitNum -> FilePath -> [String] -> FilePath -> IO ExitCode
testRunCmd (ExitNum num) _ _ _ = return $ ExitFailure num

newtype ExitNum = ExitNum {
getExitNum :: Int
} deriving Show

-- http://tldp.org/LDP/abs/html/exitcodes.html
instance Arbitrary ExitNum where
arbitrary = ExitNum <$> elements [1, 2, 126, 127, 128, 130, 255]
1 change: 1 addition & 0 deletions test/testUpdater.sh
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
exit 0