mirror of
https://github.com/digital-asset/daml.git
synced 2024-11-08 21:34:22 +03:00
Include daml ledger
tests in compatibility tests (#5740)
* Copy daml ledger test to compatibility Specifically: - `daml-assistant/daml-helper/test/DA/Daml/Helper/Test/Deployment.hs` - `libs-haskell/test-utils/DA/Test/Sandbox.hs` * Adapt daml ledger test for compatibility Avoid dependencies on the daml repository and make the SDK and platform components configurable. * Add test certificates to compatibility Taken from `@daml//ledger/test-common/test-certificates`. * Define daml_ledger_test CHANGELOG_BEGIN CHANGELOG_END * Add note on keeping daml ledger tests in sync * ./fmt.sh * Strictly require --sdk-version flag Tasty doesn't allow options without a default value, so we default to `error` to enforce a value being set. Co-authored-by: Andreas Herrmann <andreas.herrmann@tweag.io>
This commit is contained in:
parent
d1db5c1c96
commit
effd05b894
@ -117,6 +117,15 @@ filegroup(
|
||||
repositories = dev_env_nix_repos,
|
||||
)
|
||||
|
||||
nixpkgs_package(
|
||||
name = "openssl_nix",
|
||||
attribute_path = "openssl",
|
||||
fail_not_supported = False,
|
||||
nix_file = "@daml//nix:bazel.nix",
|
||||
nix_file_deps = common_nix_file_deps,
|
||||
repositories = dev_env_nix_repos,
|
||||
)
|
||||
|
||||
nixpkgs_package(
|
||||
name = "hlint_nix",
|
||||
attribute_path = "hlint",
|
||||
|
@ -28,6 +28,8 @@ def daml_haskell_deps():
|
||||
},
|
||||
flags = dicts.add(
|
||||
{
|
||||
"cryptonite": ["-integer-gmp"],
|
||||
"hashable": ["-integer-gmp"],
|
||||
"integer-logarithms": ["-integer-gmp"],
|
||||
"text": ["integer-simple"],
|
||||
"scientific": ["integer-simple"],
|
||||
@ -36,15 +38,22 @@ def daml_haskell_deps():
|
||||
haddock = False,
|
||||
local_snapshot = "//:stack-snapshot.yaml",
|
||||
packages = [
|
||||
"aeson",
|
||||
"base",
|
||||
"containers",
|
||||
"directory",
|
||||
"extra",
|
||||
"filepath",
|
||||
"jwt",
|
||||
"monad-loops",
|
||||
"network",
|
||||
"process",
|
||||
"safe",
|
||||
"safe-exceptions",
|
||||
"split",
|
||||
"tagged",
|
||||
"tasty",
|
||||
"tasty-hunit",
|
||||
"text",
|
||||
] + (["unix"] if not is_windows else ["Win32"]),
|
||||
stack = None,
|
||||
|
@ -1 +1,4 @@
|
||||
exports_files(["sandbox-with-postgres.sh"])
|
||||
exports_files([
|
||||
"daml_ledger_test.sh",
|
||||
"sandbox-with-postgres.sh",
|
||||
])
|
||||
|
86
compatibility/bazel_tools/daml_ledger/BUILD.bazel
Normal file
86
compatibility/bazel_tools/daml_ledger/BUILD.bazel
Normal file
@ -0,0 +1,86 @@
|
||||
# Copyright (c) 2020 Digital Asset (Switzerland) GmbH and/or its affiliates. All rights reserved.
|
||||
# SPDX-License-Identifier: Apache-2.0
|
||||
|
||||
load(
|
||||
"@daml//bazel_tools:haskell.bzl",
|
||||
"da_haskell_binary",
|
||||
"da_haskell_library",
|
||||
)
|
||||
|
||||
da_haskell_library(
|
||||
name = "sandbox-helper",
|
||||
srcs = ["Sandbox.hs"],
|
||||
hackage_deps = [
|
||||
"base",
|
||||
"directory",
|
||||
"extra",
|
||||
"filepath",
|
||||
"process",
|
||||
"safe",
|
||||
"safe-exceptions",
|
||||
"tasty",
|
||||
"text",
|
||||
],
|
||||
)
|
||||
|
||||
da_haskell_binary(
|
||||
name = "runner",
|
||||
srcs = ["Main.hs"],
|
||||
hackage_deps = [
|
||||
"aeson",
|
||||
"base",
|
||||
"containers",
|
||||
"extra",
|
||||
"filepath",
|
||||
"jwt",
|
||||
"process",
|
||||
"tagged",
|
||||
"tasty",
|
||||
"tasty-hunit",
|
||||
"text",
|
||||
],
|
||||
visibility = ["//visibility:public"],
|
||||
deps = [
|
||||
":sandbox-helper",
|
||||
"@rules_haskell//tools/runfiles",
|
||||
],
|
||||
)
|
||||
|
||||
genrule(
|
||||
name = "test-certificates",
|
||||
srcs = [":openssl-extensions.cnf"],
|
||||
outs = [
|
||||
"ca.key",
|
||||
"ca.crt",
|
||||
"client.csr",
|
||||
"client.crt",
|
||||
"client.key",
|
||||
"client.pem",
|
||||
"server.csr",
|
||||
"server.crt",
|
||||
"server.key",
|
||||
"server.pem",
|
||||
],
|
||||
cmd = """
|
||||
set -eou pipefail
|
||||
# Generate CA key and crt
|
||||
$(location @openssl_nix//:bin/openssl) genrsa -out $(location ca.key) 4096
|
||||
$(location @openssl_nix//:bin/openssl) req -new -x509 -key $(location ca.key) -out $(location ca.crt) -subj '/CN=0.0.0.0.ca' -days 3650
|
||||
|
||||
# Generate server key, csr and crt
|
||||
$(location @openssl_nix//:bin/openssl) genrsa -out $(location server.key) 4096
|
||||
$(location @openssl_nix//:bin/openssl) pkey -in $(location server.key) -out $(location server.pem)
|
||||
$(location @openssl_nix//:bin/openssl) req -new -key $(location server.key) -out $(location server.csr) -subj '/CN=0.0.0.0.server'
|
||||
$(location @openssl_nix//:bin/openssl) x509 -req -in $(location server.csr) -CA $(location ca.crt) -CAkey $(location ca.key) -CAcreateserial -out $(location server.crt) -extfile $(location openssl-extensions.cnf) -extensions req_ext -days 3650
|
||||
|
||||
# Generate client key, csr and crt
|
||||
$(location @openssl_nix//:bin/openssl) genrsa -out $(location client.key) 4096
|
||||
$(location @openssl_nix//:bin/openssl) pkey -in $(location client.key) -out $(location client.pem)
|
||||
$(location @openssl_nix//:bin/openssl) req -new -key $(location client.key) -out $(location client.csr) -subj '/CN=0.0.0.0.client'
|
||||
$(location @openssl_nix//:bin/openssl) x509 -req -in $(location client.csr) -CA $(location ca.crt) -CAkey $(location ca.key) -CAcreateserial -out $(location client.crt) -extfile $(location openssl-extensions.cnf) -extensions req_ext -days 3650
|
||||
""",
|
||||
tools = [
|
||||
"@openssl_nix//:bin/openssl",
|
||||
],
|
||||
visibility = ["//visibility:public"],
|
||||
)
|
256
compatibility/bazel_tools/daml_ledger/Main.hs
Normal file
256
compatibility/bazel_tools/daml_ledger/Main.hs
Normal file
@ -0,0 +1,256 @@
|
||||
-- Copyright (c) 2020 Digital Asset (Switzerland) GmbH and/or its affiliates. All rights reserved.
|
||||
-- SPDX-License-Identifier: Apache-2.0
|
||||
|
||||
module Main (main) where
|
||||
|
||||
import Control.Applicative (many)
|
||||
import Control.Monad (unless, void)
|
||||
import Data.Function ((&))
|
||||
import Data.Maybe (fromMaybe)
|
||||
import Data.Proxy (Proxy (..))
|
||||
import Data.Tagged (Tagged (..))
|
||||
import System.Directory.Extra (withCurrentDirectory)
|
||||
import System.Environment (lookupEnv)
|
||||
import System.Environment.Blank (setEnv)
|
||||
import System.Exit (ExitCode(..), exitFailure)
|
||||
import System.FilePath ((</>), takeBaseName)
|
||||
import System.IO (hPutStrLn, stderr)
|
||||
import System.IO.Extra (withTempDir,writeFileUTF8)
|
||||
import System.Process (CreateProcess,proc,readCreateProcessWithExitCode)
|
||||
import Test.Tasty (TestTree,askOption,defaultMainWithIngredients,defaultIngredients,includingOptions,testGroup,withResource)
|
||||
import Test.Tasty.Options (IsOption(..), OptionDescription(..), mkOptionCLParser)
|
||||
import Test.Tasty.HUnit (testCaseSteps)
|
||||
import qualified Bazel.Runfiles
|
||||
import qualified Data.Aeson as Aeson
|
||||
import qualified Data.List as List
|
||||
import qualified Data.Map as Map
|
||||
import qualified Data.Text as T
|
||||
import qualified Web.JWT as JWT
|
||||
|
||||
import Sandbox
|
||||
|
||||
data Tools = Tools
|
||||
{ daml :: FilePath
|
||||
, sandboxConfig :: SandboxConfig
|
||||
}
|
||||
|
||||
newtype DamlOption = DamlOption FilePath
|
||||
instance IsOption DamlOption where
|
||||
defaultValue = DamlOption $ "daml"
|
||||
parseValue = Just . DamlOption
|
||||
optionName = Tagged "daml"
|
||||
optionHelp = Tagged "runfiles path to the daml executable"
|
||||
|
||||
newtype SandboxOption = SandboxOption FilePath
|
||||
instance IsOption SandboxOption where
|
||||
defaultValue = SandboxOption $ "sandbox"
|
||||
parseValue = Just . SandboxOption
|
||||
optionName = Tagged "sandbox"
|
||||
optionHelp = Tagged "runfiles path to the sandbox executable"
|
||||
|
||||
newtype SandboxArgsOption = SandboxArgsOption { unSandboxArgsOption :: [String] }
|
||||
instance IsOption SandboxArgsOption where
|
||||
defaultValue = SandboxArgsOption []
|
||||
parseValue = Just . SandboxArgsOption . (:[])
|
||||
optionName = Tagged "sandbox-arg"
|
||||
optionHelp = Tagged "extra arguments to pass to sandbox executable"
|
||||
optionCLParser = concatMany (mkOptionCLParser mempty)
|
||||
where concatMany = fmap (SandboxArgsOption . concat) . many . fmap unSandboxArgsOption
|
||||
|
||||
newtype CertificatesOption = CertificatesOption FilePath
|
||||
instance IsOption CertificatesOption where
|
||||
defaultValue = CertificatesOption $ "certificates"
|
||||
parseValue = Just . CertificatesOption
|
||||
optionName = Tagged "certs"
|
||||
optionHelp = Tagged "runfiles path to the certificates directory"
|
||||
|
||||
withTools :: (IO Tools -> TestTree) -> TestTree
|
||||
withTools tests = do
|
||||
askOption $ \(DamlOption damlPath) -> do
|
||||
askOption $ \(SandboxOption sandboxPath) -> do
|
||||
askOption $ \(SandboxArgsOption sandboxArgs) -> do
|
||||
askOption $ \(CertificatesOption certificatesPath) -> do
|
||||
let createRunfiles :: IO (FilePath -> FilePath)
|
||||
createRunfiles = do
|
||||
runfiles <- Bazel.Runfiles.create
|
||||
mainWorkspace <- fromMaybe "compatibility" <$> lookupEnv "TEST_WORKSPACE"
|
||||
pure (\path -> Bazel.Runfiles.rlocation runfiles $ mainWorkspace </> path)
|
||||
withResource createRunfiles (\_ -> pure ()) $ \locateRunfiles -> do
|
||||
let tools = do
|
||||
daml <- locateRunfiles <*> pure damlPath
|
||||
sandboxBinary <- locateRunfiles <*> pure sandboxPath
|
||||
sandboxCertificates <- locateRunfiles <*> pure certificatesPath
|
||||
let sandboxConfig = defaultSandboxConf
|
||||
{ sandboxBinary
|
||||
, sandboxArgs
|
||||
, sandboxCertificates
|
||||
}
|
||||
pure Tools
|
||||
{ daml
|
||||
, sandboxConfig
|
||||
}
|
||||
tests tools
|
||||
|
||||
newtype SdkVersion = SdkVersion String
|
||||
instance IsOption SdkVersion where
|
||||
defaultValue = SdkVersion (error "SDK version has to be set explicitly using --sdk-version")
|
||||
parseValue = Just . SdkVersion
|
||||
optionName = Tagged "sdk-version"
|
||||
optionHelp = Tagged "The SDK version number"
|
||||
|
||||
main :: IO ()
|
||||
main = do
|
||||
-- We manipulate global state via the working directory
|
||||
-- so running tests in parallel will cause trouble.
|
||||
setEnv "TASTY_NUM_THREADS" "1" True
|
||||
let options =
|
||||
[ Option @DamlOption Proxy
|
||||
, Option @SandboxOption Proxy
|
||||
, Option @SandboxArgsOption Proxy
|
||||
, Option @CertificatesOption Proxy
|
||||
, Option @SdkVersion Proxy
|
||||
]
|
||||
let ingredients = defaultIngredients ++ [includingOptions options]
|
||||
defaultMainWithIngredients ingredients $
|
||||
withTools $ \getTools -> do
|
||||
askOption $ \sdkVersion -> do
|
||||
testGroup "Deployment"
|
||||
[ authenticatedUploadTest sdkVersion getTools
|
||||
, fetchTest sdkVersion getTools
|
||||
]
|
||||
|
||||
-- | Test `daml ledger upload-dar --access-token-file`
|
||||
authenticatedUploadTest :: SdkVersion -> IO Tools -> TestTree
|
||||
authenticatedUploadTest sdkVersion getTools = do
|
||||
let sharedSecret = "TheSharedSecret"
|
||||
let getSandboxConfig = do
|
||||
cfg <- sandboxConfig <$> getTools
|
||||
pure cfg { mbSharedSecret = Just sharedSecret }
|
||||
withSandbox getSandboxConfig $ \getSandboxPort ->
|
||||
testCaseSteps "authenticatedUploadTest" $ \step -> do
|
||||
Tools{..} <- getTools
|
||||
port <- getSandboxPort
|
||||
withTempDir $ \deployDir -> do
|
||||
withCurrentDirectory deployDir $ do
|
||||
writeMinimalProject sdkVersion
|
||||
step "build"
|
||||
callProcessSilent daml ["damlc", "build"]
|
||||
let dar = ".daml/dist/proj1-0.0.1.dar"
|
||||
let tokenFile = deployDir </> "secretToken.jwt"
|
||||
step "upload"
|
||||
-- The trailing newline is not required but we want to test that it is supported.
|
||||
writeFileUTF8 tokenFile ("Bearer " <> makeSignedJwt sharedSecret <> "\n")
|
||||
callProcessSilent daml
|
||||
[ "ledger", "upload-dar"
|
||||
, "--access-token-file", tokenFile
|
||||
, "--host", "localhost", "--port", show port
|
||||
, dar
|
||||
]
|
||||
|
||||
makeSignedJwt :: String -> String
|
||||
makeSignedJwt sharedSecret = do
|
||||
let urc = JWT.ClaimsMap $ Map.fromList [ ("admin", Aeson.Bool True)]
|
||||
let cs = mempty { JWT.unregisteredClaims = urc }
|
||||
let key = JWT.hmacSecret $ T.pack sharedSecret
|
||||
let text = JWT.encodeSigned key mempty cs
|
||||
T.unpack text
|
||||
|
||||
-- | Test `daml ledger fetch-dar`
|
||||
fetchTest :: SdkVersion -> IO Tools -> TestTree
|
||||
fetchTest sdkVersion getTools = do
|
||||
let getSandboxConfig = sandboxConfig <$> getTools
|
||||
withSandbox getSandboxConfig $ \getSandboxPort ->
|
||||
testCaseSteps "fetchTest" $ \step -> do
|
||||
Tools{..} <- getTools
|
||||
port <- getSandboxPort
|
||||
withTempDir $ \fetchDir -> do
|
||||
withCurrentDirectory fetchDir $ do
|
||||
writeMinimalProject sdkVersion
|
||||
let origDar = ".daml/dist/proj1-0.0.1.dar"
|
||||
step "build/upload"
|
||||
callProcessSilent daml ["damlc", "build"]
|
||||
callProcessSilent daml
|
||||
[ "ledger", "upload-dar"
|
||||
, "--host", "localhost" , "--port" , show port
|
||||
, origDar
|
||||
]
|
||||
pid <- getMainPidOfDar daml origDar
|
||||
step "fetch/validate"
|
||||
let fetchedDar = "fetched.dar"
|
||||
callProcessSilent daml
|
||||
[ "ledger", "fetch-dar"
|
||||
, "--host", "localhost" , "--port", show port
|
||||
, "--main-package-id", pid
|
||||
, "-o", fetchedDar
|
||||
]
|
||||
callProcessSilent daml ["damlc", "validate-dar", fetchedDar]
|
||||
|
||||
-- | Discover the main package-identifier of a dar.
|
||||
--
|
||||
-- Parses the output of damlc inspect-dar. Unfortunately, this output is not
|
||||
-- currently optimized for machine readability. This function expects the
|
||||
-- following format.
|
||||
--
|
||||
-- @
|
||||
-- ...
|
||||
--
|
||||
-- DAR archive contains the following packages:
|
||||
--
|
||||
-- ...
|
||||
-- proj1-0.0.1-... "<package-id>"
|
||||
-- ...
|
||||
-- @
|
||||
getMainPidOfDar :: FilePath -> FilePath -> IO String
|
||||
getMainPidOfDar daml fp = do
|
||||
darContents <- callProcessForStdout daml ["damlc", "inspect-dar", fp]
|
||||
let packageName = takeBaseName fp
|
||||
let mbPackageLine =
|
||||
darContents
|
||||
& lines
|
||||
& dropWhile (not . List.isInfixOf "DAR archive contains the following packages")
|
||||
& drop 1
|
||||
& List.find (List.isPrefixOf packageName)
|
||||
let mbPackageId = do
|
||||
line <- mbPackageLine
|
||||
[_, quoted] <- pure $ words line
|
||||
let stripQuotes = takeWhile (/= '"') . dropWhile (== '"')
|
||||
pure $ stripQuotes quoted
|
||||
case mbPackageId of
|
||||
Nothing -> fail $ "Couldn't determine package ID for " ++ fp
|
||||
Just pkgId -> pure pkgId
|
||||
|
||||
-- | Write `daml.yaml` and `Main.daml` files in the current directory.
|
||||
writeMinimalProject :: SdkVersion -> IO ()
|
||||
writeMinimalProject (SdkVersion sdkVersion) = do
|
||||
writeFileUTF8 "daml.yaml" $ unlines
|
||||
[ "sdk-version: " <> sdkVersion
|
||||
, "name: proj1"
|
||||
, "version: 0.0.1"
|
||||
, "source: ."
|
||||
, "dependencies:"
|
||||
, " - daml-prim"
|
||||
, " - daml-stdlib"
|
||||
]
|
||||
writeFileUTF8 "Main.daml" $ unlines
|
||||
[ "daml 1.2"
|
||||
, "module Main where"
|
||||
, "template T with p : Party where signatory p"
|
||||
]
|
||||
|
||||
callProcessSilent :: FilePath -> [String] -> IO ()
|
||||
callProcessSilent cmd args =
|
||||
void $ run (proc cmd args)
|
||||
|
||||
callProcessForStdout :: FilePath -> [String] -> IO String
|
||||
callProcessForStdout cmd args =
|
||||
run (proc cmd args)
|
||||
|
||||
run :: CreateProcess -> IO String
|
||||
run cp = do
|
||||
(exitCode, out, err) <- readCreateProcessWithExitCode cp ""
|
||||
unless (exitCode == ExitSuccess) $ do
|
||||
hPutStrLn stderr $ "Failure: Command \"" <> show cp <> "\" exited with " <> show exitCode
|
||||
hPutStrLn stderr $ unlines ["stdout: ", out]
|
||||
hPutStrLn stderr $ unlines ["stderr: ", err]
|
||||
exitFailure
|
||||
return out
|
147
compatibility/bazel_tools/daml_ledger/Sandbox.hs
Normal file
147
compatibility/bazel_tools/daml_ledger/Sandbox.hs
Normal file
@ -0,0 +1,147 @@
|
||||
-- Copyright (c) 2020 Digital Asset (Switzerland) GmbH and/or its affiliates. All rights reserved.
|
||||
-- SPDX-License-Identifier: Apache-2.0
|
||||
|
||||
module Sandbox
|
||||
( SandboxConfig (..)
|
||||
, SandboxResource (..)
|
||||
, ClientAuth (..)
|
||||
, TimeMode (..)
|
||||
, defaultSandboxConf
|
||||
, withSandbox
|
||||
, createSandbox
|
||||
, destroySandbox
|
||||
) where
|
||||
|
||||
import Control.Concurrent (threadDelay)
|
||||
import Control.Exception.Safe (catchJust, mask, onException)
|
||||
import Control.Monad (guard)
|
||||
import qualified Data.Text.IO as T
|
||||
import Safe (readMay)
|
||||
import System.Exit (exitFailure)
|
||||
import System.FilePath ((</>))
|
||||
import System.IO.Error (isDoesNotExistError)
|
||||
import System.IO.Extra (Handle, IOMode (..), hClose, newTempFile, openBinaryFile, stderr)
|
||||
import System.Info.Extra (isWindows)
|
||||
import System.Process
|
||||
import Test.Tasty (TestTree, withResource)
|
||||
|
||||
data ClientAuth
|
||||
= None
|
||||
| Optional
|
||||
| Require
|
||||
|
||||
data TimeMode
|
||||
= WallClock
|
||||
| Static
|
||||
|
||||
data SandboxConfig = SandboxConfig
|
||||
{ sandboxBinary :: FilePath
|
||||
-- ^ Path to the sandbox executable.
|
||||
, sandboxArgs :: [String]
|
||||
-- ^ Extra arguments required to run the sandbox.
|
||||
, sandboxCertificates :: FilePath
|
||||
-- ^ Path to the directory holding the certificates.
|
||||
--
|
||||
-- Should contain @ca.crt@, @server.pem@, and @server.crt@.
|
||||
, enableTls :: Bool
|
||||
, dars :: [FilePath]
|
||||
, timeMode :: TimeMode
|
||||
, mbClientAuth :: Maybe ClientAuth
|
||||
, mbSharedSecret :: Maybe String
|
||||
, mbLedgerId :: Maybe String
|
||||
}
|
||||
|
||||
defaultSandboxConf :: SandboxConfig
|
||||
defaultSandboxConf = SandboxConfig
|
||||
{ sandboxBinary = "sandbox"
|
||||
, sandboxArgs = []
|
||||
, sandboxCertificates = ""
|
||||
, enableTls = False
|
||||
, dars = []
|
||||
, timeMode = WallClock
|
||||
, mbClientAuth = Nothing
|
||||
, mbSharedSecret = Nothing
|
||||
, mbLedgerId = Nothing
|
||||
}
|
||||
|
||||
getSandboxProc :: SandboxConfig -> FilePath -> IO CreateProcess
|
||||
getSandboxProc SandboxConfig{..} portFile = do
|
||||
tlsArgs <- if enableTls
|
||||
then do
|
||||
pure
|
||||
[ "--cacrt", sandboxCertificates </> "ca.crt"
|
||||
, "--pem", sandboxCertificates </> "server.pem"
|
||||
, "--crt", sandboxCertificates </> "server.crt"
|
||||
]
|
||||
else pure []
|
||||
pure $ proc sandboxBinary $ concat
|
||||
[ sandboxArgs
|
||||
, [ "--port=0", "--port-file", portFile ]
|
||||
, tlsArgs
|
||||
, [ timeArg ]
|
||||
, [ "--client-auth=" <> clientAuthArg auth | Just auth <- [mbClientAuth] ]
|
||||
, [ "--auth-jwt-hs256-unsafe=" <> secret | Just secret <- [mbSharedSecret] ]
|
||||
, [ "--ledgerid=" <> ledgerId | Just ledgerId <- [mbLedgerId] ]
|
||||
, dars
|
||||
]
|
||||
where timeArg = case timeMode of
|
||||
WallClock -> "--wall-clock-time"
|
||||
Static -> "--static-time"
|
||||
clientAuthArg auth = case auth of
|
||||
None -> "none"
|
||||
Optional -> "optional"
|
||||
Require -> "require"
|
||||
|
||||
createSandbox :: FilePath -> Handle -> SandboxConfig -> IO SandboxResource
|
||||
createSandbox portFile sandboxOutput conf = do
|
||||
sandboxProc <- getSandboxProc conf portFile
|
||||
mask $ \unmask -> do
|
||||
ph <- createProcess sandboxProc { std_out = UseHandle sandboxOutput }
|
||||
let waitForStart = do
|
||||
port <- readPortFile maxRetries portFile
|
||||
pure (SandboxResource ph port)
|
||||
unmask (waitForStart `onException` cleanupProcess ph)
|
||||
|
||||
withSandbox :: IO SandboxConfig -> (IO Int -> TestTree) -> TestTree
|
||||
withSandbox getConf f =
|
||||
withResource (openBinaryFile nullDevice ReadWriteMode) hClose $ \getDevNull ->
|
||||
withResource newTempFile snd $ \getPortFile ->
|
||||
let createSandbox' = do
|
||||
(portFile, _) <- getPortFile
|
||||
devNull <- getDevNull
|
||||
conf <- getConf
|
||||
createSandbox portFile devNull conf
|
||||
in withResource createSandbox' destroySandbox (f . fmap sandboxPort)
|
||||
|
||||
|
||||
data SandboxResource = SandboxResource
|
||||
{ sandboxProcess :: (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle)
|
||||
, sandboxPort :: Int
|
||||
}
|
||||
|
||||
destroySandbox :: SandboxResource -> IO ()
|
||||
destroySandbox = cleanupProcess . sandboxProcess
|
||||
|
||||
nullDevice :: FilePath
|
||||
nullDevice
|
||||
-- taken from typed-process
|
||||
| isWindows = "\\\\.\\NUL"
|
||||
| otherwise = "/dev/null"
|
||||
|
||||
readPortFile :: Int -> String -> IO Int
|
||||
readPortFile 0 _file = do
|
||||
T.hPutStrLn stderr "Port file was not written to in time."
|
||||
exitFailure
|
||||
readPortFile n file = do
|
||||
fileContent <- catchJust (guard . isDoesNotExistError) (readFile file) (const $ pure "")
|
||||
case readMay fileContent of
|
||||
Nothing -> do
|
||||
threadDelay (1000 * retryDelayMillis)
|
||||
readPortFile (n-1) file
|
||||
Just p -> pure p
|
||||
|
||||
retryDelayMillis :: Int
|
||||
retryDelayMillis = 50
|
||||
|
||||
maxRetries :: Int
|
||||
maxRetries = 120 * (1000 `div` retryDelayMillis)
|
@ -0,0 +1,7 @@
|
||||
|
||||
[ req_ext ]
|
||||
subjectAltName = @alt_names
|
||||
|
||||
[ alt_names ]
|
||||
DNS = localhost
|
||||
IP = 127.0.0.1
|
27
compatibility/bazel_tools/daml_ledger_test.sh
Executable file
27
compatibility/bazel_tools/daml_ledger_test.sh
Executable file
@ -0,0 +1,27 @@
|
||||
#!/usr/bin/env bash
|
||||
# Copyright (c) 2020 Digital Asset (Switzerland) GmbH and/or its affiliates. All rights reserved.
|
||||
# SPDX-License-Identifier: Apache-2.0
|
||||
|
||||
# Copy-pasted from the Bazel Bash runfiles library v2.
|
||||
set -uo pipefail; f=bazel_tools/tools/bash/runfiles/runfiles.bash
|
||||
source "${RUNFILES_DIR:-/dev/null}/$f" 2>/dev/null || \
|
||||
source "$(grep -sm1 "^$f " "${RUNFILES_MANIFEST_FILE:-/dev/null}" | cut -f2- -d' ')" 2>/dev/null || \
|
||||
source "$0.runfiles/$f" 2>/dev/null || \
|
||||
source "$(grep -sm1 "^$f " "$0.runfiles_manifest" | cut -f2- -d' ')" 2>/dev/null || \
|
||||
source "$(grep -sm1 "^$f " "$0.exe.runfiles_manifest" | cut -f2- -d' ')" 2>/dev/null || \
|
||||
{ echo>&2 "ERROR: cannot find $f"; exit 1; }; f=; set -e
|
||||
# --- end runfiles.bash initialization v2 ---
|
||||
set -euo pipefail
|
||||
|
||||
RUNNER="$(rlocation "$TEST_WORKSPACE/$1")"
|
||||
SDK_VERSION="$2"
|
||||
DAML="$(rlocation "$TEST_WORKSPACE/$3")"
|
||||
CERTS="$4"
|
||||
SANDBOX="$(rlocation "$TEST_WORKSPACE/$5")"
|
||||
|
||||
"$RUNNER" \
|
||||
--sdk-version "$SDK_VERSION" \
|
||||
--daml "$DAML" \
|
||||
--certs "$CERTS" \
|
||||
--sandbox "$SANDBOX" \
|
||||
"${@:6}"
|
@ -64,8 +64,55 @@ def extra_tags(sdk_version, platform_version):
|
||||
return ["head-quick"]
|
||||
return []
|
||||
|
||||
def _concat(lists):
|
||||
return [v for l in lists for v in l]
|
||||
|
||||
def daml_ledger_test(
|
||||
name,
|
||||
sdk_version,
|
||||
daml,
|
||||
sandbox,
|
||||
sandbox_args = [],
|
||||
data = [],
|
||||
**kwargs):
|
||||
native.sh_test(
|
||||
name = name,
|
||||
# TODO[AH]: rules_haskell's runfiles library uses the runfiles tree
|
||||
# relative to the actual executable path (`getExecutablePath`) instead
|
||||
# of argument 0, as [specified][runfiles-spec]. This means that the
|
||||
# symlink generated by `sh_test` does not override the runfiles tree
|
||||
# and `data` dependencies of the `sh_test` rule are not found by the
|
||||
# test runner. This should be fixed in rules_haskell. In the meantime
|
||||
# we work around the issue by using a wrapper script that does the
|
||||
# `rlocation` lookup using the correct runfiles tree.
|
||||
# [runfiles-spec]: https://docs.google.com/document/d/e/2PACX-1vSDIrFnFvEYhKsCMdGdD40wZRBX3m3aZ5HhVj4CtHPmiXKDCxioTUbYsDydjKtFDAzER5eg7OjJWs3V/pub
|
||||
srcs = ["//bazel_tools:daml_ledger_test.sh"],
|
||||
args = [
|
||||
"$(rootpath //bazel_tools/daml_ledger:runner)",
|
||||
#"--sdk-version",
|
||||
sdk_version,
|
||||
#"--daml",
|
||||
"$(rootpath %s)" % daml,
|
||||
#"--certs",
|
||||
"bazel_tools/test_certificates",
|
||||
#"--sandbox",
|
||||
"$(rootpath %s)" % sandbox,
|
||||
] + _concat([["--sandbox-arg", arg] for arg in sandbox_args]),
|
||||
data = data + depset(direct = [
|
||||
"//bazel_tools/daml_ledger:runner",
|
||||
"//bazel_tools/daml_ledger:test-certificates",
|
||||
# Deduplicate if daml and sandbox come from the same release.
|
||||
daml,
|
||||
sandbox,
|
||||
]).to_list(),
|
||||
**kwargs
|
||||
)
|
||||
|
||||
def sdk_platform_test(sdk_version, platform_version):
|
||||
# SDK components
|
||||
daml_assistant = "@daml-sdk-{sdk_version}//:daml".format(
|
||||
sdk_version = sdk_version,
|
||||
)
|
||||
ledger_api_test_tool = "@daml-sdk-{sdk_version}//:ledger-api-test-tool".format(
|
||||
sdk_version = sdk_version,
|
||||
)
|
||||
@ -79,7 +126,7 @@ def sdk_platform_test(sdk_version, platform_version):
|
||||
)
|
||||
sandbox_args = ["sandbox"]
|
||||
|
||||
# Test case
|
||||
# ledger-api-test-tool test-cases
|
||||
name = "ledger-api-test-tool-{sdk_version}-platform-{platform_version}".format(
|
||||
sdk_version = sdk_version,
|
||||
platform_version = platform_version,
|
||||
@ -122,3 +169,16 @@ def sdk_platform_test(sdk_version, platform_version):
|
||||
)],
|
||||
tags = ["exclusive"] + extra_tags(sdk_version, platform_version),
|
||||
)
|
||||
|
||||
# daml-ledger test-cases
|
||||
name = "daml-ledger-{sdk_version}-platform-{platform_version}".format(
|
||||
sdk_version = sdk_version,
|
||||
platform_version = platform_version,
|
||||
)
|
||||
daml_ledger_test(
|
||||
name = name,
|
||||
sdk_version = sdk_version,
|
||||
daml = daml_assistant,
|
||||
sandbox = sandbox,
|
||||
sandbox_args = sandbox_args,
|
||||
)
|
||||
|
@ -26,6 +26,12 @@ import qualified DA.Daml.LF.Proto3.Archive as LFArchive
|
||||
|
||||
data Tools = Tools { damlc :: FilePath, damlHelper :: FilePath }
|
||||
|
||||
-- NOTE: This test was moved to the compatibility tests in
|
||||
-- `compatibility/bazel_tools/daml_ledger/Main.hs`. This file remains for now
|
||||
-- for easier iterative testing during development. If you modify these tests
|
||||
-- then please keep them in sync with the corresponding tests in the
|
||||
-- compatibility workspace.
|
||||
|
||||
main :: IO ()
|
||||
main = do
|
||||
-- We manipulate global state via the working directory
|
||||
|
Loading…
Reference in New Issue
Block a user