[LF] use stable Tuple for fecth_by_key primitive (#19537)

This commit is contained in:
Remy 2024-07-10 15:45:37 +02:00 committed by GitHub
parent 5e33a0a23c
commit 34034d3d0e
No known key found for this signature in database
GPG Key ID: B5690EEEBB952194
28 changed files with 446 additions and 246 deletions

View File

@ -190,6 +190,18 @@ pattern TGenMap t1 t2 = TApp (TApp (TBuiltin BTGenMap) t1) t2
pattern TTextMapEntry :: Type -> Type
pattern TTextMapEntry a = TStruct [(FieldName "key", TText), (FieldName "value", a)]
pattern TTuple2 :: Type -> Type -> Type
pattern TTuple2 t1 t2 = TApp (TApp (TCon Tuple2TCon) t1) t2
pattern Tuple2TCon :: Qualified TypeConName
pattern Tuple2TCon = (Qualified
-- We cannot look up these stable IDs using stablePackageByModuleName because
-- it would introduce a cyclic dependency with StablePackages.
(PRImport (PackageId "5aee9b21b8e9a4c4975b5f4c4198e6e6e8469df49e2010820e792f393db870f4"))
(ModuleName ["DA", "Types"])
(TypeConName ["Tuple2"])
)
pattern TConApp :: Qualified TypeConName -> [Type] -> Type
pattern TConApp tcon targs <- (view (leftSpine _TApp) -> (TCon tcon, targs))
where

View File

@ -648,7 +648,7 @@ typeOfUpdate = \case
return (TUpdate typ)
UFetchByKey retrieveByKey -> do
(cidType, contractType) <- checkRetrieveByKey retrieveByKey
return (TUpdate (TStruct [(FieldName "contractId", cidType), (FieldName "contract", contractType)]))
return (TUpdate (TTuple2 cidType contractType))
ULookupByKey retrieveByKey -> do
(cidType, _contractType) <- checkRetrieveByKey retrieveByKey
return (TUpdate (TOptional cidType))

View File

@ -321,19 +321,11 @@ convertPrim _ "ULookupByKey" (key :-> TUpdate (TOptional (TContractId (TCon temp
ULookupByKey $ RetrieveByKey template (EVar $ mkVar "key")
convertPrim _ "UFetchByKey"
(key :-> TUpdate ty@(TApp (TApp (TCon tuple) ty1@(TContractId (TCon template))) ty2))
(key :-> TUpdate (TTuple2 (TContractId (TCon template)) ty2))
| ty2 == TCon template =
pure $
ETmLam (mkVar "key", key) $
EUpdate $ UBind
(Binding (mkVar "res", TStruct
[ (FieldName "contractId", ty1)
, (FieldName "contract", ty2)])
(EUpdate $ UFetchByKey (RetrieveByKey template (EVar $ mkVar "key"))))
(EUpdate $ UPure ty $ ERecCon (TypeConApp tuple [ty1, ty2])
[ (mkIndexedField 1, EStructProj (FieldName "contractId") (EVar (mkVar "res")))
, (mkIndexedField 2, EStructProj (FieldName "contract") (EVar (mkVar "res")))
])
EUpdate $ UFetchByKey (RetrieveByKey template (EVar $ mkVar "key"))
convertPrim _ "ETemplateTypeRep"
(tProxy@(TApp _ tCon@(TCon _)) :-> TTypeRep) =

View File

@ -35,6 +35,7 @@ da_scala_binary(
"//daml-lf/interpreter",
"//daml-lf/language",
"//daml-lf/scenario-interpreter",
"//daml-lf/stable-packages",
"//daml-lf/transaction",
"//daml-lf/validation",
"//daml-script/converter",

View File

@ -27,6 +27,7 @@ import com.daml.script.converter
import com.google.protobuf.ByteString
import com.digitalasset.daml.lf.engine.script.{Runner, Script}
import com.daml.logging.LoggingContext
import com.digitalasset.daml.lf.stablepackages.StablePackages
import org.slf4j.LoggerFactory
import scala.concurrent.ExecutionContext
@ -130,12 +131,17 @@ class Context(
newModules
}
val interface = new language.PackageInterface(this.allSignatures)
val compiler = new Compiler(interface, compilerConfig)
val pkgInterface = new language.PackageInterface(this.allSignatures)
val compiler = new Compiler(pkgInterface, compilerConfig)
modulesToCompile.foreach { mod =>
if (!omitValidation)
assertRight(Validation.checkModule(interface, homePackageId, mod).left.map(_.pretty))
assertRight(
Validation
.checkModule(StablePackages(languageVersion.major), pkgInterface, homePackageId, mod)
.left
.map(_.pretty)
)
modDefns +=
mod.name -> compiler.unsafeCompileModule(homePackageId, mod).toMap
}

View File

@ -62,6 +62,7 @@ da_scala_test_suite(
"//daml-lf/data",
"//daml-lf/language",
"//daml-lf/parser",
"//daml-lf/stable-packages",
"//daml-lf/validation",
"@maven//:com_google_protobuf_protobuf_java",
"@maven//:org_scalatest_scalatest_compatible",
@ -86,6 +87,7 @@ da_scala_binary(
"//daml-lf/data",
"//daml-lf/language",
"//daml-lf/parser",
"//daml-lf/stable-packages",
"//daml-lf/validation",
"@maven//:com_google_protobuf_protobuf_java",
],

View File

@ -11,6 +11,7 @@ import com.digitalasset.daml.lf.language.{LanguageVersion, PackageInterface}
import com.digitalasset.daml.lf.testing.parser.{ParserParameters, parsePackage}
import com.digitalasset.daml.lf.validation.Validation
import com.daml.SdkVersion
import com.digitalasset.daml.lf.stablepackages.StablePackagesV2
import scala.annotation.tailrec
import scala.collection.immutable.Queue
@ -69,7 +70,15 @@ private[daml] object DamlLfEncoder extends App {
val pkgs = PackageInterface(Map(pkgId -> pkg))
if (validation)
Validation.checkPackage(pkgs, pkgId, pkg).left.foreach(e => error(e.pretty))
Validation
.checkPackage(
stablePackages = StablePackagesV2,
pkgInterface = pkgs,
pkgId = pkgId,
pkg = pkg,
)
.left
.foreach(e => error(e.pretty))
encodeArchive(pkgId -> pkg, parserParameters.languageVersion)
}

View File

@ -20,13 +20,21 @@ import scala.language.implicitConversions
class EncodeV2Spec extends EncodeSpec(LanguageVersion.v2_dev)
class EncodeSpec(languageVersion: LanguageVersion)
abstract class EncodeSpec(languageVersion: LanguageVersion)
extends AnyWordSpec
with Matchers
with TableDrivenPropertyChecks {
import EncodeSpec._
private val stablePackages =
com.digitalasset.daml.lf.stablepackages.StablePackages(languageVersion.major)
private val tuple2TyCon: String = {
import stablePackages.Tuple2
s"'${Tuple2.packageId}':${Tuple2.qualifiedName}"
}
private val pkgId: PackageId = "self"
private val defaultParserParameters: ParserParameters[this.type] =
@ -158,7 +166,7 @@ class EncodeSpec(languageVersion: LanguageVersion)
val identity: forall (a: *). a -> a = /\ (a: *). \(x: a) -> x;
val anExercise: (ContractId Mod:Person) -> Update Unit = \(cId: ContractId Mod:Person) ->
exercise @Mod:Person Sleep (Mod:identity @(ContractId Mod:Person) cId) ();
val aFecthByKey: Party -> Update <contract: Mod:Person, contractId: ContractId Mod:Person> = \(party: Party) ->
val aFecthByKey: Party -> Update ($tuple2TyCon (ContractId Mod:Person) Mod:Person) = \(party: Party) ->
fetch_by_key @Mod:Person party;
val aLookUpByKey: Party -> Update (Option (ContractId Mod:Person)) = \(party: Party) ->
lookup_by_key @Mod:Person party;
@ -260,6 +268,18 @@ class EncodeSpec(languageVersion: LanguageVersion)
}
}
private def validate(pkgId: PackageId, pkg: Package): Unit = {
Validation
.checkPackage(
stablePackages,
language.PackageInterface(stablePackages.packagesMap + (pkgId -> pkg)),
pkgId,
pkg,
)
.left
.foreach(e => sys.error(e.toString))
}
}
object EncodeSpec {
@ -279,10 +299,4 @@ object EncodeSpec {
normalizer.apply(pkg)
}
private def validate(pkgId: PackageId, pkg: Package): Unit =
Validation
.checkPackage(language.PackageInterface(Map(pkgId -> pkg)), pkgId, pkg)
.left
.foreach(e => sys.error(e.toString))
}

View File

@ -38,7 +38,7 @@ import com.digitalasset.daml.lf.language.{
PackageInterface,
}
import com.digitalasset.daml.lf.speedy.Speedy.Machine.newTraceLog
import com.digitalasset.daml.lf.stablepackages.StablePackages
import com.digitalasset.daml.lf.stablepackages._
import com.digitalasset.daml.lf.validation.Validation
import com.daml.logging.LoggingContext
import com.daml.nameof.NameOf
@ -597,7 +597,7 @@ class Engine(val config: EngineConfig) {
// we trust already loaded packages
.collect {
case (pkgId, pkg) if !compiledPackages.contains(pkgId) =>
Validation.checkPackage(pkgInterface, pkgId, pkg)
Validation.checkPackage(StablePackagesV2, pkgInterface, pkgId, pkg)
}
.collectFirst { case Left(err) => Error.Package.Validation(err) }
}.toLeft(())

View File

@ -62,6 +62,7 @@ da_scala_library(
"//daml-lf/data",
"//daml-lf/language",
"//daml-lf/parser",
"//daml-lf/stable-packages",
"//daml-lf/transaction",
"//daml-lf/validation",
"//libs-scala/contextualized-logging",

View File

@ -21,7 +21,7 @@ import com.digitalasset.daml.lf.speedy.SBuiltinFun._
import com.digitalasset.daml.lf.speedy.SValue._
import com.digitalasset.daml.lf.speedy.{SExpr => t}
import com.digitalasset.daml.lf.speedy.{SExpr0 => s}
import com.digitalasset.daml.lf.stablepackages.StablePackages
import com.digitalasset.daml.lf.stablepackages.{StablePackages, StablePackagesV2}
import com.digitalasset.daml.lf.validation.{Validation, ValidationError}
import com.daml.scalautil.Statement.discard
import org.slf4j.LoggerFactory
@ -453,7 +453,7 @@ private[lf] final class Compiler(
config.packageValidation match {
case Compiler.NoPackageValidation =>
case Compiler.FullPackageValidation =>
Validation.checkPackage(pkgInterface, pkgId, pkg).left.foreach(throw _)
Validation.checkPackage(StablePackagesV2, pkgInterface, pkgId, pkg).left.foreach(throw _)
}
val t1 = Time.Timestamp.now()
@ -994,8 +994,10 @@ private[lf] final class Compiler(
}
}
private[this] val FetchByKeyResult =
SBStructCon(Struct.assertFromSeq(List(contractIdFieldName, contractFieldName).zipWithIndex))
private[this] val Tuple2 = {
val fields = ImmArray(Name.assertFromString("_1"), Name.assertFromString("_2"))
SBRecCon(StablePackagesV2.Tuple2, fields)
}
@inline
private[this] def compileFetchByKey(
@ -1020,7 +1022,7 @@ private[lf] final class Compiler(
tokenPos,
),
) { (contractPos, env) =>
FetchByKeyResult(env.toSEVar(cidPos), env.toSEVar(contractPos))
Tuple2(env.toSEVar(cidPos), env.toSEVar(contractPos))
}
}
}

View File

@ -52,7 +52,7 @@ class TestTraceLog extends TraceLog {
class EvaluationOrderTest_V2 extends EvaluationOrderTest(LanguageVersion.v2_dev)
class EvaluationOrderTest(languageVersion: LanguageVersion)
abstract class EvaluationOrderTest(languageVersion: LanguageVersion)
extends AnyFreeSpec
with Matchers
with Inside {
@ -65,6 +65,12 @@ class EvaluationOrderTest(languageVersion: LanguageVersion)
private val upgradingEnabled = languageVersion >= LanguageVersion.Features.packageUpgrades
private[this] final def tuple2TyCon: String = {
val Tuple2 =
com.digitalasset.daml.lf.stablepackages.StablePackages(languageVersion.major).Tuple2
s"'${Tuple2.packageId}':${Tuple2.qualifiedName}"
}
val pkg = p""" metadata ( 'evaluation-order-test' : '1.0.0' )
module M {
@ -277,7 +283,7 @@ class EvaluationOrderTest(languageVersion: LanguageVersion)
controllers Cons @Party [Test:Helper {sig} this] (Nil @Party),
observers Nil @Party
to let key: M:TKey = Test:buildTKey params
in Test:run @<contract: M:T, contractId: ContractId M:T> (fetch_by_key @M:T key);
in Test:run @($tuple2TyCon (ContractId M:T) M:T) (fetch_by_key @M:T key);
choice LookupByKey (self) (params: Test:TKeyParams): Unit,
controllers Cons @Party [Test:Helper {sig} this] (Nil @Party),
observers Nil @Party

View File

@ -18,6 +18,7 @@ import com.daml.logging.LoggingContext
import transaction.{GlobalKey, GlobalKeyWithMaintainers, SubmittedTransaction}
import value.Value
import com.daml.scalautil.Statement.discard
import com.digitalasset.daml.lf.stablepackages.StablePackages
import scala.annotation.tailrec
@ -205,7 +206,11 @@ private[speedy] object SpeedyTestLib {
s"these packages don't have the expected major language version $majorLanguageVersion: $wrongPackages"
},
)
Validation.unsafeCheckPackages(PackageInterface(pkgs), pkgs)
Validation.unsafeCheckPackages(
StablePackages(majorLanguageVersion),
PackageInterface(pkgs),
pkgs,
)
PureCompiledPackages.assertBuild(
pkgs,
Compiler.Config
@ -220,7 +225,9 @@ private[speedy] object SpeedyTestLib {
): PureCompiledPackages =
typeAndCompile(
pkg.languageVersion.major,
Map(parserParameter.defaultPackageId -> pkg),
StablePackages(
parserParameter.languageVersion.major
).packagesMap + (parserParameter.defaultPackageId -> pkg),
)
private[speedy] object Implicits {

View File

@ -0,0 +1,43 @@
// Copyright (c) 2024 Digital Asset (Switzerland) GmbH and/or its affiliates. All rights reserved.
// SPDX-License-Identifier: Apache-2.0
package com.digitalasset.daml.lf.language
import com.digitalasset.daml.lf.data.Ref
private[lf] final case class StablePackage(
moduleName: Ref.ModuleName,
packageId: Ref.PackageId,
pkg: Ast.Package,
) {
require(Set(moduleName) == pkg.modules.keySet)
def name: Ref.PackageName = pkg.pkgName
def languageVersion: LanguageVersion = pkg.languageVersion
def identifier(idName: Ref.DottedName): Ref.Identifier =
Ref.Identifier(packageId, Ref.QualifiedName(moduleName, idName))
@throws[IllegalArgumentException]
def assertIdentifier(idName: String): Ref.Identifier =
identifier(Ref.DottedName.assertFromString(idName))
}
private[daml] abstract class StablePackages {
val allPackages: Seq[StablePackage]
val ArithmeticError: Ref.TypeConName
val AnyChoice: Ref.TypeConName
val AnyContractKey: Ref.TypeConName
val AnyTemplate: Ref.TypeConName
val TemplateTypeRep: Ref.TypeConName
val NonEmpty: Ref.TypeConName
val Tuple2: Ref.TypeConName
val Tuple3: Ref.TypeConName
val Either: Ref.TypeConName
final def packagesMap: Map[Ref.PackageId, Ast.Package] =
allPackages.view.map(sp => sp.packageId -> sp.pkg).toMap
}

View File

@ -24,6 +24,7 @@ da_scala_binary(
"//daml-lf/language",
"//daml-lf/parser",
"//daml-lf/scenario-interpreter",
"//daml-lf/stable-packages",
"//daml-lf/transaction",
"//daml-lf/validation",
"//libs-scala/contextualized-logging",

View File

@ -23,6 +23,7 @@ import com.digitalasset.daml.lf.language.{
LanguageVersion => LV,
}
import com.daml.logging.LoggingContext
import com.digitalasset.daml.lf.stablepackages.StablePackages
import java.io.{File, PrintWriter, StringWriter}
import java.nio.file.{Path, Paths}
@ -133,7 +134,12 @@ class Repl(majorLanguageVersion: LanguageMajorVersion) {
def cmdValidate(state: State): (Boolean, State) = {
val (validationResults, validationTime) = time(state.packages.map { case (pkgId, pkg) =>
Validation.checkPackage(PackageInterface(state.packages), pkgId, pkg)
Validation.checkPackage(
stablePackages = StablePackages(majorLanguageVersion),
pkgInterface = PackageInterface(state.packages),
pkgId = pkgId,
pkg = pkg,
)
})
System.err.println(s"${state.packages.size} package(s) validated in $validationTime ms.")
validationResults collectFirst { case Left(e) =>

View File

@ -8,34 +8,12 @@ import com.digitalasset.daml.lf.VersionRange
import com.digitalasset.daml.lf.archive
import com.digitalasset.daml.lf.archive.ArchiveDecoder
import com.digitalasset.daml.lf.data.Ref
import com.digitalasset.daml.lf.language.{Ast, LanguageMajorVersion, LanguageVersion}
private[daml] sealed case class StablePackage(
moduleName: Ref.ModuleName,
packageId: Ref.PackageId,
name: Ref.PackageName,
languageVersion: LanguageVersion,
) {
def identifier(idName: Ref.DottedName): Ref.Identifier =
Ref.Identifier(packageId, Ref.QualifiedName(moduleName, idName))
@throws[IllegalArgumentException]
def assertIdentifier(idName: String): Ref.Identifier =
identifier(Ref.DottedName.assertFromString(idName))
}
private[daml] sealed abstract class StablePackages {
val allPackages: Seq[StablePackage]
val ArithmeticError: Ref.TypeConName
val AnyChoice: Ref.TypeConName
val AnyContractKey: Ref.TypeConName
val AnyTemplate: Ref.TypeConName
val TemplateTypeRep: Ref.TypeConName
val NonEmpty: Ref.TypeConName
val Tuple2: Ref.TypeConName
val Tuple3: Ref.TypeConName
val Either: Ref.TypeConName
import com.digitalasset.daml.lf.language.{
Ast,
LanguageMajorVersion,
LanguageVersion,
StablePackage,
StablePackages,
}
final object StablePackagesV2
@ -55,7 +33,7 @@ private[daml] object StablePackages {
import scala.Ordering.Implicits.infixOrderingOps
StablePackages(allowedLanguageVersions.majorVersion).allPackages.view
.filter(_.languageVersion <= allowedLanguageVersions.max)
.filter(_.pkg.languageVersion <= allowedLanguageVersions.max)
.map(_.packageId)
.toSet
}
@ -117,8 +95,7 @@ private[daml] sealed class StablePackagesImpl(
StablePackage(
moduleName = pkgAst.modules.head._1,
packageId = pkgId,
name = pkgAst.pkgName,
languageVersion = pkgAst.languageVersion,
pkg = pkgAst,
)
}
}

View File

@ -33,7 +33,6 @@ da_scala_library(
":transaction_proto_java",
"//daml-lf/data",
"//daml-lf/language",
"//daml-lf/stable-packages",
"//libs-scala/crypto",
"//libs-scala/safe-proto",
"//libs-scala/scala-utils",

View File

@ -7,8 +7,7 @@ package value
import com.digitalasset.daml.lf.crypto.Hash
import com.digitalasset.daml.lf.data.Ref.{Identifier, Name, TypeConName}
import com.digitalasset.daml.lf.data._
import com.digitalasset.daml.lf.language.Ast
import com.digitalasset.daml.lf.stablepackages.StablePackages
import com.digitalasset.daml.lf.language.{Ast, StablePackages}
import data.ScalazEqual._
import scalaz.{@@, Equal, Order, Tag}
import scalaz.Ordering.EQ

View File

@ -117,6 +117,7 @@ da_scala_test_suite(
"//daml-lf/data",
"//daml-lf/language",
"//daml-lf/parser",
"//daml-lf/stable-packages",
],
)
@ -278,6 +279,7 @@ da_scala_benchmark_jmh(
"//daml-lf/interpreter",
"//daml-lf/language",
"//daml-lf/scenario-interpreter",
"//daml-lf/stable-packages",
"//daml-lf/transaction",
"//daml-lf/validation",
"//test-common:dar-files-default-lib",

View File

@ -11,6 +11,8 @@ import com.digitalasset.daml.lf.language.PackageInterface
import com.daml.bazeltools.BazelRunfiles.rlocation
import com.daml.ledger.test.ModelTestDar
import com.digitalasset.daml.lf.archive.DarDecoder
import com.digitalasset.daml.lf.stablepackages.StablePackagesV2
import java.io.File
import org.openjdk.jmh.annotations._
@ -57,9 +59,18 @@ class TypecheckingBench {
def bench(): Unit = {
val r = module match {
case Some((pkgId, m)) =>
Validation.checkModule(pkgInterface, pkgId, m)
Validation.checkModule(
stablePackages = StablePackagesV2,
pkgInterface = pkgInterface,
pkgId = pkgId,
module = m,
)
case None =>
Validation.checkPackages(pkgInterface, darMap)
Validation.checkPackages(
stablePackages = StablePackagesV2,
pkgInterface = pkgInterface,
pkgs = darMap,
)
}
assert(r.isRight)
}

View File

@ -8,7 +8,12 @@ import com.digitalasset.daml.lf.data.TemplateOrInterface
import com.digitalasset.daml.lf.data.Ref._
import com.digitalasset.daml.lf.language.Ast._
import com.digitalasset.daml.lf.language.Util._
import com.digitalasset.daml.lf.language.{LanguageVersion, PackageInterface, Reference}
import com.digitalasset.daml.lf.language.{
LanguageVersion,
PackageInterface,
Reference,
StablePackages,
}
import com.digitalasset.daml.lf.language.iterable.TypeIterable
import com.digitalasset.daml.lf.validation.Util._
import com.daml.scalautil.Statement.discard
@ -301,16 +306,22 @@ private[validation] object Typing {
case BCUnit => TUnit
}
def checkModule(pkgInterface: PackageInterface, pkgId: PackageId, mod: Module): Unit = { // entry point
def checkModule(
stablePackages: StablePackages,
pkgInterface: PackageInterface,
pkgId: PackageId,
mod: Module,
): Unit = { // entry point
val langVersion = handleLookup(Context.None, pkgInterface.lookupPackage(pkgId)).languageVersion
mod.definitions.foreach {
case (dfnName, DDataType(_, params, cons)) =>
val env =
Env(
langVersion,
pkgInterface,
Context.DefDataType(pkgId, mod.name, dfnName),
params.toMap,
languageVersion = langVersion,
stablePackages = stablePackages,
pkgInterface = pkgInterface,
ctx = Context.DefDataType(pkgId, mod.name, dfnName),
tVars = params.toMap,
)
params.values.foreach(env.checkKind)
checkUniq[TypeVarName](params.keys, EDuplicateTypeParam(env.ctx, _))
@ -327,17 +338,35 @@ private[validation] object Typing {
env.checkInterfaceType(tyConName, params)
}
case (dfnName, dfn: DValue) =>
Env(langVersion, pkgInterface, Context.DefValue(pkgId, mod.name, dfnName)).checkDValue(dfn)
Env(
languageVersion = langVersion,
stablePackages = stablePackages,
pkgInterface = pkgInterface,
ctx = Context.DefValue(pkgId, mod.name, dfnName),
).checkDValue(dfn)
case (dfnName, DTypeSyn(params, replacementTyp)) =>
val env =
Env(langVersion, pkgInterface, Context.Template(pkgId, mod.name, dfnName), params.toMap)
Env(
languageVersion = langVersion,
stablePackages = stablePackages,
pkgInterface = pkgInterface,
ctx = Context.Template(pkgId, mod.name, dfnName),
tVars = params.toMap,
)
params.values.foreach(env.checkKind)
checkUniq[TypeVarName](params.keys, EDuplicateTypeParam(env.ctx, _))
env.checkType(replacementTyp, KStar)
}
mod.templates.foreach { case (dfnName, template) =>
val tyConName = TypeConName(pkgId, QualifiedName(mod.name, dfnName))
val env = Env(langVersion, pkgInterface, Context.Template(tyConName), Map.empty)
val env =
Env(
languageVersion = langVersion,
stablePackages = stablePackages,
pkgInterface = pkgInterface,
ctx = Context.Template(tyConName),
tVars = Map.empty,
)
handleLookup(env.ctx, pkgInterface.lookupDataType(tyConName)) match {
case DDataType(_, ImmArray(), DataRecord(_)) =>
env.checkTemplate(tyConName, template)
@ -347,7 +376,14 @@ private[validation] object Typing {
}
mod.exceptions.foreach { case (exnName, message) =>
val tyConName = TypeConName(pkgId, QualifiedName(mod.name, exnName))
val env = Env(langVersion, pkgInterface, Context.DefException(tyConName), Map.empty)
val env =
Env(
languageVersion = langVersion,
stablePackages = stablePackages,
pkgInterface = pkgInterface,
ctx = Context.DefException(tyConName),
tVars = Map.empty,
)
handleLookup(env.ctx, pkgInterface.lookupDataType(tyConName)) match {
case DDataType(_, ImmArray(), DataRecord(_)) =>
env.checkDefException(tyConName, message)
@ -358,19 +394,30 @@ private[validation] object Typing {
mod.interfaces.foreach { case (ifaceName, iface) =>
// uniquess of choice names is already checked on construction of the choice map.
val tyConName = TypeConName(pkgId, QualifiedName(mod.name, ifaceName))
val env = Env(langVersion, pkgInterface, Context.DefInterface(tyConName), Map.empty)
val env =
Env(
languageVersion = langVersion,
stablePackages = stablePackages,
pkgInterface = pkgInterface,
ctx = Context.DefInterface(tyConName),
tVars = Map.empty,
)
env.checkDefIface(tyConName, iface)
}
}
case class Env(
languageVersion: LanguageVersion,
stablePackages: StablePackages,
pkgInterface: PackageInterface,
ctx: Context,
tVars: Map[TypeVarName, Kind] = Map.empty,
eVars: Map[ExprVarName, Type] = Map.empty,
) {
private[lf] def TTuple2(t1: Type, t2: Type) =
TApp(TApp(TTyCon(stablePackages.Tuple2), t1), t2)
private[lf] def kindOf(typ: Type): Kind = { // testing entry point
// must *NOT* be used for sub-types
runWork(kindOfType(typ))
@ -602,7 +649,12 @@ private[validation] object Typing {
handleLookup(ctx, pkgInterface.lookupInterface(interfaceId))
// Note (MA): we use an empty environment and add `tmplParam : TTyCon(templateId)`
val env = Env(languageVersion, pkgInterface, ctx)
val env = Env(
languageVersion = languageVersion,
stablePackages = stablePackages,
pkgInterface = pkgInterface,
ctx = ctx,
)
.introExprVar(tmplParam, TTyCon(templateId))
requires
@ -1320,18 +1372,14 @@ private[validation] object Typing {
}
case UpdateFetchByKey(retrieveByKey) =>
checkByKey(retrieveByKey.templateId, retrieveByKey.key) {
// fetches return the contract id and the contract itself
val ty = TUpdate(
TStruct(
Struct.assertFromSeq(
List(
contractIdFieldName -> TContractId(TTyCon(retrieveByKey.templateId)),
contractFieldName -> TTyCon(retrieveByKey.templateId),
)
Ret(
TUpdate(
TTuple2(
TContractId(TTyCon(retrieveByKey.templateId)),
TTyCon(retrieveByKey.templateId),
)
)
)
Ret(ty)
}
case UpdateLookupByKey(retrieveByKey) =>
checkByKey(retrieveByKey.templateId, retrieveByKey.key) {

View File

@ -6,7 +6,7 @@ package validation
import com.digitalasset.daml.lf.data.Ref.PackageId
import com.digitalasset.daml.lf.language.Ast._
import com.digitalasset.daml.lf.language.PackageInterface
import com.digitalasset.daml.lf.language.{PackageInterface, StablePackages}
object Validation {
@ -17,31 +17,40 @@ object Validation {
case e: ValidationError => Left(e)
}
def checkPackages(pkgs: Map[PackageId, Package]): Either[ValidationError, Unit] =
runSafely {
unsafeCheckPackages(PackageInterface(pkgs), pkgs)
}
def checkPackages(
stablePackages: StablePackages,
pkgs: Map[PackageId, Package],
): Either[ValidationError, Unit] =
runSafely(
unsafeCheckPackages(stablePackages, PackageInterface(pkgs), pkgs)
)
private[lf] def checkPackages(
stablePackages: StablePackages,
pkgInterface: PackageInterface,
pkgs: Map[PackageId, Package],
): Either[ValidationError, Unit] =
runSafely(unsafeCheckPackages(pkgInterface, pkgs))
runSafely(unsafeCheckPackages(stablePackages, pkgInterface, pkgs))
private[lf] def unsafeCheckPackages(
stablePackages: StablePackages,
pkgInterface: PackageInterface,
pkgs: Map[PackageId, Package],
): Unit =
pkgs.foreach { case (pkgId, pkg) => unsafeCheckPackage(pkgInterface, pkgId, pkg) }
pkgs.foreach { case (pkgId, pkg) =>
unsafeCheckPackage(stablePackages, pkgInterface, pkgId, pkg)
}
def checkPackage(
stablePackages: StablePackages,
pkgInterface: PackageInterface,
pkgId: PackageId,
pkg: Package,
): Either[ValidationError, Unit] =
runSafely(unsafeCheckPackage(pkgInterface, pkgId, pkg))
runSafely(unsafeCheckPackage(stablePackages, pkgInterface, pkgId, pkg))
private def unsafeCheckPackage(
stablePackages: StablePackages,
pkgInterface: PackageInterface,
pkgId: PackageId,
pkg: Package,
@ -49,22 +58,24 @@ object Validation {
Collision.checkPackage(pkgId, pkg)
Recursion.checkPackage(pkgId, pkg)
DependencyVersion.checkPackage(pkgInterface, pkgId, pkg)
pkg.modules.values.foreach(unsafeCheckModule(pkgInterface, pkgId, _))
pkg.modules.values.foreach(unsafeCheckModule(stablePackages, pkgInterface, pkgId, _))
}
private[lf] def checkModule(
stablePackages: StablePackages,
pkgInterface: PackageInterface,
pkgId: PackageId,
module: Module,
): Either[ValidationError, Unit] =
runSafely(unsafeCheckModule(pkgInterface, pkgId, module))
runSafely(unsafeCheckModule(stablePackages, pkgInterface, pkgId, module))
private def unsafeCheckModule(
stablePackages: StablePackages,
pkgInterface: PackageInterface,
pkgId: PackageId,
mod: Module,
): Unit = {
Typing.checkModule(pkgInterface, pkgId, mod)
Typing.checkModule(stablePackages, pkgInterface, pkgId, mod)
Serializability.checkModule(pkgInterface, pkgId, mod)
}
}

View File

@ -7,6 +7,7 @@ package validation
import com.digitalasset.daml.lf.data.Ref.DottedName
import com.digitalasset.daml.lf.language.Ast.Package
import com.digitalasset.daml.lf.language.LanguageMajorVersion
import com.digitalasset.daml.lf.stablepackages.StablePackages
import com.digitalasset.daml.lf.testing.parser.Implicits.SyntaxHelper
import com.digitalasset.daml.lf.testing.parser.ParserParameters
import org.scalatest.prop.TableDrivenPropertyChecks
@ -375,7 +376,12 @@ class SerializabilitySpec(majorLanguageVersion: LanguageMajorVersion)
val w = pkgInterface(pkg)
val longModName = DottedName.assertFromString(modName)
val mod = pkg.modules(longModName)
Typing.checkModule(w, defaultPackageId, mod)
Typing.checkModule(
stablePackages = StablePackages(majorLanguageVersion),
pkgInterface = w,
pkgId = defaultPackageId,
mod = mod,
)
Serializability.checkModule(w, defaultPackageId, mod)
}

View File

@ -9,7 +9,7 @@ import com.digitalasset.daml.lf.data.Struct
import com.digitalasset.daml.lf.language.Ast._
import com.digitalasset.daml.lf.language.LanguageVersion
import com.digitalasset.daml.lf.language.PackageInterface
import com.digitalasset.daml.lf.stablepackages.StablePackages
import org.scalatest.freespec.AnyFreeSpec
import org.scalatest.matchers.should.Matchers
import org.scalatest.prop.TableDrivenPropertyChecks
@ -81,7 +81,12 @@ class StackSafeTyping extends AnyFreeSpec with Matchers with TableDrivenProperty
val signatures: PartialFunction[PackageId, PackageSignature] = Map.empty
val pkgInterface = new PackageInterface(signatures)
val ctx: Context = Context.None
val env = Typing.Env(langVersion, pkgInterface, ctx)
val env = Typing.Env(
languageVersion = langVersion,
stablePackages = StablePackages(langVersion.major),
pkgInterface = pkgInterface,
ctx = ctx,
)
try {
val _: Kind = env.kindOf(typ)
None
@ -278,7 +283,12 @@ class StackSafeTyping extends AnyFreeSpec with Matchers with TableDrivenProperty
val signatures: PartialFunction[PackageId, PackageSignature] = Map.empty
val pkgInterface = new PackageInterface(signatures)
val ctx: Context = Context.None
val env = Typing.Env(langVersion, pkgInterface, ctx)
val env = Typing.Env(
languageVersion = langVersion,
stablePackages = StablePackages(langVersion.major),
pkgInterface = pkgInterface,
ctx = ctx,
)
try {
val _: Type = env.typeOfTopExpr(expr)
None

View File

@ -13,6 +13,7 @@ import com.digitalasset.daml.lf.language.{
Reference,
LanguageVersion => LV,
}
import com.digitalasset.daml.lf.stablepackages.StablePackages
import com.digitalasset.daml.lf.testing.parser.Implicits._
import com.digitalasset.daml.lf.testing.parser.ParserParameters
import org.scalatest.prop.TableDrivenPropertyChecks
@ -21,7 +22,7 @@ import org.scalatest.wordspec.AnyWordSpec
class TypingSpecV2 extends TypingSpec(LanguageMajorVersion.V2)
class TypingSpec(majorLanguageVersion: LanguageMajorVersion)
abstract class TypingSpec(majorLanguageVersion: LanguageMajorVersion)
extends AnyWordSpec
with TableDrivenPropertyChecks
with Matchers {
@ -36,6 +37,13 @@ class TypingSpec(majorLanguageVersion: LanguageMajorVersion)
None,
)
private[this] val stablePackages = StablePackages(majorLanguageVersion)
private[this] val tuple2TyCon: String = {
import stablePackages.Tuple2
s"'${Tuple2.packageId}':${Tuple2.qualifiedName}"
}
import SpecUtil._
"checkKind" should {
@ -417,7 +425,7 @@ class TypingSpec(majorLanguageVersion: LanguageMajorVersion)
E"λ (e: ContractId Mod:I) → (( fetch_interface @Mod:I e ))" ->
T"ContractId Mod:I → (( Update Mod:I ))",
E"λ (e: Party) → (( fetch_by_key @Mod:T e ))" ->
T"Party → (( Update (⟨ contract: Mod:T, contractId: ContractId Mod:T ⟩) ))",
T"Party → (( Update ($tuple2TyCon (ContractId Mod:T) Mod:T) ))",
E"λ (e: Party) → (( lookup_by_key @Mod:T e ))" ->
T"Party → (( Update (Option (ContractId Mod:T)) ))",
E"(( uget_time ))" ->
@ -1410,9 +1418,10 @@ class TypingSpec(majorLanguageVersion: LanguageMajorVersion)
val pkgIface = PackageInterface(Map(defaultPackageId -> pkg))
def checkModule(modName: String): Unit = Typing.checkModule(
pkgIface,
defaultPackageId,
pkg.modules(DottedName.assertFromString(modName)),
stablePackages = stablePackages,
pkgInterface = pkgIface,
pkgId = defaultPackageId,
mod = pkg.modules(DottedName.assertFromString(modName)),
)
checkModule("NegativeTestCase") shouldBe ()
@ -1660,9 +1669,10 @@ class TypingSpec(majorLanguageVersion: LanguageMajorVersion)
def checkModule(pkg: Package, modName: String) =
Typing.checkModule(
pkgInterface,
defaultPackageId,
pkg.modules(DottedName.assertFromString(modName)),
stablePackages = stablePackages,
pkgInterface = pkgInterface,
pkgId = defaultPackageId,
mod = pkg.modules(DottedName.assertFromString(modName)),
)
checkModule(pkg, "NegativeTestCase")
@ -1760,9 +1770,10 @@ class TypingSpec(majorLanguageVersion: LanguageMajorVersion)
"""
def checkModule(pkg: Package, modName: String) = Typing.checkModule(
PackageInterface(Map(defaultPackageId -> pkg)),
defaultPackageId,
pkg.modules(DottedName.assertFromString(modName)),
stablePackages = stablePackages,
pkgInterface = PackageInterface(Map(defaultPackageId -> pkg)),
pkgId = defaultPackageId,
mod = pkg.modules(DottedName.assertFromString(modName)),
)
checkModule(pkg, "NegativeTestCase")
@ -1791,7 +1802,12 @@ class TypingSpec(majorLanguageVersion: LanguageMajorVersion)
"""
val mod = pkg.modules(DottedName.assertFromString("TypeVarShadowing2"))
Typing.checkModule(PackageInterface(Map(defaultPackageId -> pkg)), defaultPackageId, mod)
Typing.checkModule(
stablePackages = stablePackages,
pkgInterface = PackageInterface(Map(defaultPackageId -> pkg)),
pkgId = defaultPackageId,
mod = mod,
)
}
"expand type synonyms correctly" in {
@ -1857,7 +1873,12 @@ class TypingSpec(majorLanguageVersion: LanguageMajorVersion)
def checkModule(mod: Module) = {
val pkg = Package.build(List(mod), List.empty, defaultLanguageVersion, packageMetadata)
Typing.checkModule(PackageInterface(Map(defaultPackageId -> pkg)), defaultPackageId, mod)
Typing.checkModule(
stablePackages = stablePackages,
pkgInterface = PackageInterface(Map(defaultPackageId -> pkg)),
pkgId = defaultPackageId,
mod = mod,
)
}
val negativeTestCases = Table(
@ -1880,7 +1901,12 @@ class TypingSpec(majorLanguageVersion: LanguageMajorVersion)
def checkModule(mod: Module) = {
val pkg = Package.build(List(mod), List.empty, defaultLanguageVersion, packageMetadata)
Typing.checkModule(PackageInterface(Map(defaultPackageId -> pkg)), defaultPackageId, mod)
Typing.checkModule(
stablePackages = stablePackages,
pkgInterface = PackageInterface(Map(defaultPackageId -> pkg)),
pkgId = defaultPackageId,
mod = mod,
)
}
val negativeTestCases = Table(
@ -1903,7 +1929,12 @@ class TypingSpec(majorLanguageVersion: LanguageMajorVersion)
def checkModule(mod: Module) = {
val pkg = Package.build(List(mod), List.empty, defaultLanguageVersion, packageMetadata)
Typing.checkModule(PackageInterface(Map(defaultPackageId -> pkg)), defaultPackageId, mod)
Typing.checkModule(
stablePackages = stablePackages,
pkgInterface = PackageInterface(Map(defaultPackageId -> pkg)),
pkgId = defaultPackageId,
mod = mod,
)
}
val negativeTestCases = Table(
@ -2002,7 +2033,12 @@ class TypingSpec(majorLanguageVersion: LanguageMajorVersion)
}
"""
Typing.Env(LV.default, PackageInterface(Map(defaultPackageId -> pkg)), Context.None)
Typing.Env(
LV.default,
stablePackages,
PackageInterface(Map(defaultPackageId -> pkg)),
Context.None,
)
}
}

View File

@ -15,7 +15,6 @@ import com.digitalasset.daml.lf.speedy.SBuiltinFun._
import com.digitalasset.daml.lf.speedy.SExpr._
import com.digitalasset.daml.lf.speedy.SValue._
import com.digitalasset.daml.lf.speedy.{ArrayList, SValue}
import com.digitalasset.daml.lf.stablepackages.StablePackages
import com.digitalasset.daml.lf.typesig.EnvironmentSignature
import com.digitalasset.daml.lf.typesig.reader.SignatureReader
import com.digitalasset.daml.lf.value.Value
@ -82,7 +81,7 @@ object Converter {
}
}
abstract class ConverterMethods(stablePackages: StablePackages) {
abstract class ConverterMethods(stablePackages: language.StablePackages) {
import com.daml.script.converter.Converter._
private def toNonEmptySet[A](as: OneAnd[FrontStack, A]): OneAnd[Set, A] = {

View File

@ -32,145 +32,145 @@
- ensure correct privacy for rollback subtree: [BlindingSpec.scala](daml-lf/engine/src/test/scala/com/digitalasset/daml/lf/engine/BlindingSpec.scala#L228)
## Integrity:
- Evaluation order of create with authorization failure: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L583)
- Evaluation order of create with contract ID in contract key: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L617)
- Evaluation order of create with contract key exceeding max nesting: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L668)
- Evaluation order of create with create argument exceeding max nesting: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L643)
- Evaluation order of create with duplicate contract key: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L534)
- Evaluation order of create with empty contract key maintainers: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L558)
- Evaluation order of create with failed precondition: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L516)
- Evaluation order of create_interface with authorization failure: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L790)
- Evaluation order of create_interface with contract ID in contract key: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L824)
- Evaluation order of create_interface with contract key exceeding max nesting: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L875)
- Evaluation order of create_interface with create argument exceeding max nesting: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L850)
- Evaluation order of create_interface with duplicate contract key: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L741)
- Evaluation order of create_interface with empty contract key maintainers: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L765)
- Evaluation order of create_interface with failed precondition: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L721)
- Evaluation order of exercise by interface of a cached global contract that does not implement the interface.: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L1892)
- Evaluation order of exercise by interface of an inactive global contract: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L1874)
- Evaluation order of exercise by interface of cached global contract with failed authorization: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L1934)
- Evaluation order of exercise of a cached global contract with failure authorization: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L1230)
- Evaluation order of exercise of a non-cached global contract with failure authorization: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L948)
- Evaluation order of exercise of a non-cached global contract with inconsistent key: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L992)
- Evaluation order of exercise of a wrongly typed cached global contract: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L1066)
- Evaluation order of exercise of a wrongly typed non-cached global contract: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L933)
- Evaluation order of exercise of an inactive global contract: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L1049)
- Evaluation order of exercise of an inactive local contract: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L1172)
- Evaluation order of exercise of an unknown contract: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L1273)
- Evaluation order of exercise of an wrongly typed local contract: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L1191)
- Evaluation order of exercise of cached global contract with failure authorization: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L1106)
- Evaluation order of exercise with argument exceeding max nesting: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L1287)
- Evaluation order of exercise with output exceeding max nesting: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L1315)
- Evaluation order of exercise_by_key of a cached global contract with failure authorization: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L1595)
- Evaluation order of exercise_by_key of a non-cached global contract with failure authorization: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L1393)
- Evaluation order of exercise_by_key of a wrongly typed cached global contract: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L1486)
- Evaluation order of exercise_by_key of an inactive global contract: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L1467)
- Evaluation order of exercise_by_key of an inactive local contract: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L1575)
- Evaluation order of exercise_by_key of an unknown contract: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L1638)
- Evaluation order of exercise_by_key of cached global contract with failure authorization: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L1505)
- Evaluation order of exercise_by_key with argument exceeding max nesting: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L1653)
- Evaluation order of exercise_by_key with contract ID in contract key: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L1728)
- Evaluation order of exercise_by_key with result exceeding max nesting: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L1682)
- Evaluation order of exercise_interface of a cached local contract with failed authorization: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L2066)
- Evaluation order of exercise_interface of a non-cached global contract with failed authorization: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L1799)
- Evaluation order of exercise_interface of an inactive local contract: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L2002)
- Evaluation order of exercise_interface of an local contract not implementing the interface: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L2021)
- Evaluation order of exercise_vy_key with empty contract key maintainers: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L1712)
- Evaluation order of fetch of a cached global contract with failure authorization: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L2387)
- Evaluation order of fetch of a non-cached global contract with failure authorization: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L2152)
- Evaluation order of fetch of a non-cached global contract with inconsistent key: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L2187)
- Evaluation order of fetch of a wrongly typed cached global contract: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L2250)
- Evaluation order of fetch of a wrongly typed disclosed contract: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L2419)
- Evaluation order of fetch of a wrongly typed non-cached global contract: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L2137)
- Evaluation order of fetch of an inactive global contract: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L2234)
- Evaluation order of fetch of an inactive local contract: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L2335)
- Evaluation order of fetch of an unknown contract: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L2438)
- Evaluation order of fetch of an wrongly typed local contract: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L2352)
- Evaluation order of fetch of cached global contract with failure authorization: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L2288)
- Evaluation order of fetch_by_key of a cached global contract with authorization failure: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L2577)
- Evaluation order of fetch_by_key of a local contract with authorization failure: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L2643)
- Evaluation order of fetch_by_key of a non-cached global contract with authorization failure: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L2502)
- Evaluation order of fetch_by_key of an inactive global contract: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L2558)
- Evaluation order of fetch_by_key of an inactive global contract: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L2625)
- Evaluation order of fetch_by_key of an unknown contract key: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L2673)
- Evaluation order of fetch_by_key with contract ID in contract key: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L2705)
- Evaluation order of fetch_by_key with contract key exceeding max nesting: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L2719)
- Evaluation order of fetch_by_key with empty contract key maintainers: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L2689)
- Evaluation order of fetch_interface of a cached global contract not implementing the interface.: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L2856)
- Evaluation order of fetch_interface of a cached global contract with failure authorization: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L2996)
- Evaluation order of fetch_interface of a non-cached global contract that doesn't implement interface.: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L2764)
- Evaluation order of fetch_interface of a non-cached global contract with failed authorization: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L2783)
- Evaluation order of fetch_interface of an inactive global contract: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L2839)
- Evaluation order of fetch_interface of an inactive local contract: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L2941)
- Evaluation order of fetch_interface of an local contract not implementing the interface: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L2958)
- Evaluation order of fetch_interface of an unknown contract: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L3026)
- Evaluation order of fetch_interface of cached global contract with failure authorization: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L2894)
- Evaluation order of lookup_by_key of a cached global contract with authorization failure: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L3143)
- Evaluation order of lookup_by_key of a local contract with failure authorization: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L3208)
- Evaluation order of lookup_by_key of a non-cached global contract with authorization failure: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L3070)
- Evaluation order of lookup_by_key of an inactive global contract: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L3125)
- Evaluation order of lookup_by_key of an inactive local contract: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L3191)
- Evaluation order of lookup_by_key of an unknown contract key: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L3238)
- Evaluation order of lookup_by_key with contract ID in contract key: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L3270)
- Evaluation order of lookup_by_key with contract key exceeding max nesting: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L3284)
- Evaluation order of lookup_by_key with empty contract key maintainers: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L3254)
- Evaluation order of successful create: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L493)
- Evaluation order of successful create_interface: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L697)
- Evaluation order of successful exercise by interface of a non-cached global contract: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L1753)
- Evaluation order of successful exercise of a cached global contract: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L1025)
- Evaluation order of successful exercise of a local contract: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L1149)
- Evaluation order of successful exercise of a non-cached global contract: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L906)
- Evaluation order of successful exercise_by_key of a cached global contract: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L1441)
- Evaluation order of successful exercise_by_key of a local contract: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L1551)
- Evaluation order of successful exercise_by_key of a non-cached global contract: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L1349)
- Evaluation order of successful exercise_interface of a cached global contract: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L1849)
- Evaluation order of successful exercise_interface of a local contract: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L1978)
- Evaluation order of successful fetch of a cached global contract: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L2217)
- Evaluation order of successful fetch of a local contract: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L2320)
- Evaluation order of successful fetch of a non-cached global contract: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L2114)
- Evaluation order of successful fetch_by_key of a cached global contract: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L2541)
- Evaluation order of successful fetch_by_key of a local contract: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L2609)
- Evaluation order of successful fetch_by_key of a non-cached global contract: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L2457)
- Evaluation order of successful fetch_interface of a cached global contract: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L2822)
- Evaluation order of successful fetch_interface of a local contract: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L2926)
- Evaluation order of successful fetch_interface of a non-cached global contract: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L2740)
- Evaluation order of successful lookup_by_key of a cached global contract: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L3108)
- Evaluation order of successful lookup_by_key of a local contract: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L3175)
- Evaluation order of successful lookup_by_key of a non-cached global contract: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L3046)
- Evaluation order of create with authorization failure: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L589)
- Evaluation order of create with contract ID in contract key: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L623)
- Evaluation order of create with contract key exceeding max nesting: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L674)
- Evaluation order of create with create argument exceeding max nesting: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L649)
- Evaluation order of create with duplicate contract key: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L540)
- Evaluation order of create with empty contract key maintainers: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L564)
- Evaluation order of create with failed precondition: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L522)
- Evaluation order of create_interface with authorization failure: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L796)
- Evaluation order of create_interface with contract ID in contract key: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L830)
- Evaluation order of create_interface with contract key exceeding max nesting: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L881)
- Evaluation order of create_interface with create argument exceeding max nesting: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L856)
- Evaluation order of create_interface with duplicate contract key: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L747)
- Evaluation order of create_interface with empty contract key maintainers: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L771)
- Evaluation order of create_interface with failed precondition: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L727)
- Evaluation order of exercise by interface of a cached global contract that does not implement the interface.: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L1898)
- Evaluation order of exercise by interface of an inactive global contract: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L1880)
- Evaluation order of exercise by interface of cached global contract with failed authorization: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L1940)
- Evaluation order of exercise of a cached global contract with failure authorization: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L1236)
- Evaluation order of exercise of a non-cached global contract with failure authorization: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L954)
- Evaluation order of exercise of a non-cached global contract with inconsistent key: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L998)
- Evaluation order of exercise of a wrongly typed cached global contract: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L1072)
- Evaluation order of exercise of a wrongly typed non-cached global contract: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L939)
- Evaluation order of exercise of an inactive global contract: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L1055)
- Evaluation order of exercise of an inactive local contract: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L1178)
- Evaluation order of exercise of an unknown contract: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L1279)
- Evaluation order of exercise of an wrongly typed local contract: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L1197)
- Evaluation order of exercise of cached global contract with failure authorization: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L1112)
- Evaluation order of exercise with argument exceeding max nesting: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L1293)
- Evaluation order of exercise with output exceeding max nesting: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L1321)
- Evaluation order of exercise_by_key of a cached global contract with failure authorization: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L1601)
- Evaluation order of exercise_by_key of a non-cached global contract with failure authorization: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L1399)
- Evaluation order of exercise_by_key of a wrongly typed cached global contract: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L1492)
- Evaluation order of exercise_by_key of an inactive global contract: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L1473)
- Evaluation order of exercise_by_key of an inactive local contract: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L1581)
- Evaluation order of exercise_by_key of an unknown contract: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L1644)
- Evaluation order of exercise_by_key of cached global contract with failure authorization: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L1511)
- Evaluation order of exercise_by_key with argument exceeding max nesting: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L1659)
- Evaluation order of exercise_by_key with contract ID in contract key: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L1734)
- Evaluation order of exercise_by_key with result exceeding max nesting: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L1688)
- Evaluation order of exercise_interface of a cached local contract with failed authorization: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L2072)
- Evaluation order of exercise_interface of a non-cached global contract with failed authorization: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L1805)
- Evaluation order of exercise_interface of an inactive local contract: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L2008)
- Evaluation order of exercise_interface of an local contract not implementing the interface: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L2027)
- Evaluation order of exercise_vy_key with empty contract key maintainers: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L1718)
- Evaluation order of fetch of a cached global contract with failure authorization: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L2393)
- Evaluation order of fetch of a non-cached global contract with failure authorization: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L2158)
- Evaluation order of fetch of a non-cached global contract with inconsistent key: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L2193)
- Evaluation order of fetch of a wrongly typed cached global contract: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L2256)
- Evaluation order of fetch of a wrongly typed disclosed contract: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L2425)
- Evaluation order of fetch of a wrongly typed non-cached global contract: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L2143)
- Evaluation order of fetch of an inactive global contract: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L2240)
- Evaluation order of fetch of an inactive local contract: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L2341)
- Evaluation order of fetch of an unknown contract: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L2444)
- Evaluation order of fetch of an wrongly typed local contract: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L2358)
- Evaluation order of fetch of cached global contract with failure authorization: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L2294)
- Evaluation order of fetch_by_key of a cached global contract with authorization failure: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L2583)
- Evaluation order of fetch_by_key of a local contract with authorization failure: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L2649)
- Evaluation order of fetch_by_key of a non-cached global contract with authorization failure: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L2508)
- Evaluation order of fetch_by_key of an inactive global contract: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L2564)
- Evaluation order of fetch_by_key of an inactive global contract: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L2631)
- Evaluation order of fetch_by_key of an unknown contract key: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L2679)
- Evaluation order of fetch_by_key with contract ID in contract key: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L2711)
- Evaluation order of fetch_by_key with contract key exceeding max nesting: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L2725)
- Evaluation order of fetch_by_key with empty contract key maintainers: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L2695)
- Evaluation order of fetch_interface of a cached global contract not implementing the interface.: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L2862)
- Evaluation order of fetch_interface of a cached global contract with failure authorization: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L3002)
- Evaluation order of fetch_interface of a non-cached global contract that doesn't implement interface.: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L2770)
- Evaluation order of fetch_interface of a non-cached global contract with failed authorization: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L2789)
- Evaluation order of fetch_interface of an inactive global contract: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L2845)
- Evaluation order of fetch_interface of an inactive local contract: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L2947)
- Evaluation order of fetch_interface of an local contract not implementing the interface: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L2964)
- Evaluation order of fetch_interface of an unknown contract: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L3032)
- Evaluation order of fetch_interface of cached global contract with failure authorization: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L2900)
- Evaluation order of lookup_by_key of a cached global contract with authorization failure: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L3149)
- Evaluation order of lookup_by_key of a local contract with failure authorization: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L3214)
- Evaluation order of lookup_by_key of a non-cached global contract with authorization failure: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L3076)
- Evaluation order of lookup_by_key of an inactive global contract: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L3131)
- Evaluation order of lookup_by_key of an inactive local contract: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L3197)
- Evaluation order of lookup_by_key of an unknown contract key: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L3244)
- Evaluation order of lookup_by_key with contract ID in contract key: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L3276)
- Evaluation order of lookup_by_key with contract key exceeding max nesting: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L3290)
- Evaluation order of lookup_by_key with empty contract key maintainers: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L3260)
- Evaluation order of successful create: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L499)
- Evaluation order of successful create_interface: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L703)
- Evaluation order of successful exercise by interface of a non-cached global contract: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L1759)
- Evaluation order of successful exercise of a cached global contract: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L1031)
- Evaluation order of successful exercise of a local contract: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L1155)
- Evaluation order of successful exercise of a non-cached global contract: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L912)
- Evaluation order of successful exercise_by_key of a cached global contract: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L1447)
- Evaluation order of successful exercise_by_key of a local contract: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L1557)
- Evaluation order of successful exercise_by_key of a non-cached global contract: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L1355)
- Evaluation order of successful exercise_interface of a cached global contract: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L1855)
- Evaluation order of successful exercise_interface of a local contract: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L1984)
- Evaluation order of successful fetch of a cached global contract: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L2223)
- Evaluation order of successful fetch of a local contract: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L2326)
- Evaluation order of successful fetch of a non-cached global contract: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L2120)
- Evaluation order of successful fetch_by_key of a cached global contract: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L2547)
- Evaluation order of successful fetch_by_key of a local contract: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L2615)
- Evaluation order of successful fetch_by_key of a non-cached global contract: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L2463)
- Evaluation order of successful fetch_interface of a cached global contract: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L2828)
- Evaluation order of successful fetch_interface of a local contract: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L2932)
- Evaluation order of successful fetch_interface of a non-cached global contract: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L2746)
- Evaluation order of successful lookup_by_key of a cached global contract: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L3114)
- Evaluation order of successful lookup_by_key of a local contract: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L3181)
- Evaluation order of successful lookup_by_key of a non-cached global contract: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L3052)
- Exceptions, throw/catch.: [ExceptionTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/ExceptionTest.scala#L28)
- Rollback creates cannot be exercise: [EngineTest.scala](daml-lf/engine/src/test/scala/com/digitalasset/daml/lf/engine/EngineTest.scala#L2128)
- This checks that type checking in exercise_interface is done after checking activeness.: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L2046)
- This checks that type checking is done after checking activeness.: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L1916)
- This checks that type checking is done after checking activeness.: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L2978)
- This checks that type checking in exercise_interface is done after checking activeness.: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L2052)
- This checks that type checking is done after checking activeness.: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L1922)
- This checks that type checking is done after checking activeness.: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L2984)
- contract key behaviour (non-unique mode): [ContractKeySpec.scala](daml-lf/engine/src/test/scala/com/digitalasset/daml/lf/engine/ContractKeySpec.scala#L426)
- contract key behaviour (unique mode): [ContractKeySpec.scala](daml-lf/engine/src/test/scala/com/digitalasset/daml/lf/engine/ContractKeySpec.scala#L436)
- contract keys must have a non-empty set of maintainers: [ContractKeySpec.scala](daml-lf/engine/src/test/scala/com/digitalasset/daml/lf/engine/ContractKeySpec.scala#L240)
- contract keys should be evaluated after ensure clause: [ContractKeySpec.scala](daml-lf/engine/src/test/scala/com/digitalasset/daml/lf/engine/ContractKeySpec.scala#L208)
- contract keys should be evaluated only when executing create: [ContractKeySpec.scala](daml-lf/engine/src/test/scala/com/digitalasset/daml/lf/engine/ContractKeySpec.scala#L167)
- ensure builtin operators have the correct type: [TypingSpec.scala](daml-lf/validation/src/test/scala/com/digitalasset/daml/lf/validation/TypingSpec.scala#L70)
- ensure expression forms have the correct type: [TypingSpec.scala](daml-lf/validation/src/test/scala/com/digitalasset/daml/lf/validation/TypingSpec.scala#L130)
- ensure builtin operators have the correct type: [TypingSpec.scala](daml-lf/validation/src/test/scala/com/digitalasset/daml/lf/validation/TypingSpec.scala#L78)
- ensure expression forms have the correct type: [TypingSpec.scala](daml-lf/validation/src/test/scala/com/digitalasset/daml/lf/validation/TypingSpec.scala#L138)
- exercise-by-interface command is rejected for a: [ApiCommandPreprocessorSpec.scala](daml-lf/engine/src/test/scala/com/digitalasset/daml/lf/engine/preprocessing/ApiCommandPreprocessorSpec.scala#L191)
- exercise_interface with a contract instance that does not implement the interface fails.: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L1781)
- exercise_interface with a contract instance that does not implement the interface fails.: [EvaluationOrderTest.scala](daml-lf/interpreter/src/test/scala/com/digitalasset/daml/lf/speedy/EvaluationOrderTest.scala#L1787)
- ill-formed create API command is rejected: [ApiCommandPreprocessorSpec.scala](daml-lf/engine/src/test/scala/com/digitalasset/daml/lf/engine/preprocessing/ApiCommandPreprocessorSpec.scala#L179)
- ill-formed create replay command is rejected: [ReplayCommandPreprocessorSpec.scala](daml-lf/engine/src/test/scala/com/digitalasset/daml/lf/engine/preprocessing/ReplayCommandPreprocessorSpec.scala#L124)
- ill-formed create-and-exercise API command is rejected: [ApiCommandPreprocessorSpec.scala](daml-lf/engine/src/test/scala/com/digitalasset/daml/lf/engine/preprocessing/ApiCommandPreprocessorSpec.scala#L204)
- ill-formed exception definitions are rejected: [TypingSpec.scala](daml-lf/validation/src/test/scala/com/digitalasset/daml/lf/validation/TypingSpec.scala#L1710)
- ill-formed exception definitions are rejected: [TypingSpec.scala](daml-lf/validation/src/test/scala/com/digitalasset/daml/lf/validation/TypingSpec.scala#L1720)
- ill-formed exercise API command is rejected: [ApiCommandPreprocessorSpec.scala](daml-lf/engine/src/test/scala/com/digitalasset/daml/lf/engine/preprocessing/ApiCommandPreprocessorSpec.scala#L184)
- ill-formed exercise replay command is rejected: [ReplayCommandPreprocessorSpec.scala](daml-lf/engine/src/test/scala/com/digitalasset/daml/lf/engine/preprocessing/ReplayCommandPreprocessorSpec.scala#L129)
- ill-formed exercise-by-key API command is rejected: [ApiCommandPreprocessorSpec.scala](daml-lf/engine/src/test/scala/com/digitalasset/daml/lf/engine/preprocessing/ApiCommandPreprocessorSpec.scala#L195)
- ill-formed exercise-by-key replay command is rejected: [ReplayCommandPreprocessorSpec.scala](daml-lf/engine/src/test/scala/com/digitalasset/daml/lf/engine/preprocessing/ReplayCommandPreprocessorSpec.scala#L136)
- ill-formed expressions are rejected: [TypingSpec.scala](daml-lf/validation/src/test/scala/com/digitalasset/daml/lf/validation/TypingSpec.scala#L476)
- ill-formed expressions are rejected: [TypingSpec.scala](daml-lf/validation/src/test/scala/com/digitalasset/daml/lf/validation/TypingSpec.scala#L484)
- ill-formed fetch command is rejected: [ReplayCommandPreprocessorSpec.scala](daml-lf/engine/src/test/scala/com/digitalasset/daml/lf/engine/preprocessing/ReplayCommandPreprocessorSpec.scala#L183)
- ill-formed fetch-by-key command is rejected: [ReplayCommandPreprocessorSpec.scala](daml-lf/engine/src/test/scala/com/digitalasset/daml/lf/engine/preprocessing/ReplayCommandPreprocessorSpec.scala#L186)
- ill-formed interfaces are rejected: [TypingSpec.scala](daml-lf/validation/src/test/scala/com/digitalasset/daml/lf/validation/TypingSpec.scala#L1442)
- ill-formed kinds are rejected: [TypingSpec.scala](daml-lf/validation/src/test/scala/com/digitalasset/daml/lf/validation/TypingSpec.scala#L42)
- ill-formed interfaces are rejected: [TypingSpec.scala](daml-lf/validation/src/test/scala/com/digitalasset/daml/lf/validation/TypingSpec.scala#L1451)
- ill-formed kinds are rejected: [TypingSpec.scala](daml-lf/validation/src/test/scala/com/digitalasset/daml/lf/validation/TypingSpec.scala#L50)
- ill-formed lookup command is rejected: [ReplayCommandPreprocessorSpec.scala](daml-lf/engine/src/test/scala/com/digitalasset/daml/lf/engine/preprocessing/ReplayCommandPreprocessorSpec.scala#L191)
- ill-formed records are rejected: [TypingSpec.scala](daml-lf/validation/src/test/scala/com/digitalasset/daml/lf/validation/TypingSpec.scala#L1855)
- ill-formed templates are rejected: [TypingSpec.scala](daml-lf/validation/src/test/scala/com/digitalasset/daml/lf/validation/TypingSpec.scala#L1087)
- ill-formed type synonyms applications are rejected: [TypingSpec.scala](daml-lf/validation/src/test/scala/com/digitalasset/daml/lf/validation/TypingSpec.scala#L1834)
- ill-formed type synonyms definitions are rejected: [TypingSpec.scala](daml-lf/validation/src/test/scala/com/digitalasset/daml/lf/validation/TypingSpec.scala#L1901)
- ill-formed types are rejected: [TypingSpec.scala](daml-lf/validation/src/test/scala/com/digitalasset/daml/lf/validation/TypingSpec.scala#L122)
- ill-formed variants are rejected: [TypingSpec.scala](daml-lf/validation/src/test/scala/com/digitalasset/daml/lf/validation/TypingSpec.scala#L1878)
- ill-formed records are rejected: [TypingSpec.scala](daml-lf/validation/src/test/scala/com/digitalasset/daml/lf/validation/TypingSpec.scala#L1871)
- ill-formed templates are rejected: [TypingSpec.scala](daml-lf/validation/src/test/scala/com/digitalasset/daml/lf/validation/TypingSpec.scala#L1095)
- ill-formed type synonyms applications are rejected: [TypingSpec.scala](daml-lf/validation/src/test/scala/com/digitalasset/daml/lf/validation/TypingSpec.scala#L1850)
- ill-formed type synonyms definitions are rejected: [TypingSpec.scala](daml-lf/validation/src/test/scala/com/digitalasset/daml/lf/validation/TypingSpec.scala#L1927)
- ill-formed types are rejected: [TypingSpec.scala](daml-lf/validation/src/test/scala/com/digitalasset/daml/lf/validation/TypingSpec.scala#L130)
- ill-formed variants are rejected: [TypingSpec.scala](daml-lf/validation/src/test/scala/com/digitalasset/daml/lf/validation/TypingSpec.scala#L1899)
- well formed create API command is accepted: [ApiCommandPreprocessorSpec.scala](daml-lf/engine/src/test/scala/com/digitalasset/daml/lf/engine/preprocessing/ApiCommandPreprocessorSpec.scala#L131)
- well formed create replay command is accepted: [ReplayCommandPreprocessorSpec.scala](daml-lf/engine/src/test/scala/com/digitalasset/daml/lf/engine/preprocessing/ReplayCommandPreprocessorSpec.scala#L95)
- well formed create-and-exercise API command is accepted: [ApiCommandPreprocessorSpec.scala](daml-lf/engine/src/test/scala/com/digitalasset/daml/lf/engine/preprocessing/ApiCommandPreprocessorSpec.scala#L159)