Script package vetting (#17035)

* Version the script runner

* Fix import

* Add v2 files

* Add v1/v2 switching logic

* Add -- @ SCRIPT-V2 flag to integration tests

* Fix daml-v2 docs gen, refactor withDamlScriptDep

* Fix package name for daml-script2

* Fix polymorphic script warning for daml-script2

* Address review comments

* Scala, not haskell

* Add warnings to template files

* Rename daml-v2 to daml3, daml-script-v2 to daml3-script

* Fix polymorphic warning again

* Switch try catch to a command

* Use free properly, make all continues identity

* Split up DamlScript, implement Questions logic

* Fix most of the issues

* Drop internal callstack frames

* Minor fixes

* Prevent Catch being treated as an old-style typeclass

* Fix catch parsing

* Implement package vetting and unvetting

* Add no such template error to scenario service proto

* Notes for updateCompiledPackages in IdeLedgerClient

* Improve script src copying

* Add package vetting test, and framework for extra packages in integration tests

* Fix daml script dar rule mistake

* Apply suggestions from code review

Co-authored-by: Remy <remy.haemmerle@daml.com>

* Convert PureCompiledPackages to case class

* Generalise Lookup error over scenario proto

* Address review

---------

Co-authored-by: Remy <remy.haemmerle@daml.com>
This commit is contained in:
Samuel Williams 2023-06-29 15:42:34 +01:00 committed by GitHub
parent cace97977d
commit 95dd64bc02
No known key found for this signature in database
GPG Key ID: 4AEE18F83AFDEB23
26 changed files with 692 additions and 55 deletions

View File

@ -436,7 +436,7 @@ runDamldocMany' testfiles importPathM mScriptPackageData = do
, optScenarioService = EnableScenarioService False
, optImportPath = maybeToList importPathM
, optPackageDbs = maybeToList $ fst <$> mScriptPackageData
, optPackageImports = maybeToList $ snd <$> mScriptPackageData
, optPackageImports = maybe [] snd mScriptPackageData
}
-- run the doc generator on that file

View File

@ -227,6 +227,8 @@ da_haskell_test(
":bond-trading",
":cant-skip-preprocessor",
":daml-test-files",
":package-vetting-package-a.dar",
":package-vetting-package-b.dar",
":query-lf-lib",
"//compiler/damlc/pkg-db",
"//compiler/damlc/stable-packages",
@ -1162,3 +1164,19 @@ da_haskell_test(
"//libs-haskell/da-hs-base",
],
)
daml_compile(
name = "package-vetting-package-a",
srcs = ["daml-test-files/external-packages/package-vetting-test-files/PackageAModule.daml"],
project_name = "package-vetting-package-a",
target = "1.dev",
version = "1.0.0",
)
daml_compile(
name = "package-vetting-package-b",
srcs = ["daml-test-files/external-packages/package-vetting-test-files/PackageBModule.daml"],
project_name = "package-vetting-package-b",
target = "1.dev",
version = "1.0.0",
)

View File

@ -0,0 +1,103 @@
-- Copyright (c) 2023 Digital Asset (Switzerland) GmbH and/or its affiliates. All rights reserved.
-- SPDX-License-Identifier: Apache-2.0
-- @ SCRIPT-V2
module Daml3ScriptPackageVetting where
import Daml.Script
import PackageAModule
import DA.Assert
packageA : PackageName
packageA = PackageName "package-vetting-package-a" "1.0.0"
packageB : PackageName
packageB = PackageName "package-vetting-package-b" "1.0.0"
canUseImportedPackage : Script ()
canUseImportedPackage = script do
alice <- allocateParty "Alice"
alice `submit` createCmd PackageATemplate with p = alice
pure ()
canUseReVettedPackage : Script ()
canUseReVettedPackage = script do
alice <- allocateParty "Alice"
unvetPackages [packageA]
vetPackages [packageA]
alice `submit` createCmd PackageATemplate with p = alice
pure ()
-- @ ERROR range=34:1-34:25; Failed to find package
cannotUseUnvettedPackage : Script ()
cannotUseUnvettedPackage = script do
alice <- allocateParty "Alice"
unvetPackages [packageA]
alice `submit` createCmd PackageATemplate with p = alice
pure ()
-- @ ERROR range=42:1-42:30; Failed to find package
cannotExerciseUnvettedPackage : Script ()
cannotExerciseUnvettedPackage = script do
alice <- allocateParty "Alice"
cid <- alice `submit` createCmd PackageATemplate with p = alice
unvetPackages [packageA]
alice `submit` exerciseCmd cid Call
pure ()
hasAllOf : Eq a => [a] -> [a] -> Bool
hasAllOf as = all (`elem` as)
hasNoneOf : Eq a => [a] -> [a] -> Bool
hasNoneOf as = not . any (`elem` as)
assertPackages : Script [PackageName] -> [PackageName] -> [PackageName] -> Script ()
assertPackages getPackages expected notExpected = script do
packages <- getPackages
assertMsg ("Expected " <> show expected <> " to be a subset of " <> show packages <> ", but it wasn't.") $ packages `hasAllOf` expected
assertMsg ("Expected none of " <> show notExpected <> " to be in " <> show packages <> ", but some were.") $ packages `hasNoneOf` notExpected
assertVettedPackages : [PackageName] -> [PackageName] -> Script ()
assertVettedPackages = assertPackages listVettedPackages
assertAllPackages : Script ()
assertAllPackages = assertPackages listAllPackages [packageA, packageB] []
listPackagesIsCorrect : Script ()
listPackagesIsCorrect = script do
-- Good starting position
assertVettedPackages [packageA, packageB] []
assertAllPackages
-- Check we can disable A
unvetPackages [packageA]
assertVettedPackages [packageB] [packageA]
assertAllPackages
-- Check we can disable B on top of A
unvetPackages [packageB]
assertVettedPackages [] [packageA, packageB]
assertAllPackages
-- Check we can bring back in A
vetPackages [packageA]
assertVettedPackages [packageA] [packageB]
assertAllPackages
-- Check we can bring in packages that are already enabled
vetPackages [packageA, packageB]
assertVettedPackages [packageA, packageB] []
assertAllPackages
-- Check we can disable multiple at a time
unvetPackages [packageA, packageB]
assertVettedPackages [] [packageA, packageB]
assertAllPackages
-- Check default packages count (as packageA and packageB previously disabled)
-- 6 packages in prim (5 specific modules + prim itself)
-- 6 packages in stdlib (5 specific modules + stdlib itself)
-- 1 package for daml3-script
packages <- listVettedPackages
length packages === 13

