mirror of
https://github.com/digital-asset/daml.git
synced 2024-11-05 03:56:26 +03:00
remove agreement text from the compiler (#18272)
* remove agreement text from the compiler * update GHC_REV run-all-tests: true * point to the HEAD of master-8.8.1
This commit is contained in:
parent
c590c6c942
commit
57d28c15fa
@ -9,7 +9,7 @@ GHC_LIB_PATCHES = [
|
||||
]
|
||||
|
||||
GHC_REPO_URL = "https://github.com/digital-asset/ghc"
|
||||
GHC_REV = "1fe909eaa56718aaf4701151ac69af7f2db0088f"
|
||||
GHC_REV = "5ee7177f406540ce7011119a213c456ee1353020"
|
||||
GHC_PATCHES = [
|
||||
]
|
||||
|
||||
|
@ -964,9 +964,6 @@ data Template = Template
|
||||
, tplObservers :: !Expr
|
||||
-- ^ Observers of the contract. They have type @List Party@ and the
|
||||
-- template paramter in scope.
|
||||
, tplAgreement :: !Expr
|
||||
-- ^ Agreement text associated with the contract. It has type @Text@ and
|
||||
-- the template paramter in scope.
|
||||
, tplChoices :: !(NM.NameMap TemplateChoice)
|
||||
-- ^ Choices of the template.
|
||||
, tplKey :: !(Maybe TemplateKey)
|
||||
|
@ -69,12 +69,11 @@ templateChoiceExpr f (TemplateChoice loc name consuming controllers observers au
|
||||
<*> f update
|
||||
|
||||
templateExpr :: Traversal' Template Expr
|
||||
templateExpr f (Template loc tpl param precond signatories observers agreement choices key implements) =
|
||||
templateExpr f (Template loc tpl param precond signatories observers choices key implements) =
|
||||
Template loc tpl param
|
||||
<$> f precond
|
||||
<*> f signatories
|
||||
<*> f observers
|
||||
<*> f agreement
|
||||
<*> (NM.traverse . templateChoiceExpr) f choices
|
||||
<*> (traverse . templateKeyExpr) f key
|
||||
<*> (NM.traverse . templateImplementsExpr) f implements
|
||||
|
@ -638,16 +638,15 @@ pPrintTemplateChoice lvl modName tpl (TemplateChoice mbLoc name isConsuming cont
|
||||
|
||||
pPrintTemplate ::
|
||||
PrettyLevel -> ModuleName -> Template -> Doc ann
|
||||
pPrintTemplate lvl modName (Template mbLoc tpl param precond signatories observers agreement choices mbKey implements) =
|
||||
pPrintTemplate lvl modName (Template mbLoc tpl param precond signatories observers choices mbKey implements) =
|
||||
withSourceLoc lvl mbLoc $
|
||||
keyword_ "template" <-> pPrint tpl <-> pPrint param
|
||||
<-> keyword_ "where"
|
||||
$$ nest 2 (vcat ([signatoriesDoc, observersDoc, precondDoc, agreementDoc] ++ implementsDoc ++ mbKeyDoc ++ choiceDocs))
|
||||
$$ nest 2 (vcat ([signatoriesDoc, observersDoc, precondDoc] ++ implementsDoc ++ mbKeyDoc ++ choiceDocs))
|
||||
where
|
||||
signatoriesDoc = keyword_ "signatory" <-> pPrintPrec lvl 0 signatories
|
||||
observersDoc = keyword_ "observer" <-> pPrintPrec lvl 0 observers
|
||||
precondDoc = keyword_ "ensure" <-> pPrintPrec lvl 0 precond
|
||||
agreementDoc = hang (keyword_ "agreement") 2 (pPrintPrec lvl 0 agreement)
|
||||
choiceDocs = map (pPrintTemplateChoice lvl modName tpl) (NM.toList choices)
|
||||
mbKeyDoc = toList $ do
|
||||
key <- mbKey
|
||||
|
@ -317,7 +317,6 @@ decodeDefTemplate LF2.DefTemplate{..} = do
|
||||
<*> mayDecode "defTemplatePrecond" defTemplatePrecond decodeExpr
|
||||
<*> mayDecode "defTemplateSignatories" defTemplateSignatories decodeExpr
|
||||
<*> mayDecode "defTemplateObservers" defTemplateObservers decodeExpr
|
||||
<*> mayDecode "defTemplateAgreement" defTemplateAgreement decodeExpr
|
||||
<*> decodeNM DuplicateChoice decodeChoice defTemplateChoices
|
||||
<*> mapM (decodeDefTemplateKey tplParam) defTemplateKey
|
||||
<*> decodeNM DuplicateImplements decodeDefTemplateImplements defTemplateImplements
|
||||
|
@ -947,11 +947,11 @@ encodeTemplate Template{..} = do
|
||||
defTemplatePrecond <- encodeExpr tplPrecondition
|
||||
defTemplateSignatories <- encodeExpr tplSignatories
|
||||
defTemplateObservers <- encodeExpr tplObservers
|
||||
defTemplateAgreement <- encodeExpr tplAgreement
|
||||
defTemplateChoices <- encodeNameMap encodeTemplateChoice tplChoices
|
||||
defTemplateLocation <- traverse encodeSourceLoc tplLocation
|
||||
defTemplateKey <- traverse encodeTemplateKey tplKey
|
||||
defTemplateImplements <- encodeNameMap encodeTemplateImplements tplImplements
|
||||
let defTemplateAgreement = Nothing
|
||||
pure P.DefTemplate{..}
|
||||
|
||||
encodeTemplateImplements :: TemplateImplements -> Encode P.DefTemplate_Implements
|
||||
|
@ -1002,7 +1002,7 @@ checkTemplateChoice tpl (TemplateChoice _loc _ _ controllers mbObservers mbAutho
|
||||
checkExpr upd (TUpdate retType)
|
||||
|
||||
checkTemplate :: forall m. MonadGamma m => Module -> Template -> m ()
|
||||
checkTemplate m t@(Template _loc tpl param precond signatories observers text choices mbKey implements) = do
|
||||
checkTemplate m t@(Template _loc tpl param precond signatories observers choices mbKey implements) = do
|
||||
let tcon = Qualified PRSelf (moduleName m) tpl
|
||||
DefDataType _loc _naem _serializable tparams dataCons <- inWorld (lookupDataType tcon)
|
||||
unless (null tparams) $ throwWithContext (EExpectedTemplatableType tpl)
|
||||
@ -1011,7 +1011,6 @@ checkTemplate m t@(Template _loc tpl param precond signatories observers text ch
|
||||
withPart TPPrecondition $ checkExpr precond TBool
|
||||
withPart TPSignatories $ checkExpr signatories (TList TParty)
|
||||
withPart TPObservers $ checkExpr observers (TList TParty)
|
||||
withPart TPAgreement $ checkExpr text TText
|
||||
for_ choices $ \c -> withPart (TPChoice c) $ checkTemplateChoice tcon c
|
||||
forM_ implements \TemplateImplements {tpiInterface, tpiBody, tpiLocation} -> do
|
||||
let iiHead = InterfaceInstanceHead tpiInterface tcon
|
||||
|
@ -42,7 +42,6 @@ data TemplatePart
|
||||
| TPPrecondition
|
||||
| TPSignatories
|
||||
| TPObservers
|
||||
| TPAgreement
|
||||
| TPKey
|
||||
-- ^ Specifically the `key` keyword, not maintainers
|
||||
| TPChoice TemplateChoice
|
||||
@ -203,8 +202,7 @@ templateLocation t = \case
|
||||
TPWhole -> tplLocation t
|
||||
TPPrecondition -> extractExprSourceLoc $ tplPrecondition t
|
||||
TPSignatories -> extractExprSourceLoc $ tplSignatories t
|
||||
TPObservers -> extractExprSourceLoc $ tplObservers t
|
||||
TPAgreement -> extractExprSourceLoc $ tplAgreement t
|
||||
TPObservers -> extractExprSourceLoc $ tplObservers t
|
||||
TPKey -> tplKey t >>= extractExprSourceLoc . tplKeyBody
|
||||
TPChoice tc -> chcLocation tc
|
||||
TPInterfaceInstance _ loc -> loc
|
||||
@ -252,7 +250,6 @@ instance Show TemplatePart where
|
||||
TPPrecondition -> "precondition"
|
||||
TPSignatories -> "signatories"
|
||||
TPObservers -> "observers"
|
||||
TPAgreement -> "agreement"
|
||||
TPKey -> "key"
|
||||
TPChoice choice -> "choice " <> T.unpack (unChoiceName $ chcName choice)
|
||||
TPInterfaceInstance iiHead _ -> renderPretty iiHead
|
||||
@ -614,7 +611,6 @@ data Warning
|
||||
| WTemplateChangedPrecondition !TypeConName
|
||||
| WTemplateChangedSignatories !TypeConName
|
||||
| WTemplateChangedObservers !TypeConName
|
||||
| WTemplateChangedAgreement !TypeConName
|
||||
| WChoiceChangedControllers !ChoiceName
|
||||
| WChoiceChangedObservers !ChoiceName
|
||||
| WChoiceChangedAuthorizers !ChoiceName
|
||||
@ -642,7 +638,6 @@ instance Pretty Warning where
|
||||
WTemplateChangedPrecondition template -> "The upgraded template " <> pPrint template <> " has changed the definition of its precondition."
|
||||
WTemplateChangedSignatories template -> "The upgraded template " <> pPrint template <> " has changed the definition of its signatories."
|
||||
WTemplateChangedObservers template -> "The upgraded template " <> pPrint template <> " has changed the definition of its observers."
|
||||
WTemplateChangedAgreement template -> "The upgraded template " <> pPrint template <> " has changed the definition of agreement."
|
||||
WChoiceChangedControllers choice -> "The upgraded choice " <> pPrint choice <> " has changed the definition of controllers."
|
||||
WChoiceChangedObservers choice -> "The upgraded choice " <> pPrint choice <> " has changed the definition of observers."
|
||||
WChoiceChangedAuthorizers choice -> "The upgraded choice " <> pPrint choice <> " has changed the definition of authorizers."
|
||||
|
@ -202,9 +202,6 @@ checkTemplate module_ template = do
|
||||
withContext (ContextTemplate (present module_) (present template) TPObservers) $
|
||||
whenDifferent "observers" (extractFuncFromFuncThis . tplObservers) template $
|
||||
warnWithContext $ WTemplateChangedObservers $ NM.name $ present template
|
||||
withContext (ContextTemplate (present module_) (present template) TPAgreement) $
|
||||
whenDifferent "agreement" (extractFuncFromFuncThis . tplAgreement) template $
|
||||
warnWithContext $ WTemplateChangedAgreement $ NM.name $ present template
|
||||
|
||||
withContext (ContextTemplate (present module_) (present template) TPKey) $ do
|
||||
case fmap tplKey template of
|
||||
|
@ -138,7 +138,7 @@ pattern DesugarDFunId tyCoVars dfunArgs name classArgs <-
|
||||
)
|
||||
)
|
||||
|
||||
pattern HasSignatoryDFunId, HasEnsureDFunId, HasAgreementDFunId, HasObserverDFunId,
|
||||
pattern HasSignatoryDFunId, HasEnsureDFunId, HasObserverDFunId,
|
||||
HasArchiveDFunId, ShowDFunId :: TyCon -> GHC.Var
|
||||
|
||||
pattern HasSignatoryDFunId templateTyCon <-
|
||||
@ -147,9 +147,6 @@ pattern HasSignatoryDFunId templateTyCon <-
|
||||
pattern HasEnsureDFunId templateTyCon <-
|
||||
DesugarDFunId [] [] (NameIn DA_Internal_Template_Functions "HasEnsure")
|
||||
[splitTyConApp_maybe -> Just (templateTyCon, [])]
|
||||
pattern HasAgreementDFunId templateTyCon <-
|
||||
DesugarDFunId [] [] (NameIn DA_Internal_Template_Functions "HasAgreement")
|
||||
[splitTyConApp_maybe -> Just (templateTyCon, [])]
|
||||
pattern HasObserverDFunId templateTyCon <-
|
||||
DesugarDFunId [] [] (NameIn DA_Internal_Template_Functions "HasObserver")
|
||||
[splitTyConApp_maybe -> Just (templateTyCon, [])]
|
||||
|
@ -365,7 +365,6 @@ data TemplateBinds = TemplateBinds
|
||||
{ tbTyCon :: Maybe GHC.TyCon
|
||||
, tbSignatory :: Maybe (GHC.Expr Var)
|
||||
, tbEnsure :: Maybe (GHC.Expr Var)
|
||||
, tbAgreement :: Maybe (GHC.Expr Var)
|
||||
, tbObserver :: Maybe (GHC.Expr Var)
|
||||
, tbArchive :: Maybe (GHC.Expr Var)
|
||||
, tbKeyType :: Maybe GHC.Type
|
||||
@ -377,7 +376,7 @@ data TemplateBinds = TemplateBinds
|
||||
emptyTemplateBinds :: TemplateBinds
|
||||
emptyTemplateBinds = TemplateBinds
|
||||
Nothing Nothing Nothing Nothing Nothing Nothing
|
||||
Nothing Nothing Nothing Nothing
|
||||
Nothing Nothing Nothing
|
||||
|
||||
scrapeTemplateBinds :: [(Var, GHC.Expr Var)] -> MS.Map TypeConName TemplateBinds
|
||||
scrapeTemplateBinds binds = MS.filter (isJust . tbTyCon) $ MS.map ($ emptyTemplateBinds) $ MS.fromListWith (.)
|
||||
@ -388,8 +387,6 @@ scrapeTemplateBinds binds = MS.filter (isJust . tbTyCon) $ MS.map ($ emptyTempla
|
||||
Just (tpl, \tb -> tb { tbTyCon = Just tpl, tbSignatory = Just expr })
|
||||
HasEnsureDFunId tpl ->
|
||||
Just (tpl, \tb -> tb { tbEnsure = Just expr })
|
||||
HasAgreementDFunId tpl ->
|
||||
Just (tpl, \tb -> tb { tbAgreement = Just expr })
|
||||
HasObserverDFunId tpl ->
|
||||
Just (tpl, \tb -> tb { tbObserver = Just expr })
|
||||
HasArchiveDFunId tpl ->
|
||||
@ -1094,14 +1091,12 @@ convertTemplate env mc tplTypeCon tbinds@TemplateBinds{..}
|
||||
, Just fSignatory <- tbSignatory
|
||||
, Just fObserver <- tbObserver
|
||||
, Just fEnsure <- tbEnsure
|
||||
, Just fAgreement <- tbAgreement
|
||||
, tplLocation <- convNameLoc (GHC.tyConName tplTyCon)
|
||||
= withRange tplLocation $ do
|
||||
let tplParam = this
|
||||
tplSignatories <- useSingleMethodDict env fSignatory (`ETmApp` EVar this)
|
||||
tplObservers <- useSingleMethodDict env fObserver (`ETmApp` EVar this)
|
||||
tplPrecondition <- useSingleMethodDict env fEnsure (wrapPrecondition . (`ETmApp` EVar this))
|
||||
tplAgreement <- useSingleMethodDict env fAgreement (`ETmApp` EVar this)
|
||||
tplChoices <- convertChoices env mc tplTypeCon tbinds
|
||||
tplKey <- convertTemplateKey env tplTypeCon tbinds
|
||||
tplImplements <- convertImplements env mc tplTypeCon
|
||||
|
@ -41,11 +41,6 @@ class HasEnsure t where
|
||||
-- | A predicate that must be true, otherwise contract creation will fail.
|
||||
ensure : t -> Bool
|
||||
|
||||
-- | Exposes `agreement` function. Part of the `Template` constraint.
|
||||
class HasAgreement t where
|
||||
-- | The agreement text of a contract.
|
||||
agreement : t -> Text
|
||||
|
||||
-- | Exposes `create` function. Part of the `Template` constraint.
|
||||
class HasCreate t where
|
||||
-- | Create a contract based on a template `t`.
|
||||
|
@ -24,11 +24,6 @@ instance DA.Internal.Desugar.HasEnsure Foo where
|
||||
= DA.Internal.Desugar.True
|
||||
where
|
||||
_ = this
|
||||
instance DA.Internal.Desugar.HasAgreement Foo where
|
||||
agreement this@Foo {..}
|
||||
= ""
|
||||
where
|
||||
_ = this
|
||||
instance DA.Internal.Desugar.HasArchive Foo where
|
||||
archive cid
|
||||
= DA.Internal.Desugar.exercise cid DA.Internal.Desugar.Archive
|
||||
|
@ -132,7 +132,6 @@ jtup _tok =
|
||||
template Simple
|
||||
with p: Party
|
||||
where
|
||||
agreement show p
|
||||
signatory p
|
||||
|
||||
choice Hello : Text
|
||||
@ -144,7 +143,6 @@ template SimpleMultiParty
|
||||
p1: Party
|
||||
p2: Party
|
||||
where
|
||||
agreement show p1 <> show p2
|
||||
signatory p1, p2
|
||||
|
||||
choice HelloMultiParty : Text
|
||||
@ -155,7 +153,6 @@ template SimpleMultiParty
|
||||
template Composite
|
||||
with p1: Party
|
||||
where
|
||||
agreement show p1
|
||||
signatory p1
|
||||
|
||||
choice First : Text
|
||||
@ -300,9 +297,6 @@ template PayOut
|
||||
where
|
||||
signatory receiver
|
||||
signatory giver
|
||||
agreement
|
||||
(show giver) <> " must pay to " <>
|
||||
(show receiver) <> " the sum of five pounds."
|
||||
|
||||
|
||||
template CallablePayout
|
||||
@ -343,7 +337,6 @@ template TwoParties
|
||||
with p: Party
|
||||
p2: Party
|
||||
where
|
||||
agreement show p
|
||||
signatory p
|
||||
signatory p2
|
||||
|
||||
|
@ -71,11 +71,6 @@ instance DA.Internal.Desugar.HasEnsure TrySyntax where
|
||||
= DA.Internal.Desugar.True
|
||||
where
|
||||
_ = this
|
||||
instance DA.Internal.Desugar.HasAgreement TrySyntax where
|
||||
agreement this@TrySyntax {..}
|
||||
= ""
|
||||
where
|
||||
_ = this
|
||||
instance DA.Internal.Desugar.HasArchive TrySyntax where
|
||||
archive cid
|
||||
= DA.Internal.Desugar.exercise cid DA.Internal.Desugar.Archive
|
||||
|
@ -35,11 +35,6 @@ instance DA.Internal.Desugar.HasEnsure T where
|
||||
= DA.Internal.Desugar.True
|
||||
where
|
||||
_ = this
|
||||
instance DA.Internal.Desugar.HasAgreement T where
|
||||
agreement this@T {..}
|
||||
= ""
|
||||
where
|
||||
_ = this
|
||||
instance DA.Internal.Desugar.HasArchive T where
|
||||
archive cid
|
||||
= DA.Internal.Desugar.exercise cid DA.Internal.Desugar.Archive
|
||||
|
@ -30,11 +30,6 @@ instance DA.Internal.Desugar.HasEnsure T where
|
||||
= DA.Internal.Desugar.True
|
||||
where
|
||||
_ = this
|
||||
instance DA.Internal.Desugar.HasAgreement T where
|
||||
agreement this@T {..}
|
||||
= ""
|
||||
where
|
||||
_ = this
|
||||
instance DA.Internal.Desugar.HasArchive T where
|
||||
archive cid
|
||||
= DA.Internal.Desugar.exercise cid DA.Internal.Desugar.Archive
|
||||
|
@ -25,7 +25,7 @@ data TestCase t c = TestCase
|
||||
, divulgeChoice : c
|
||||
}
|
||||
|
||||
buildScript : (Choice t c r, HasAgreement t) => (TestData -> TestCase t c) -> Script ()
|
||||
buildScript : (Choice t c r, HasEnsure t) => (TestData -> TestCase t c) -> Script ()
|
||||
buildScript mkTestCase = do
|
||||
alice <- allocateParty "alice"
|
||||
bank <- allocateParty "bank"
|
||||
|
@ -27,11 +27,6 @@ instance DA.Internal.Desugar.HasEnsure MyTemplate where
|
||||
= False
|
||||
where
|
||||
_ = this
|
||||
instance DA.Internal.Desugar.HasAgreement MyTemplate where
|
||||
agreement this@MyTemplate {..}
|
||||
= ""
|
||||
where
|
||||
_ = this
|
||||
instance DA.Internal.Desugar.HasArchive MyTemplate where
|
||||
archive cid
|
||||
= DA.Internal.Desugar.exercise cid DA.Internal.Desugar.Archive
|
||||
@ -99,11 +94,6 @@ instance DA.Internal.Desugar.HasEnsure Test where
|
||||
= DA.Internal.Desugar.True
|
||||
where
|
||||
_ = this
|
||||
instance DA.Internal.Desugar.HasAgreement Test where
|
||||
agreement this@Test {..}
|
||||
= ""
|
||||
where
|
||||
_ = this
|
||||
instance DA.Internal.Desugar.HasArchive Test where
|
||||
archive cid
|
||||
= DA.Internal.Desugar.exercise cid DA.Internal.Desugar.Archive
|
||||
|
@ -41,11 +41,6 @@ instance DA.Internal.Desugar.HasEnsure K where
|
||||
= DA.Internal.Desugar.True
|
||||
where
|
||||
_ = this
|
||||
instance DA.Internal.Desugar.HasAgreement K where
|
||||
agreement this@K {..}
|
||||
= ""
|
||||
where
|
||||
_ = this
|
||||
instance DA.Internal.Desugar.HasArchive K where
|
||||
archive cid
|
||||
= DA.Internal.Desugar.exercise cid DA.Internal.Desugar.Archive
|
||||
@ -193,11 +188,6 @@ instance DA.Internal.Desugar.HasEnsure T where
|
||||
= DA.Internal.Desugar.True
|
||||
where
|
||||
_ = this
|
||||
instance DA.Internal.Desugar.HasAgreement T where
|
||||
agreement this@T {..}
|
||||
= ""
|
||||
where
|
||||
_ = this
|
||||
instance DA.Internal.Desugar.HasArchive T where
|
||||
archive cid
|
||||
= DA.Internal.Desugar.exercise cid DA.Internal.Desugar.Archive
|
||||
@ -658,11 +648,6 @@ instance DA.Internal.Desugar.HasEnsure Fetcher where
|
||||
= DA.Internal.Desugar.True
|
||||
where
|
||||
_ = this
|
||||
instance DA.Internal.Desugar.HasAgreement Fetcher where
|
||||
agreement this@Fetcher {..}
|
||||
= ""
|
||||
where
|
||||
_ = this
|
||||
instance DA.Internal.Desugar.HasArchive Fetcher where
|
||||
archive cid
|
||||
= DA.Internal.Desugar.exercise cid DA.Internal.Desugar.Archive
|
||||
|
@ -44,11 +44,6 @@ instance DA.Internal.Desugar.HasEnsure Test where
|
||||
= DA.Internal.Desugar.True
|
||||
where
|
||||
_ = this
|
||||
instance DA.Internal.Desugar.HasAgreement Test where
|
||||
agreement this@Test {..}
|
||||
= ""
|
||||
where
|
||||
_ = this
|
||||
instance DA.Internal.Desugar.HasArchive Test where
|
||||
archive cid
|
||||
= DA.Internal.Desugar.exercise cid DA.Internal.Desugar.Archive
|
||||
|
@ -334,11 +334,6 @@ instance DA.Internal.Desugar.HasEnsure Asset where
|
||||
= DA.Internal.Desugar.True
|
||||
where
|
||||
_ = this
|
||||
instance DA.Internal.Desugar.HasAgreement Asset where
|
||||
agreement this@Asset {..}
|
||||
= ""
|
||||
where
|
||||
_ = this
|
||||
instance DA.Internal.Desugar.HasArchive Asset where
|
||||
archive cid
|
||||
= DA.Internal.Desugar.exercise cid DA.Internal.Desugar.Archive
|
||||
|
@ -26,11 +26,6 @@ instance DA.Internal.Desugar.HasEnsure T where
|
||||
= DA.Internal.Desugar.True
|
||||
where
|
||||
_ = this
|
||||
instance DA.Internal.Desugar.HasAgreement T where
|
||||
agreement this@T {..}
|
||||
= ""
|
||||
where
|
||||
_ = this
|
||||
instance DA.Internal.Desugar.HasArchive T where
|
||||
archive cid
|
||||
= DA.Internal.Desugar.exercise cid DA.Internal.Desugar.Archive
|
||||
|
@ -140,11 +140,6 @@ instance DA.Internal.Desugar.HasEnsure T where
|
||||
= DA.Internal.Desugar.True
|
||||
where
|
||||
_ = this
|
||||
instance DA.Internal.Desugar.HasAgreement T where
|
||||
agreement this@T {..}
|
||||
= ""
|
||||
where
|
||||
_ = this
|
||||
instance DA.Internal.Desugar.HasArchive T where
|
||||
archive cid
|
||||
= DA.Internal.Desugar.exercise cid DA.Internal.Desugar.Archive
|
||||
@ -243,11 +238,6 @@ instance DA.Internal.Desugar.HasEnsure Test where
|
||||
= DA.Internal.Desugar.True
|
||||
where
|
||||
_ = this
|
||||
instance DA.Internal.Desugar.HasAgreement Test where
|
||||
agreement this@Test {..}
|
||||
= ""
|
||||
where
|
||||
_ = this
|
||||
instance DA.Internal.Desugar.HasArchive Test where
|
||||
archive cid
|
||||
= DA.Internal.Desugar.exercise cid DA.Internal.Desugar.Archive
|
||||
|
@ -140,11 +140,6 @@ instance DA.Internal.Desugar.HasEnsure T where
|
||||
= DA.Internal.Desugar.True
|
||||
where
|
||||
_ = this
|
||||
instance DA.Internal.Desugar.HasAgreement T where
|
||||
agreement this@T {..}
|
||||
= ""
|
||||
where
|
||||
_ = this
|
||||
instance DA.Internal.Desugar.HasArchive T where
|
||||
archive cid
|
||||
= DA.Internal.Desugar.exercise cid DA.Internal.Desugar.Archive
|
||||
@ -247,11 +242,6 @@ instance DA.Internal.Desugar.HasEnsure ExerciseGuarded where
|
||||
= DA.Internal.Desugar.True
|
||||
where
|
||||
_ = this
|
||||
instance DA.Internal.Desugar.HasAgreement ExerciseGuarded where
|
||||
agreement this@ExerciseGuarded {..}
|
||||
= ""
|
||||
where
|
||||
_ = this
|
||||
instance DA.Internal.Desugar.HasArchive ExerciseGuarded where
|
||||
archive cid
|
||||
= DA.Internal.Desugar.exercise cid DA.Internal.Desugar.Archive
|
||||
|
@ -218,11 +218,6 @@ instance DA.Internal.Desugar.HasEnsure T where
|
||||
= DA.Internal.Desugar.True
|
||||
where
|
||||
_ = this
|
||||
instance DA.Internal.Desugar.HasAgreement T where
|
||||
agreement this@T {..}
|
||||
= ""
|
||||
where
|
||||
_ = this
|
||||
instance DA.Internal.Desugar.HasArchive T where
|
||||
archive cid
|
||||
= DA.Internal.Desugar.exercise cid DA.Internal.Desugar.Archive
|
||||
|
@ -265,11 +265,6 @@ instance DA.Internal.Desugar.HasEnsure Template1 where
|
||||
= DA.Internal.Desugar.True
|
||||
where
|
||||
_ = this
|
||||
instance DA.Internal.Desugar.HasAgreement Template1 where
|
||||
agreement this@Template1 {..}
|
||||
= ""
|
||||
where
|
||||
_ = this
|
||||
instance DA.Internal.Desugar.HasArchive Template1 where
|
||||
archive cid
|
||||
= DA.Internal.Desugar.exercise cid DA.Internal.Desugar.Archive
|
||||
@ -370,11 +365,6 @@ instance DA.Internal.Desugar.HasEnsure Template2 where
|
||||
= DA.Internal.Desugar.True
|
||||
where
|
||||
_ = this
|
||||
instance DA.Internal.Desugar.HasAgreement Template2 where
|
||||
agreement this@Template2 {..}
|
||||
= ""
|
||||
where
|
||||
_ = this
|
||||
instance DA.Internal.Desugar.HasArchive Template2 where
|
||||
archive cid
|
||||
= DA.Internal.Desugar.exercise cid DA.Internal.Desugar.Archive
|
||||
@ -502,11 +492,6 @@ instance DA.Internal.Desugar.HasEnsure Test where
|
||||
= DA.Internal.Desugar.True
|
||||
where
|
||||
_ = this
|
||||
instance DA.Internal.Desugar.HasAgreement Test where
|
||||
agreement this@Test {..}
|
||||
= ""
|
||||
where
|
||||
_ = this
|
||||
instance DA.Internal.Desugar.HasArchive Test where
|
||||
archive cid
|
||||
= DA.Internal.Desugar.exercise cid DA.Internal.Desugar.Archive
|
||||
|
@ -164,11 +164,6 @@ instance DA.Internal.Desugar.HasEnsure Asset where
|
||||
= DA.Internal.Desugar.True
|
||||
where
|
||||
_ = this
|
||||
instance DA.Internal.Desugar.HasAgreement Asset where
|
||||
agreement this@Asset {..}
|
||||
= ""
|
||||
where
|
||||
_ = this
|
||||
instance DA.Internal.Desugar.HasArchive Asset where
|
||||
archive cid
|
||||
= DA.Internal.Desugar.exercise cid DA.Internal.Desugar.Archive
|
||||
|
@ -97,11 +97,6 @@ instance DA.Internal.Desugar.HasEnsure T where
|
||||
= DA.Internal.Desugar.True
|
||||
where
|
||||
_ = this
|
||||
instance DA.Internal.Desugar.HasAgreement T where
|
||||
agreement this@T {..}
|
||||
= ""
|
||||
where
|
||||
_ = this
|
||||
instance DA.Internal.Desugar.HasArchive T where
|
||||
archive cid
|
||||
= DA.Internal.Desugar.exercise cid DA.Internal.Desugar.Archive
|
||||
|
@ -25,11 +25,6 @@ instance DA.Internal.Desugar.HasEnsure T where
|
||||
= DA.Internal.Desugar.True
|
||||
where
|
||||
_ = this
|
||||
instance DA.Internal.Desugar.HasAgreement T where
|
||||
agreement this@T {..}
|
||||
= ""
|
||||
where
|
||||
_ = this
|
||||
instance DA.Internal.Desugar.HasArchive T where
|
||||
archive cid
|
||||
= DA.Internal.Desugar.exercise cid DA.Internal.Desugar.Archive
|
||||
|
@ -99,11 +99,6 @@ instance DA.Internal.Desugar.HasEnsure T where
|
||||
= DA.Internal.Desugar.True
|
||||
where
|
||||
_ = this
|
||||
instance DA.Internal.Desugar.HasAgreement T where
|
||||
agreement this@T {..}
|
||||
= ""
|
||||
where
|
||||
_ = this
|
||||
instance DA.Internal.Desugar.HasArchive T where
|
||||
archive cid
|
||||
= DA.Internal.Desugar.exercise cid DA.Internal.Desugar.Archive
|
||||
@ -187,11 +182,6 @@ instance DA.Internal.Desugar.HasEnsure U where
|
||||
= DA.Internal.Desugar.True
|
||||
where
|
||||
_ = this
|
||||
instance DA.Internal.Desugar.HasAgreement U where
|
||||
agreement this@U {..}
|
||||
= ""
|
||||
where
|
||||
_ = this
|
||||
instance DA.Internal.Desugar.HasArchive U where
|
||||
archive cid
|
||||
= DA.Internal.Desugar.exercise cid DA.Internal.Desugar.Archive
|
||||
|
@ -145,11 +145,6 @@ instance DA.Internal.Desugar.HasEnsure MyTemplate where
|
||||
= DA.Internal.Desugar.True
|
||||
where
|
||||
_ = this
|
||||
instance DA.Internal.Desugar.HasAgreement MyTemplate where
|
||||
agreement this@MyTemplate {..}
|
||||
= ""
|
||||
where
|
||||
_ = this
|
||||
instance DA.Internal.Desugar.HasArchive MyTemplate where
|
||||
archive cid
|
||||
= DA.Internal.Desugar.exercise cid DA.Internal.Desugar.Archive
|
||||
@ -220,11 +215,6 @@ instance DA.Internal.Desugar.HasEnsure Test where
|
||||
= DA.Internal.Desugar.True
|
||||
where
|
||||
_ = this
|
||||
instance DA.Internal.Desugar.HasAgreement Test where
|
||||
agreement this@Test {..}
|
||||
= ""
|
||||
where
|
||||
_ = this
|
||||
instance DA.Internal.Desugar.HasArchive Test where
|
||||
archive cid
|
||||
= DA.Internal.Desugar.exercise cid DA.Internal.Desugar.Archive
|
||||
|
@ -109,11 +109,6 @@ instance DA.Internal.Desugar.HasEnsure Asset where
|
||||
= DA.Internal.Desugar.True
|
||||
where
|
||||
_ = this
|
||||
instance DA.Internal.Desugar.HasAgreement Asset where
|
||||
agreement this@Asset {..}
|
||||
= ""
|
||||
where
|
||||
_ = this
|
||||
instance DA.Internal.Desugar.HasArchive Asset where
|
||||
archive cid
|
||||
= DA.Internal.Desugar.exercise cid DA.Internal.Desugar.Archive
|
||||
@ -212,11 +207,6 @@ instance DA.Internal.Desugar.HasEnsure Test where
|
||||
= DA.Internal.Desugar.True
|
||||
where
|
||||
_ = this
|
||||
instance DA.Internal.Desugar.HasAgreement Test where
|
||||
agreement this@Test {..}
|
||||
= ""
|
||||
where
|
||||
_ = this
|
||||
instance DA.Internal.Desugar.HasArchive Test where
|
||||
archive cid
|
||||
= DA.Internal.Desugar.exercise cid DA.Internal.Desugar.Archive
|
||||
|
@ -247,11 +247,6 @@ instance DA.Internal.Desugar.HasEnsure Asset where
|
||||
= DA.Internal.Desugar.True
|
||||
where
|
||||
_ = this
|
||||
instance DA.Internal.Desugar.HasAgreement Asset where
|
||||
agreement this@Asset {..}
|
||||
= ""
|
||||
where
|
||||
_ = this
|
||||
instance DA.Internal.Desugar.HasArchive Asset where
|
||||
archive cid
|
||||
= DA.Internal.Desugar.exercise cid DA.Internal.Desugar.Archive
|
||||
@ -373,11 +368,6 @@ instance DA.Internal.Desugar.HasEnsure AnotherAsset where
|
||||
= DA.Internal.Desugar.True
|
||||
where
|
||||
_ = this
|
||||
instance DA.Internal.Desugar.HasAgreement AnotherAsset where
|
||||
agreement this@AnotherAsset {..}
|
||||
= ""
|
||||
where
|
||||
_ = this
|
||||
instance DA.Internal.Desugar.HasArchive AnotherAsset where
|
||||
archive cid
|
||||
= DA.Internal.Desugar.exercise cid DA.Internal.Desugar.Archive
|
||||
@ -551,11 +541,6 @@ instance DA.Internal.Desugar.HasEnsure Test where
|
||||
= DA.Internal.Desugar.True
|
||||
where
|
||||
_ = this
|
||||
instance DA.Internal.Desugar.HasAgreement Test where
|
||||
agreement this@Test {..}
|
||||
= ""
|
||||
where
|
||||
_ = this
|
||||
instance DA.Internal.Desugar.HasArchive Test where
|
||||
archive cid
|
||||
= DA.Internal.Desugar.exercise cid DA.Internal.Desugar.Archive
|
||||
|
@ -247,11 +247,6 @@ instance DA.Internal.Desugar.HasEnsure Asset where
|
||||
= DA.Internal.Desugar.True
|
||||
where
|
||||
_ = this
|
||||
instance DA.Internal.Desugar.HasAgreement Asset where
|
||||
agreement this@Asset {..}
|
||||
= ""
|
||||
where
|
||||
_ = this
|
||||
instance DA.Internal.Desugar.HasArchive Asset where
|
||||
archive cid
|
||||
= DA.Internal.Desugar.exercise cid DA.Internal.Desugar.Archive
|
||||
@ -373,11 +368,6 @@ instance DA.Internal.Desugar.HasEnsure AnotherAsset where
|
||||
= DA.Internal.Desugar.True
|
||||
where
|
||||
_ = this
|
||||
instance DA.Internal.Desugar.HasAgreement AnotherAsset where
|
||||
agreement this@AnotherAsset {..}
|
||||
= ""
|
||||
where
|
||||
_ = this
|
||||
instance DA.Internal.Desugar.HasArchive AnotherAsset where
|
||||
archive cid
|
||||
= DA.Internal.Desugar.exercise cid DA.Internal.Desugar.Archive
|
||||
@ -551,11 +541,6 @@ instance DA.Internal.Desugar.HasEnsure Test where
|
||||
= DA.Internal.Desugar.True
|
||||
where
|
||||
_ = this
|
||||
instance DA.Internal.Desugar.HasAgreement Test where
|
||||
agreement this@Test {..}
|
||||
= ""
|
||||
where
|
||||
_ = this
|
||||
instance DA.Internal.Desugar.HasArchive Test where
|
||||
archive cid
|
||||
= DA.Internal.Desugar.exercise cid DA.Internal.Desugar.Archive
|
||||
|
@ -164,11 +164,6 @@ instance DA.Internal.Desugar.HasEnsure Asset where
|
||||
= DA.Internal.Desugar.True
|
||||
where
|
||||
_ = this
|
||||
instance DA.Internal.Desugar.HasAgreement Asset where
|
||||
agreement this@Asset {..}
|
||||
= ""
|
||||
where
|
||||
_ = this
|
||||
instance DA.Internal.Desugar.HasArchive Asset where
|
||||
archive cid
|
||||
= DA.Internal.Desugar.exercise cid DA.Internal.Desugar.Archive
|
||||
|
@ -112,11 +112,6 @@ instance DA.Internal.Desugar.HasEnsure Asset where
|
||||
= DA.Internal.Desugar.True
|
||||
where
|
||||
_ = this
|
||||
instance DA.Internal.Desugar.HasAgreement Asset where
|
||||
agreement this@Asset {..}
|
||||
= ""
|
||||
where
|
||||
_ = this
|
||||
instance DA.Internal.Desugar.HasArchive Asset where
|
||||
archive cid
|
||||
= DA.Internal.Desugar.exercise cid DA.Internal.Desugar.Archive
|
||||
|
@ -173,11 +173,6 @@ instance DA.Internal.Desugar.HasEnsure T where
|
||||
= DA.Internal.Desugar.True
|
||||
where
|
||||
_ = this
|
||||
instance DA.Internal.Desugar.HasAgreement T where
|
||||
agreement this@T {..}
|
||||
= ""
|
||||
where
|
||||
_ = this
|
||||
instance DA.Internal.Desugar.HasArchive T where
|
||||
archive cid
|
||||
= DA.Internal.Desugar.exercise cid DA.Internal.Desugar.Archive
|
||||
|
@ -180,11 +180,6 @@ instance DA.Internal.Desugar.HasEnsure T where
|
||||
= DA.Internal.Desugar.True
|
||||
where
|
||||
_ = this
|
||||
instance DA.Internal.Desugar.HasAgreement T where
|
||||
agreement this@T {..}
|
||||
= ""
|
||||
where
|
||||
_ = this
|
||||
instance DA.Internal.Desugar.HasArchive T where
|
||||
archive cid
|
||||
= DA.Internal.Desugar.exercise cid DA.Internal.Desugar.Archive
|
||||
|
@ -267,11 +267,6 @@ instance DA.Internal.Desugar.HasEnsure T1 where
|
||||
= DA.Internal.Desugar.True
|
||||
where
|
||||
_ = this
|
||||
instance DA.Internal.Desugar.HasAgreement T1 where
|
||||
agreement this@T1 {..}
|
||||
= ""
|
||||
where
|
||||
_ = this
|
||||
instance DA.Internal.Desugar.HasArchive T1 where
|
||||
archive cid
|
||||
= DA.Internal.Desugar.exercise cid DA.Internal.Desugar.Archive
|
||||
@ -388,11 +383,6 @@ instance DA.Internal.Desugar.HasEnsure T2 where
|
||||
= DA.Internal.Desugar.True
|
||||
where
|
||||
_ = this
|
||||
instance DA.Internal.Desugar.HasAgreement T2 where
|
||||
agreement this@T2 {..}
|
||||
= ""
|
||||
where
|
||||
_ = this
|
||||
instance DA.Internal.Desugar.HasArchive T2 where
|
||||
archive cid
|
||||
= DA.Internal.Desugar.exercise cid DA.Internal.Desugar.Archive
|
||||
@ -498,11 +488,6 @@ instance DA.Internal.Desugar.HasEnsure Test where
|
||||
= DA.Internal.Desugar.True
|
||||
where
|
||||
_ = this
|
||||
instance DA.Internal.Desugar.HasAgreement Test where
|
||||
agreement this@Test {..}
|
||||
= ""
|
||||
where
|
||||
_ = this
|
||||
instance DA.Internal.Desugar.HasArchive Test where
|
||||
archive cid
|
||||
= DA.Internal.Desugar.exercise cid DA.Internal.Desugar.Archive
|
||||
|
@ -26,10 +26,6 @@ template Iou
|
||||
ensure amount > 0.0
|
||||
observer owner :: regulators
|
||||
|
||||
agreement show issuer <> " promises to pay " <>
|
||||
show amount <> " " <> currency <>
|
||||
" on demand to " <> show owner
|
||||
|
||||
nonconsuming choice DoNothing : () -- DEL-6496
|
||||
controller owner
|
||||
do return ()
|
||||
|
@ -32,8 +32,6 @@ template GetCash
|
||||
amount: Amount
|
||||
where
|
||||
signatory payer, owner
|
||||
agreement
|
||||
show payer <> " pays " <> amountAsText amount <>" to " <> show owner
|
||||
|
||||
template Iou
|
||||
|
||||
|
@ -20,7 +20,6 @@ template TwoParties
|
||||
with p: Party
|
||||
p2: Party
|
||||
where
|
||||
agreement show p
|
||||
signatory p
|
||||
signatory p2
|
||||
|
||||
@ -57,7 +56,7 @@ template NoSignatory
|
||||
with
|
||||
text : Text
|
||||
where
|
||||
signatory ([] : [Party]); agreement text
|
||||
signatory ([] : [Party])
|
||||
|
||||
template X
|
||||
with p: Party
|
||||
|
@ -1,6 +1,6 @@
|
||||
Transactions:
|
||||
TX 0 1970-01-01T00:00:00Z
|
||||
mustFailAt actAs: {'Alice'} readAs: {} (LfStableMustFails:119:3)
|
||||
mustFailAt actAs: {'Alice'} readAs: {} (LfStableMustFails:118:3)
|
||||
|
||||
Active contracts:
|
||||
|
||||
|
@ -1,5 +1,5 @@
|
||||
Transactions:
|
||||
TX 0 1970-01-01T00:00:00Z (LfStableMustFails:138:10)
|
||||
TX 0 1970-01-01T00:00:00Z (LfStableMustFails:137:10)
|
||||
#0:0
|
||||
│ disclosed to (since): 'Alice' (0), 'Bob' (0)
|
||||
└─> 'Alice' creates LfStableMustFails:X
|
||||
@ -9,7 +9,7 @@ Transactions:
|
||||
pass 1 -100s
|
||||
|
||||
TX 2 1969-12-31T23:58:20Z
|
||||
mustFailAt actAs: {'Bob'} readAs: {} (LfStableMustFails:140:3)
|
||||
mustFailAt actAs: {'Bob'} readAs: {} (LfStableMustFails:139:3)
|
||||
|
||||
Active contracts: #0:0
|
||||
|
||||
|
@ -1,6 +1,6 @@
|
||||
Transactions:
|
||||
TX 0 1970-01-01T00:00:00Z
|
||||
mustFailAt actAs: {'Alice'} readAs: {} (LfStableMustFails:114:3)
|
||||
mustFailAt actAs: {'Alice'} readAs: {} (LfStableMustFails:113:3)
|
||||
|
||||
Active contracts:
|
||||
|
||||
|
@ -1,5 +1,5 @@
|
||||
Transactions:
|
||||
TX 0 1970-01-01T00:00:00Z (LfStableMustFails:188:10)
|
||||
TX 0 1970-01-01T00:00:00Z (LfStableMustFails:187:10)
|
||||
#0:0
|
||||
│ disclosed to (since): 'Alice' (0)
|
||||
└─> 'Alice' creates LfStableMustFails:Recursive
|
||||
@ -7,7 +7,7 @@ Transactions:
|
||||
p = 'Alice'
|
||||
|
||||
TX 1 1970-01-01T00:00:00Z
|
||||
mustFailAt actAs: {'Alice'} readAs: {} (LfStableMustFails:191:3)
|
||||
mustFailAt actAs: {'Alice'} readAs: {} (LfStableMustFails:190:3)
|
||||
|
||||
Active contracts: #0:0
|
||||
|
||||
|
@ -1,6 +1,6 @@
|
||||
Transactions:
|
||||
TX 0 1970-01-01T00:00:00Z
|
||||
mustFailAt actAs: {'Alice'} readAs: {} (LfStableMustFails:124:3)
|
||||
mustFailAt actAs: {'Alice'} readAs: {} (LfStableMustFails:123:3)
|
||||
|
||||
Active contracts:
|
||||
|
||||
|
@ -1,6 +1,6 @@
|
||||
Transactions:
|
||||
TX 0 1970-01-01T00:00:00Z
|
||||
mustFailAt actAs: {'Alice'} readAs: {} (LfStableMustFails:155:3)
|
||||
mustFailAt actAs: {'Alice'} readAs: {} (LfStableMustFails:154:3)
|
||||
|
||||
Active contracts:
|
||||
|
||||
|
@ -1,5 +1,5 @@
|
||||
Transactions:
|
||||
TX 0 1970-01-01T00:00:00Z (LfStableMustFails:161:11)
|
||||
TX 0 1970-01-01T00:00:00Z (LfStableMustFails:160:11)
|
||||
#0:0
|
||||
│ consumed by: #1:0
|
||||
│ referenced by #1:0
|
||||
@ -8,7 +8,7 @@ Transactions:
|
||||
with
|
||||
p = 'Alice'; p2 = 'Bob'
|
||||
|
||||
TX 1 1970-01-01T00:00:00Z (LfStableMustFails:162:11)
|
||||
TX 1 1970-01-01T00:00:00Z (LfStableMustFails:161:11)
|
||||
#1:0
|
||||
│ disclosed to (since): 'Alice' (1), 'Bob' (1)
|
||||
└─> 'Bob' exercises Convert on #0:0 (LfStableMustFails:ToTwoParties)
|
||||
@ -20,7 +20,7 @@ Transactions:
|
||||
p = 'Alice'; p2 = 'Bob'
|
||||
|
||||
TX 2 1970-01-01T00:00:00Z
|
||||
mustFailAt actAs: {'Bob'} readAs: {} (LfStableMustFails:163:3)
|
||||
mustFailAt actAs: {'Bob'} readAs: {} (LfStableMustFails:162:3)
|
||||
|
||||
Active contracts: #1:1
|
||||
|
||||
|
@ -1,5 +1,5 @@
|
||||
Transactions:
|
||||
TX 0 1970-01-01T00:00:00Z (LfStableMustFails:168:10)
|
||||
TX 0 1970-01-01T00:00:00Z (LfStableMustFails:167:10)
|
||||
#0:0
|
||||
│ disclosed to (since): 'Alice' (0)
|
||||
└─> 'Alice' creates LfStableMustFails:NoCtrls
|
||||
@ -7,7 +7,7 @@ Transactions:
|
||||
p = 'Alice'; xs = []
|
||||
|
||||
TX 1 1970-01-01T00:00:00Z
|
||||
mustFailAt actAs: {'Alice'} readAs: {} (LfStableMustFails:169:3)
|
||||
mustFailAt actAs: {'Alice'} readAs: {} (LfStableMustFails:168:3)
|
||||
|
||||
Active contracts: #0:0
|
||||
|
||||
|
@ -1,6 +1,6 @@
|
||||
Transactions:
|
||||
TX 0 1970-01-01T00:00:00Z
|
||||
mustFailAt actAs: {'Alice'} readAs: {} (LfStableMustFails:174:3)
|
||||
mustFailAt actAs: {'Alice'} readAs: {} (LfStableMustFails:173:3)
|
||||
|
||||
Active contracts:
|
||||
|
||||
|
@ -1,6 +1,6 @@
|
||||
Transactions:
|
||||
TX 0 1970-01-01T00:00:00Z
|
||||
mustFailAt actAs: {'Alice'} readAs: {} (LfStableMustFails:129:3)
|
||||
mustFailAt actAs: {'Alice'} readAs: {} (LfStableMustFails:128:3)
|
||||
|
||||
Active contracts:
|
||||
|
||||
|
@ -1,5 +1,5 @@
|
||||
Transactions:
|
||||
TX 0 1970-01-01T00:00:00Z (LfStableMustFails:180:10)
|
||||
TX 0 1970-01-01T00:00:00Z (LfStableMustFails:179:10)
|
||||
#0:0
|
||||
│ disclosed to (since): 'Alice' (0), 'Bob' (0)
|
||||
└─> 'Alice' creates LfStableMustFails:X
|
||||
@ -7,7 +7,7 @@ Transactions:
|
||||
p = 'Alice'; p2 = 'Bob'
|
||||
|
||||
TX 1 1970-01-01T00:00:00Z
|
||||
mustFailAt actAs: {'Alice'} readAs: {} (LfStableMustFails:181:3)
|
||||
mustFailAt actAs: {'Alice'} readAs: {} (LfStableMustFails:180:3)
|
||||
|
||||
Active contracts: #0:0
|
||||
|
||||
|
@ -1,5 +1,5 @@
|
||||
Transactions:
|
||||
TX 0 1970-01-01T00:00:00Z (LfStableMustFails:146:10)
|
||||
TX 0 1970-01-01T00:00:00Z (LfStableMustFails:145:10)
|
||||
#0:0
|
||||
│ disclosed to (since): 'Alice' (0)
|
||||
└─> 'Alice' creates LfStableMustFails:TwoParties
|
||||
@ -7,7 +7,7 @@ Transactions:
|
||||
p = 'Alice'; p2 = 'Alice'
|
||||
|
||||
TX 1 1970-01-01T00:00:00Z
|
||||
mustFailAt actAs: {'Bob'} readAs: {} (LfStableMustFails:147:3)
|
||||
mustFailAt actAs: {'Bob'} readAs: {} (LfStableMustFails:146:3)
|
||||
|
||||
Active contracts: #0:0
|
||||
|
||||
|
@ -1,7 +1,7 @@
|
||||
-- Copyright (c) 2020, Digital Asset (Switzerland) GmbH and/or its affiliates.
|
||||
-- All rights reserved.
|
||||
|
||||
-- @ERROR range=45:1-45:8; Script execution failed on commit at RightOfUse:57:5:
|
||||
-- @ERROR range=40:1-40:8; Script execution failed on commit at RightOfUse:52:5:
|
||||
|
||||
|
||||
module RightOfUse where
|
||||
@ -19,11 +19,6 @@ template RightOfUseAgreement
|
||||
signatory landlord
|
||||
signatory tenant
|
||||
|
||||
agreement
|
||||
show landlord <> " promises to let " <>
|
||||
show tenant <> " live at " <> show address <>
|
||||
" until " <> show expirationDate
|
||||
|
||||
template RightOfUseOffer
|
||||
with
|
||||
landlord: Party
|
||||
|
@ -8,12 +8,12 @@ import Daml.Script
|
||||
import DA.Assert
|
||||
import DA.Functor (void)
|
||||
|
||||
cantSee : forall t p. (Show t, Eq t, Template t, HasAgreement t, IsParties p) => p -> ContractId t -> Script ()
|
||||
cantSee : forall t p. (Show t, Eq t, Template t, HasEnsure t, IsParties p) => p -> ContractId t -> Script ()
|
||||
cantSee p cid = do
|
||||
cArchived <- queryContractId p cid
|
||||
cArchived === None
|
||||
|
||||
canSee : forall t p. (Show t, Eq t, Template t, HasAgreement t, IsParties p) => p -> ContractId t -> Script ()
|
||||
canSee : forall t p. (Show t, Eq t, Template t, HasEnsure t, IsParties p) => p -> ContractId t -> Script ()
|
||||
canSee p = void . queryAssertContractId p
|
||||
|
||||
-- Note that, because of the requirement of specifying `t`, this cannot be used with infix notation, consider renaming
|
||||
@ -25,7 +25,7 @@ cantSeeKey p k = do
|
||||
canSeeKey : forall t k p. (Show k, TemplateKey t k, IsParties p) => p -> k -> Script ()
|
||||
canSeeKey p = void . queryAssertContractKey @t p
|
||||
|
||||
queryAssertContractId : forall t p. (Template t, HasAgreement t, IsParties p) => p -> ContractId t -> Script t
|
||||
queryAssertContractId : forall t p. (Template t, HasEnsure t, IsParties p) => p -> ContractId t -> Script t
|
||||
queryAssertContractId p cid =
|
||||
queryContractId @t p cid >>= \case
|
||||
Some c -> pure c
|
||||
|
@ -31,11 +31,6 @@ instance DA.Internal.Desugar.HasEnsure T where
|
||||
= assertion this
|
||||
where
|
||||
_ = this
|
||||
instance DA.Internal.Desugar.HasAgreement T where
|
||||
agreement this@T {..}
|
||||
= plainEnglish this
|
||||
where
|
||||
_ = this
|
||||
instance DA.Internal.Desugar.HasArchive T where
|
||||
archive cid
|
||||
= DA.Internal.Desugar.exercise cid DA.Internal.Desugar.Archive
|
||||
|
@ -28,7 +28,6 @@ template T
|
||||
signatory sig this
|
||||
observer obs this
|
||||
ensure assertion this
|
||||
agreement plainEnglish this
|
||||
key (sig this, ident this): (Party, Text)
|
||||
maintainer key._1
|
||||
choice Revoke: () with
|
||||
|
@ -1,34 +1,34 @@
|
||||
f62d487b15d231a96d175a7e269bf714775db4eb7ab80273edbd4fd6bec9ea46 META-INF/MANIFEST.MF
|
||||
af53bfb744c41db01eb8066a4f2485bab8af7444206202213be5a37dc0e2f36d platform-independence-1.0.0-832c85e10627160a896a4612c4e9f12e1b92d23c4d0c8d3c80216286048872c9/compiler/damlc/tests/PlatformIndependence.daml
|
||||
0000000000000000000000000000000000000000000000000000000000000000 platform-independence-1.0.0-832c85e10627160a896a4612c4e9f12e1b92d23c4d0c8d3c80216286048872c9/compiler/damlc/tests/PlatformIndependence.hi
|
||||
0000000000000000000000000000000000000000000000000000000000000000 platform-independence-1.0.0-832c85e10627160a896a4612c4e9f12e1b92d23c4d0c8d3c80216286048872c9/compiler/damlc/tests/PlatformIndependence.hie
|
||||
50156da43d4d6210007cb6fe6bce2895a3a23aba9bc9a649fa6d5aa56e9a5dad platform-independence-1.0.0-832c85e10627160a896a4612c4e9f12e1b92d23c4d0c8d3c80216286048872c9/daml-prim-3697a9dababb68797d839216d0c70aec808756a39bdd95ee68a74309ac82eea0.dalf
|
||||
7753f914997075d73cb5bc6a0385d2adb9771bdbf7616dd4493061428b61094b platform-independence-1.0.0-832c85e10627160a896a4612c4e9f12e1b92d23c4d0c8d3c80216286048872c9/daml-prim-DA-Exception-ArithmeticError-0e35772044c88dda5159f70a9170eae0f07e2f1942af4ab401e7cd79166e8c94.dalf
|
||||
7d847f3b915631bdc2f02d7a728634a84aff5e10be7c0f2c3b1dede07c627103 platform-independence-1.0.0-832c85e10627160a896a4612c4e9f12e1b92d23c4d0c8d3c80216286048872c9/daml-prim-DA-Exception-AssertionFailed-ffc462638e7338aaf5d45b3eae8aba5d8e9259a2e44d1ec9db70ed4ee83601e0.dalf
|
||||
72a94dbec4cca5373146dd87eff9d2f5f17de2ed86b029e97149dca6c3e61909 platform-independence-1.0.0-832c85e10627160a896a4612c4e9f12e1b92d23c4d0c8d3c80216286048872c9/daml-prim-DA-Exception-GeneralError-48426ca53c6510a1d641cdc05dd5b3cea288bd4bcd54311ffaa284b5097d4b9d.dalf
|
||||
8aa84ab48fd28a04f16f6cbc0445e7d2a25788c83ba9481b4186bb41527f8489 platform-independence-1.0.0-832c85e10627160a896a4612c4e9f12e1b92d23c4d0c8d3c80216286048872c9/daml-prim-DA-Exception-PreconditionFailed-4d035c16dee0b8d75814624a05de9fcb062e942ff3b3b60d913335b468a84789.dalf
|
||||
b7231004ce0a71af79fd3170ad7a4722d056b33d359c40667da8945a80bb774f platform-independence-1.0.0-832c85e10627160a896a4612c4e9f12e1b92d23c4d0c8d3c80216286048872c9/daml-prim-DA-Internal-Erased-71ca307ec24fc584d601fd6d5f49ec76d100730f56eef290e41248f32ccadfb1.dalf
|
||||
e4f030ce0b2c2bf4f75d12796842b60bf19c9f6d3a3e38251d4fc7831bd21fa2 platform-independence-1.0.0-832c85e10627160a896a4612c4e9f12e1b92d23c4d0c8d3c80216286048872c9/daml-prim-DA-Internal-NatSyn-eb6926e50bb83fbc8f3e154c7c88b1219b31a3c0b812f26b276d46e212c2dd71.dalf
|
||||
7c7b9661de3b11759d2b31170a31557b31fdf71475440a1d19f9b433682d73e7 platform-independence-1.0.0-832c85e10627160a896a4612c4e9f12e1b92d23c4d0c8d3c80216286048872c9/daml-prim-DA-Internal-PromotedText-c2bac57e7a921c98523ae40766bfefab9f5b7bf4bf34e1c09d9a9d1483417b6c.dalf
|
||||
57b95cf6d28642123683263e7042d3e7aa433983bee15f02c6b3be91fdb1570b platform-independence-1.0.0-832c85e10627160a896a4612c4e9f12e1b92d23c4d0c8d3c80216286048872c9/daml-prim-DA-Types-87530dd1038863bad7bdf02c59ae851bc00f469edb2d7dbc8be3172daafa638c.dalf
|
||||
7ee841faf1822a6f2d862fd5c0124ba5c19f7e9b7aa38b51e1734e52d6e369d6 platform-independence-1.0.0-832c85e10627160a896a4612c4e9f12e1b92d23c4d0c8d3c80216286048872c9/daml-prim-GHC-Prim-37375ebfb7ebef8a38aa0d037db55833bcac40eb04074b9024ed81c249ea2387.dalf
|
||||
759096170bd66b0a9e143bcb1b13a3da9b73c1dbef8f332acf316e107b976e97 platform-independence-1.0.0-832c85e10627160a896a4612c4e9f12e1b92d23c4d0c8d3c80216286048872c9/daml-prim-GHC-Tuple-afbf83d4d9ef0fb1a4ee4d1d6bef98b5cea044a6d395c1c27834abd7e8eb57ae.dalf
|
||||
6b86980eae30973a596dd3a14604a49c3a81df83c22d427d7c8aee95f5b34986 platform-independence-1.0.0-832c85e10627160a896a4612c4e9f12e1b92d23c4d0c8d3c80216286048872c9/daml-prim-GHC-Types-2f07eb3e4731beccfd88fcd19177268f120f9a2b06a52534ee808a4ba1e89720.dalf
|
||||
561c7c585bb4dcba764dcd298599bd107d110338e6bc732c6b517065ccf31c2b platform-independence-1.0.0-832c85e10627160a896a4612c4e9f12e1b92d23c4d0c8d3c80216286048872c9/daml-stdlib-0.0.0-2f00d2a0628381f3590c755e7a3ae64e8caa62997119fe788634587d66d9c4d0.dalf
|
||||
54303c132e8d1c59140ccda13f7d2085a885ca3fb3f6fd0fa3cdfcea1f9c13dd platform-independence-1.0.0-832c85e10627160a896a4612c4e9f12e1b92d23c4d0c8d3c80216286048872c9/daml-stdlib-DA-Action-State-Type-2d7314e12cc21ce1482d7a59ab8b42f8deafbe3cdb62eae9fcd4f583ba0ad8d0.dalf
|
||||
d271f772f550b8552d4d62afeb1cf52ec5ca338afcd0f81187151043a7669111 platform-independence-1.0.0-832c85e10627160a896a4612c4e9f12e1b92d23c4d0c8d3c80216286048872c9/daml-stdlib-DA-Date-Types-a4c44a89461229bb4a4fddbdeabe3f9dfaf6db35896c87d76f638cd45e1f0678.dalf
|
||||
3eb9afc8c9d2c0c7cf2d9fce7b67176d253937df7edb445f806bb92dd35fba49 platform-independence-1.0.0-832c85e10627160a896a4612c4e9f12e1b92d23c4d0c8d3c80216286048872c9/daml-stdlib-DA-Internal-Any-7de198711a7a5b3c897eff937b85811438d22f48452a118222590b0ec080bf54.dalf
|
||||
214528ffb6a47cd06842e1c967d0229b2b40c01558f65820227724c8dc580fe5 platform-independence-1.0.0-832c85e10627160a896a4612c4e9f12e1b92d23c4d0c8d3c80216286048872c9/daml-stdlib-DA-Internal-Down-35df06619756af233f13051ba77718e172589b979d22dd3ec40c8787563bb435.dalf
|
||||
57a2209fe7455e34719b1bb144bbcaf954bb636aa84f8abd98ea4752dea0b237 platform-independence-1.0.0-832c85e10627160a896a4612c4e9f12e1b92d23c4d0c8d3c80216286048872c9/daml-stdlib-DA-Internal-Interface-AnyView-Types-db7b27684bd900f7ca47c854d526eeaffd9e84d761859c66cc6cf5957ad89ed4.dalf
|
||||
087da7033930c176e6bc0f8fdff465d496a749c807f154d1ce00ab38a5551c86 platform-independence-1.0.0-832c85e10627160a896a4612c4e9f12e1b92d23c4d0c8d3c80216286048872c9/daml-stdlib-DA-Internal-Template-c2eed01333d3c95b12ca5ef0f196db5cd481c58902e01c8ac6b1e49a62875aa5.dalf
|
||||
3bd856f195b5fe6878155acd30d64f76bcf0065747725a4f4756647fd61d17c1 platform-independence-1.0.0-832c85e10627160a896a4612c4e9f12e1b92d23c4d0c8d3c80216286048872c9/daml-stdlib-DA-Logic-Types-19cfdcbac283f2a26c05bfcea437177cfb7adb0b2eb8aa82944e91b13b671912.dalf
|
||||
71f6d54039b58970475720e76737351995ba8782ce97df708efbc0bc79f8150a platform-independence-1.0.0-832c85e10627160a896a4612c4e9f12e1b92d23c4d0c8d3c80216286048872c9/daml-stdlib-DA-Monoid-Types-bb581ddc78c4c0e682727d9a2302dc1eba5941809c528aca149a5fdaf25c6cbd.dalf
|
||||
ed2942d4af24cb2caf20d61d7ea21f724197dcf3a7bf83c41ed19644074fb9e0 platform-independence-1.0.0-832c85e10627160a896a4612c4e9f12e1b92d23c4d0c8d3c80216286048872c9/daml-stdlib-DA-NonEmpty-Types-d3a94c9e99da7fbb5e35d52d05eec84db27233d4c1aed75548dba1057c84ad81.dalf
|
||||
13a66a07ebec59ee8f86a20d0ce97db3bee35ba326766c88e89598a6df96ef29 platform-independence-1.0.0-832c85e10627160a896a4612c4e9f12e1b92d23c4d0c8d3c80216286048872c9/daml-stdlib-DA-Random-Types-58f4cb7b68a305d056a067c03083f80550ed7d98d6fe100a5ddfa282851ba49a.dalf
|
||||
c1860753e8cefcec4dd6af70cd50827e6dbcfdedc6b6345d42e1114955aa3eaa platform-independence-1.0.0-832c85e10627160a896a4612c4e9f12e1b92d23c4d0c8d3c80216286048872c9/daml-stdlib-DA-Semigroup-Types-ceb729ab26af3934f35fb803534d633c4dd37b466888afcced34a32155e9c2cd.dalf
|
||||
7eacd55658d4500b89762f1f67fe8a9ae72a35716ea15108ddd361abb9e4f7ae platform-independence-1.0.0-832c85e10627160a896a4612c4e9f12e1b92d23c4d0c8d3c80216286048872c9/daml-stdlib-DA-Set-Types-9d88bb9904dab8f44a47e4f27c8d8ee4fc57fece9c2e3d385ef7ed19fcc24049.dalf
|
||||
cb1de1fd96f95c42268fb15cf2353d0ea8d506f75caebd686896c1838df712ff platform-independence-1.0.0-832c85e10627160a896a4612c4e9f12e1b92d23c4d0c8d3c80216286048872c9/daml-stdlib-DA-Stack-Types-747f749a860db32a01ae0c5c741e6648497b93ffcfef3948854c31cc8167eacf.dalf
|
||||
b7ce18d5f2642b00d49f8957d0311ebd89c6de164fae0992059c7eaae1818935 platform-independence-1.0.0-832c85e10627160a896a4612c4e9f12e1b92d23c4d0c8d3c80216286048872c9/daml-stdlib-DA-Time-Types-b47113ba94c31372c553e3869fffed9a45ef1c0f5ac1be3287857cd9450c0bae.dalf
|
||||
a6d1d84b5f296dd1eb7bd9b7cbee4d8a133f18f9d04b77fa95e52599ddcbbc92 platform-independence-1.0.0-832c85e10627160a896a4612c4e9f12e1b92d23c4d0c8d3c80216286048872c9/daml-stdlib-DA-Validation-Types-4687117abb53238857bccdb0d00be7fc005eb334e1f232de3d78152b90b3f202.dalf
|
||||
198f4a6cb7022442df1b2f7ecf8bd95514be7404ebfa30bb867297845ef269ce platform-independence-1.0.0-832c85e10627160a896a4612c4e9f12e1b92d23c4d0c8d3c80216286048872c9/data/platform-independence-1.0.0.conf
|
||||
fe13f237df63b20ed997f154824bd858bf05b459a1a0cebb0bb08f1823fa216a platform-independence-1.0.0-832c85e10627160a896a4612c4e9f12e1b92d23c4d0c8d3c80216286048872c9/platform-independence-1.0.0-832c85e10627160a896a4612c4e9f12e1b92d23c4d0c8d3c80216286048872c9.dalf
|
||||
9f622dd8d5c200f2d4a8692cb92048ad9b6774dc2a31323af8644a1a9b35037d META-INF/MANIFEST.MF
|
||||
af53bfb744c41db01eb8066a4f2485bab8af7444206202213be5a37dc0e2f36d platform-independence-1.0.0-770bf0763cd6ccc4a883e3bce8bff4f0a8adcff0a16825665536fb27e96b2fd3/compiler/damlc/tests/PlatformIndependence.daml
|
||||
0000000000000000000000000000000000000000000000000000000000000000 platform-independence-1.0.0-770bf0763cd6ccc4a883e3bce8bff4f0a8adcff0a16825665536fb27e96b2fd3/compiler/damlc/tests/PlatformIndependence.hi
|
||||
0000000000000000000000000000000000000000000000000000000000000000 platform-independence-1.0.0-770bf0763cd6ccc4a883e3bce8bff4f0a8adcff0a16825665536fb27e96b2fd3/compiler/damlc/tests/PlatformIndependence.hie
|
||||
50156da43d4d6210007cb6fe6bce2895a3a23aba9bc9a649fa6d5aa56e9a5dad platform-independence-1.0.0-770bf0763cd6ccc4a883e3bce8bff4f0a8adcff0a16825665536fb27e96b2fd3/daml-prim-3697a9dababb68797d839216d0c70aec808756a39bdd95ee68a74309ac82eea0.dalf
|
||||
7753f914997075d73cb5bc6a0385d2adb9771bdbf7616dd4493061428b61094b platform-independence-1.0.0-770bf0763cd6ccc4a883e3bce8bff4f0a8adcff0a16825665536fb27e96b2fd3/daml-prim-DA-Exception-ArithmeticError-0e35772044c88dda5159f70a9170eae0f07e2f1942af4ab401e7cd79166e8c94.dalf
|
||||
7d847f3b915631bdc2f02d7a728634a84aff5e10be7c0f2c3b1dede07c627103 platform-independence-1.0.0-770bf0763cd6ccc4a883e3bce8bff4f0a8adcff0a16825665536fb27e96b2fd3/daml-prim-DA-Exception-AssertionFailed-ffc462638e7338aaf5d45b3eae8aba5d8e9259a2e44d1ec9db70ed4ee83601e0.dalf
|
||||
72a94dbec4cca5373146dd87eff9d2f5f17de2ed86b029e97149dca6c3e61909 platform-independence-1.0.0-770bf0763cd6ccc4a883e3bce8bff4f0a8adcff0a16825665536fb27e96b2fd3/daml-prim-DA-Exception-GeneralError-48426ca53c6510a1d641cdc05dd5b3cea288bd4bcd54311ffaa284b5097d4b9d.dalf
|
||||
8aa84ab48fd28a04f16f6cbc0445e7d2a25788c83ba9481b4186bb41527f8489 platform-independence-1.0.0-770bf0763cd6ccc4a883e3bce8bff4f0a8adcff0a16825665536fb27e96b2fd3/daml-prim-DA-Exception-PreconditionFailed-4d035c16dee0b8d75814624a05de9fcb062e942ff3b3b60d913335b468a84789.dalf
|
||||
b7231004ce0a71af79fd3170ad7a4722d056b33d359c40667da8945a80bb774f platform-independence-1.0.0-770bf0763cd6ccc4a883e3bce8bff4f0a8adcff0a16825665536fb27e96b2fd3/daml-prim-DA-Internal-Erased-71ca307ec24fc584d601fd6d5f49ec76d100730f56eef290e41248f32ccadfb1.dalf
|
||||
e4f030ce0b2c2bf4f75d12796842b60bf19c9f6d3a3e38251d4fc7831bd21fa2 platform-independence-1.0.0-770bf0763cd6ccc4a883e3bce8bff4f0a8adcff0a16825665536fb27e96b2fd3/daml-prim-DA-Internal-NatSyn-eb6926e50bb83fbc8f3e154c7c88b1219b31a3c0b812f26b276d46e212c2dd71.dalf
|
||||
7c7b9661de3b11759d2b31170a31557b31fdf71475440a1d19f9b433682d73e7 platform-independence-1.0.0-770bf0763cd6ccc4a883e3bce8bff4f0a8adcff0a16825665536fb27e96b2fd3/daml-prim-DA-Internal-PromotedText-c2bac57e7a921c98523ae40766bfefab9f5b7bf4bf34e1c09d9a9d1483417b6c.dalf
|
||||
57b95cf6d28642123683263e7042d3e7aa433983bee15f02c6b3be91fdb1570b platform-independence-1.0.0-770bf0763cd6ccc4a883e3bce8bff4f0a8adcff0a16825665536fb27e96b2fd3/daml-prim-DA-Types-87530dd1038863bad7bdf02c59ae851bc00f469edb2d7dbc8be3172daafa638c.dalf
|
||||
7ee841faf1822a6f2d862fd5c0124ba5c19f7e9b7aa38b51e1734e52d6e369d6 platform-independence-1.0.0-770bf0763cd6ccc4a883e3bce8bff4f0a8adcff0a16825665536fb27e96b2fd3/daml-prim-GHC-Prim-37375ebfb7ebef8a38aa0d037db55833bcac40eb04074b9024ed81c249ea2387.dalf
|
||||
759096170bd66b0a9e143bcb1b13a3da9b73c1dbef8f332acf316e107b976e97 platform-independence-1.0.0-770bf0763cd6ccc4a883e3bce8bff4f0a8adcff0a16825665536fb27e96b2fd3/daml-prim-GHC-Tuple-afbf83d4d9ef0fb1a4ee4d1d6bef98b5cea044a6d395c1c27834abd7e8eb57ae.dalf
|
||||
6b86980eae30973a596dd3a14604a49c3a81df83c22d427d7c8aee95f5b34986 platform-independence-1.0.0-770bf0763cd6ccc4a883e3bce8bff4f0a8adcff0a16825665536fb27e96b2fd3/daml-prim-GHC-Types-2f07eb3e4731beccfd88fcd19177268f120f9a2b06a52534ee808a4ba1e89720.dalf
|
||||
cedbc8b0d8da32f0e9a328e393882b0698d1e440e64d1651b0bdf2c5366a8bce platform-independence-1.0.0-770bf0763cd6ccc4a883e3bce8bff4f0a8adcff0a16825665536fb27e96b2fd3/daml-stdlib-0.0.0-ca2e1a09bb485603603fe51823126dd3efd90f55cfdd8bdee5355c90e1104a9c.dalf
|
||||
54303c132e8d1c59140ccda13f7d2085a885ca3fb3f6fd0fa3cdfcea1f9c13dd platform-independence-1.0.0-770bf0763cd6ccc4a883e3bce8bff4f0a8adcff0a16825665536fb27e96b2fd3/daml-stdlib-DA-Action-State-Type-2d7314e12cc21ce1482d7a59ab8b42f8deafbe3cdb62eae9fcd4f583ba0ad8d0.dalf
|
||||
d271f772f550b8552d4d62afeb1cf52ec5ca338afcd0f81187151043a7669111 platform-independence-1.0.0-770bf0763cd6ccc4a883e3bce8bff4f0a8adcff0a16825665536fb27e96b2fd3/daml-stdlib-DA-Date-Types-a4c44a89461229bb4a4fddbdeabe3f9dfaf6db35896c87d76f638cd45e1f0678.dalf
|
||||
3eb9afc8c9d2c0c7cf2d9fce7b67176d253937df7edb445f806bb92dd35fba49 platform-independence-1.0.0-770bf0763cd6ccc4a883e3bce8bff4f0a8adcff0a16825665536fb27e96b2fd3/daml-stdlib-DA-Internal-Any-7de198711a7a5b3c897eff937b85811438d22f48452a118222590b0ec080bf54.dalf
|
||||
214528ffb6a47cd06842e1c967d0229b2b40c01558f65820227724c8dc580fe5 platform-independence-1.0.0-770bf0763cd6ccc4a883e3bce8bff4f0a8adcff0a16825665536fb27e96b2fd3/daml-stdlib-DA-Internal-Down-35df06619756af233f13051ba77718e172589b979d22dd3ec40c8787563bb435.dalf
|
||||
57a2209fe7455e34719b1bb144bbcaf954bb636aa84f8abd98ea4752dea0b237 platform-independence-1.0.0-770bf0763cd6ccc4a883e3bce8bff4f0a8adcff0a16825665536fb27e96b2fd3/daml-stdlib-DA-Internal-Interface-AnyView-Types-db7b27684bd900f7ca47c854d526eeaffd9e84d761859c66cc6cf5957ad89ed4.dalf
|
||||
087da7033930c176e6bc0f8fdff465d496a749c807f154d1ce00ab38a5551c86 platform-independence-1.0.0-770bf0763cd6ccc4a883e3bce8bff4f0a8adcff0a16825665536fb27e96b2fd3/daml-stdlib-DA-Internal-Template-c2eed01333d3c95b12ca5ef0f196db5cd481c58902e01c8ac6b1e49a62875aa5.dalf
|
||||
3bd856f195b5fe6878155acd30d64f76bcf0065747725a4f4756647fd61d17c1 platform-independence-1.0.0-770bf0763cd6ccc4a883e3bce8bff4f0a8adcff0a16825665536fb27e96b2fd3/daml-stdlib-DA-Logic-Types-19cfdcbac283f2a26c05bfcea437177cfb7adb0b2eb8aa82944e91b13b671912.dalf
|
||||
71f6d54039b58970475720e76737351995ba8782ce97df708efbc0bc79f8150a platform-independence-1.0.0-770bf0763cd6ccc4a883e3bce8bff4f0a8adcff0a16825665536fb27e96b2fd3/daml-stdlib-DA-Monoid-Types-bb581ddc78c4c0e682727d9a2302dc1eba5941809c528aca149a5fdaf25c6cbd.dalf
|
||||
ed2942d4af24cb2caf20d61d7ea21f724197dcf3a7bf83c41ed19644074fb9e0 platform-independence-1.0.0-770bf0763cd6ccc4a883e3bce8bff4f0a8adcff0a16825665536fb27e96b2fd3/daml-stdlib-DA-NonEmpty-Types-d3a94c9e99da7fbb5e35d52d05eec84db27233d4c1aed75548dba1057c84ad81.dalf
|
||||
13a66a07ebec59ee8f86a20d0ce97db3bee35ba326766c88e89598a6df96ef29 platform-independence-1.0.0-770bf0763cd6ccc4a883e3bce8bff4f0a8adcff0a16825665536fb27e96b2fd3/daml-stdlib-DA-Random-Types-58f4cb7b68a305d056a067c03083f80550ed7d98d6fe100a5ddfa282851ba49a.dalf
|
||||
c1860753e8cefcec4dd6af70cd50827e6dbcfdedc6b6345d42e1114955aa3eaa platform-independence-1.0.0-770bf0763cd6ccc4a883e3bce8bff4f0a8adcff0a16825665536fb27e96b2fd3/daml-stdlib-DA-Semigroup-Types-ceb729ab26af3934f35fb803534d633c4dd37b466888afcced34a32155e9c2cd.dalf
|
||||
7eacd55658d4500b89762f1f67fe8a9ae72a35716ea15108ddd361abb9e4f7ae platform-independence-1.0.0-770bf0763cd6ccc4a883e3bce8bff4f0a8adcff0a16825665536fb27e96b2fd3/daml-stdlib-DA-Set-Types-9d88bb9904dab8f44a47e4f27c8d8ee4fc57fece9c2e3d385ef7ed19fcc24049.dalf
|
||||
cb1de1fd96f95c42268fb15cf2353d0ea8d506f75caebd686896c1838df712ff platform-independence-1.0.0-770bf0763cd6ccc4a883e3bce8bff4f0a8adcff0a16825665536fb27e96b2fd3/daml-stdlib-DA-Stack-Types-747f749a860db32a01ae0c5c741e6648497b93ffcfef3948854c31cc8167eacf.dalf
|
||||
b7ce18d5f2642b00d49f8957d0311ebd89c6de164fae0992059c7eaae1818935 platform-independence-1.0.0-770bf0763cd6ccc4a883e3bce8bff4f0a8adcff0a16825665536fb27e96b2fd3/daml-stdlib-DA-Time-Types-b47113ba94c31372c553e3869fffed9a45ef1c0f5ac1be3287857cd9450c0bae.dalf
|
||||
a6d1d84b5f296dd1eb7bd9b7cbee4d8a133f18f9d04b77fa95e52599ddcbbc92 platform-independence-1.0.0-770bf0763cd6ccc4a883e3bce8bff4f0a8adcff0a16825665536fb27e96b2fd3/daml-stdlib-DA-Validation-Types-4687117abb53238857bccdb0d00be7fc005eb334e1f232de3d78152b90b3f202.dalf
|
||||
2fb8b3ce9e1bdc7e59368cd2081b0274dd6c715ca3d764dc6c14d652c9383299 platform-independence-1.0.0-770bf0763cd6ccc4a883e3bce8bff4f0a8adcff0a16825665536fb27e96b2fd3/data/platform-independence-1.0.0.conf
|
||||
002e5a299d8afe7f68613b421dcf7c7157efc1fc94a99e7ff4e7f48c91dc2bf2 platform-independence-1.0.0-770bf0763cd6ccc4a883e3bce8bff4f0a8adcff0a16825665536fb27e96b2fd3/platform-independence-1.0.0-770bf0763cd6ccc4a883e3bce8bff4f0a8adcff0a16825665536fb27e96b2fd3.dalf
|
||||
|
@ -106,33 +106,6 @@ tests damlc =
|
||||
]
|
||||
)
|
||||
]
|
||||
, test
|
||||
"Warns when template changes agreement"
|
||||
(SucceedWithWarning "\ESC\\[0;93mwarning while type checking template MyLib.A agreement:\n The upgraded template A has changed the definition of agreement.")
|
||||
[ ( "daml/MyLib.daml"
|
||||
, unlines
|
||||
[ "module MyLib where"
|
||||
, "template A with"
|
||||
, " p : Party"
|
||||
, " q : Party"
|
||||
, " where"
|
||||
, " signatory p"
|
||||
, " agreement \"agreement1\""
|
||||
]
|
||||
)
|
||||
]
|
||||
[ ("daml/MyLib.daml"
|
||||
, unlines
|
||||
[ "module MyLib where"
|
||||
, "template A with"
|
||||
, " p : Party"
|
||||
, " q : Party"
|
||||
, " where"
|
||||
, " signatory p"
|
||||
, " agreement \"agreement2\""
|
||||
]
|
||||
)
|
||||
]
|
||||
, test
|
||||
"Warns when template changes key expression"
|
||||
(SucceedWithWarning "\ESC\\[0;93mwarning while type checking template MyLib.A key:\n The upgraded template A has changed the expression for computing its key.")
|
||||
|
@ -118,7 +118,6 @@ main = do
|
||||
, tplPrecondition = mkBool True
|
||||
, tplSignatories = tplParties
|
||||
, tplObservers = ENil TParty
|
||||
, tplAgreement = mkEmptyText
|
||||
, tplChoices = NM.fromList ([chc,chc2] <> [arc | optWithArchiveChoice])
|
||||
, tplKey = Nothing
|
||||
, tplImplements = NM.empty
|
||||
|
@ -745,7 +745,6 @@ goToDefinitionTests lfVersion mbScenarioService scriptPackageData = Tasty.testGr
|
||||
, " owner: Party"
|
||||
, " where"
|
||||
, " signatory owner"
|
||||
, " agreement show owner <> \" has a coin\""
|
||||
]
|
||||
setFilesOfInterest [foo]
|
||||
expectNoErrors
|
||||
|
@ -9,5 +9,4 @@ module AtVersion13 where
|
||||
template Contract13
|
||||
with p: Party
|
||||
where
|
||||
agreement show p
|
||||
signatory p
|
||||
|
@ -9,5 +9,4 @@ module AtVersion14 where
|
||||
template Contract14
|
||||
with p: Party
|
||||
where
|
||||
agreement show p
|
||||
signatory p
|
||||
|
@ -17,7 +17,6 @@ exception MyError
|
||||
template MySimple
|
||||
with p: Party
|
||||
where
|
||||
agreement show p
|
||||
signatory p
|
||||
|
||||
choice MyHello : Text
|
||||
|
@ -14,7 +14,6 @@ exception MyError
|
||||
template MySimple
|
||||
with p: Party
|
||||
where
|
||||
agreement show p
|
||||
signatory p
|
||||
|
||||
choice MyHello : Text
|
||||
|
@ -210,8 +210,8 @@ data QueryACS a = QueryACS
|
||||
|
||||
-- | Query the set of active contracts of the template
|
||||
-- that are visible to the given party.
|
||||
query : forall t p. (Template t, HasAgreement t, IsParties p) => p -> Script [(ContractId t, t)]
|
||||
-- The 'HasAgreement t' constraint prevents this function from being used on interface types.
|
||||
query : forall t p. (Template t, HasEnsure t, IsParties p) => p -> Script [(ContractId t, t)]
|
||||
-- The 'HasEnsure t' constraint prevents this function from being used on interface types.
|
||||
query p = lift $ Free $ Query QueryACS with
|
||||
parties = toParties p
|
||||
tplId = templateTypeRep @t
|
||||
@ -220,8 +220,8 @@ query p = lift $ Free $ Query QueryACS with
|
||||
|
||||
-- | Query the set of active contracts of the template
|
||||
-- that are visible to the given party and match the given predicate.
|
||||
queryFilter : (Template c, HasAgreement c, IsParties p) => p -> (c -> Bool) -> Script [(ContractId c, c)]
|
||||
-- The 'HasAgreement c' constraint prevents this function from being used on interface types.
|
||||
queryFilter : (Template c, HasEnsure c, IsParties p) => p -> (c -> Bool) -> Script [(ContractId c, c)]
|
||||
-- The 'HasEnsure c' constraint prevents this function from being used on interface types.
|
||||
queryFilter p f = filter (\(_, c) -> f c) <$> query p
|
||||
|
||||
data QueryContractIdPayload a = QueryContractIdPayload
|
||||
@ -242,8 +242,8 @@ data QueryContractIdPayload a = QueryContractIdPayload
|
||||
--
|
||||
-- This is semantically equivalent to calling `query`
|
||||
-- and filtering on the client side.
|
||||
queryContractId : forall t p. (Template t, HasAgreement t, IsParties p) => HasCallStack => p -> ContractId t -> Script (Optional t)
|
||||
-- The 'HasAgreement t' constraint prevents this function from being used on interface types.
|
||||
queryContractId : forall t p. (Template t, HasEnsure t, IsParties p) => HasCallStack => p -> ContractId t -> Script (Optional t)
|
||||
-- The 'HasEnsure t' constraint prevents this function from being used on interface types.
|
||||
queryContractId p c = lift $ Free $ QueryContractId QueryContractIdPayload with
|
||||
parties = toParties p
|
||||
tplId = templateTypeRep @t
|
||||
@ -311,8 +311,8 @@ data QueryDisclosurePayload a = QueryDisclosurePayload
|
||||
-- WARNING: Over the gRPC this performs a linear search so only use this if the number of
|
||||
-- active contracts is small.
|
||||
-- Not supported by JSON API
|
||||
queryDisclosure : forall t p. (Template t, HasAgreement t, IsParties p) => HasCallStack => p -> ContractId t -> Script (Optional Disclosure)
|
||||
-- The 'HasAgreement t' constraint prevents this function from being used on interface types.
|
||||
queryDisclosure : forall t p. (Template t, HasEnsure t, IsParties p) => HasCallStack => p -> ContractId t -> Script (Optional Disclosure)
|
||||
-- The 'HasEnsure t' constraint prevents this function from being used on interface types.
|
||||
queryDisclosure p c = lift $ Free $ QueryDisclosure QueryDisclosurePayload with
|
||||
parties = toParties p
|
||||
tplId = templateTypeRep @t
|
||||
@ -719,8 +719,8 @@ internalCreateAndExerciseCmd : forall r. AnyTemplate -> AnyChoice -> Commands r
|
||||
internalCreateAndExerciseCmd tplArg choiceArg = Commands $ Ap (\f -> f (CreateAndExercise tplArg choiceArg identity) (pure (fromLedgerValue @r)))
|
||||
|
||||
-- | Create a contract of the given template.
|
||||
createCmd : (Template t, HasAgreement t) => t -> Commands (ContractId t)
|
||||
-- The 'HasAgreement t' constraint prevents this function from being used on interface types.
|
||||
createCmd : (Template t, HasEnsure t) => t -> Commands (ContractId t)
|
||||
-- The 'HasEnsure t' constraint prevents this function from being used on interface types.
|
||||
createCmd arg = internalCreateCmd (toAnyTemplate arg)
|
||||
|
||||
-- | Exercise a choice on the given contract.
|
||||
@ -732,8 +732,8 @@ exerciseByKeyCmd : forall t k c r. (TemplateKey t k, Choice t c r) => k -> c ->
|
||||
exerciseByKeyCmd key arg = internalExerciseByKeyCmd (templateTypeRep @t) (toAnyContractKey @t key) (toAnyChoice @t arg)
|
||||
|
||||
-- | Create a contract and exercise a choice on it in the same transaction.
|
||||
createAndExerciseCmd : forall t c r. (Template t, Choice t c r, HasAgreement t) => t -> c -> Commands r
|
||||
-- The 'HasAgreement t' constraint prevents this function from being used on interface types.
|
||||
createAndExerciseCmd : forall t c r. (Template t, Choice t c r, HasEnsure t) => t -> c -> Commands r
|
||||
-- The 'HasEnsure t' constraint prevents this function from being used on interface types.
|
||||
createAndExerciseCmd tplArg choiceArg = internalCreateAndExerciseCmd (toAnyTemplate tplArg) (toAnyChoice @t choiceArg)
|
||||
|
||||
-- | Archive the given contract.
|
||||
|
@ -47,7 +47,7 @@ data Commands a = Commands with
|
||||
commands : [CommandWithMeta]
|
||||
continue : [CommandResult] -> a
|
||||
deriving Functor
|
||||
|
||||
|
||||
data Disclosure = Disclosure with
|
||||
templateId: TemplateTypeRep
|
||||
contractId : ContractId ()
|
||||
@ -73,7 +73,7 @@ instance Applicative Commands where
|
||||
liftA2 : (a -> b -> c) -> Commands a -> Commands b -> Commands c
|
||||
liftA2 f a b = Commands
|
||||
{ commands = a.commands <> b.commands
|
||||
, continue = \results ->
|
||||
, continue = \results ->
|
||||
let (aResults, bResults) = splitAt (expectedCommandsResults a.commands) results
|
||||
in f (a.continue aResults) (b.continue bResults)
|
||||
}
|
||||
@ -105,8 +105,8 @@ internalCreateAndExerciseCmd tplArg choiceArg explicitPackageId = Commands [Comm
|
||||
|
||||
-- Typed commands but still internal as explicitPackageId not determined
|
||||
-- | HIDE
|
||||
internalTypedCreateCmd : (Template t, HasAgreement t) => t -> Bool -> Commands (ContractId t)
|
||||
-- The 'HasAgreement t' constraint prevents this function from being used on interface types.
|
||||
internalTypedCreateCmd : (Template t, HasEnsure t) => t -> Bool -> Commands (ContractId t)
|
||||
-- The 'HasEnsure t' constraint prevents this function from being used on interface types.
|
||||
internalTypedCreateCmd arg explicitPackageId =
|
||||
coerceContractId <$> internalCreateCmd (toAnyTemplate arg) explicitPackageId
|
||||
|
||||
@ -121,15 +121,15 @@ internalTypedExerciseByKeyCmd key arg explicitPackageId =
|
||||
fromLedgerValue @r <$> internalExerciseByKeyCmd (templateTypeRep @t) (toAnyContractKey @t key) (toAnyChoice @t arg) explicitPackageId
|
||||
|
||||
-- | HIDE
|
||||
internalTypedCreateAndExerciseCmdWithCid : forall t c r. (Template t, Choice t c r, HasAgreement t) => t -> c -> Bool -> Commands (ContractId t, r)
|
||||
-- The 'HasAgreement t' constraint prevents this function from being used on interface types.
|
||||
internalTypedCreateAndExerciseCmdWithCid : forall t c r. (Template t, Choice t c r, HasEnsure t) => t -> c -> Bool -> Commands (ContractId t, r)
|
||||
-- The 'HasEnsure t' constraint prevents this function from being used on interface types.
|
||||
internalTypedCreateAndExerciseCmdWithCid tplArg choiceArg explicitPackageId =
|
||||
bimap coerceContractId (fromLedgerValue @r) <$> internalCreateAndExerciseCmd (toAnyTemplate tplArg) (toAnyChoice @t choiceArg) explicitPackageId
|
||||
|
||||
-- Main command API, without explicit package ids
|
||||
-- | Create a contract of the given template.
|
||||
createCmd : (Template t, HasAgreement t) => t -> Commands (ContractId t)
|
||||
-- The 'HasAgreement t' constraint prevents this function from being used on interface types.
|
||||
createCmd : (Template t, HasEnsure t) => t -> Commands (ContractId t)
|
||||
-- The 'HasEnsure t' constraint prevents this function from being used on interface types.
|
||||
createCmd arg = internalTypedCreateCmd arg False
|
||||
|
||||
-- | Exercise a choice on the given contract.
|
||||
@ -141,19 +141,19 @@ exerciseByKeyCmd : forall t k c r. (TemplateKey t k, Choice t c r) => k -> c ->
|
||||
exerciseByKeyCmd key arg = internalTypedExerciseByKeyCmd @t key arg False
|
||||
|
||||
-- | Create a contract and exercise a choice on it in the same transaction, returns the created ContractId, and the choice result.
|
||||
createAndExerciseWithCidCmd : forall t c r. (Template t, Choice t c r, HasAgreement t) => t -> c -> Commands (ContractId t, r)
|
||||
-- The 'HasAgreement t' constraint prevents this function from being used on interface types.
|
||||
createAndExerciseWithCidCmd : forall t c r. (Template t, Choice t c r, HasEnsure t) => t -> c -> Commands (ContractId t, r)
|
||||
-- The 'HasEnsure t' constraint prevents this function from being used on interface types.
|
||||
createAndExerciseWithCidCmd tplArg choiceArg = internalTypedCreateAndExerciseCmdWithCid tplArg choiceArg False
|
||||
|
||||
-- | Create a contract and exercise a choice on it in the same transaction, returns only the choice result.
|
||||
createAndExerciseCmd : forall t c r. (Template t, Choice t c r, HasAgreement t) => t -> c -> Commands r
|
||||
-- The 'HasAgreement t' constraint prevents this function from being used on interface types.
|
||||
createAndExerciseCmd : forall t c r. (Template t, Choice t c r, HasEnsure t) => t -> c -> Commands r
|
||||
-- The 'HasEnsure t' constraint prevents this function from being used on interface types.
|
||||
createAndExerciseCmd tplArg choiceArg = snd <$> createAndExerciseWithCidCmd tplArg choiceArg
|
||||
|
||||
-- Main command API, WITH explicit package ids
|
||||
-- | Create a contract of the given template, using the exact package ID of the template given - upgrades are disabled.
|
||||
createExactCmd : (Template t, HasAgreement t) => t -> Commands (ContractId t)
|
||||
-- The 'HasAgreement t' constraint prevents this function from being used on interface types.
|
||||
createExactCmd : (Template t, HasEnsure t) => t -> Commands (ContractId t)
|
||||
-- The 'HasEnsure t' constraint prevents this function from being used on interface types.
|
||||
createExactCmd arg = internalTypedCreateCmd arg True
|
||||
|
||||
-- | Exercise a choice on the given contract, using the exact package ID of the template given - upgrades are disabled.
|
||||
@ -166,13 +166,13 @@ exerciseByKeyExactCmd key arg = internalTypedExerciseByKeyCmd @t key arg True
|
||||
|
||||
-- | Create a contract and exercise a choice on it in the same transaction, returns the created ContractId, and the choice result.
|
||||
-- Uses the exact package ID of the template given - upgrades are disabled.
|
||||
createAndExerciseWithCidExactCmd : forall t c r. (Template t, Choice t c r, HasAgreement t) => t -> c -> Commands (ContractId t, r)
|
||||
-- The 'HasAgreement t' constraint prevents this function from being used on interface types.
|
||||
createAndExerciseWithCidExactCmd : forall t c r. (Template t, Choice t c r, HasEnsure t) => t -> c -> Commands (ContractId t, r)
|
||||
-- The 'HasEnsure t' constraint prevents this function from being used on interface types.
|
||||
createAndExerciseWithCidExactCmd tplArg choiceArg = internalTypedCreateAndExerciseCmdWithCid tplArg choiceArg True
|
||||
|
||||
-- | Create a contract and exercise a choice on it in the same transaction, returns only the choice result.
|
||||
createAndExerciseExactCmd : forall t c r. (Template t, Choice t c r, HasAgreement t) => t -> c -> Commands r
|
||||
-- The 'HasAgreement t' constraint prevents this function from being used on interface types.
|
||||
createAndExerciseExactCmd : forall t c r. (Template t, Choice t c r, HasEnsure t) => t -> c -> Commands r
|
||||
-- The 'HasEnsure t' constraint prevents this function from being used on interface types.
|
||||
createAndExerciseExactCmd tplArg choiceArg = snd <$> createAndExerciseWithCidExactCmd tplArg choiceArg
|
||||
|
||||
-- | Archive the given contract.
|
||||
|
@ -17,8 +17,8 @@ instance IsQuestion QueryACS [(ContractId (), AnyTemplate)] where command = "Que
|
||||
|
||||
-- | Query the set of active contracts of the template
|
||||
-- that are visible to the given party.
|
||||
query : forall t p. (Template t, HasAgreement t, IsParties p) => p -> Script [(ContractId t, t)]
|
||||
-- The 'HasAgreement t' constraint prevents this function from being used on interface types.
|
||||
query : forall t p. (Template t, HasEnsure t, IsParties p) => p -> Script [(ContractId t, t)]
|
||||
-- The 'HasEnsure t' constraint prevents this function from being used on interface types.
|
||||
query p = fmap convert $ lift $ QueryACS with
|
||||
parties = toParties p
|
||||
tplId = templateTypeRep @t
|
||||
@ -28,8 +28,8 @@ query p = fmap convert $ lift $ QueryACS with
|
||||
|
||||
-- | Query the set of active contracts of the template
|
||||
-- that are visible to the given party and match the given predicate.
|
||||
queryFilter : (Template c, HasAgreement c, IsParties p) => p -> (c -> Bool) -> Script [(ContractId c, c)]
|
||||
-- The 'HasAgreement c' constraint prevents this function from being used on interface types.
|
||||
queryFilter : (Template c, HasEnsure c, IsParties p) => p -> (c -> Bool) -> Script [(ContractId c, c)]
|
||||
-- The 'HasEnsure c' constraint prevents this function from being used on interface types.
|
||||
queryFilter p f = filter (\(_, c) -> f c) <$> query p
|
||||
|
||||
data QueryContractId = QueryContractId with
|
||||
@ -49,7 +49,6 @@ instance IsQuestion QueryContractId (Optional (AnyTemplate, Text)) where command
|
||||
-- This is semantically equivalent to calling `query`
|
||||
-- and filtering on the client side.
|
||||
queryContractId_ : forall t p. (Template t, IsParties p) => HasCallStack => p -> ContractId t -> Script (Optional (AnyTemplate, Text))
|
||||
-- The 'HasAgreement t' constraint prevents this function from being used on interface types.
|
||||
queryContractId_ p c = lift $ QueryContractId with
|
||||
parties = toParties p
|
||||
tplId = templateTypeRep @t
|
||||
@ -58,15 +57,15 @@ queryContractId_ p c = lift $ QueryContractId with
|
||||
-- convert : Optional AnyTemplate -> Optional t
|
||||
-- convert = fmap $ fromSome . fromAnyTemplate
|
||||
|
||||
queryContractId: forall t p. (Template t, HasAgreement t, IsParties p) => HasCallStack => p -> ContractId t -> Script (Optional t)
|
||||
queryContractId: forall t p. (Template t, HasEnsure t, IsParties p) => HasCallStack => p -> ContractId t -> Script (Optional t)
|
||||
queryContractId p c = fmap (fmap $ fromSome . fromAnyTemplate . fst) $ queryContractId_ p c
|
||||
|
||||
-- TODO https://github.com/digital-asset/daml/issues/17755
|
||||
-- clean the API for different query function
|
||||
queryDisclosure: forall t p. (Template t, IsParties p) => HasCallStack => p -> ContractId t -> Script (Optional Disclosure)
|
||||
queryDisclosure p c = fmap (fmap $ \(_, blob) -> Disclosure tplId cid blob) $ queryContractId_ p c
|
||||
where
|
||||
tplId = templateTypeRep @t
|
||||
where
|
||||
tplId = templateTypeRep @t
|
||||
cid = coerceContractId c
|
||||
|
||||
data QueryInterface = QueryInterface with
|
||||
|
@ -71,7 +71,7 @@ tries : Int
|
||||
tries = 60
|
||||
|
||||
|
||||
waitForCid : (Template t, HasAgreement t) => Int -> Party -> ContractId t -> Script ()
|
||||
waitForCid : (Template t, HasEnsure t) => Int -> Party -> ContractId t -> Script ()
|
||||
waitForCid tries p cid
|
||||
| tries <= 0 = abort $ "Cid " <> show cid <> " did not appear"
|
||||
| otherwise = do
|
||||
@ -151,7 +151,7 @@ inactiveDisclosureDoesNotFailDuringSubmission = do
|
||||
disclosure <- fromSome <$> queryDisclosure alice did
|
||||
alice `submit` archiveCmd did
|
||||
|
||||
-- we double check exercising the consumed disclosure fail
|
||||
-- we double check exercising the consumed disclosure fail
|
||||
submitMustFail alice $ exerciseCmd did (Open alice)
|
||||
|
||||
submitWithDisclosures alice [disclosure] $ do
|
||||
|
@ -112,7 +112,7 @@ tests = mconcat
|
||||
("Succeeds explicitly calling a removed V1 choice on a V2 contract", explicitRemovedV1ChoiceV2Contract)
|
||||
, ("Fails implicitly calling a removed V1 choice on a V2 contract, as V2 is selected", implicitRemovedV1ChoiceV2Contract)
|
||||
, ("Fails implicitly calling a removed V1 choice on a V1 contract, as V2 is selected", implicitRemovedV1ChoiceV1Contract)
|
||||
|
||||
|
||||
, -- Invalid signatory/observer changes
|
||||
("Succeeds if the signatories don't change", unchangedSignatoryUpgrade)
|
||||
, ("Fails if the signatories set gets larger", largerSignatoryUpgrade)
|
||||
@ -222,7 +222,7 @@ fetchDowngradedSome = do
|
||||
cid <- a `submit` createCmd V2.ValidUpgrade with party = a, newField = Some "hi"
|
||||
let v1Cid = coerceContractId @V2.ValidUpgrade @V1.ValidUpgrade cid
|
||||
eV1Name <- a `tryExerciseV1Util` V1Fetch with cid = v1Cid
|
||||
|
||||
|
||||
case eV1Name of
|
||||
Left (DevError Upgrade msg)
|
||||
| "An optional contract field with a value of Some may not be dropped during downgrading" `isInfixOf` msg
|
||||
@ -307,9 +307,9 @@ exerciseV2ChoiceV2ContractSameType = do
|
||||
sameTypeResult <- a `exerciseV2Util` V2SameChoiceExercise with cid = cid
|
||||
sameTypeResult === "V2"
|
||||
|
||||
genericUpgradeTest
|
||||
genericUpgradeTest
|
||||
: forall t2 t1 c2 r
|
||||
. (Template t1, HasAgreement t1, Choice t2 c2 r)
|
||||
. (Template t1, HasEnsure t1, Choice t2 c2 r)
|
||||
=> (Party -> t1)
|
||||
-> c2
|
||||
-> Bool
|
||||
@ -322,7 +322,7 @@ genericUpgradeTest makeV1Contract v2Choice explicitPackageIds handleRes = do
|
||||
res <- a `trySubmit` (if explicitPackageIds then exerciseExactCmd else exerciseCmd) cidV2 v2Choice
|
||||
handleRes res
|
||||
|
||||
choiceTest : forall t2 t1 c2 r. (Template t1, HasAgreement t1, Choice t2 c2 r, Eq r, Show r) => (Party -> t1) -> c2 -> Bool -> r -> Script ()
|
||||
choiceTest : forall t2 t1 c2 r. (Template t1, HasEnsure t1, Choice t2 c2 r, Eq r, Show r) => (Party -> t1) -> c2 -> Bool -> r -> Script ()
|
||||
choiceTest makeV1Contract v2Choice explicitPackageIds expectedResult = genericUpgradeTest @t2 makeV1Contract v2Choice explicitPackageIds $ \res ->
|
||||
case res of
|
||||
Right returnValue -> returnValue === expectedResult
|
||||
@ -455,7 +455,7 @@ signatoryObserverUpgrade shouldSucceed sigF obsF = do
|
||||
charlie <- allocatePartyOn "charlie" participant0
|
||||
let (preSignatories, postSignatories) = sigF (alice, bob, charlie)
|
||||
(preObservers, postObservers) = obsF (alice, bob, charlie)
|
||||
|
||||
|
||||
cid <- submitMulti [alice, bob, charlie] [] $ createExactCmd V1.InvalidUpgradeStakeholders with
|
||||
signatories = preSignatories
|
||||
observers = preObservers
|
||||
@ -499,7 +499,7 @@ smallerObserverUpgrade : Script ()
|
||||
smallerObserverUpgrade = observerUpgrade False $ \(alice, bob, charlie) -> ([alice, bob, charlie], [alice, bob])
|
||||
|
||||
canRemoveObserversThatAreSignatories : Script ()
|
||||
canRemoveObserversThatAreSignatories =
|
||||
canRemoveObserversThatAreSignatories =
|
||||
signatoryObserverUpgrade
|
||||
True
|
||||
(\(alice, bob, charlie) -> ([alice, bob, charlie], [alice, bob, charlie])) -- signatories
|
||||
@ -524,7 +524,7 @@ ensureClauseDowngradeToNoLongerValid =
|
||||
Left (UnhandledException (Some (fromAnyException -> Some (PreconditionFailed _)))) -> pure ()
|
||||
res -> assertFail $ "Expected PreconditionFailed, got " <> show res
|
||||
|
||||
templateInvalidChange : forall t2 t1 c2. (Template t1, HasAgreement t1, Choice t2 c2 Text) => Bool -> (Party -> t1) -> c2 -> Script ()
|
||||
templateInvalidChange : forall t2 t1 c2. (Template t1, HasEnsure t1, Choice t2 c2 Text) => Bool -> (Party -> t1) -> c2 -> Script ()
|
||||
templateInvalidChange shouldSucceed makeV1Contract v2Choice =
|
||||
genericUpgradeTest @t2 makeV1Contract v2Choice False $ \res ->
|
||||
case (res, shouldSucceed) of
|
||||
@ -552,7 +552,7 @@ templateFieldsRemovedNested : Script ()
|
||||
templateFieldsRemovedNested =
|
||||
templateInvalidChange
|
||||
@V2.FieldsRemovedNested
|
||||
False
|
||||
False
|
||||
(\p -> V1.FieldsRemovedNested $ V1.FieldsRemovedNestedData p 1)
|
||||
V2.FieldsRemovedNestedCall
|
||||
|
||||
|
@ -126,7 +126,7 @@ initializeUser = do
|
||||
tries : Int
|
||||
tries = 60
|
||||
|
||||
waitForCid : (Template t, HasAgreement t) => Int -> Party -> ContractId t -> Script ()
|
||||
waitForCid : (Template t, HasEnsure t) => Int -> Party -> ContractId t -> Script ()
|
||||
waitForCid tries p cid
|
||||
| tries <= 0 = abort $ "Cid " <> show cid <> " did not appear"
|
||||
| otherwise = do
|
||||
|
@ -245,7 +245,7 @@ mkArchiveNftTransferProposalTest Parties {..} = do
|
||||
|
||||
-- MK_ASSET_TEST_BEGIN
|
||||
mkAssetTest : forall t.
|
||||
(Template t, Implements t IAsset, HasAgreement t) =>
|
||||
(Template t, Implements t IAsset, HasEnsure t) =>
|
||||
Text -> Parties -> (Party -> Party -> t) -> Script (ContractId IAsset)
|
||||
mkAssetTest assetTxt Parties {..} mkAsset = do
|
||||
aliceAsset <-
|
||||
@ -314,7 +314,7 @@ mkAssetTest assetTxt Parties {..} mkAsset = do
|
||||
-- MK_ASSET_TEST_END
|
||||
|
||||
mkArchiveAssetTest : forall t.
|
||||
(Template t, Implements t IAsset, HasAgreement t) =>
|
||||
(Template t, Implements t IAsset, HasEnsure t) =>
|
||||
Parties -> (Party -> Party -> t) -> Script ()
|
||||
mkArchiveAssetTest Parties {..} mkAsset = do
|
||||
aliceAsset <-
|
||||
@ -326,7 +326,7 @@ mkArchiveAssetTest Parties {..} mkAsset = do
|
||||
archiveCmd aliceAsset
|
||||
|
||||
mkArchiveAssetTransferProposalTest : forall t.
|
||||
(Template t, Implements t IAsset, HasAgreement t) =>
|
||||
(Template t, Implements t IAsset, HasEnsure t) =>
|
||||
Parties -> (Party -> Party -> t) -> Script ()
|
||||
mkArchiveAssetTransferProposalTest Parties {..} mkAsset = do
|
||||
aliceAsset <-
|
||||
|
Loading…
Reference in New Issue
Block a user