View File

@ -0,0 +1,9 @@
module PackageAModule where
template PackageATemplate with
p : Party
where
signatory p
choice Call : ()
controller p
do pure ()

View File

@ -0,0 +1,6 @@
module PackageBModule where
template PackageBTemplate with
p : Party
where
signatory p

View File

@ -94,7 +94,7 @@ generateTests scriptPackageData = testGroup "generate doctest module"
{ optHaddock = Haddock True
, optScenarioService = EnableScenarioService False
, optPackageDbs = [fst scriptPackageData]
, optPackageImports = [snd scriptPackageData]
, optPackageImports = snd scriptPackageData
}
withDamlIdeState opts Logger.makeNopHandle (NotificationHandler $ \_ _ -> pure ()) $ \ideState -> do
Just pm <- runActionSync ideState $ use GetParsedModule $ toNormalizedFilePath' tmpFile

View File

@ -121,7 +121,7 @@ instance IsOption IsScriptV2Opt where
optionName = Tagged "daml-script-v2"
optionHelp = Tagged "Use daml script v2 (true|false)"
type ScriptPackageData = (FilePath, PackageFlag)
type ScriptPackageData = (FilePath, [PackageFlag])
-- | Creates a temp directory with daml script v1 installed, gives the database db path and package flag
withDamlScriptDep :: Maybe Version -> (ScriptPackageData -> IO a) -> IO a
@ -129,40 +129,52 @@ withDamlScriptDep mLfVer =
let
lfVerStr = maybe "" (\lfVer -> "-" <> renderVersion lfVer) mLfVer
darPath = "daml-script" </> "daml" </> "daml-script" <> lfVerStr <> ".dar"
in withVersionedDamlScriptDep ("daml-script-" <> sdkPackageVersion) darPath mLfVer
in withVersionedDamlScriptDep ("daml-script-" <> sdkPackageVersion) darPath mLfVer []
-- Daml-script v2 is only 1.dev right now
withDamlScriptV2Dep :: (ScriptPackageData -> IO a) -> IO a
withDamlScriptV2Dep =
let
darPath = "daml-script" </> "daml3" </> "daml3-script.dar"
in withVersionedDamlScriptDep ("daml3-script-" <> sdkPackageVersion) darPath (Just versionDev)
in withVersionedDamlScriptDep ("daml3-script-" <> sdkPackageVersion) darPath (Just versionDev) scriptV2ExternalPackages
-- External dars for scriptv2 when testing upgrades.
-- package name and version
scriptV2ExternalPackages :: [(String, String)]
scriptV2ExternalPackages =
[ ("package-vetting-package-a", "1.0.0")
, ("package-vetting-package-b", "1.0.0")
]
-- | Takes the bazel namespace, dar suffix (used for lf versions in v1) and lf version, installs relevant daml script and gives
-- database db path and package flag
withVersionedDamlScriptDep :: String -> String -> Maybe Version -> (ScriptPackageData -> IO a) -> IO a
withVersionedDamlScriptDep packageFlagName darPath mLfVer cont = do
withVersionedDamlScriptDep :: String -> String -> Maybe Version -> [(String, String)] -> (ScriptPackageData -> IO a) -> IO a
withVersionedDamlScriptDep packageFlagName darPath mLfVer extraPackages cont = do
withTempDir $ \dir -> do
withCurrentDirectory dir $ do
let projDir = toNormalizedFilePath' dir
-- Bring in daml-script as previously installed by withDamlScriptDep, must include package db
-- daml-script and daml-triggers use the sdkPackageVersion for their versioning
packageFlag = ExposePackage ("--package " <> packageFlagName) (UnitIdArg $ stringToUnitId packageFlagName) (ModRenaming True [])
mkPackageFlag flagName = ExposePackage ("--package " <> flagName) (UnitIdArg $ stringToUnitId flagName) (ModRenaming True [])
toPackageName (name, version) = name <> "-" <> version
packageFlags = mkPackageFlag <$> packageFlagName : (toPackageName <$> extraPackages)
scriptDar <- locateRunfiles $ mainWorkspace </> darPath
extraDars <- traverse (\(name, _) -> locateRunfiles $ mainWorkspace </> "compiler" </> "damlc" </> "tests" </> name <> ".dar") extraPackages
installDependencies
projDir
(defaultOptions mLfVer)
(PackageSdkVersion sdkVersion)
["daml-prim", "daml-stdlib", scriptDar]
[]
extraDars
createProjectPackageDb
projDir
(defaultOptions mLfVer)
mempty
cont (dir </> projectPackageDatabase, packageFlag)
cont (dir </> projectPackageDatabase, packageFlags)
main :: IO ()
main = do
@ -249,7 +261,7 @@ getCantSkipPreprocessorTestFiles = do
pure [("cant-skip-preprocessor/DA/Internal/Hack.daml", file, anns)]
getIntegrationTests :: (TODO -> IO ()) -> SS.Handle -> ScriptPackageData -> IO TestTree
getIntegrationTests registerTODO scenarioService (packageDbPath, packageFlag) = do
getIntegrationTests registerTODO scenarioService (packageDbPath, packageFlags) = do
putStrLn $ "rtsSupportsBoundThreads: " ++ show rtsSupportsBoundThreads
do n <- getNumCapabilities; putStrLn $ "getNumCapabilities: " ++ show n
@ -277,7 +289,7 @@ getIntegrationTests registerTODO scenarioService (packageDbPath, packageFlag) =
, dlintHintFiles = NoDlintHintFiles
}
, optSkipScenarioValidation = SkipScenarioValidation skipValidation
, optPackageImports = [packageFlag]
, optPackageImports = packageFlags
}
mkIde options = do

View File

@ -55,9 +55,9 @@ ideTests mbScenarioService scriptPackageData =
]
addScriptOpts :: Maybe ScriptPackageData -> Daml.Options -> Daml.Options
addScriptOpts = maybe id $ \(packageDbPath, packageFlag) opts -> opts
addScriptOpts = maybe id $ \(packageDbPath, packageFlags) opts -> opts
{ Daml.optPackageDbs = [packageDbPath]
, Daml.optPackageImports = [packageFlag]
, Daml.optPackageImports = packageFlags
}
-- | Tasty test case from a ShakeTest.

View File

@ -509,6 +509,30 @@ prettyScenarioErrorError (Just err) = do
pure $ text $ T.pack $ "Evaluation timed out after " <> show timeout <> " seconds"
ScenarioErrorErrorCancelledByRequest _ ->
pure $ text $ T.pack "Evaluation was cancelled because the test was changed and rerun in a new thread."
ScenarioErrorErrorLookupError ScenarioError_LookupError {..} -> do
let
errMsg =
case scenarioError_LookupErrorError of
Just (ScenarioError_LookupErrorErrorNotFound ScenarioError_LookupError_NotFound {..}) ->
"Failed to find " <> scenarioError_LookupError_NotFoundNotFound <>
if scenarioError_LookupError_NotFoundNotFound == scenarioError_LookupError_NotFoundContext
then ""
else " when looking for " <> scenarioError_LookupError_NotFoundContext
Just (ScenarioError_LookupErrorErrorAmbiguousInterfaceInstance ScenarioError_LookupError_AmbiguousInterfaceInstance {..}) ->
"Multiple possible instances of " <> scenarioError_LookupError_AmbiguousInterfaceInstanceInstance <>
if scenarioError_LookupError_AmbiguousInterfaceInstanceInstance == scenarioError_LookupError_AmbiguousInterfaceInstanceContext
then ""
else " in the context of " <> scenarioError_LookupError_AmbiguousInterfaceInstanceContext
Nothing -> "Unknown Lookup error"
pure $ vcat
[ text $ TL.toStrict errMsg
, label_ "Package name:" $
prettyMay "<missing package name>"
prettyPackageMetadata
scenarioError_LookupErrorPackageMetadata
, label_ "Package id:" $ text $ TL.toStrict scenarioError_LookupErrorPackageId
]
partyDifference :: V.Vector Party -> V.Vector Party -> Doc SyntaxClass
partyDifference with without =
@ -992,6 +1016,9 @@ prettyDefName world (Identifier mbPkgId (UnmangledQualifiedName modName defName)
ppName = text name <> ppPkgId
ppPkgId = maybe mempty prettyPackageIdentifier mbPkgId
prettyPackageMetadata :: PackageMetadata -> Doc SyntaxClass
prettyPackageMetadata (PackageMetadata name version) = text $ TL.toStrict $ name <> "-" <> version
prettyChoiceId
:: LF.World -> Maybe Identifier -> TL.Text
-> Doc SyntaxClass

View File

@ -170,6 +170,11 @@ message ContractRef {
Identifier template_id = 3;
}
message PackageMetadata {
string package_name = 1;
string package_version = 2;
}
message ScenarioError {
message TemplatePreconditionViolated {
Identifier template_id = 1;
@ -263,6 +268,25 @@ message ScenarioError {
Identifier required_interface_id = 3;
}
message LookupError {
message NotFound {
string not_found = 1;
string context = 2;
}
message AmbiguousInterfaceInstance {
string instance = 1;
string context = 2;
}
oneof error {
NotFound not_found = 1;
AmbiguousInterfaceInstance ambiguous_interface_instance = 2;
}
PackageMetadata package_metadata = 3; // optional
string package_id = 4;
}
// The state of the ledger at the time of the error
repeated ScenarioStep scenario_steps = 1;
repeated Node nodes = 2;
@ -337,7 +361,8 @@ message ScenarioError {
DisclosedContractKeyHashingError disclosed_contract_key_hashing_error = 39;
int64 evaluationTimeout = 40;
Empty cancelledByRequest = 41;
// next is 43;
LookupError lookup_error = 43;
// next is 44;
}
}

View File

@ -5,6 +5,7 @@ package com.daml.lf
package scenario
import com.daml.lf.data.{ImmArray, Numeric, Ref}
import com.daml.lf.language.Ast.PackageMetadata
import com.daml.lf.ledger.EventId
import com.daml.lf.scenario.api.{v1 => proto}
import com.daml.lf.speedy.{SError, SValue, TraceLog, Warning, WarningLog}
@ -330,6 +331,28 @@ final class Conversions(
builder.setEvaluationTimeout(timeout.toSeconds)
case Error.CanceledByRequest() =>
builder.setCancelledByRequest(empty)
case Error.LookupError(err, oPackageMeta, packageId) =>
val nstBuilder =
proto.ScenarioError.LookupError.newBuilder
.setPackageId(packageId)
err match {
case language.LookupError.NotFound(notFound, context) =>
nstBuilder.setNotFound(
proto.ScenarioError.LookupError.NotFound.newBuilder
.setNotFound(notFound.pretty)
.setContext(context.pretty)
)
case language.LookupError.AmbiguousInterfaceInstance(instance, context) =>
nstBuilder.setAmbiguousInterfaceInstance(
proto.ScenarioError.LookupError.AmbiguousInterfaceInstance.newBuilder
.setInstance(instance.pretty)
.setContext(context.pretty)
)
}
oPackageMeta.foreach(packageMeta =>
nstBuilder.setPackageMetadata(mkPackageMetadata(packageMeta))
)
builder.setLookupError(nstBuilder.build)
}
builder.build
}
@ -486,6 +509,12 @@ final class Conversions(
.setTemplateId(convertIdentifier(templateId))
.build
def mkPackageMetadata(packageMetadata: PackageMetadata): proto.PackageMetadata =
proto.PackageMetadata.newBuilder
.setPackageName(packageMetadata.name.toString)
.setPackageVersion(packageMetadata.version.toString)
.build
def convertScenarioStep(
stepId: Int,
step: ScenarioLedger.ScenarioStep,

View File

@ -27,7 +27,7 @@ private[lf] abstract class CompiledPackages(
/** Important: use the constructor only if you _know_ you have all the definitions! Otherwise
* use the apply in the companion object, which will compile them for you.
*/
private[lf] final class PureCompiledPackages(
private[lf] final case class PureCompiledPackages(
val packageIds: Set[PackageId],
val pkgInterface: PackageInterface,
val defns: Map[SDefinitionRef, SDefinition],

View File

@ -54,7 +54,7 @@ sealed abstract class Reference extends Product with Serializable {
object Reference {
final case class Package(packageId: PackageId) extends Reference {
override def pretty: String = s"package $packageId."
override def pretty: String = s"package $packageId"
}
final case class Module(packageId: PackageId, moduleName: ModuleName) extends Reference {

View File

@ -9,7 +9,7 @@ import com.daml.lf.data.Ref._
import com.daml.lf.language.Ast._
import scala.annotation.tailrec
private[lf] class PackageInterface(signatures: PartialFunction[PackageId, PackageSignature]) {
private[lf] class PackageInterface(val signatures: PartialFunction[PackageId, PackageSignature]) {
import PackageInterface._

View File

@ -4,8 +4,9 @@
package com.daml.lf
package scenario
import com.daml.lf.data.Ref.{Identifier, Party}
import com.daml.lf.data.Ref.{Identifier, Party, PackageId}
import com.daml.lf.data.Time
import com.daml.lf.language.Ast.PackageMetadata
import com.daml.lf.ledger.EventId
import com.daml.lf.speedy.SError.SError
import com.daml.lf.transaction.{GlobalKey, VersionedTransaction}
@ -82,4 +83,11 @@ object Error {
/** Submitted commands for parties that have not been allocated. */
final case class PartiesNotAllocated(parties: Set[Party]) extends Error
/** Lookup error from the engine */
final case class LookupError(
err: language.LookupError,
packageMeta: Option[PackageMetadata],
packageId: PackageId,
) extends Error
}

View File

@ -4,6 +4,7 @@
package com.daml.lf
package scenario
import com.daml.lf.language.Ast.PackageMetadata
import org.typelevel.paiges.Doc
import org.typelevel.paiges.Doc._
@ -80,6 +81,15 @@ private[lf] object Pretty {
case Error.CanceledByRequest() =>
text("Evaluation was cancelled because the test was changed and rerun in a new thread.")
case Error.LookupError(err, packageMetadata, packageId) => {
val packageName = packageMetadata.fold(packageId.toString)({
case PackageMetadata(name, version, _) => s"$name-$version"
})
text(
s"Error: ${err.pretty}\nin package ${packageName}"
)
}
}
}

View File

@ -75,6 +75,12 @@ module Daml.Script
, listUserRightsOn
, submitUser
, submitUserOn
, PackageName (..)
, vetPackages
, unvetPackages
, listVettedPackages
, listAllPackages
) where
import Daml.Script.Internal

View File

@ -4,6 +4,7 @@
module Daml.Script.Questions
( module Daml.Script.Questions.Commands
, module Daml.Script.Questions.Exceptions
, module Daml.Script.Questions.Packages
, module Daml.Script.Questions.PartyManagement
, module Daml.Script.Questions.Query
, module Daml.Script.Questions.Submit
@ -15,6 +16,7 @@ module Daml.Script.Questions
import Daml.Script.Questions.Commands
import Daml.Script.Questions.Exceptions
import Daml.Script.Questions.Packages
import Daml.Script.Questions.PartyManagement
import Daml.Script.Questions.Query
import Daml.Script.Questions.Submit

View File

@ -0,0 +1,44 @@
-- Copyright (c) 2023 Digital Asset (Switzerland) GmbH and/or its affiliates. All rights reserved.
-- SPDX-License-Identifier: Apache-2.0
-- TODO[SW]: Add some kind of warning here saying this _only_ works for IdeLedgerClient
module Daml.Script.Questions.Packages where
import Daml.Script.Internal
import DA.Stack
data VetPackages = VetPackages with
packages : [PackageName]
instance IsQuestion VetPackages ()
data UnvetPackages = UnvetPackages with
packages : [PackageName]
instance IsQuestion UnvetPackages ()
data ListVettedPackages = ListVettedPackages {}
instance IsQuestion ListVettedPackages [PackageName]
data ListAllPackages = ListAllPackages {}
instance IsQuestion ListAllPackages [PackageName]
data PackageName = PackageName
with
name : Text
version : Text
deriving (Eq, Ord)
instance Show PackageName where
show (PackageName name version) = name <> "-" <> version
vetPackages : HasCallStack => [PackageName] -> Script ()
vetPackages = lift . VetPackages
unvetPackages : HasCallStack => [PackageName] -> Script ()
unvetPackages = lift . UnvetPackages
listVettedPackages : HasCallStack => Script [PackageName]
listVettedPackages = lift ListVettedPackages
listAllPackages : HasCallStack => Script [PackageName]
listAllPackages = lift ListAllPackages

View File

@ -61,7 +61,7 @@ final case class JsonLedgerClient(
}
final case class IdeLedgerClient(
compiledPackages: CompiledPackages,
compiledPackages: PureCompiledPackages,
traceLog: TraceLog,
warningLog: WarningLog,
canceled: () => Boolean,

View File

@ -292,4 +292,17 @@ object Converter extends script.ConverterMethods {
)
case _ => Left(s"Expected command but got $v")
}
// Encodes as Daml.Script.Questions.Packages.PackageName
def fromReadablePackageId(
scriptIds: ScriptIds,
packageName: ScriptLedgerClient.ReadablePackageId,
): SValue = {
val packageNameTy = scriptIds.damlScriptModule("Daml.Script.Questions.Packages", "PackageName")
record(
packageNameTy,
("name", SText(packageName.name.toString)),
("version", SText(packageName.version.toString)),
)
}
}

View File

@ -12,7 +12,15 @@ import com.daml.grpc.adapter.ExecutionSequencerFactory
import com.daml.ledger.api.domain.{User, UserRight}
import com.daml.lf.data.FrontStack
import com.daml.lf.{CompiledPackages, command}
import com.daml.lf.data.Ref.{Identifier, Name, PackageId, Party, UserId}
import com.daml.lf.data.Ref.{
Identifier,
Name,
PackageId,
PackageName,
PackageVersion,
Party,
UserId,
}
import com.daml.lf.data.Time.Timestamp
import com.daml.lf.engine.preprocessing.ValueTranslator
import com.daml.lf.engine.script.v2.ledgerinteraction.ScriptLedgerClient
@ -638,6 +646,62 @@ object ScriptF {
} yield SEValue(rights)
}
final case class VetPackages(
packages: List[ScriptLedgerClient.ReadablePackageId]
) extends Cmd {
override def execute(env: Env)(implicit
ec: ExecutionContext,
mat: Materializer,
esf: ExecutionSequencerFactory,
): Future[SExpr] =
for {
client <- Converter.toFuture(env.clients.getParticipant(None))
_ <- client.vetPackages(packages)
} yield SEValue(SUnit)
}
final case class UnvetPackages(
packages: List[ScriptLedgerClient.ReadablePackageId]
) extends Cmd {
override def execute(env: Env)(implicit
ec: ExecutionContext,
mat: Materializer,
esf: ExecutionSequencerFactory,
): Future[SExpr] =
for {
client <- Converter.toFuture(env.clients.getParticipant(None))
_ <- client.unvetPackages(packages)
} yield SEValue(SUnit)
}
final case class ListVettedPackages() extends Cmd {
override def execute(env: Env)(implicit
ec: ExecutionContext,
mat: Materializer,
esf: ExecutionSequencerFactory,
): Future[SExpr] =
for {
client <- Converter.toFuture(env.clients.getParticipant(None))
packages <- client.listVettedPackages()
} yield SEValue(
SList(packages.to(FrontStack).map(Converter.fromReadablePackageId(env.scriptIds, _)))
)
}
final case class ListAllPackages() extends Cmd {
override def execute(env: Env)(implicit
ec: ExecutionContext,
mat: Materializer,
esf: ExecutionSequencerFactory,
): Future[SExpr] =
for {
client <- Converter.toFuture(env.clients.getParticipant(None))
packages <- client.listAllPackages()
} yield SEValue(
SList(packages.to(FrontStack).map(Converter.fromReadablePackageId(env.scriptIds, _)))
)
}
// Shared between Submit, SubmitMustFail and SubmitTree
final case class SubmitData(
actAs: OneAnd[Set, Party],
@ -746,10 +810,10 @@ object ScriptF {
case _ => Left(s"Expected ListKnownParties payload but got $v")
}
private def parseGetTime(v: SValue): Either[String, GetTime] =
private def parseEmpty[A](result: A)(v: SValue): Either[String, A] =
v match {
case SRecord(_, _, ArrayList()) => Right(GetTime())
case _ => Left(s"Expected GetTime payload but got $v")
case SRecord(_, _, ArrayList()) => Right(result)
case _ => Left(s"Expected ${result.getClass.getSimpleName} payload but got $v")
}
private def parseSetTime(v: SValue): Either[String, SetTime] =
@ -862,6 +926,25 @@ object ScriptF {
case _ => Left(s"Expected ListUserRights payload but got $v")
}
private def parseChangePackages(
v: SValue
): Either[String, List[ScriptLedgerClient.ReadablePackageId]] = {
def toReadablePackageId(s: SValue): Either[String, ScriptLedgerClient.ReadablePackageId] =
s match {
case SRecord(_, _, ArrayList(SText(name), SText(version))) =>
for {
pname <- PackageName.fromString(name)
pversion <- PackageVersion.fromString(version)
} yield ScriptLedgerClient.ReadablePackageId(pname, pversion)
case _ => Left(s"Expected PackageName but got $s")
}
v match {
case SRecord(_, _, ArrayList(packages)) =>
Converter.toList(packages, toReadablePackageId)
case _ => Left(s"Expected Packages payload but got $v")
}
}
def parse(constr: Ast.VariantConName, v: SValue, stackTrace: StackTrace): Either[String, Cmd] =
constr match {
case "Submit" => parseSubmit(v, stackTrace).map(Submit(_))
@ -874,7 +957,7 @@ object ScriptF {
case "QueryContractKey" => parseQueryContractKey(v)
case "AllocateParty" => parseAllocParty(v)
case "ListKnownParties" => parseListKnownParties(v)
case "GetTime" => parseGetTime(v)
case "GetTime" => parseEmpty(GetTime())(v)
case "SetTime" => parseSetTime(v)
case "Sleep" => parseSleep(v)
case "Catch" => parseCatch(v)
@ -887,6 +970,10 @@ object ScriptF {
case "GrantUserRights" => parseGrantUserRights(v)
case "RevokeUserRights" => parseRevokeUserRights(v)
case "ListUserRights" => parseListUserRights(v)
case "VetPackages" => parseChangePackages(v).map(VetPackages)
case "UnvetPackages" => parseChangePackages(v).map(UnvetPackages)
case "ListVettedPackages" => parseEmpty(ListVettedPackages())(v)
case "ListAllPackages" => parseEmpty(ListAllPackages())(v)
case _ => Left(s"Unknown constructor $constr")
}

View File

@ -519,4 +519,28 @@ class GrpcLedgerClient(val grpcClient: LedgerClient, val applicationId: Applicat
grpcClient.userManagementClient.listUserRights(id).map(_.toList).map(Some(_)).recover {
case e: StatusRuntimeException if e.getStatus.getCode == Status.Code.NOT_FOUND => None
}
override def vetPackages(packages: List[ScriptLedgerClient.ReadablePackageId])(implicit
ec: ExecutionContext,
esf: ExecutionSequencerFactory,
mat: Materializer,
): Future[Unit] = unsupportedOn("vetPackages")
override def unvetPackages(packages: List[ScriptLedgerClient.ReadablePackageId])(implicit
ec: ExecutionContext,
esf: ExecutionSequencerFactory,
mat: Materializer,
): Future[Unit] = unsupportedOn("unvetPackages")
override def listVettedPackages()(implicit
ec: ExecutionContext,
esf: ExecutionSequencerFactory,
mat: Materializer,
): Future[List[ScriptLedgerClient.ReadablePackageId]] = unsupportedOn("listVettedPackages")
override def listAllPackages()(implicit
ec: ExecutionContext,
esf: ExecutionSequencerFactory,
mat: Materializer,
): Future[List[ScriptLedgerClient.ReadablePackageId]] = unsupportedOn("listAllPackages")
}

View File

@ -15,7 +15,9 @@ import com.daml.lf.data.{ImmArray, Ref, Time}
import com.daml.lf.engine.preprocessing.ValueTranslator
import com.daml.lf.interpretation.Error.ContractIdInContractKey
import com.daml.lf.language.Ast
import com.daml.lf.language.Ast.PackageMetadata
import com.daml.lf.language.Ast.TTyCon
import com.daml.lf.language.{LookupError, PackageInterface, Reference}
import com.daml.lf.scenario.{ScenarioLedger, ScenarioRunner}
import com.daml.lf.speedy.Speedy.Machine
import com.daml.lf.speedy.{SValue, TraceLog, WarningLog, SError}
@ -43,7 +45,7 @@ import scala.util.{Failure, Success}
// Client for the script service.
class IdeLedgerClient(
val compiledPackages: CompiledPackages,
val originalCompiledPackages: PureCompiledPackages,
traceLog: TraceLog,
warningLog: WarningLog,
canceled: () => Boolean,
@ -59,12 +61,47 @@ class IdeLedgerClient(
def currentSubmission: Option[ScenarioRunner.CurrentSubmission] = _currentSubmission
private[this] val preprocessor =
private[this] var compiledPackages = originalCompiledPackages
private[this] var preprocessor = makePreprocessor
private[this] var unvettedPackages: Set[PackageId] = Set.empty
private[this] def makePreprocessor =
new preprocessing.CommandPreprocessor(
compiledPackages.pkgInterface,
requireV1ContractIdSuffix = false,
)
private[this] def partialFunctionFilterNot[A](f: A => Boolean): PartialFunction[A, A] = {
case x if !f(x) => x
}
// Given a set of disabled packages, filter out all definitions from those packages from the original compiled packages
// Similar logic to Scenario-services' Context.scala, however here we make no changes on the module level, and never directly add new packages
// We only maintain a subset of an original known package set.
private[this] def updateCompiledPackages() = {
compiledPackages =
if (!unvettedPackages.isEmpty)(
originalCompiledPackages.copy(
// Remove packages from the set
packageIds = originalCompiledPackages.packageIds -- unvettedPackages,
// Filter out pkgId "key" to the partial function
pkgInterface = new PackageInterface(
partialFunctionFilterNot(
unvettedPackages
) andThen originalCompiledPackages.pkgInterface.signatures
),
// Filter out any defs in a disabled package
defns = originalCompiledPackages.defns.view
.filterKeys(sDefRef => !unvettedPackages(sDefRef.packageId))
.toMap,
),
)
else originalCompiledPackages
preprocessor = makePreprocessor
}
private var _ledger: ScenarioLedger = ScenarioLedger.initialLedger(Time.Timestamp.Epoch)
def ledger: ScenarioLedger = _ledger
@ -246,6 +283,66 @@ class IdeLedgerClient(
}
}
// Build a SubmissionError with empty transaction
private def makeEmptySubmissionError(err: scenario.Error): ScenarioRunner.SubmissionError =
ScenarioRunner.SubmissionError(
err,
IncompleteTransaction(
transaction = Transaction(Map.empty, ImmArray.empty),
locationInfo = Map.empty,
),
)
private def getReferencePackageId(ref: Reference): PackageId =
ref match {
case Reference.Package(packageId) => packageId
case Reference.Module(packageId, _) => packageId
case Reference.Definition(name) => name.packageId
case Reference.TypeSyn(name) => name.packageId
case Reference.DataType(name) => name.packageId
case Reference.DataRecord(name) => name.packageId
case Reference.DataRecordField(name, _) => name.packageId
case Reference.DataVariant(name) => name.packageId
case Reference.DataVariantConstructor(name, _) => name.packageId
case Reference.DataEnum(name) => name.packageId
case Reference.DataEnumConstructor(name, _) => name.packageId
case Reference.Value(name) => name.packageId
case Reference.Template(name) => name.packageId
case Reference.Interface(name) => name.packageId
case Reference.TemplateKey(name) => name.packageId
case Reference.InterfaceInstance(_, name) => name.packageId
case Reference.ConcreteInterfaceInstance(_, ref) => getReferencePackageId(ref)
case Reference.TemplateChoice(name, _) => name.packageId
case Reference.InterfaceChoice(name, _) => name.packageId
case Reference.InheritedChoice(name, _, _) => name.packageId
case Reference.TemplateOrInterface(name) => name.packageId
case Reference.Choice(name, _) => name.packageId
case Reference.Method(name, _) => name.packageId
case Reference.Exception(name) => name.packageId
}
private def getLookupErrorPackageId(err: LookupError): PackageId =
err match {
case LookupError.NotFound(notFound, _) => getReferencePackageId(notFound)
case LookupError.AmbiguousInterfaceInstance(instance, _) => getReferencePackageId(instance)
}
private def makeLookupError(
err: LookupError
): ScenarioRunner.SubmissionError = {
val packageId = getLookupErrorPackageId(err)
val packageMetadata = getPackageIdReverseMap().lift(packageId).map {
case ScriptLedgerClient.ReadablePackageId(packageName, packageVersion) =>
PackageMetadata(packageName, packageVersion, None)
}
makeEmptySubmissionError(scenario.Error.LookupError(err, packageMetadata, packageId))
}
private def makePartiesNotAllocatedError(
unallocatedSubmitters: Set[Party]
): ScenarioRunner.SubmissionError =
makeEmptySubmissionError(scenario.Error.PartiesNotAllocated(unallocatedSubmitters))
// unsafe version of submit that does not clear the commit.
private def unsafeSubmit(
actAs: OneAnd[Set, Ref.Party],
@ -261,34 +358,8 @@ class IdeLedgerClient(
val unallocatedSubmitters: Set[Party] =
(actAs.toSet union readAs) -- allocatedParties.values.map(_.party)
if (unallocatedSubmitters.nonEmpty) {
Left(
ScenarioRunner.SubmissionError(
scenario.Error.PartiesNotAllocated(unallocatedSubmitters),
IncompleteTransaction(
transaction = Transaction(Map.empty, ImmArray.empty),
locationInfo = Map.empty,
),
)
)
Left(makePartiesNotAllocatedError(unallocatedSubmitters))
} else {
val speedyCommands = preprocessor.unsafePreprocessApiCommands(commands.to(ImmArray))
val translated = compiledPackages.compiler.unsafeCompile(speedyCommands, ImmArray.empty)
val ledgerApi = ScenarioRunner.ScenarioLedgerApi(ledger)
val result =
ScenarioRunner.submit(
compiledPackages,
ledgerApi,
actAs.toSet,
readAs,
translated,
optLocation,
nextSeed(),
traceLog,
warningLog,
)(Script.DummyLoggingContext)
@tailrec
def loop(
result: ScenarioRunner.SubmissionResult[ScenarioLedger.CommitResult]
@ -317,7 +388,33 @@ class IdeLedgerClient(
)
}
loop(result)
// We use try + unsafePreprocess here to avoid the addition template lookup logic in `preprocessApiCommands`
val eitherSpeedyCommands =
try {
Right(preprocessor.unsafePreprocessApiCommands(commands.to(ImmArray)))
} catch {
case Error.Preprocessing.Lookup(err) => Left(makeLookupError(err))
}
val ledgerApi = ScenarioRunner.ScenarioLedgerApi(ledger)
for {
speedyCommands <- eitherSpeedyCommands
translated = compiledPackages.compiler.unsafeCompile(speedyCommands, ImmArray.empty)
result =
ScenarioRunner.submit(
compiledPackages,
ledgerApi,
actAs.toSet,
readAs,
translated,
optLocation,
nextSeed(),
traceLog,
warningLog,
)(Script.DummyLoggingContext)
res <- loop(result)
} yield res
}
}
@ -545,4 +642,67 @@ class IdeLedgerClient(
userManagementStore
.listUserRights(id, IdentityProviderId.Default)(LoggingContext.empty)
.map(_.toOption.map(_.toList))
def getPackageIdMap(): Map[ScriptLedgerClient.ReadablePackageId, PackageId] =
getPackageIdPairs().toMap
def getPackageIdReverseMap(): Map[PackageId, ScriptLedgerClient.ReadablePackageId] =
getPackageIdPairs().map(_.swap).toMap
def getPackageIdPairs(): Set[(ScriptLedgerClient.ReadablePackageId, PackageId)] = {
originalCompiledPackages.packageIds
.collect(
Function.unlift(pkgId =>
for {
pkgSig <- originalCompiledPackages.pkgInterface.lookupPackage(pkgId).toOption
meta <- pkgSig.metadata
readablePackageId = meta match {
case PackageMetadata(name, version, _) =>
ScriptLedgerClient.ReadablePackageId(name, version)
}
} yield (readablePackageId, pkgId)
)
)
}
override def vetPackages(packages: List[ScriptLedgerClient.ReadablePackageId])(implicit
ec: ExecutionContext,
esf: ExecutionSequencerFactory,
mat: Materializer,
): Future[Unit] = Future {
val packageMap = getPackageIdMap()
val pkgIdsToVet = packages.map(pkg =>
packageMap.getOrElse(pkg, throw new IllegalArgumentException(s"Unknown package $pkg"))
)
unvettedPackages = unvettedPackages -- pkgIdsToVet.toSet
updateCompiledPackages()
}
override def unvetPackages(packages: List[ScriptLedgerClient.ReadablePackageId])(implicit
ec: ExecutionContext,
esf: ExecutionSequencerFactory,
mat: Materializer,
): Future[Unit] = Future {
val packageMap = getPackageIdMap()
val pkgIdsToUnvet = packages.map(pkg =>
packageMap.getOrElse(pkg, throw new IllegalArgumentException(s"Unknown package $pkg"))
)
unvettedPackages = unvettedPackages ++ pkgIdsToUnvet.toSet
updateCompiledPackages()
}
override def listVettedPackages()(implicit
ec: ExecutionContext,
esf: ExecutionSequencerFactory,
mat: Materializer,
): Future[List[ScriptLedgerClient.ReadablePackageId]] =
Future.successful(getPackageIdMap().filter(kv => !unvettedPackages(kv._2)).keys.toList)
override def listAllPackages()(implicit
ec: ExecutionContext,
esf: ExecutionSequencerFactory,
mat: Materializer,
): Future[List[ScriptLedgerClient.ReadablePackageId]] =
Future.successful(getPackageIdMap().keys.toList)
}

View File

@ -671,6 +671,30 @@ class JsonLedgerClient(
UserIdRequest(id),
)
}
override def vetPackages(packages: List[ScriptLedgerClient.ReadablePackageId])(implicit
ec: ExecutionContext,
esf: ExecutionSequencerFactory,
mat: Materializer,
): Future[Unit] = unsupportedOn("vetPackages")
override def unvetPackages(packages: List[ScriptLedgerClient.ReadablePackageId])(implicit
ec: ExecutionContext,
esf: ExecutionSequencerFactory,
mat: Materializer,
): Future[Unit] = unsupportedOn("unvetPackages")
override def listVettedPackages()(implicit
ec: ExecutionContext,
esf: ExecutionSequencerFactory,
mat: Materializer,
): Future[List[ScriptLedgerClient.ReadablePackageId]] = unsupportedOn("listVettedPackages")
override def listAllPackages()(implicit
ec: ExecutionContext,
esf: ExecutionSequencerFactory,
mat: Materializer,
): Future[List[ScriptLedgerClient.ReadablePackageId]] = unsupportedOn("listAllPackages")
}
object JsonLedgerClient {

View File

@ -61,6 +61,12 @@ object ScriptLedgerClient {
case abstractLedgers.IdeLedgerClient(compiledPackages, traceLog, warningLog, canceled) =>
new IdeLedgerClient(compiledPackages, traceLog, warningLog, canceled)
}
// Essentially PackageMetadata but without the possibility of extension
final case class ReadablePackageId(
name: PackageName,
version: PackageVersion,
)
}
// This abstracts over the interaction with the ledger. This allows
@ -201,4 +207,28 @@ trait ScriptLedgerClient {
esf: ExecutionSequencerFactory,
mat: Materializer,
): Future[Option[List[UserRight]]]
def vetPackages(packages: List[ScriptLedgerClient.ReadablePackageId])(implicit
ec: ExecutionContext,
esf: ExecutionSequencerFactory,
mat: Materializer,
): Future[Unit]
def unvetPackages(packages: List[ScriptLedgerClient.ReadablePackageId])(implicit
ec: ExecutionContext,
esf: ExecutionSequencerFactory,
mat: Materializer,
): Future[Unit]
def listVettedPackages()(implicit
ec: ExecutionContext,
esf: ExecutionSequencerFactory,
mat: Materializer,
): Future[List[ScriptLedgerClient.ReadablePackageId]]
def listAllPackages()(implicit
ec: ExecutionContext,
esf: ExecutionSequencerFactory,
mat: Materializer,
): Future[List[ScriptLedgerClient.ReadablePackageId]]
}