(herald minipay-rely-guar (try-old-strands) (bound 16)) (comment "CPSA 4.4.0") (comment "All input read from minipay-rely-guar.scm") (comment "Strand count bounded at 16") (comment "Old strands tried first") (defprotocol minipay-rely-guar basic (defrole cust (vars (c m b name) (cost amount) (item merchandise) (merc-conf bank-conf btr mtr text) (account acct) (n ncb ncm data)) (trace (send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) (facts (neq n ncb) (neq n ncm) (neq ncm ncb))) (defrole merc (vars (c m b name) (cost amount) (item merchandise) (merc-conf btr mtr text) (n ncm data) (for-bank bank-conf-commit bank-conf-decommit mesg)) (trace (recv (enc n cost item merc-conf ncm bank-conf-commit (sign (order c m b cost for-bank) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost for-bank) (privk "sig" c)) for-bank)) (pubk "enc" b))) (recv (enc bank-conf-decommit (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n bank-conf-decommit)) btr mtr) (privk "sig" m)))) (uniq-orig mtr)) (defrole bank (vars (c m b name) (cost amount) (bank-conf btr mtr text) (merc-conf-decommit mesg) (account acct) (n ncb data)) (trace (recv (enc (payreq c m b (hash cost n) merc-conf-decommit mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n merc-conf-decommit) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n merc-conf-decommit) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n merc-conf-decommit)) btr mtr) (privk "sig" b)) (pubk "enc" m)))) (uniq-orig btr)) (defrule rely-cust-3 (forall ((z strd) (mtr text) (item merchandise) (b m c name)) (implies (and (p "cust" z (idx 3)) (p "cust" "mtr" z mtr) (p "cust" "item" z item) (p "cust" "b" z b) (p "cust" "m" z m) (p "cust" "c" z c)) (fact will-ship c m b item mtr)))) (defrule rely-cust-2 (forall ((z strd) (btr mtr text) (n data) (cost amount) (b m c name)) (implies (and (p "cust" z (idx 2)) (p "cust" "btr" z btr) (p "cust" "mtr" z mtr) (p "cust" "n" z n) (p "cust" "cost" z cost) (p "cust" "b" z b) (p "cust" "m" z m) (p "cust" "c" z c)) (fact will-transfer c m b cost n mtr btr)))) (defrule rely-merc-3 (forall ((z strd) (n data) (cost amount) (item merchandise) (b m c name) (btr mtr text)) (implies (and (p "merc" z (idx 3)) (p "merc" "n" z n) (p "merc" "cost" z cost) (p "merc" "item" z item) (p "merc" "b" z b) (p "merc" "m" z m) (p "merc" "c" z c) (p "merc" "btr" z btr) (p "merc" "mtr" z mtr)) (and (fact buy-via c m b item cost n) (fact will-transfer c m b cost n mtr btr))))) (defrule rely-bank-1 (forall ((z strd) (n data) (cost amount) (b m c name)) (implies (and (p "bank" z (idx 1)) (p "bank" "n" z n) (p "bank" "cost" z cost) (p "bank" "b" z b) (p "bank" "m" z m) (p "bank" "c" z c)) (exists ((item merchandise)) (fact buy-via c m b item cost n))))) (defrule guar-cust-1 (forall ((z strd) (n data) (cost amount) (item merchandise) (b m c name)) (implies (and (p "cust" z (idx 1)) (p "cust" "n" z n) (p "cust" "cost" z cost) (p "cust" "item" z item) (p "cust" "b" z b) (p "cust" "m" z m) (p "cust" "c" z c)) (fact buy-via c m b item cost n)))) (defrule guar-merc-4 (forall ((z strd) (mtr text) (item merchandise) (b m c name)) (implies (and (p "merc" z (idx 4)) (p "merc" "mtr" z mtr) (p "merc" "item" z item) (p "merc" "b" z b) (p "merc" "m" z m) (p "merc" "c" z c)) (fact will-ship c m b item mtr)))) (defrule guar-bank-2 (forall ((z strd) (btr mtr text) (n data) (cost amount) (c b m name)) (implies (and (p "bank" z (idx 2)) (p "bank" "btr" z btr) (p "bank" "mtr" z mtr) (p "bank" "n" z n) (p "bank" "cost" z cost) (p "bank" "c" z c) (p "bank" "b" z b) (p "bank" "m" z m)) (and (non (privk "sig" c)) (fact will-transfer c m b cost n mtr btr))))) (defrule cheq-merc-4 (forall ((z strd) (n data) (bank-conf-decommit bank-conf-commit mesg)) (implies (and (p "merc" z (idx 4)) (p "merc" "n" z n) (p "merc" "bank-conf-decommit" z bank-conf-decommit) (p "merc" "bank-conf-commit" z bank-conf-commit)) (= bank-conf-commit (hash n bank-conf-decommit))))) (defgenrule neqRl_indx (forall ((x indx)) (implies (fact neq x x) (false)))) (defgenrule neqRl_strd (forall ((x strd)) (implies (fact neq x x) (false)))) (defgenrule neqRl_mesg (forall ((x mesg)) (implies (fact neq x x) (false)))) (defgenrule fact-cust-neq2 (forall ((z strd) (ncb n data)) (implies (and (p "cust" z (idx 1)) (p "cust" "ncb" z ncb) (p "cust" "n" z n)) (fact neq n ncb)))) (defgenrule fact-cust-neq1 (forall ((z strd) (ncm n data)) (implies (and (p "cust" z (idx 1)) (p "cust" "ncm" z ncm) (p "cust" "n" z n)) (fact neq n ncm)))) (defgenrule fact-cust-neq0 (forall ((z strd) (ncb ncm data)) (implies (and (p "cust" z (idx 1)) (p "cust" "ncb" z ncb) (p "cust" "ncm" z ncm)) (fact neq ncm ncb)))) (lang (acct atom) (amount atom) (merchandise atom) (sign sign) (order (tuple 5)) (bconf (tuple 3)) (mconf (tuple 3)) (payreq (tuple 7)))) (defskeleton minipay-rely-guar (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (merc-conf bank-conf btr mtr text) (c m b name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m))))) (label 0) (unrealized (0 1) (0 2)) (origs (n (0 0))) (comment "Not closed under rules")) (defskeleton minipay-rely-guar (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (merc-conf bank-conf btr mtr text) (c m b name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (will-ship c m b item mtr) (will-transfer c m b cost n mtr btr) (buy-via c m b item cost n)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-cust-1 rely-cust-2 rely-cust-3) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m))))) (label 1) (parent 0) (unrealized (0 1) (0 2)) (origs (n (0 0))) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay-rely-guar (vars (account account-0 acct) (cost amount) (n ncb ncm ncb-0 data) (item merchandise) (merc-conf bank-conf btr mtr bank-conf-0 text) (c m b name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account-0) (cost cost) (n n) (ncb ncb-0) (bank-conf bank-conf-0) (btr btr) (mtr mtr) (c c) (m m) (b b)) (precedes ((0 0) (1 0)) ((1 1) (0 1))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (will-ship c m b item mtr) (buy-via c m b item cost n) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 rely-cust-3) (operation encryption-test (added-strand bank 2) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (0 1)) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb-0 bank-conf-0) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))))) (label 2) (parent 1) (unrealized (0 1) (0 2) (1 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay-rely-guar (vars (for-bank mesg) (account account-0 acct) (cost amount) (n ncb ncm ncb-0 data) (item merchandise) (merc-conf bank-conf btr mtr bank-conf-0 text) (c m b name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account-0) (cost cost) (n n) (ncb ncb-0) (bank-conf bank-conf-0) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 4 (for-bank for-bank) (bank-conf-commit (hash n (hash ncb-0 bank-conf-0))) (bank-conf-decommit (hash ncb-0 bank-conf-0)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (precedes ((0 0) (2 0)) ((1 1) (2 2)) ((2 1) (1 0)) ((2 3) (0 1))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-ship c m b item mtr) (will-transfer c m b cost n mtr btr)) (rule cheq-merc-4 fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 guar-merc-4) (operation encryption-test (added-strand merc 4) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (0 1) (enc (hash ncb-0 bank-conf-0) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb-0 bank-conf-0) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb-0 bank-conf-0)) (sign (order c m b cost for-bank) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost for-bank) (privk "sig" c)) for-bank)) (pubk "enc" b))) (recv (enc (hash ncb-0 bank-conf-0) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))))) (label 3) (parent 2) (unrealized (0 2) (1 0) (2 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay-rely-guar (vars (for-bank mesg) (account account-0 acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr merc-conf text) (c m b name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account-0) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 5 (for-bank for-bank) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (precedes ((0 0) (2 0)) ((1 1) (2 2)) ((2 1) (1 0)) ((2 3) (0 1)) ((2 4) (0 2))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-ship c m b item mtr) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 guar-merc-4) (operation encryption-test (displaced 2 3 merc 5) (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)) (0 2)) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account-0 bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-0 bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost for-bank) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost for-bank) (privk "sig" c)) for-bank)) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m))))) (label 4) (parent 3) (unrealized (1 0) (2 0)) (comment "3 in cohort - 3 not yet seen")) (defskeleton minipay-rely-guar (vars (account account-0 acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr merc-conf text) (c m b name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account-0) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 5 (for-bank (enc n cost account-0 bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (precedes ((0 0) (2 0)) ((1 1) (2 2)) ((2 1) (1 0)) ((2 3) (0 1)) ((2 4) (0 2))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-ship c m b item mtr) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 guar-merc-4) (operation encryption-test (contracted (for-bank (enc n cost account-0 bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (hash cost n) (1 0) (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account-0 bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-0 bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account-0 bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-0 bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account-0 bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account-0 bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-0 bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m))))) (label 5) (parent 4) (unrealized (2 0)) (comment "2 in cohort - 2 not yet seen")) (defskeleton minipay-rely-guar (vars (for-bank for-bank-0 bank-conf-commit mesg) (account account-0 acct) (cost amount) (n ncb ncm ncm-0 data) (item item-0 merchandise) (bank-conf btr mtr merc-conf merc-conf-0 mtr-0 text) (c m b c-0 m-0 b-0 name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account-0) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 5 (for-bank for-bank) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 2 (for-bank for-bank-0) (bank-conf-commit bank-conf-commit) (cost cost) (n n) (ncm ncm-0) (item item-0) (merc-conf merc-conf-0) (mtr mtr-0) (c c-0) (m m-0) (b b-0)) (precedes ((0 0) (2 0)) ((0 0) (3 0)) ((1 1) (2 2)) ((2 1) (1 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-ship c m b item mtr) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 guar-merc-4) (operation encryption-test (added-strand merc 2) (hash cost n) (1 0) (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost for-bank) (privk "sig" c)) for-bank)) (pubk "enc" b))) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account-0 bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-0 bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost for-bank) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost for-bank) (privk "sig" c)) for-bank)) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc n cost item-0 merc-conf-0 ncm-0 bank-conf-commit (sign (order c-0 m-0 b-0 cost for-bank-0) (privk "sig" c-0)) (pubk "enc" m-0))) (send (enc (payreq c-0 m-0 b-0 (hash cost n) (hash ncm-0 item-0 merc-conf-0) mtr-0 (cat (sign (order c-0 m-0 b-0 cost for-bank-0) (privk "sig" c-0)) for-bank-0)) (pubk "enc" b-0))))) (label 6) (parent 4) (unrealized (1 0) (2 0) (3 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay-rely-guar (vars (for-bank mesg) (account account-0 acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr merc-conf text) (c m b name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account-0) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 5 (for-bank for-bank) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (deflistener (cat cost n)) (precedes ((0 0) (2 0)) ((0 0) (3 0)) ((1 1) (2 2)) ((2 1) (1 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-ship c m b item mtr) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 guar-merc-4) (operation encryption-test (added-listener (cat cost n)) (hash cost n) (1 0) (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost for-bank) (privk "sig" c)) for-bank)) (pubk "enc" b))) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account-0 bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-0 bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost for-bank) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost for-bank) (privk "sig" c)) for-bank)) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (cat cost n)) (send (cat cost n)))) (label 7) (parent 4) (unrealized (1 0) (2 0) (3 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay-rely-guar (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr merc-conf text) (c m b name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 5 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (precedes ((0 0) (2 0)) ((1 1) (2 2)) ((2 1) (1 0)) ((2 3) (0 1)) ((2 4) (0 2))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-ship c m b item mtr) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 guar-merc-4) (operation encryption-test (contracted (account-0 account)) (hash n (hash ncb bank-conf)) (2 0) (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m))))) (label 8) (parent 5) (realized) (shape) (maps ((0) ((c c) (m m) (b b) (n n) (cost cost) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (account account) (ncb ncb) (ncm ncm)))) (origs (mtr (2 1)) (btr (1 1)) (n (0 0)))) (defskeleton minipay-rely-guar (vars (account account-0 acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr merc-conf text) (c m b name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account-0) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 5 (for-bank (enc n cost account-0 bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (deflistener (cat n (hash ncb bank-conf))) (precedes ((0 0) (3 0)) ((1 1) (2 2)) ((2 1) (1 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (2 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-ship c m b item mtr) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 guar-merc-4) (operation encryption-test (added-listener (cat n (hash ncb bank-conf))) (hash n (hash ncb bank-conf)) (2 0) (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account-0 bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-0 bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account-0 bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account-0 bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-0 bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (cat n (hash ncb bank-conf))) (send (cat n (hash ncb bank-conf))))) (label 9) (parent 5) (unrealized (2 0) (3 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay-rely-guar (vars (for-bank for-bank-0 bank-conf-commit mesg) (account acct) (cost amount) (n ncb ncm ncm-0 data) (item item-0 merchandise) (bank-conf btr mtr merc-conf merc-conf-0 mtr-0 text) (c m b c-0 m-0 b-0 name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 5 (for-bank for-bank) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 2 (for-bank for-bank-0) (bank-conf-commit bank-conf-commit) (cost cost) (n n) (ncm ncm-0) (item item-0) (merc-conf merc-conf-0) (mtr mtr-0) (c c-0) (m m-0) (b b-0)) (precedes ((0 0) (2 0)) ((0 0) (3 0)) ((1 1) (2 2)) ((2 1) (1 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-ship c m b item mtr) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 guar-merc-4) (operation encryption-test (displaced 4 0 cust 1) (sign (order c m b cost (enc n cost account-0 bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (1 0)) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost for-bank) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost for-bank) (privk "sig" c)) for-bank)) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc n cost item-0 merc-conf-0 ncm-0 bank-conf-commit (sign (order c-0 m-0 b-0 cost for-bank-0) (privk "sig" c-0)) (pubk "enc" m-0))) (send (enc (payreq c-0 m-0 b-0 (hash cost n) (hash ncm-0 item-0 merc-conf-0) mtr-0 (cat (sign (order c-0 m-0 b-0 cost for-bank-0) (privk "sig" c-0)) for-bank-0)) (pubk "enc" b-0))))) (label 10) (parent 6) (unrealized (1 0) (2 0) (3 0)) (comment "3 in cohort - 3 not yet seen")) (defskeleton minipay-rely-guar (vars (for-bank mesg) (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr merc-conf text) (c m b name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 5 (for-bank for-bank) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (deflistener (cat cost n)) (precedes ((0 0) (2 0)) ((0 0) (3 0)) ((1 1) (2 2)) ((2 1) (1 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-ship c m b item mtr) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 guar-merc-4) (operation encryption-test (displaced 4 0 cust 1) (sign (order c m b cost (enc n cost account-0 bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (1 0)) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost for-bank) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost for-bank) (privk "sig" c)) for-bank)) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (cat cost n)) (send (cat cost n)))) (label 11) (parent 7) (unrealized (1 0) (2 0) (3 0)) (comment "2 in cohort - 2 not yet seen")) (defskeleton minipay-rely-guar (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr merc-conf text) (c m b name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 5 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (deflistener (cat n (hash ncb bank-conf))) (precedes ((0 0) (3 0)) ((1 1) (2 2)) ((2 1) (1 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (2 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-ship c m b item mtr) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 guar-merc-4) (operation encryption-test (displaced 4 0 cust 1) (sign (order c m b cost (enc n cost account-0 bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (2 0)) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (cat n (hash ncb bank-conf))) (send (cat n (hash ncb bank-conf))))) (label 12) (parent 9) (unrealized (3 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay-rely-guar (vars (for-bank bank-conf-commit mesg) (account acct) (cost amount) (n ncb ncm ncm-0 data) (item item-0 merchandise) (bank-conf btr mtr merc-conf merc-conf-0 mtr-0 text) (c m b c-0 m-0 b-0 name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 5 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 2 (for-bank for-bank) (bank-conf-commit bank-conf-commit) (cost cost) (n n) (ncm ncm-0) (item item-0) (merc-conf merc-conf-0) (mtr mtr-0) (c c-0) (m m-0) (b b-0)) (precedes ((0 0) (2 0)) ((0 0) (3 0)) ((1 1) (2 2)) ((2 1) (1 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-ship c m b item mtr) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 guar-merc-4) (operation encryption-test (displaced 4 2 merc 2) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (1 0) (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc n cost item-0 merc-conf-0 ncm-0 bank-conf-commit (sign (order c-0 m-0 b-0 cost for-bank) (privk "sig" c-0)) (pubk "enc" m-0))) (send (enc (payreq c-0 m-0 b-0 (hash cost n) (hash ncm-0 item-0 merc-conf-0) mtr-0 (cat (sign (order c-0 m-0 b-0 cost for-bank) (privk "sig" c-0)) for-bank)) (pubk "enc" b-0))))) (label 13) (parent 10) (unrealized (3 0)) (comment "3 in cohort - 3 not yet seen")) (defskeleton minipay-rely-guar (vars (for-bank mesg) (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr merc-conf mtr-0 text) (c m b name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 5 (for-bank for-bank) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-0) (c c) (m m) (b b)) (precedes ((0 0) (2 0)) ((0 0) (3 0)) ((1 1) (2 2)) ((2 1) (1 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-ship c m b item mtr) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 guar-merc-4) (operation encryption-test (displaced 4 3 merc 2) (sign (order c-0 m-0 b-0 cost (enc n cost account bank-conf ncb (hash n (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b-0))) (privk "sig" c-0)) (1 0) (enc n cost item-0 merc-conf-0 ncm-0 (hash n (hash ncb bank-conf)) (sign (order c-0 m-0 b-0 cost (enc n cost account bank-conf ncb (hash n (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b-0))) (privk "sig" c-0)) (pubk "enc" m-0))) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost for-bank) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost for-bank) (privk "sig" c)) for-bank)) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))))) (label 14) (parent 10) (seen 15 17 19) (unrealized (1 0) (2 0)) (comment "3 in cohort - 0 not yet seen")) (defskeleton minipay-rely-guar (vars (for-bank for-bank-0 bank-conf-commit mesg) (account acct) (cost amount) (n ncb ncm ncm-0 data) (item item-0 merchandise) (bank-conf btr mtr merc-conf merc-conf-0 mtr-0 mtr-1 text) (c m b c-0 m-0 b-0 name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 5 (for-bank for-bank) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 2 (for-bank for-bank-0) (bank-conf-commit bank-conf-commit) (cost cost) (n n) (ncm ncm-0) (item item-0) (merc-conf merc-conf-0) (mtr mtr-0) (c c-0) (m m-0) (b b-0)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-1) (c c) (m m) (b b)) (precedes ((0 0) (2 0)) ((0 0) (3 0)) ((0 0) (4 0)) ((1 1) (2 2)) ((2 1) (1 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-ship c m b item mtr) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 guar-merc-4) (operation encryption-test (added-strand merc 2) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (1 0) (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost for-bank) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost for-bank) (privk "sig" c)) for-bank)) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc n cost item-0 merc-conf-0 ncm-0 bank-conf-commit (sign (order c-0 m-0 b-0 cost for-bank-0) (privk "sig" c-0)) (pubk "enc" m-0))) (send (enc (payreq c-0 m-0 b-0 (hash cost n) (hash ncm-0 item-0 merc-conf-0) mtr-0 (cat (sign (order c-0 m-0 b-0 cost for-bank-0) (privk "sig" c-0)) for-bank-0)) (pubk "enc" b-0)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-1 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))))) (label 15) (parent 10) (unrealized (1 0) (2 0) (3 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay-rely-guar (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr merc-conf text) (c m b name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 5 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (deflistener (cat cost n)) (precedes ((0 0) (2 0)) ((0 0) (3 0)) ((1 1) (2 2)) ((2 1) (1 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-ship c m b item mtr) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 guar-merc-4) (operation encryption-test (displaced 4 2 merc 2) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (1 0) (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (cat cost n)) (send (cat cost n)))) (label 16) (parent 11) (unrealized (3 0)) (comment "2 in cohort - 2 not yet seen")) (defskeleton minipay-rely-guar (vars (for-bank mesg) (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr merc-conf mtr-0 text) (c m b name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 5 (for-bank for-bank) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (deflistener (cat cost n)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-0) (c c) (m m) (b b)) (precedes ((0 0) (2 0)) ((0 0) (3 0)) ((0 0) (4 0)) ((1 1) (2 2)) ((2 1) (1 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-ship c m b item mtr) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 guar-merc-4) (operation encryption-test (added-strand merc 2) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (1 0) (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost for-bank) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost for-bank) (privk "sig" c)) for-bank)) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (cat cost n)) (send (cat cost n))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))))) (label 17) (parent 11) (unrealized (1 0) (2 0) (3 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay-rely-guar (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr merc-conf mtr-0 text) (c m b name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 5 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (deflistener (cat n (hash ncb bank-conf))) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-0) (c c) (m m) (b b)) (precedes ((0 0) (4 0)) ((1 1) (2 2)) ((2 1) (1 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (2 0)) ((4 1) (3 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-ship c m b item mtr) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 guar-merc-4) (operation nonce-test (added-strand merc 2) n (3 0) (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (cat n (hash ncb bank-conf))) (send (cat n (hash ncb bank-conf)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))))) (label 18) (parent 12) (unrealized (3 0)) (dead) (comment "empty cohort")) (defskeleton minipay-rely-guar (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr merc-conf mtr-0 text) (c m b name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 5 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-0) (c c) (m m) (b b)) (precedes ((0 0) (2 0)) ((0 0) (3 0)) ((1 1) (2 2)) ((2 1) (1 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-ship c m b item mtr) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 guar-merc-4) (operation nonce-test (contracted (c-0 c) (m-0 m) (b-0 b) (item-0 item) (merc-conf-0 merc-conf) (ncm-0 ncm) (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf)))) n (3 0) (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))))) (label 19) (parent 13) (seen 8) (realized) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay-rely-guar (vars (for-bank bank-conf-commit mesg) (account acct) (cost amount) (n ncb ncm ncm-0 data) (item item-0 merchandise) (bank-conf btr mtr merc-conf merc-conf-0 mtr-0 text) (c m b c-0 m-0 b-0 name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 5 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 2 (for-bank for-bank) (bank-conf-commit bank-conf-commit) (cost cost) (n n) (ncm ncm-0) (item item-0) (merc-conf merc-conf-0) (mtr mtr-0) (c c-0) (m m-0) (b b-0)) (precedes ((0 0) (2 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-ship c m b item mtr) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 guar-merc-4) (operation nonce-test (displaced 4 2 merc 2) n (3 0) (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc n cost item-0 merc-conf-0 ncm-0 bank-conf-commit (sign (order c-0 m-0 b-0 cost for-bank) (privk "sig" c-0)) (pubk "enc" m-0))) (send (enc (payreq c-0 m-0 b-0 (hash cost n) (hash ncm-0 item-0 merc-conf-0) mtr-0 (cat (sign (order c-0 m-0 b-0 cost for-bank) (privk "sig" c-0)) for-bank)) (pubk "enc" b-0))))) (label 20) (parent 13) (unrealized (3 0)) (comment "2 in cohort - 2 not yet seen")) (defskeleton minipay-rely-guar (vars (for-bank bank-conf-commit mesg) (account acct) (cost amount) (n ncb ncm ncm-0 data) (item item-0 merchandise) (bank-conf btr mtr merc-conf merc-conf-0 mtr-0 mtr-1 text) (c m b c-0 m-0 b-0 name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 5 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 2 (for-bank for-bank) (bank-conf-commit bank-conf-commit) (cost cost) (n n) (ncm ncm-0) (item item-0) (merc-conf merc-conf-0) (mtr mtr-0) (c c-0) (m m-0) (b b-0)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-1) (c c) (m m) (b b)) (precedes ((0 0) (2 0)) ((0 0) (4 0)) ((1 1) (2 2)) ((2 1) (1 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (3 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-ship c m b item mtr) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 guar-merc-4) (operation nonce-test (added-strand merc 2) n (3 0) (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc n cost item-0 merc-conf-0 ncm-0 bank-conf-commit (sign (order c-0 m-0 b-0 cost for-bank) (privk "sig" c-0)) (pubk "enc" m-0))) (send (enc (payreq c-0 m-0 b-0 (hash cost n) (hash ncm-0 item-0 merc-conf-0) mtr-0 (cat (sign (order c-0 m-0 b-0 cost for-bank) (privk "sig" c-0)) for-bank)) (pubk "enc" b-0)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-1 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))))) (label 21) (parent 13) (seen 27) (unrealized (3 0)) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay-rely-guar (vars (for-bank bank-conf-commit mesg) (account acct) (cost amount) (n ncb ncm ncm-0 data) (item item-0 merchandise) (bank-conf btr mtr merc-conf merc-conf-0 mtr-0 mtr-1 text) (c m b c-0 m-0 b-0 name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 5 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 2 (for-bank for-bank) (bank-conf-commit bank-conf-commit) (cost cost) (n n) (ncm ncm-0) (item item-0) (merc-conf merc-conf-0) (mtr mtr-0) (c c-0) (m m-0) (b b-0)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-1) (c c) (m m) (b b)) (precedes ((0 0) (2 0)) ((0 0) (3 0)) ((0 0) (4 0)) ((1 1) (2 2)) ((2 1) (1 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-ship c m b item mtr) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 guar-merc-4) (operation encryption-test (displaced 5 2 merc 2) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (1 0) (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)) (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-1 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc n cost item-0 merc-conf-0 ncm-0 bank-conf-commit (sign (order c-0 m-0 b-0 cost for-bank) (privk "sig" c-0)) (pubk "enc" m-0))) (send (enc (payreq c-0 m-0 b-0 (hash cost n) (hash ncm-0 item-0 merc-conf-0) mtr-0 (cat (sign (order c-0 m-0 b-0 cost for-bank) (privk "sig" c-0)) for-bank)) (pubk "enc" b-0)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-1 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))))) (label 22) (parent 15) (seen 21) (unrealized (3 0)) (comment "3 in cohort - 2 not yet seen")) (defskeleton minipay-rely-guar (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr merc-conf text) (c m b name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 5 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (deflistener (cat cost n)) (precedes ((0 0) (2 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-ship c m b item mtr) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 guar-merc-4) (operation nonce-test (displaced 4 2 merc 2) n (3 0) (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (cat cost n)) (send (cat cost n)))) (label 23) (parent 16) (unrealized (3 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay-rely-guar (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr merc-conf mtr-0 text) (c m b name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 5 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (deflistener (cat cost n)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-0) (c c) (m m) (b b)) (precedes ((0 0) (2 0)) ((0 0) (4 0)) ((1 1) (2 2)) ((2 1) (1 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (3 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-ship c m b item mtr) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 guar-merc-4) (operation nonce-test (added-strand merc 2) n (3 0) (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (cat cost n)) (send (cat cost n))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))))) (label 24) (parent 16) (seen 30) (unrealized (3 0)) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay-rely-guar (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr merc-conf mtr-0 text) (c m b name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 5 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (deflistener (cat cost n)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-0) (c c) (m m) (b b)) (precedes ((0 0) (2 0)) ((0 0) (3 0)) ((0 0) (4 0)) ((1 1) (2 2)) ((2 1) (1 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-ship c m b item mtr) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 guar-merc-4) (operation encryption-test (displaced 5 2 merc 2) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (1 0) (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)) (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (cat cost n)) (send (cat cost n))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))))) (label 25) (parent 17) (seen 24) (unrealized (3 0)) (comment "3 in cohort - 2 not yet seen")) (defskeleton minipay-rely-guar (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr merc-conf mtr-0 text) (c m b name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 5 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-0) (c c) (m m) (b b)) (precedes ((0 0) (2 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-ship c m b item mtr) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 guar-merc-4) (operation nonce-test (contracted (c-0 c) (m-0 m) (b-0 b) (item-0 item) (merc-conf-0 merc-conf) (ncm-0 ncm) (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf)))) n (3 0) (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)) (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))))) (label 26) (parent 20) (seen 8) (realized) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay-rely-guar (vars (for-bank bank-conf-commit mesg) (account acct) (cost amount) (n ncb ncm ncm-0 data) (item item-0 merchandise) (bank-conf btr mtr merc-conf merc-conf-0 mtr-0 mtr-1 text) (c m b c-0 m-0 b-0 name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 5 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 2 (for-bank for-bank) (bank-conf-commit bank-conf-commit) (cost cost) (n n) (ncm ncm-0) (item item-0) (merc-conf merc-conf-0) (mtr mtr-0) (c c-0) (m m-0) (b b-0)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-1) (c c) (m m) (b b)) (precedes ((0 0) (2 0)) ((0 0) (4 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (3 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-ship c m b item mtr) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 guar-merc-4) (operation nonce-test (added-strand merc 2) n (3 0) (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)) (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc n cost item-0 merc-conf-0 ncm-0 bank-conf-commit (sign (order c-0 m-0 b-0 cost for-bank) (privk "sig" c-0)) (pubk "enc" m-0))) (send (enc (payreq c-0 m-0 b-0 (hash cost n) (hash ncm-0 item-0 merc-conf-0) mtr-0 (cat (sign (order c-0 m-0 b-0 cost for-bank) (privk "sig" c-0)) for-bank)) (pubk "enc" b-0)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-1 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))))) (label 27) (parent 20) (unrealized (3 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay-rely-guar (vars (for-bank bank-conf-commit mesg) (account acct) (cost amount) (n ncb ncm ncm-0 data) (item item-0 merchandise) (bank-conf btr mtr merc-conf merc-conf-0 mtr-0 mtr-1 text) (c m b c-0 m-0 b-0 name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 5 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 2 (for-bank for-bank) (bank-conf-commit bank-conf-commit) (cost cost) (n n) (ncm ncm-0) (item item-0) (merc-conf merc-conf-0) (mtr mtr-0) (c c-0) (m m-0) (b b-0)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-1) (c c) (m m) (b b)) (precedes ((0 0) (2 0)) ((0 0) (4 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-ship c m b item mtr) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 guar-merc-4) (operation nonce-test (displaced 5 2 merc 2) n (3 0) (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc n cost item-0 merc-conf-0 ncm-0 bank-conf-commit (sign (order c-0 m-0 b-0 cost for-bank) (privk "sig" c-0)) (pubk "enc" m-0))) (send (enc (payreq c-0 m-0 b-0 (hash cost n) (hash ncm-0 item-0 merc-conf-0) mtr-0 (cat (sign (order c-0 m-0 b-0 cost for-bank) (privk "sig" c-0)) for-bank)) (pubk "enc" b-0)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-1 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))))) (label 28) (parent 22) (seen 27) (unrealized (3 0)) (comment "3 in cohort - 2 not yet seen")) (defskeleton minipay-rely-guar (vars (for-bank bank-conf-commit mesg) (account acct) (cost amount) (n ncb ncm ncm-0 data) (item item-0 merchandise) (bank-conf btr mtr merc-conf merc-conf-0 mtr-0 mtr-1 mtr-2 text) (c m b c-0 m-0 b-0 name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 5 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 2 (for-bank for-bank) (bank-conf-commit bank-conf-commit) (cost cost) (n n) (ncm ncm-0) (item item-0) (merc-conf merc-conf-0) (mtr mtr-0) (c c-0) (m m-0) (b b-0)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-1) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-2) (c c) (m m) (b b)) (precedes ((0 0) (2 0)) ((0 0) (4 0)) ((0 0) (5 0)) ((1 1) (2 2)) ((2 1) (1 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (3 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 mtr-1 mtr-2) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-ship c m b item mtr) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 guar-merc-4) (operation nonce-test (added-strand merc 2) n (3 0) (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc n cost item-0 merc-conf-0 ncm-0 bank-conf-commit (sign (order c-0 m-0 b-0 cost for-bank) (privk "sig" c-0)) (pubk "enc" m-0))) (send (enc (payreq c-0 m-0 b-0 (hash cost n) (hash ncm-0 item-0 merc-conf-0) mtr-0 (cat (sign (order c-0 m-0 b-0 cost for-bank) (privk "sig" c-0)) for-bank)) (pubk "enc" b-0)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-1 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-2 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))))) (label 29) (parent 22) (seen 35) (unrealized (3 0)) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay-rely-guar (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr merc-conf mtr-0 text) (c m b name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 5 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (deflistener (cat cost n)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-0) (c c) (m m) (b b)) (precedes ((0 0) (2 0)) ((0 0) (4 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (3 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-ship c m b item mtr) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 guar-merc-4) (operation nonce-test (added-strand merc 2) n (3 0) (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)) (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (cat cost n)) (send (cat cost n))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))))) (label 30) (parent 23) (unrealized (3 0)) (dead) (comment "empty cohort")) (defskeleton minipay-rely-guar (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr merc-conf mtr-0 text) (c m b name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 5 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (deflistener (cat cost n)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-0) (c c) (m m) (b b)) (precedes ((0 0) (2 0)) ((0 0) (4 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-ship c m b item mtr) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 guar-merc-4) (operation nonce-test (displaced 5 2 merc 2) n (3 0) (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (cat cost n)) (send (cat cost n))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))))) (label 31) (parent 25) (seen 30) (unrealized (3 0)) (comment "2 in cohort - 1 not yet seen")) (defskeleton minipay-rely-guar (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr merc-conf mtr-0 mtr-1 text) (c m b name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 5 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (deflistener (cat cost n)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-0) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-1) (c c) (m m) (b b)) (precedes ((0 0) (2 0)) ((0 0) (4 0)) ((0 0) (5 0)) ((1 1) (2 2)) ((2 1) (1 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (3 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-ship c m b item mtr) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 guar-merc-4) (operation nonce-test (added-strand merc 2) n (3 0) (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (cat cost n)) (send (cat cost n))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-1 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))))) (label 32) (parent 25) (seen 36) (unrealized (3 0)) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay-rely-guar (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr merc-conf mtr-0 mtr-1 text) (c m b name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 5 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-0) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-1) (c c) (m m) (b b)) (precedes ((0 0) (2 0)) ((0 0) (4 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (3 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-ship c m b item mtr) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 guar-merc-4) (operation nonce-test (contracted (c-0 c) (m-0 m) (b-0 b) (item-0 item) (merc-conf-0 merc-conf) (ncm-0 ncm) (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf)))) n (3 0) (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)) (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b)) (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-1 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-1 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))))) (label 33) (parent 27) (seen 19) (realized) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay-rely-guar (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr merc-conf mtr-0 mtr-1 text) (c m b name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 5 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-0) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-1) (c c) (m m) (b b)) (precedes ((0 0) (2 0)) ((0 0) (4 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-ship c m b item mtr) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 guar-merc-4) (operation nonce-test (contracted (c-0 c) (m-0 m) (b-0 b) (item-0 item) (merc-conf-0 merc-conf) (ncm-0 ncm) (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf)))) n (3 0) (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)) (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-1 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))))) (label 34) (parent 28) (seen 19) (realized) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay-rely-guar (vars (for-bank bank-conf-commit mesg) (account acct) (cost amount) (n ncb ncm ncm-0 data) (item item-0 merchandise) (bank-conf btr mtr merc-conf merc-conf-0 mtr-0 mtr-1 mtr-2 text) (c m b c-0 m-0 b-0 name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 5 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 2 (for-bank for-bank) (bank-conf-commit bank-conf-commit) (cost cost) (n n) (ncm ncm-0) (item item-0) (merc-conf merc-conf-0) (mtr mtr-0) (c c-0) (m m-0) (b b-0)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-1) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-2) (c c) (m m) (b b)) (precedes ((0 0) (2 0)) ((0 0) (4 0)) ((0 0) (5 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (3 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 mtr-1 mtr-2) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-ship c m b item mtr) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 guar-merc-4) (operation nonce-test (added-strand merc 2) n (3 0) (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)) (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc n cost item-0 merc-conf-0 ncm-0 bank-conf-commit (sign (order c-0 m-0 b-0 cost for-bank) (privk "sig" c-0)) (pubk "enc" m-0))) (send (enc (payreq c-0 m-0 b-0 (hash cost n) (hash ncm-0 item-0 merc-conf-0) mtr-0 (cat (sign (order c-0 m-0 b-0 cost for-bank) (privk "sig" c-0)) for-bank)) (pubk "enc" b-0)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-1 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-2 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))))) (label 35) (parent 28) (unrealized (3 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay-rely-guar (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr merc-conf mtr-0 mtr-1 text) (c m b name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 5 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (deflistener (cat cost n)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-0) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-1) (c c) (m m) (b b)) (precedes ((0 0) (2 0)) ((0 0) (4 0)) ((0 0) (5 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (3 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-ship c m b item mtr) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 guar-merc-4) (operation nonce-test (added-strand merc 2) n (3 0) (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)) (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (cat cost n)) (send (cat cost n))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-1 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))))) (label 36) (parent 31) (unrealized (3 0)) (dead) (comment "empty cohort")) (defskeleton minipay-rely-guar (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr merc-conf mtr-0 mtr-1 mtr-2 text) (c m b name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 5 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-0) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-1) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-2) (c c) (m m) (b b)) (precedes ((0 0) (2 0)) ((0 0) (4 0)) ((0 0) (5 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (3 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 mtr-1 mtr-2) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-ship c m b item mtr) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 guar-merc-4) (operation nonce-test (contracted (c-0 c) (m-0 m) (b-0 b) (item-0 item) (merc-conf-0 merc-conf) (ncm-0 ncm) (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf)))) n (3 0) (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)) (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b)) (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-2 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-1 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-2 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))))) (label 37) (parent 35) (realized) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay-rely-guar (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr merc-conf mtr-0 mtr-1 text) (c m b name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 5 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-0) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-1) (c c) (m m) (b b)) (precedes ((0 0) (2 0)) ((0 0) (3 0)) ((0 0) (4 0)) ((1 1) (2 2)) ((2 1) (1 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-ship c m b item mtr) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 guar-merc-4) (operation generalization deleted (3 0)) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-1 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))))) (label 38) (parent 37) (seen 19) (realized) (comment "1 in cohort - 0 not yet seen")) (comment "Nothing left to do") (defprotocol minipay-rely-guar basic (defrole cust (vars (c m b name) (cost amount) (item merchandise) (merc-conf bank-conf btr mtr text) (account acct) (n ncb ncm data)) (trace (send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) (facts (neq n ncb) (neq n ncm) (neq ncm ncb))) (defrole merc (vars (c m b name) (cost amount) (item merchandise) (merc-conf btr mtr text) (n ncm data) (for-bank bank-conf-commit bank-conf-decommit mesg)) (trace (recv (enc n cost item merc-conf ncm bank-conf-commit (sign (order c m b cost for-bank) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost for-bank) (privk "sig" c)) for-bank)) (pubk "enc" b))) (recv (enc bank-conf-decommit (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n bank-conf-decommit)) btr mtr) (privk "sig" m)))) (uniq-orig mtr)) (defrole bank (vars (c m b name) (cost amount) (bank-conf btr mtr text) (merc-conf-decommit mesg) (account acct) (n ncb data)) (trace (recv (enc (payreq c m b (hash cost n) merc-conf-decommit mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n merc-conf-decommit) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n merc-conf-decommit) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n merc-conf-decommit)) btr mtr) (privk "sig" b)) (pubk "enc" m)))) (uniq-orig btr)) (defrule rely-cust-3 (forall ((z strd) (mtr text) (item merchandise) (b m c name)) (implies (and (p "cust" z (idx 3)) (p "cust" "mtr" z mtr) (p "cust" "item" z item) (p "cust" "b" z b) (p "cust" "m" z m) (p "cust" "c" z c)) (fact will-ship c m b item mtr)))) (defrule rely-cust-2 (forall ((z strd) (btr mtr text) (n data) (cost amount) (b m c name)) (implies (and (p "cust" z (idx 2)) (p "cust" "btr" z btr) (p "cust" "mtr" z mtr) (p "cust" "n" z n) (p "cust" "cost" z cost) (p "cust" "b" z b) (p "cust" "m" z m) (p "cust" "c" z c)) (fact will-transfer c m b cost n mtr btr)))) (defrule rely-merc-3 (forall ((z strd) (n data) (cost amount) (item merchandise) (b m c name) (btr mtr text)) (implies (and (p "merc" z (idx 3)) (p "merc" "n" z n) (p "merc" "cost" z cost) (p "merc" "item" z item) (p "merc" "b" z b) (p "merc" "m" z m) (p "merc" "c" z c) (p "merc" "btr" z btr) (p "merc" "mtr" z mtr)) (and (fact buy-via c m b item cost n) (fact will-transfer c m b cost n mtr btr))))) (defrule rely-bank-1 (forall ((z strd) (n data) (cost amount) (b m c name)) (implies (and (p "bank" z (idx 1)) (p "bank" "n" z n) (p "bank" "cost" z cost) (p "bank" "b" z b) (p "bank" "m" z m) (p "bank" "c" z c)) (exists ((item merchandise)) (fact buy-via c m b item cost n))))) (defrule guar-cust-1 (forall ((z strd) (n data) (cost amount) (item merchandise) (b m c name)) (implies (and (p "cust" z (idx 1)) (p "cust" "n" z n) (p "cust" "cost" z cost) (p "cust" "item" z item) (p "cust" "b" z b) (p "cust" "m" z m) (p "cust" "c" z c)) (fact buy-via c m b item cost n)))) (defrule guar-merc-4 (forall ((z strd) (mtr text) (item merchandise) (b m c name)) (implies (and (p "merc" z (idx 4)) (p "merc" "mtr" z mtr) (p "merc" "item" z item) (p "merc" "b" z b) (p "merc" "m" z m) (p "merc" "c" z c)) (fact will-ship c m b item mtr)))) (defrule guar-bank-2 (forall ((z strd) (btr mtr text) (n data) (cost amount) (c b m name)) (implies (and (p "bank" z (idx 2)) (p "bank" "btr" z btr) (p "bank" "mtr" z mtr) (p "bank" "n" z n) (p "bank" "cost" z cost) (p "bank" "c" z c) (p "bank" "b" z b) (p "bank" "m" z m)) (and (non (privk "sig" c)) (fact will-transfer c m b cost n mtr btr))))) (defrule cheq-merc-4 (forall ((z strd) (n data) (bank-conf-decommit bank-conf-commit mesg)) (implies (and (p "merc" z (idx 4)) (p "merc" "n" z n) (p "merc" "bank-conf-decommit" z bank-conf-decommit) (p "merc" "bank-conf-commit" z bank-conf-commit)) (= bank-conf-commit (hash n bank-conf-decommit))))) (defgenrule neqRl_indx (forall ((x indx)) (implies (fact neq x x) (false)))) (defgenrule neqRl_strd (forall ((x strd)) (implies (fact neq x x) (false)))) (defgenrule neqRl_mesg (forall ((x mesg)) (implies (fact neq x x) (false)))) (defgenrule fact-cust-neq2 (forall ((z strd) (ncb n data)) (implies (and (p "cust" z (idx 1)) (p "cust" "ncb" z ncb) (p "cust" "n" z n)) (fact neq n ncb)))) (defgenrule fact-cust-neq1 (forall ((z strd) (ncm n data)) (implies (and (p "cust" z (idx 1)) (p "cust" "ncm" z ncm) (p "cust" "n" z n)) (fact neq n ncm)))) (defgenrule fact-cust-neq0 (forall ((z strd) (ncb ncm data)) (implies (and (p "cust" z (idx 1)) (p "cust" "ncb" z ncb) (p "cust" "ncm" z ncm)) (fact neq ncm ncb)))) (lang (acct atom) (amount atom) (merchandise atom) (sign sign) (order (tuple 5)) (bconf (tuple 3)) (mconf (tuple 3)) (payreq (tuple 7)))) (defskeleton minipay-rely-guar (vars (for-bank bank-conf-commit bank-conf-decommit mesg) (cost amount) (n ncm data) (item merchandise) (merc-conf btr mtr text) (c m b name)) (defstrand merc 3 (for-bank for-bank) (bank-conf-commit bank-conf-commit) (bank-conf-decommit bank-conf-decommit) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig mtr) (traces ((recv (enc n cost item merc-conf ncm bank-conf-commit (sign (order c m b cost for-bank) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost for-bank) (privk "sig" c)) for-bank)) (pubk "enc" b))) (recv (enc bank-conf-decommit (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))))) (label 39) (unrealized (0 2)) (origs (mtr (0 1))) (comment "Not closed under rules")) (defskeleton minipay-rely-guar (vars (for-bank bank-conf-commit bank-conf-decommit mesg) (cost amount) (n ncm data) (item merchandise) (merc-conf btr mtr text) (c m b name)) (defstrand merc 3 (for-bank for-bank) (bank-conf-commit bank-conf-commit) (bank-conf-decommit bank-conf-decommit) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig mtr) (facts (will-transfer c m b cost n mtr btr) (buy-via c m b item cost n)) (rule rely-merc-3) (traces ((recv (enc n cost item merc-conf ncm bank-conf-commit (sign (order c m b cost for-bank) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost for-bank) (privk "sig" c)) for-bank)) (pubk "enc" b))) (recv (enc bank-conf-decommit (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))))) (label 40) (parent 39) (unrealized (0 2)) (origs (mtr (0 1))) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay-rely-guar (vars (for-bank bank-conf-commit bank-conf-decommit mesg) (account acct) (cost amount) (n ncm ncb data) (item merchandise) (merc-conf btr mtr bank-conf text) (c m b name)) (defstrand merc 3 (for-bank for-bank) (bank-conf-commit bank-conf-commit) (bank-conf-decommit bank-conf-decommit) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (precedes ((0 1) (1 0)) ((1 1) (0 2))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig btr mtr) (facts (buy-via c m b item cost n) (will-transfer c m b cost n mtr btr)) (rule guar-bank-2 rely-merc-3) (operation encryption-test (added-strand bank 2) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (0 2)) (traces ((recv (enc n cost item merc-conf ncm bank-conf-commit (sign (order c m b cost for-bank) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost for-bank) (privk "sig" c)) for-bank)) (pubk "enc" b))) (recv (enc bank-conf-decommit (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))))) (label 41) (parent 40) (unrealized (0 0) (0 2) (1 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay-rely-guar (vars (bank-conf-commit bank-conf-decommit mesg) (account account-0 acct) (cost amount) (n ncm ncb n-0 ncb-0 ncm-0 data) (item item-0 merchandise) (merc-conf btr mtr bank-conf merc-conf-0 bank-conf-0 text) (c m b name)) (defstrand merc 3 (for-bank (enc n-0 cost account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit) (bank-conf-decommit bank-conf-decommit) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account-0) (cost cost) (n n-0) (ncb ncb-0) (ncm ncm-0) (item item-0) (merc-conf merc-conf-0) (bank-conf bank-conf-0) (c c) (m m) (b b)) (precedes ((0 1) (1 0)) ((1 1) (0 2)) ((2 0) (0 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig btr mtr) (facts (neq n-0 ncb-0) (neq n-0 ncm-0) (neq ncm-0 ncb-0) (buy-via c m b item cost n) (buy-via c m b item-0 cost n-0) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 rely-merc-3) (operation encryption-test (added-strand cust 1) (sign (order c m b cost (enc n-0 cost account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (0 0)) (traces ((recv (enc n cost item merc-conf ncm bank-conf-commit (sign (order c m b cost (enc n-0 cost account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n-0 cost account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (enc n-0 cost account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n-0 cost item-0 merc-conf-0 ncm-0 (hash n-0 (hash ncb-0 bank-conf-0)) (sign (order c m b cost (enc n-0 cost account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))))) (label 42) (parent 41) (unrealized (0 0) (0 2) (1 0)) (comment "2 in cohort - 2 not yet seen")) (defskeleton minipay-rely-guar (vars (bank-conf-decommit mesg) (account account-0 acct) (cost amount) (ncb n ncb-0 ncm data) (item merchandise) (btr mtr bank-conf merc-conf bank-conf-0 text) (c m b name)) (defstrand merc 3 (for-bank (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb-0 bank-conf-0))) (bank-conf-decommit bank-conf-decommit) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account-0) (cost cost) (n n) (ncb ncb-0) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf-0) (c c) (m m) (b b)) (precedes ((0 1) (1 0)) ((1 1) (0 2)) ((2 0) (0 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig btr mtr) (facts (neq n ncb-0) (neq n ncm) (neq ncm ncb-0) (buy-via c m b item cost n) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1) (operation encryption-test (contracted (item-0 item) (merc-conf-0 merc-conf) (n-0 n) (ncm-0 ncm) (bank-conf-commit (hash n (hash ncb-0 bank-conf-0)))) (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (0 0) (enc n cost item merc-conf ncm (hash n (hash ncb-0 bank-conf-0)) (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (traces ((recv (enc n cost item merc-conf ncm (hash n (hash ncb-0 bank-conf-0)) (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb-0 bank-conf-0)) (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))))) (label 43) (parent 42) (unrealized (0 2) (1 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay-rely-guar (vars (bank-conf-commit bank-conf-decommit mesg) (account account-0 acct) (cost amount) (n ncm ncb n-0 ncb-0 ncm-0 data) (item item-0 merchandise) (merc-conf btr mtr bank-conf merc-conf-0 bank-conf-0 mtr-0 text) (c m b name)) (defstrand merc 3 (for-bank (enc n-0 cost account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit) (bank-conf-decommit bank-conf-decommit) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account-0) (cost cost) (n n-0) (ncb ncb-0) (ncm ncm-0) (item item-0) (merc-conf merc-conf-0) (bank-conf bank-conf-0) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n-0 cost account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (bank-conf-commit (hash n-0 (hash ncb-0 bank-conf-0))) (cost cost) (n n-0) (ncm ncm-0) (item item-0) (merc-conf merc-conf-0) (mtr mtr-0) (c c) (m m) (b b)) (precedes ((0 1) (1 0)) ((1 1) (0 2)) ((2 0) (0 0)) ((3 1) (0 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig btr mtr mtr-0) (facts (neq n-0 ncb-0) (neq n-0 ncm-0) (neq ncm-0 ncb-0) (buy-via c m b item cost n) (buy-via c m b item-0 cost n-0) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 rely-merc-3) (operation encryption-test (added-strand merc 2) (sign (order c m b cost (enc n-0 cost account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (0 0) (enc n-0 cost item-0 merc-conf-0 ncm-0 (hash n-0 (hash ncb-0 bank-conf-0)) (sign (order c m b cost (enc n-0 cost account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (traces ((recv (enc n cost item merc-conf ncm bank-conf-commit (sign (order c m b cost (enc n-0 cost account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n-0 cost account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (enc n-0 cost account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n-0 cost item-0 merc-conf-0 ncm-0 (hash n-0 (hash ncb-0 bank-conf-0)) (sign (order c m b cost (enc n-0 cost account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n-0 cost item-0 merc-conf-0 ncm-0 (hash n-0 (hash ncb-0 bank-conf-0)) (sign (order c m b cost (enc n-0 cost account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n-0) (hash ncm-0 item-0 merc-conf-0) mtr-0 (cat (sign (order c m b cost (enc n-0 cost account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (enc n-0 cost account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b)))) (pubk "enc" b))))) (label 44) (parent 42) (unrealized (0 0) (0 2) (1 0) (3 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay-rely-guar (vars (account account-0 acct) (cost amount) (ncb n ncb-0 ncm data) (item merchandise) (btr mtr bank-conf merc-conf bank-conf-0 text) (c m b name)) (defstrand merc 3 (for-bank (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb-0 bank-conf-0))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account-0) (cost cost) (n n) (ncb ncb-0) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf-0) (c c) (m m) (b b)) (precedes ((0 1) (1 0)) ((1 1) (0 2)) ((2 0) (0 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig btr mtr) (facts (neq n ncb-0) (neq n ncm) (neq ncm ncb-0) (buy-via c m b item cost n) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1) (operation encryption-test (contracted (bank-conf-decommit (hash ncb bank-conf))) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (0 2) (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (traces ((recv (enc n cost item merc-conf ncm (hash n (hash ncb-0 bank-conf-0)) (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb-0 bank-conf-0)) (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))))) (label 45) (parent 43) (unrealized (1 0)) (comment "2 in cohort - 2 not yet seen")) (defskeleton minipay-rely-guar (vars (bank-conf-decommit mesg) (account account-0 acct) (cost amount) (ncb n ncb-0 ncm data) (item merchandise) (btr mtr bank-conf merc-conf bank-conf-0 mtr-0 text) (c m b name)) (defstrand merc 3 (for-bank (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb-0 bank-conf-0))) (bank-conf-decommit bank-conf-decommit) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account-0) (cost cost) (n n) (ncb ncb-0) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf-0) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb-0 bank-conf-0))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-0) (c c) (m m) (b b)) (precedes ((0 1) (1 0)) ((1 1) (0 2)) ((2 0) (0 0)) ((3 1) (0 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig btr mtr mtr-0) (facts (neq n ncb-0) (neq n ncm) (neq ncm ncb-0) (buy-via c m b item cost n) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1) (operation encryption-test (contracted (item-0 item) (merc-conf-0 merc-conf) (n-0 n) (ncm-0 ncm) (bank-conf-commit (hash n (hash ncb-0 bank-conf-0)))) (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (0 0) (enc n cost item merc-conf ncm (hash n (hash ncb-0 bank-conf-0)) (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)) (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (traces ((recv (enc n cost item merc-conf ncm (hash n (hash ncb-0 bank-conf-0)) (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb-0 bank-conf-0)) (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb-0 bank-conf-0)) (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))))) (label 46) (parent 44) (unrealized (0 2) (1 0) (3 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay-rely-guar (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (btr mtr merc-conf bank-conf text) (c m b name)) (defstrand merc 3 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (precedes ((0 1) (1 0)) ((1 1) (0 2)) ((2 0) (0 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig btr mtr) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1) (operation encryption-test (displaced 3 2 cust 1) (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (1 0)) (traces ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))))) (label 47) (parent 45) (realized) (shape) (maps ((0) ((c c) (m m) (b b) (cost cost) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (n n) (ncm ncm) (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf))))) (origs (btr (1 1)) (mtr (0 1)))) (defskeleton minipay-rely-guar (vars (account account-0 acct) (cost amount) (ncb n ncb-0 ncm data) (item merchandise) (btr mtr bank-conf merc-conf bank-conf-0 text) (c m b name)) (defstrand merc 3 (for-bank (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb-0 bank-conf-0))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account-0) (cost cost) (n n) (ncb ncb-0) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf-0) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (precedes ((0 1) (1 0)) ((1 1) (0 2)) ((2 0) (0 0)) ((3 0) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig btr mtr) (facts (neq n ncb) (neq n ncb-0) (neq n ncm) (neq ncm ncb) (neq ncm ncb-0) (buy-via c m b item cost n) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1) (operation encryption-test (added-strand cust 1) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (1 0)) (traces ((recv (enc n cost item merc-conf ncm (hash n (hash ncb-0 bank-conf-0)) (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb-0 bank-conf-0)) (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))))) (label 48) (parent 45) (unrealized (1 0)) (comment "2 in cohort - 2 not yet seen")) (defskeleton minipay-rely-guar (vars (account account-0 acct) (cost amount) (ncb n ncb-0 ncm data) (item merchandise) (btr mtr bank-conf merc-conf bank-conf-0 mtr-0 text) (c m b name)) (defstrand merc 3 (for-bank (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb-0 bank-conf-0))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account-0) (cost cost) (n n) (ncb ncb-0) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf-0) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb-0 bank-conf-0))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-0) (c c) (m m) (b b)) (precedes ((0 1) (1 0)) ((1 1) (0 2)) ((2 0) (0 0)) ((3 1) (0 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig btr mtr mtr-0) (facts (neq n ncb-0) (neq n ncm) (neq ncm ncb-0) (buy-via c m b item cost n) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1) (operation encryption-test (contracted (bank-conf-decommit (hash ncb bank-conf))) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (0 2) (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (traces ((recv (enc n cost item merc-conf ncm (hash n (hash ncb-0 bank-conf-0)) (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb-0 bank-conf-0)) (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb-0 bank-conf-0)) (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))))) (label 49) (parent 46) (unrealized (1 0) (3 0)) (comment "2 in cohort - 2 not yet seen")) (defskeleton minipay-rely-guar (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (btr mtr merc-conf bank-conf text) (c m b name)) (defstrand merc 3 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (precedes ((0 1) (1 0)) ((1 1) (0 2)) ((2 0) (0 0)) ((3 0) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig btr mtr) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1) (operation encryption-test (displaced 4 0 merc 2) (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (1 0) (enc n cost item merc-conf ncm (hash n (hash ncb-0 bank-conf-0)) (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (traces ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))))) (label 50) (parent 48) (seen 47) (realized) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay-rely-guar (vars (account account-0 acct) (cost amount) (ncb n ncb-0 ncm data) (item merchandise) (btr mtr bank-conf merc-conf bank-conf-0 mtr-0 text) (c m b name)) (defstrand merc 3 (for-bank (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb-0 bank-conf-0))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account-0) (cost cost) (n n) (ncb ncb-0) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf-0) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-0) (c c) (m m) (b b)) (precedes ((0 1) (1 0)) ((1 1) (0 2)) ((2 0) (0 0)) ((3 0) (1 0)) ((4 1) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig btr mtr mtr-0) (facts (neq n ncb) (neq n ncb-0) (neq n ncm) (neq ncm ncb) (neq ncm ncb-0) (buy-via c m b item cost n) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1) (operation encryption-test (added-strand merc 2) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (1 0) (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (traces ((recv (enc n cost item merc-conf ncm (hash n (hash ncb-0 bank-conf-0)) (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb-0 bank-conf-0)) (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))))) (label 51) (parent 48) (unrealized (1 0) (4 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay-rely-guar (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (btr mtr merc-conf bank-conf mtr-0 text) (c m b name)) (defstrand merc 3 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-0) (c c) (m m) (b b)) (precedes ((0 1) (1 0)) ((1 1) (0 2)) ((2 0) (0 0)) ((3 1) (0 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1) (operation encryption-test (displaced 4 2 cust 1) (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (1 0)) (traces ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))))) (label 52) (parent 49) (unrealized (3 0)) (comment "2 in cohort - 2 not yet seen")) (defskeleton minipay-rely-guar (vars (account account-0 acct) (cost amount) (ncb n ncb-0 ncm data) (item merchandise) (btr mtr bank-conf merc-conf bank-conf-0 mtr-0 text) (c m b name)) (defstrand merc 3 (for-bank (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb-0 bank-conf-0))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account-0) (cost cost) (n n) (ncb ncb-0) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf-0) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb-0 bank-conf-0))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-0) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (precedes ((0 1) (1 0)) ((1 1) (0 2)) ((2 0) (0 0)) ((3 1) (0 0)) ((4 0) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig btr mtr mtr-0) (facts (neq n ncb) (neq n ncb-0) (neq n ncm) (neq ncm ncb) (neq ncm ncb-0) (buy-via c m b item cost n) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1) (operation encryption-test (added-strand cust 1) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (1 0)) (traces ((recv (enc n cost item merc-conf ncm (hash n (hash ncb-0 bank-conf-0)) (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb-0 bank-conf-0)) (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb-0 bank-conf-0)) (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))))) (label 53) (parent 49) (unrealized (1 0) (3 0)) (comment "2 in cohort - 2 not yet seen")) (defskeleton minipay-rely-guar (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (btr mtr merc-conf bank-conf mtr-0 text) (c m b name)) (defstrand merc 3 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-0) (c c) (m m) (b b)) (precedes ((0 1) (1 0)) ((1 1) (0 2)) ((2 0) (0 0)) ((3 0) (1 0)) ((4 1) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1) (operation encryption-test (displaced 5 0 merc 2) (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (1 0) (enc n cost item merc-conf ncm (hash n (hash ncb-0 bank-conf-0)) (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)) (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (traces ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))))) (label 54) (parent 51) (unrealized (4 0)) (comment "3 in cohort - 3 not yet seen")) (defskeleton minipay-rely-guar (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (btr mtr merc-conf bank-conf mtr-0 text) (c m b name)) (defstrand merc 3 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-0) (c c) (m m) (b b)) (precedes ((0 1) (1 0)) ((1 1) (0 2)) ((2 0) (3 0)) ((3 1) (0 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1) (operation encryption-test (displaced 4 2 cust 1) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (3 0)) (traces ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))))) (label 55) (parent 52) (seen 47) (realized) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay-rely-guar (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (btr mtr merc-conf bank-conf mtr-0 text) (c m b name)) (defstrand merc 3 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-0) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (precedes ((0 1) (1 0)) ((1 1) (0 2)) ((2 0) (0 0)) ((3 1) (0 0)) ((4 0) (3 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1) (operation encryption-test (added-strand cust 1) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (3 0)) (traces ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))))) (label 56) (parent 52) (seen 55) (realized) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay-rely-guar (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (btr mtr merc-conf bank-conf mtr-0 text) (c m b name)) (defstrand merc 3 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-0) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (precedes ((0 1) (1 0)) ((1 1) (0 2)) ((2 0) (0 0)) ((3 1) (0 0)) ((4 0) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1) (operation encryption-test (displaced 5 3 merc 2) (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (1 0) (enc n cost item merc-conf ncm (hash n (hash ncb-0 bank-conf-0)) (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (traces ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))))) (label 57) (parent 53) (seen 56) (unrealized (3 0)) (comment "3 in cohort - 2 not yet seen")) (defskeleton minipay-rely-guar (vars (account account-0 acct) (cost amount) (ncb n ncb-0 ncm data) (item merchandise) (btr mtr bank-conf merc-conf bank-conf-0 mtr-0 mtr-1 text) (c m b name)) (defstrand merc 3 (for-bank (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb-0 bank-conf-0))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account-0) (cost cost) (n n) (ncb ncb-0) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf-0) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb-0 bank-conf-0))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-0) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-1) (c c) (m m) (b b)) (precedes ((0 1) (1 0)) ((1 1) (0 2)) ((2 0) (0 0)) ((3 1) (0 0)) ((4 0) (1 0)) ((5 1) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig btr mtr mtr-0 mtr-1) (facts (neq n ncb) (neq n ncb-0) (neq n ncm) (neq ncm ncb) (neq ncm ncb-0) (buy-via c m b item cost n) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1) (operation encryption-test (added-strand merc 2) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (1 0) (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (traces ((recv (enc n cost item merc-conf ncm (hash n (hash ncb-0 bank-conf-0)) (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb-0 bank-conf-0)) (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb-0 bank-conf-0)) (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-1 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))))) (label 58) (parent 53) (unrealized (1 0) (3 0) (5 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay-rely-guar (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (btr mtr merc-conf bank-conf mtr-0 text) (c m b name)) (defstrand merc 3 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-0) (c c) (m m) (b b)) (precedes ((0 1) (1 0)) ((1 1) (0 2)) ((2 0) (0 0)) ((2 0) (4 0)) ((3 0) (1 0)) ((4 1) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1) (operation encryption-test (displaced 5 2 cust 1) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (4 0)) (traces ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))))) (label 59) (parent 54) (realized) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay-rely-guar (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (btr mtr merc-conf bank-conf mtr-0 text) (c m b name)) (defstrand merc 3 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-0) (c c) (m m) (b b)) (precedes ((0 1) (1 0)) ((1 1) (0 2)) ((2 0) (0 0)) ((3 0) (4 0)) ((4 1) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1) (operation encryption-test (displaced 5 3 cust 1) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (4 0)) (traces ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))))) (label 60) (parent 54) (seen 50) (realized) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay-rely-guar (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (btr mtr merc-conf bank-conf mtr-0 text) (c m b name)) (defstrand merc 3 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-0) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (precedes ((0 1) (1 0)) ((1 1) (0 2)) ((2 0) (0 0)) ((3 0) (1 0)) ((4 1) (1 0)) ((5 0) (4 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1) (operation encryption-test (added-strand cust 1) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (4 0)) (traces ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))))) (label 61) (parent 54) (seen 60) (realized) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay-rely-guar (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (btr mtr merc-conf bank-conf mtr-0 text) (c m b name)) (defstrand merc 3 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-0) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (precedes ((0 1) (1 0)) ((1 1) (0 2)) ((2 0) (3 0)) ((3 1) (0 0)) ((4 0) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1) (operation encryption-test (displaced 5 2 cust 1) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (3 0)) (traces ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))))) (label 62) (parent 57) (seen 50) (realized) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay-rely-guar (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (btr mtr merc-conf bank-conf mtr-0 text) (c m b name)) (defstrand merc 3 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-0) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (precedes ((0 1) (1 0)) ((1 1) (0 2)) ((2 0) (0 0)) ((3 1) (0 0)) ((4 0) (1 0)) ((5 0) (3 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1) (operation encryption-test (added-strand cust 1) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (3 0)) (traces ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))))) (label 63) (parent 57) (seen 62) (realized) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay-rely-guar (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (btr mtr merc-conf bank-conf mtr-0 mtr-1 text) (c m b name)) (defstrand merc 3 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-0) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-1) (c c) (m m) (b b)) (precedes ((0 1) (1 0)) ((1 1) (0 2)) ((2 0) (0 0)) ((3 1) (0 0)) ((4 0) (1 0)) ((5 1) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig btr mtr mtr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1) (operation encryption-test (displaced 6 3 merc 2) (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (1 0) (enc n cost item merc-conf ncm (hash n (hash ncb-0 bank-conf-0)) (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)) (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-1 (cat (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (traces ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-1 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))))) (label 64) (parent 58) (unrealized (3 0) (5 0)) (comment "3 in cohort - 3 not yet seen")) (defskeleton minipay-rely-guar (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (btr mtr merc-conf bank-conf mtr-0 text) (c m b name)) (defstrand merc 3 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-0) (c c) (m m) (b b)) (precedes ((0 1) (1 0)) ((1 1) (0 2)) ((2 0) (0 0)) ((2 0) (3 0)) ((3 1) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1) (operation generalization deleted (3 0)) (traces ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))))) (label 65) (parent 59) (seen 47) (realized) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay-rely-guar (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (btr mtr merc-conf bank-conf mtr-0 mtr-1 text) (c m b name)) (defstrand merc 3 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-0) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-1) (c c) (m m) (b b)) (precedes ((0 1) (1 0)) ((1 1) (0 2)) ((2 0) (3 0)) ((3 1) (0 0)) ((4 0) (1 0)) ((5 1) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig btr mtr mtr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1) (operation encryption-test (displaced 6 2 cust 1) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (3 0)) (traces ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-1 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))))) (label 66) (parent 64) (unrealized (5 0)) (comment "3 in cohort - 3 not yet seen")) (defskeleton minipay-rely-guar (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (btr mtr merc-conf bank-conf mtr-0 mtr-1 text) (c m b name)) (defstrand merc 3 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-0) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-1) (c c) (m m) (b b)) (precedes ((0 1) (1 0)) ((1 1) (0 2)) ((2 0) (0 0)) ((3 1) (0 0)) ((4 0) (3 0)) ((5 1) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig btr mtr mtr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1) (operation encryption-test (displaced 6 4 cust 1) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (3 0)) (traces ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-1 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))))) (label 67) (parent 64) (unrealized (5 0)) (comment "3 in cohort - 3 not yet seen")) (defskeleton minipay-rely-guar (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (btr mtr merc-conf bank-conf mtr-0 mtr-1 text) (c m b name)) (defstrand merc 3 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-0) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-1) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (precedes ((0 1) (1 0)) ((1 1) (0 2)) ((2 0) (0 0)) ((3 1) (0 0)) ((4 0) (1 0)) ((5 1) (1 0)) ((6 0) (3 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig btr mtr mtr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1) (operation encryption-test (added-strand cust 1) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (3 0)) (traces ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-1 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))))) (label 68) (parent 64) (seen 74) (unrealized (5 0)) (comment "4 in cohort - 3 not yet seen")) (defskeleton minipay-rely-guar (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (btr mtr merc-conf bank-conf mtr-0 mtr-1 text) (c m b name)) (defstrand merc 3 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-0) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-1) (c c) (m m) (b b)) (precedes ((0 1) (1 0)) ((1 1) (0 2)) ((2 0) (3 0)) ((2 0) (5 0)) ((3 1) (0 0)) ((4 0) (1 0)) ((5 1) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig btr mtr mtr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1) (operation encryption-test (displaced 6 2 cust 1) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (5 0)) (traces ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-1 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))))) (label 69) (parent 66) (seen 59) (realized) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay-rely-guar (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (btr mtr merc-conf bank-conf mtr-0 mtr-1 text) (c m b name)) (defstrand merc 3 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-0) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-1) (c c) (m m) (b b)) (precedes ((0 1) (1 0)) ((1 1) (0 2)) ((2 0) (3 0)) ((3 1) (0 0)) ((4 0) (5 0)) ((5 1) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig btr mtr mtr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1) (operation encryption-test (displaced 6 4 cust 1) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (5 0)) (traces ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-1 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))))) (label 70) (parent 66) (seen 60) (realized) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay-rely-guar (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (btr mtr merc-conf bank-conf mtr-0 mtr-1 text) (c m b name)) (defstrand merc 3 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-0) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-1) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (precedes ((0 1) (1 0)) ((1 1) (0 2)) ((2 0) (3 0)) ((3 1) (0 0)) ((4 0) (1 0)) ((5 1) (1 0)) ((6 0) (5 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig btr mtr mtr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1) (operation encryption-test (added-strand cust 1) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (5 0)) (traces ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-1 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))))) (label 71) (parent 66) (seen 61) (realized) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay-rely-guar (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (btr mtr merc-conf bank-conf mtr-0 mtr-1 text) (c m b name)) (defstrand merc 3 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-0) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-1) (c c) (m m) (b b)) (precedes ((0 1) (1 0)) ((1 1) (0 2)) ((2 0) (0 0)) ((2 0) (5 0)) ((3 1) (0 0)) ((4 0) (3 0)) ((5 1) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig btr mtr mtr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1) (operation encryption-test (displaced 6 2 cust 1) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (5 0)) (traces ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-1 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))))) (label 72) (parent 67) (realized) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay-rely-guar (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (btr mtr merc-conf bank-conf mtr-0 mtr-1 text) (c m b name)) (defstrand merc 3 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-0) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-1) (c c) (m m) (b b)) (precedes ((0 1) (1 0)) ((1 1) (0 2)) ((2 0) (0 0)) ((3 1) (0 0)) ((4 0) (3 0)) ((4 0) (5 0)) ((5 1) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig btr mtr mtr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1) (operation encryption-test (displaced 6 4 cust 1) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (5 0)) (traces ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-1 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))))) (label 73) (parent 67) (realized) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay-rely-guar (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (btr mtr merc-conf bank-conf mtr-0 mtr-1 text) (c m b name)) (defstrand merc 3 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-0) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-1) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (precedes ((0 1) (1 0)) ((1 1) (0 2)) ((2 0) (0 0)) ((3 1) (0 0)) ((4 0) (3 0)) ((5 1) (1 0)) ((6 0) (5 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig btr mtr mtr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1) (operation encryption-test (added-strand cust 1) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (5 0)) (traces ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-1 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))))) (label 74) (parent 67) (seen 70) (realized) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay-rely-guar (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (btr mtr merc-conf bank-conf mtr-0 mtr-1 text) (c m b name)) (defstrand merc 3 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-0) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-1) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (precedes ((0 1) (1 0)) ((1 1) (0 2)) ((2 0) (0 0)) ((2 0) (5 0)) ((3 1) (0 0)) ((4 0) (1 0)) ((5 1) (1 0)) ((6 0) (3 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig btr mtr mtr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1) (operation encryption-test (displaced 7 2 cust 1) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (5 0)) (traces ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-1 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))))) (label 75) (parent 68) (realized) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay-rely-guar (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (btr mtr merc-conf bank-conf mtr-0 mtr-1 text) (c m b name)) (defstrand merc 3 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-0) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-1) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (precedes ((0 1) (1 0)) ((1 1) (0 2)) ((2 0) (0 0)) ((3 1) (0 0)) ((4 0) (1 0)) ((5 1) (1 0)) ((6 0) (3 0)) ((6 0) (5 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig btr mtr mtr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1) (operation encryption-test (displaced 7 6 cust 1) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (5 0)) (traces ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-1 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))))) (label 76) (parent 68) (seen 69) (realized) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay-rely-guar (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (btr mtr merc-conf bank-conf mtr-0 mtr-1 text) (c m b name)) (defstrand merc 3 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-0) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-1) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (precedes ((0 1) (1 0)) ((1 1) (0 2)) ((2 0) (0 0)) ((3 1) (0 0)) ((4 0) (1 0)) ((5 1) (1 0)) ((6 0) (3 0)) ((7 0) (5 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig btr mtr mtr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1) (operation encryption-test (added-strand cust 1) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (5 0)) (traces ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-1 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))))) (label 77) (parent 68) (seen 71) (realized) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay-rely-guar (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (btr mtr merc-conf bank-conf mtr-0 text) (c m b name)) (defstrand merc 3 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-0) (c c) (m m) (b b)) (precedes ((0 1) (1 0)) ((1 1) (0 2)) ((2 0) (0 0)) ((2 0) (4 0)) ((3 0) (0 0)) ((4 1) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1) (operation generalization deleted (3 0)) (traces ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))))) (label 78) (parent 72) (seen 65) (realized) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay-rely-guar (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (btr mtr merc-conf bank-conf mtr-0 mtr-1 text) (c m b name)) (defstrand merc 3 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-0) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-1) (c c) (m m) (b b)) (precedes ((0 1) (1 0)) ((1 1) (0 2)) ((2 1) (0 0)) ((3 0) (2 0)) ((3 0) (4 0)) ((4 1) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig btr mtr mtr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1) (operation generalization deleted (2 0)) (traces ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-1 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))))) (label 79) (parent 73) (seen 65) (realized) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay-rely-guar (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (btr mtr merc-conf bank-conf mtr-0 text) (c m b name)) (defstrand merc 3 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-0) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (precedes ((0 1) (1 0)) ((1 1) (0 2)) ((2 0) (0 0)) ((2 0) (4 0)) ((3 0) (1 0)) ((4 1) (1 0)) ((5 0) (0 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1) (operation generalization deleted (3 0)) (traces ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))))) (label 80) (parent 75) (seen 78) (realized) (comment "1 in cohort - 0 not yet seen")) (comment "Nothing left to do") (defprotocol minipay-rely-guar basic (defrole cust (vars (c m b name) (cost amount) (item merchandise) (merc-conf bank-conf btr mtr text) (account acct) (n ncb ncm data)) (trace (send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) (facts (neq n ncb) (neq n ncm) (neq ncm ncb))) (defrole merc (vars (c m b name) (cost amount) (item merchandise) (merc-conf btr mtr text) (n ncm data) (for-bank bank-conf-commit bank-conf-decommit mesg)) (trace (recv (enc n cost item merc-conf ncm bank-conf-commit (sign (order c m b cost for-bank) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost for-bank) (privk "sig" c)) for-bank)) (pubk "enc" b))) (recv (enc bank-conf-decommit (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n bank-conf-decommit)) btr mtr) (privk "sig" m)))) (uniq-orig mtr)) (defrole bank (vars (c m b name) (cost amount) (bank-conf btr mtr text) (merc-conf-decommit mesg) (account acct) (n ncb data)) (trace (recv (enc (payreq c m b (hash cost n) merc-conf-decommit mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n merc-conf-decommit) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n merc-conf-decommit) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n merc-conf-decommit)) btr mtr) (privk "sig" b)) (pubk "enc" m)))) (uniq-orig btr)) (defrule rely-cust-3 (forall ((z strd) (mtr text) (item merchandise) (b m c name)) (implies (and (p "cust" z (idx 3)) (p "cust" "mtr" z mtr) (p "cust" "item" z item) (p "cust" "b" z b) (p "cust" "m" z m) (p "cust" "c" z c)) (fact will-ship c m b item mtr)))) (defrule rely-cust-2 (forall ((z strd) (btr mtr text) (n data) (cost amount) (b m c name)) (implies (and (p "cust" z (idx 2)) (p "cust" "btr" z btr) (p "cust" "mtr" z mtr) (p "cust" "n" z n) (p "cust" "cost" z cost) (p "cust" "b" z b) (p "cust" "m" z m) (p "cust" "c" z c)) (fact will-transfer c m b cost n mtr btr)))) (defrule rely-merc-3 (forall ((z strd) (n data) (cost amount) (item merchandise) (b m c name) (btr mtr text)) (implies (and (p "merc" z (idx 3)) (p "merc" "n" z n) (p "merc" "cost" z cost) (p "merc" "item" z item) (p "merc" "b" z b) (p "merc" "m" z m) (p "merc" "c" z c) (p "merc" "btr" z btr) (p "merc" "mtr" z mtr)) (and (fact buy-via c m b item cost n) (fact will-transfer c m b cost n mtr btr))))) (defrule rely-bank-1 (forall ((z strd) (n data) (cost amount) (b m c name)) (implies (and (p "bank" z (idx 1)) (p "bank" "n" z n) (p "bank" "cost" z cost) (p "bank" "b" z b) (p "bank" "m" z m) (p "bank" "c" z c)) (exists ((item merchandise)) (fact buy-via c m b item cost n))))) (defrule guar-cust-1 (forall ((z strd) (n data) (cost amount) (item merchandise) (b m c name)) (implies (and (p "cust" z (idx 1)) (p "cust" "n" z n) (p "cust" "cost" z cost) (p "cust" "item" z item) (p "cust" "b" z b) (p "cust" "m" z m) (p "cust" "c" z c)) (fact buy-via c m b item cost n)))) (defrule guar-merc-4 (forall ((z strd) (mtr text) (item merchandise) (b m c name)) (implies (and (p "merc" z (idx 4)) (p "merc" "mtr" z mtr) (p "merc" "item" z item) (p "merc" "b" z b) (p "merc" "m" z m) (p "merc" "c" z c)) (fact will-ship c m b item mtr)))) (defrule guar-bank-2 (forall ((z strd) (btr mtr text) (n data) (cost amount) (c b m name)) (implies (and (p "bank" z (idx 2)) (p "bank" "btr" z btr) (p "bank" "mtr" z mtr) (p "bank" "n" z n) (p "bank" "cost" z cost) (p "bank" "c" z c) (p "bank" "b" z b) (p "bank" "m" z m)) (and (non (privk "sig" c)) (fact will-transfer c m b cost n mtr btr))))) (defrule cheq-merc-4 (forall ((z strd) (n data) (bank-conf-decommit bank-conf-commit mesg)) (implies (and (p "merc" z (idx 4)) (p "merc" "n" z n) (p "merc" "bank-conf-decommit" z bank-conf-decommit) (p "merc" "bank-conf-commit" z bank-conf-commit)) (= bank-conf-commit (hash n bank-conf-decommit))))) (defgenrule neqRl_indx (forall ((x indx)) (implies (fact neq x x) (false)))) (defgenrule neqRl_strd (forall ((x strd)) (implies (fact neq x x) (false)))) (defgenrule neqRl_mesg (forall ((x mesg)) (implies (fact neq x x) (false)))) (defgenrule fact-cust-neq2 (forall ((z strd) (ncb n data)) (implies (and (p "cust" z (idx 1)) (p "cust" "ncb" z ncb) (p "cust" "n" z n)) (fact neq n ncb)))) (defgenrule fact-cust-neq1 (forall ((z strd) (ncm n data)) (implies (and (p "cust" z (idx 1)) (p "cust" "ncm" z ncm) (p "cust" "n" z n)) (fact neq n ncm)))) (defgenrule fact-cust-neq0 (forall ((z strd) (ncb ncm data)) (implies (and (p "cust" z (idx 1)) (p "cust" "ncb" z ncb) (p "cust" "ncm" z ncm)) (fact neq ncm ncb)))) (lang (acct atom) (amount atom) (merchandise atom) (sign sign) (order (tuple 5)) (bconf (tuple 3)) (mconf (tuple 3)) (payreq (tuple 7)))) (defskeleton minipay-rely-guar (vars (merc-conf-decommit mesg) (account acct) (cost amount) (n ncb data) (bank-conf btr mtr text) (c m b name)) (defstrand bank 2 (merc-conf-decommit merc-conf-decommit) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m)) (uniq-orig btr) (traces ((recv (enc (payreq c m b (hash cost n) merc-conf-decommit mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n merc-conf-decommit) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n merc-conf-decommit) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n merc-conf-decommit)) btr mtr) (privk "sig" b)) (pubk "enc" m))))) (label 81) (unrealized (0 0)) (origs (btr (0 1))) (comment "Not closed under rules")) (defskeleton minipay-rely-guar (vars (item merchandise) (merc-conf-decommit mesg) (account acct) (cost amount) (n ncb data) (bank-conf btr mtr text) (c m b name)) (defstrand bank 2 (merc-conf-decommit merc-conf-decommit) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m)) (uniq-orig btr) (facts (buy-via c m b item cost n) (will-transfer c m b cost n mtr btr)) (rule guar-bank-2 rely-bank-1) (traces ((recv (enc (payreq c m b (hash cost n) merc-conf-decommit mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n merc-conf-decommit) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n merc-conf-decommit) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n merc-conf-decommit)) btr mtr) (privk "sig" b)) (pubk "enc" m))))) (label 82) (parent 81) (unrealized (0 0)) (origs (btr (0 1))) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay-rely-guar (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr merc-conf text) (c m b name)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (precedes ((1 0) (0 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m)) (uniq-orig btr) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1) (operation encryption-test (added-strand cust 1) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (0 0)) (traces ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))))) (label 83) (parent 82) (unrealized (0 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay-rely-guar (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr merc-conf mtr-0 text) (c m b name)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-0) (c c) (m m) (b b)) (precedes ((1 0) (0 0)) ((2 1) (0 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m)) (uniq-orig btr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1) (operation encryption-test (added-strand merc 2) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (0 0) (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (traces ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))))) (label 84) (parent 83) (unrealized (0 0) (2 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay-rely-guar (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr merc-conf mtr text) (c m b name)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr) (c c) (m m) (b b)) (precedes ((1 0) (0 0)) ((2 1) (0 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m)) (uniq-orig btr mtr) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1) (operation encryption-test (contracted (mtr-0 mtr)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (0 0) (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)) (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (traces ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))))) (label 85) (parent 84) (unrealized (2 0)) (comment "2 in cohort - 2 not yet seen")) (defskeleton minipay-rely-guar (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr merc-conf mtr text) (c m b name)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr) (c c) (m m) (b b)) (precedes ((1 0) (2 0)) ((2 1) (0 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m)) (uniq-orig btr mtr) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1) (operation encryption-test (displaced 3 1 cust 1) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (2 0)) (traces ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))))) (label 86) (parent 85) (realized) (shape) (maps ((0) ((c c) (m m) (b b) (n n) (cost cost) (bank-conf bank-conf) (btr btr) (mtr mtr) (merc-conf-decommit (hash ncm item merc-conf)) (account account) (ncb ncb)))) (origs (mtr (2 1)) (btr (0 1)))) (defskeleton minipay-rely-guar (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr merc-conf mtr text) (c m b name)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (precedes ((1 0) (0 0)) ((2 1) (0 0)) ((3 0) (2 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m)) (uniq-orig btr mtr) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1) (operation encryption-test (added-strand cust 1) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (2 0)) (traces ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))))) (label 87) (parent 85) (seen 86) (realized) (comment "1 in cohort - 0 not yet seen")) (comment "Nothing left to do") (defprotocol minipay-rely-guar basic (defrole cust (vars (c m b name) (cost amount) (item merchandise) (merc-conf bank-conf btr mtr text) (account acct) (n ncb ncm data)) (trace (send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) (facts (neq n ncb) (neq n ncm) (neq ncm ncb))) (defrole merc (vars (c m b name) (cost amount) (item merchandise) (merc-conf btr mtr text) (n ncm data) (for-bank bank-conf-commit bank-conf-decommit mesg)) (trace (recv (enc n cost item merc-conf ncm bank-conf-commit (sign (order c m b cost for-bank) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost for-bank) (privk "sig" c)) for-bank)) (pubk "enc" b))) (recv (enc bank-conf-decommit (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n bank-conf-decommit)) btr mtr) (privk "sig" m)))) (uniq-orig mtr)) (defrole bank (vars (c m b name) (cost amount) (bank-conf btr mtr text) (merc-conf-decommit mesg) (account acct) (n ncb data)) (trace (recv (enc (payreq c m b (hash cost n) merc-conf-decommit mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n merc-conf-decommit) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n merc-conf-decommit) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n merc-conf-decommit)) btr mtr) (privk "sig" b)) (pubk "enc" m)))) (uniq-orig btr)) (defrule rely-cust-3 (forall ((z strd) (mtr text) (item merchandise) (b m c name)) (implies (and (p "cust" z (idx 3)) (p "cust" "mtr" z mtr) (p "cust" "item" z item) (p "cust" "b" z b) (p "cust" "m" z m) (p "cust" "c" z c)) (fact will-ship c m b item mtr)))) (defrule rely-cust-2 (forall ((z strd) (btr mtr text) (n data) (cost amount) (b m c name)) (implies (and (p "cust" z (idx 2)) (p "cust" "btr" z btr) (p "cust" "mtr" z mtr) (p "cust" "n" z n) (p "cust" "cost" z cost) (p "cust" "b" z b) (p "cust" "m" z m) (p "cust" "c" z c)) (fact will-transfer c m b cost n mtr btr)))) (defrule rely-merc-3 (forall ((z strd) (n data) (cost amount) (item merchandise) (b m c name) (btr mtr text)) (implies (and (p "merc" z (idx 3)) (p "merc" "n" z n) (p "merc" "cost" z cost) (p "merc" "item" z item) (p "merc" "b" z b) (p "merc" "m" z m) (p "merc" "c" z c) (p "merc" "btr" z btr) (p "merc" "mtr" z mtr)) (and (fact buy-via c m b item cost n) (fact will-transfer c m b cost n mtr btr))))) (defrule rely-bank-1 (forall ((z strd) (n data) (cost amount) (b m c name)) (implies (and (p "bank" z (idx 1)) (p "bank" "n" z n) (p "bank" "cost" z cost) (p "bank" "b" z b) (p "bank" "m" z m) (p "bank" "c" z c)) (exists ((item merchandise)) (fact buy-via c m b item cost n))))) (defrule guar-cust-1 (forall ((z strd) (n data) (cost amount) (item merchandise) (b m c name)) (implies (and (p "cust" z (idx 1)) (p "cust" "n" z n) (p "cust" "cost" z cost) (p "cust" "item" z item) (p "cust" "b" z b) (p "cust" "m" z m) (p "cust" "c" z c)) (fact buy-via c m b item cost n)))) (defrule guar-merc-4 (forall ((z strd) (mtr text) (item merchandise) (b m c name)) (implies (and (p "merc" z (idx 4)) (p "merc" "mtr" z mtr) (p "merc" "item" z item) (p "merc" "b" z b) (p "merc" "m" z m) (p "merc" "c" z c)) (fact will-ship c m b item mtr)))) (defrule guar-bank-2 (forall ((z strd) (btr mtr text) (n data) (cost amount) (c b m name)) (implies (and (p "bank" z (idx 2)) (p "bank" "btr" z btr) (p "bank" "mtr" z mtr) (p "bank" "n" z n) (p "bank" "cost" z cost) (p "bank" "c" z c) (p "bank" "b" z b) (p "bank" "m" z m)) (and (non (privk "sig" c)) (fact will-transfer c m b cost n mtr btr))))) (defrule cheq-merc-4 (forall ((z strd) (n data) (bank-conf-decommit bank-conf-commit mesg)) (implies (and (p "merc" z (idx 4)) (p "merc" "n" z n) (p "merc" "bank-conf-decommit" z bank-conf-decommit) (p "merc" "bank-conf-commit" z bank-conf-commit)) (= bank-conf-commit (hash n bank-conf-decommit))))) (defgenrule neqRl_indx (forall ((x indx)) (implies (fact neq x x) (false)))) (defgenrule neqRl_strd (forall ((x strd)) (implies (fact neq x x) (false)))) (defgenrule neqRl_mesg (forall ((x mesg)) (implies (fact neq x x) (false)))) (defgenrule fact-cust-neq2 (forall ((z strd) (ncb n data)) (implies (and (p "cust" z (idx 1)) (p "cust" "ncb" z ncb) (p "cust" "n" z n)) (fact neq n ncb)))) (defgenrule fact-cust-neq1 (forall ((z strd) (ncm n data)) (implies (and (p "cust" z (idx 1)) (p "cust" "ncm" z ncm) (p "cust" "n" z n)) (fact neq n ncm)))) (defgenrule fact-cust-neq0 (forall ((z strd) (ncb ncm data)) (implies (and (p "cust" z (idx 1)) (p "cust" "ncb" z ncb) (p "cust" "ncm" z ncm)) (fact neq ncm ncb)))) (lang (acct atom) (amount atom) (merchandise atom) (sign sign) (order (tuple 5)) (bconf (tuple 3)) (mconf (tuple 3)) (payreq (tuple 7)))) (defskeleton minipay-rely-guar (vars (merc-conf-decommit mesg) (account acct) (cost amount) (n ncb data) (bank-conf btr mtr text) (c m b name)) (defstrand bank 2 (merc-conf-decommit merc-conf-decommit) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (non-orig (privk "enc" m) (privk "sig" c)) (uniq-orig btr) (traces ((recv (enc (payreq c m b (hash cost n) merc-conf-decommit mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n merc-conf-decommit) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n merc-conf-decommit) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n merc-conf-decommit)) btr mtr) (privk "sig" b)) (pubk "enc" m))))) (label 88) (unrealized (0 0)) (origs (btr (0 1))) (comment "Not closed under rules")) (defskeleton minipay-rely-guar (vars (item merchandise) (merc-conf-decommit mesg) (account acct) (cost amount) (n ncb data) (bank-conf btr mtr text) (c m b name)) (defstrand bank 2 (merc-conf-decommit merc-conf-decommit) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (non-orig (privk "enc" m) (privk "sig" c)) (uniq-orig btr) (facts (buy-via c m b item cost n) (will-transfer c m b cost n mtr btr)) (rule guar-bank-2 rely-bank-1) (traces ((recv (enc (payreq c m b (hash cost n) merc-conf-decommit mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n merc-conf-decommit) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n merc-conf-decommit) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n merc-conf-decommit)) btr mtr) (privk "sig" b)) (pubk "enc" m))))) (label 89) (parent 88) (unrealized (0 0)) (origs (btr (0 1))) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay-rely-guar (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr merc-conf text) (c m b name)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (precedes ((1 0) (0 0))) (non-orig (privk "enc" m) (privk "sig" c)) (uniq-orig btr) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1) (operation encryption-test (added-strand cust 1) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (0 0)) (traces ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))))) (label 90) (parent 89) (unrealized (0 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay-rely-guar (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr merc-conf mtr-0 text) (c m b name)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-0) (c c) (m m) (b b)) (precedes ((1 0) (0 0)) ((2 1) (0 0))) (non-orig (privk "enc" m) (privk "sig" c)) (uniq-orig btr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1) (operation encryption-test (added-strand merc 2) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (0 0) (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (traces ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))))) (label 91) (parent 90) (unrealized (2 0)) (comment "2 in cohort - 2 not yet seen")) (defskeleton minipay-rely-guar (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr merc-conf mtr-0 text) (c m b name)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-0) (c c) (m m) (b b)) (precedes ((1 0) (2 0)) ((2 1) (0 0))) (non-orig (privk "enc" m) (privk "sig" c)) (uniq-orig btr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1) (operation encryption-test (displaced 3 1 cust 1) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (2 0)) (traces ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))))) (label 92) (parent 91) (realized) (shape) (maps ((0) ((c c) (m m) (b b) (n n) (cost cost) (bank-conf bank-conf) (btr btr) (mtr mtr) (merc-conf-decommit (hash ncm item merc-conf)) (account account) (ncb ncb)))) (origs (mtr-0 (2 1)) (btr (0 1)))) (defskeleton minipay-rely-guar (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr merc-conf mtr-0 text) (c m b name)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-0) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (precedes ((1 0) (0 0)) ((2 1) (0 0)) ((3 0) (2 0))) (non-orig (privk "enc" m) (privk "sig" c)) (uniq-orig btr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1) (operation encryption-test (added-strand cust 1) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (2 0)) (traces ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))))) (label 93) (parent 91) (seen 92) (realized) (comment "1 in cohort - 0 not yet seen")) (comment "Nothing left to do") (defprotocol minipay-rely-guar basic (defrole cust (vars (c m b name) (cost amount) (item merchandise) (merc-conf bank-conf btr mtr text) (account acct) (n ncb ncm data)) (trace (send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) (facts (neq n ncb) (neq n ncm) (neq ncm ncb))) (defrole merc (vars (c m b name) (cost amount) (item merchandise) (merc-conf btr mtr text) (n ncm data) (for-bank bank-conf-commit bank-conf-decommit mesg)) (trace (recv (enc n cost item merc-conf ncm bank-conf-commit (sign (order c m b cost for-bank) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost for-bank) (privk "sig" c)) for-bank)) (pubk "enc" b))) (recv (enc bank-conf-decommit (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n bank-conf-decommit)) btr mtr) (privk "sig" m)))) (uniq-orig mtr)) (defrole bank (vars (c m b name) (cost amount) (bank-conf btr mtr text) (merc-conf-decommit mesg) (account acct) (n ncb data)) (trace (recv (enc (payreq c m b (hash cost n) merc-conf-decommit mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n merc-conf-decommit) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n merc-conf-decommit) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n merc-conf-decommit)) btr mtr) (privk "sig" b)) (pubk "enc" m)))) (uniq-orig btr)) (defrule rely-cust-3 (forall ((z strd) (mtr text) (item merchandise) (b m c name)) (implies (and (p "cust" z (idx 3)) (p "cust" "mtr" z mtr) (p "cust" "item" z item) (p "cust" "b" z b) (p "cust" "m" z m) (p "cust" "c" z c)) (fact will-ship c m b item mtr)))) (defrule rely-cust-2 (forall ((z strd) (btr mtr text) (n data) (cost amount) (b m c name)) (implies (and (p "cust" z (idx 2)) (p "cust" "btr" z btr) (p "cust" "mtr" z mtr) (p "cust" "n" z n) (p "cust" "cost" z cost) (p "cust" "b" z b) (p "cust" "m" z m) (p "cust" "c" z c)) (fact will-transfer c m b cost n mtr btr)))) (defrule rely-merc-3 (forall ((z strd) (n data) (cost amount) (item merchandise) (b m c name) (btr mtr text)) (implies (and (p "merc" z (idx 3)) (p "merc" "n" z n) (p "merc" "cost" z cost) (p "merc" "item" z item) (p "merc" "b" z b) (p "merc" "m" z m) (p "merc" "c" z c) (p "merc" "btr" z btr) (p "merc" "mtr" z mtr)) (and (fact buy-via c m b item cost n) (fact will-transfer c m b cost n mtr btr))))) (defrule rely-bank-1 (forall ((z strd) (n data) (cost amount) (b m c name)) (implies (and (p "bank" z (idx 1)) (p "bank" "n" z n) (p "bank" "cost" z cost) (p "bank" "b" z b) (p "bank" "m" z m) (p "bank" "c" z c)) (exists ((item merchandise)) (fact buy-via c m b item cost n))))) (defrule guar-cust-1 (forall ((z strd) (n data) (cost amount) (item merchandise) (b m c name)) (implies (and (p "cust" z (idx 1)) (p "cust" "n" z n) (p "cust" "cost" z cost) (p "cust" "item" z item) (p "cust" "b" z b) (p "cust" "m" z m) (p "cust" "c" z c)) (fact buy-via c m b item cost n)))) (defrule guar-merc-4 (forall ((z strd) (mtr text) (item merchandise) (b m c name)) (implies (and (p "merc" z (idx 4)) (p "merc" "mtr" z mtr) (p "merc" "item" z item) (p "merc" "b" z b) (p "merc" "m" z m) (p "merc" "c" z c)) (fact will-ship c m b item mtr)))) (defrule guar-bank-2 (forall ((z strd) (btr mtr text) (n data) (cost amount) (c b m name)) (implies (and (p "bank" z (idx 2)) (p "bank" "btr" z btr) (p "bank" "mtr" z mtr) (p "bank" "n" z n) (p "bank" "cost" z cost) (p "bank" "c" z c) (p "bank" "b" z b) (p "bank" "m" z m)) (and (non (privk "sig" c)) (fact will-transfer c m b cost n mtr btr))))) (defrule cheq-merc-4 (forall ((z strd) (n data) (bank-conf-decommit bank-conf-commit mesg)) (implies (and (p "merc" z (idx 4)) (p "merc" "n" z n) (p "merc" "bank-conf-decommit" z bank-conf-decommit) (p "merc" "bank-conf-commit" z bank-conf-commit)) (= bank-conf-commit (hash n bank-conf-decommit))))) (defgenrule neqRl_indx (forall ((x indx)) (implies (fact neq x x) (false)))) (defgenrule neqRl_strd (forall ((x strd)) (implies (fact neq x x) (false)))) (defgenrule neqRl_mesg (forall ((x mesg)) (implies (fact neq x x) (false)))) (defgenrule fact-cust-neq2 (forall ((z strd) (ncb n data)) (implies (and (p "cust" z (idx 1)) (p "cust" "ncb" z ncb) (p "cust" "n" z n)) (fact neq n ncb)))) (defgenrule fact-cust-neq1 (forall ((z strd) (ncm n data)) (implies (and (p "cust" z (idx 1)) (p "cust" "ncm" z ncm) (p "cust" "n" z n)) (fact neq n ncm)))) (defgenrule fact-cust-neq0 (forall ((z strd) (ncb ncm data)) (implies (and (p "cust" z (idx 1)) (p "cust" "ncb" z ncb) (p "cust" "ncm" z ncm)) (fact neq ncm ncb)))) (lang (acct atom) (amount atom) (merchandise atom) (sign sign) (order (tuple 5)) (bconf (tuple 3)) (mconf (tuple 3)) (payreq (tuple 7)))) (defskeleton minipay-rely-guar (vars (for-bank bank-conf-commit bank-conf-decommit for-bank-0 bank-conf-commit-0 bank-conf-decommit-0 mesg) (account acct) (cost cost-0 cost-1 amount) (n ncb ncm ncm-0 ncm-1 data) (item item-0 item-1 merchandise) (merc-conf bank-conf btr mtr merc-conf-0 btr-0 mtr-0 merc-conf-1 btr-1 mtr-1 text) (c m b name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 3 (for-bank for-bank) (bank-conf-commit bank-conf-commit) (bank-conf-decommit bank-conf-decommit) (cost cost-0) (n n) (ncm ncm-0) (item item-0) (merc-conf merc-conf-0) (btr btr-0) (mtr mtr-0) (c c) (m m) (b b)) (defstrand merc 3 (for-bank for-bank-0) (bank-conf-commit bank-conf-commit-0) (bank-conf-decommit bank-conf-decommit-0) (cost cost-1) (n n) (ncm ncm-1) (item item-1) (merc-conf merc-conf-1) (btr btr-1) (mtr mtr-1) (c c) (m m) (b b)) (non-orig (privk "enc" b) (privk "sig" b)) (uniq-orig n mtr-0 mtr-1) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc n cost-0 item-0 merc-conf-0 ncm-0 bank-conf-commit (sign (order c m b cost-0 for-bank) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost-0 n) (hash ncm-0 item-0 merc-conf-0) mtr-0 (cat (sign (order c m b cost-0 for-bank) (privk "sig" c)) for-bank)) (pubk "enc" b))) (recv (enc bank-conf-decommit (sign (bconf (hash c m b n cost-0 (hash n (hash ncm-0 item-0 merc-conf-0))) btr-0 mtr-0) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc n cost-1 item-1 merc-conf-1 ncm-1 bank-conf-commit-0 (sign (order c m b cost-1 for-bank-0) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost-1 n) (hash ncm-1 item-1 merc-conf-1) mtr-1 (cat (sign (order c m b cost-1 for-bank-0) (privk "sig" c)) for-bank-0)) (pubk "enc" b))) (recv (enc bank-conf-decommit-0 (sign (bconf (hash c m b n cost-1 (hash n (hash ncm-1 item-1 merc-conf-1))) btr-1 mtr-1) (privk "sig" b)) (pubk "enc" m))))) (label 94) (unrealized (0 1) (1 0) (1 2) (2 0) (2 2)) (preskeleton) (origs (mtr-1 (2 1)) (mtr-0 (1 1)) (n (0 0))) (comment "Not a skeleton")) (defskeleton minipay-rely-guar (vars (for-bank bank-conf-commit bank-conf-decommit for-bank-0 bank-conf-commit-0 bank-conf-decommit-0 mesg) (account acct) (cost cost-0 cost-1 amount) (n ncb ncm ncm-0 ncm-1 data) (item item-0 item-1 merchandise) (merc-conf bank-conf btr mtr merc-conf-0 btr-0 mtr-0 merc-conf-1 btr-1 mtr-1 text) (c m b name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 3 (for-bank for-bank) (bank-conf-commit bank-conf-commit) (bank-conf-decommit bank-conf-decommit) (cost cost-0) (n n) (ncm ncm-0) (item item-0) (merc-conf merc-conf-0) (btr btr-0) (mtr mtr-0) (c c) (m m) (b b)) (defstrand merc 3 (for-bank for-bank-0) (bank-conf-commit bank-conf-commit-0) (bank-conf-decommit bank-conf-decommit-0) (cost cost-1) (n n) (ncm ncm-1) (item item-1) (merc-conf merc-conf-1) (btr btr-1) (mtr mtr-1) (c c) (m m) (b b)) (precedes ((0 0) (1 0)) ((0 0) (2 0))) (non-orig (privk "enc" b) (privk "sig" b)) (uniq-orig n mtr-0 mtr-1) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc n cost-0 item-0 merc-conf-0 ncm-0 bank-conf-commit (sign (order c m b cost-0 for-bank) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost-0 n) (hash ncm-0 item-0 merc-conf-0) mtr-0 (cat (sign (order c m b cost-0 for-bank) (privk "sig" c)) for-bank)) (pubk "enc" b))) (recv (enc bank-conf-decommit (sign (bconf (hash c m b n cost-0 (hash n (hash ncm-0 item-0 merc-conf-0))) btr-0 mtr-0) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc n cost-1 item-1 merc-conf-1 ncm-1 bank-conf-commit-0 (sign (order c m b cost-1 for-bank-0) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost-1 n) (hash ncm-1 item-1 merc-conf-1) mtr-1 (cat (sign (order c m b cost-1 for-bank-0) (privk "sig" c)) for-bank-0)) (pubk "enc" b))) (recv (enc bank-conf-decommit-0 (sign (bconf (hash c m b n cost-1 (hash n (hash ncm-1 item-1 merc-conf-1))) btr-1 mtr-1) (privk "sig" b)) (pubk "enc" m))))) (label 95) (parent 94) (unrealized (0 1) (1 2) (2 2)) (origs (mtr-1 (2 1)) (mtr-0 (1 1)) (n (0 0))) (comment "Not closed under rules")) (defskeleton minipay-rely-guar (vars (for-bank bank-conf-commit bank-conf-decommit for-bank-0 bank-conf-commit-0 bank-conf-decommit-0 mesg) (account acct) (cost cost-0 cost-1 amount) (n ncb ncm ncm-0 ncm-1 data) (item item-0 item-1 merchandise) (merc-conf bank-conf btr mtr merc-conf-0 btr-0 mtr-0 merc-conf-1 btr-1 mtr-1 text) (c m b name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 3 (for-bank for-bank) (bank-conf-commit bank-conf-commit) (bank-conf-decommit bank-conf-decommit) (cost cost-0) (n n) (ncm ncm-0) (item item-0) (merc-conf merc-conf-0) (btr btr-0) (mtr mtr-0) (c c) (m m) (b b)) (defstrand merc 3 (for-bank for-bank-0) (bank-conf-commit bank-conf-commit-0) (bank-conf-decommit bank-conf-decommit-0) (cost cost-1) (n n) (ncm ncm-1) (item item-1) (merc-conf merc-conf-1) (btr btr-1) (mtr mtr-1) (c c) (m m) (b b)) (precedes ((0 0) (1 0)) ((0 0) (2 0))) (non-orig (privk "enc" b) (privk "sig" b)) (uniq-orig n mtr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (will-ship c m b item mtr) (will-transfer c m b cost n mtr btr) (will-transfer c m b cost-1 n mtr-1 btr-1) (buy-via c m b item-1 cost-1 n) (will-transfer c m b cost-0 n mtr-0 btr-0) (buy-via c m b item-0 cost-0 n) (buy-via c m b item cost n)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-cust-1 rely-cust-2 rely-cust-3 rely-merc-3) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc n cost-0 item-0 merc-conf-0 ncm-0 bank-conf-commit (sign (order c m b cost-0 for-bank) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost-0 n) (hash ncm-0 item-0 merc-conf-0) mtr-0 (cat (sign (order c m b cost-0 for-bank) (privk "sig" c)) for-bank)) (pubk "enc" b))) (recv (enc bank-conf-decommit (sign (bconf (hash c m b n cost-0 (hash n (hash ncm-0 item-0 merc-conf-0))) btr-0 mtr-0) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc n cost-1 item-1 merc-conf-1 ncm-1 bank-conf-commit-0 (sign (order c m b cost-1 for-bank-0) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost-1 n) (hash ncm-1 item-1 merc-conf-1) mtr-1 (cat (sign (order c m b cost-1 for-bank-0) (privk "sig" c)) for-bank-0)) (pubk "enc" b))) (recv (enc bank-conf-decommit-0 (sign (bconf (hash c m b n cost-1 (hash n (hash ncm-1 item-1 merc-conf-1))) btr-1 mtr-1) (privk "sig" b)) (pubk "enc" m))))) (label 96) (parent 95) (unrealized (0 1) (1 2) (2 2)) (origs (mtr-1 (2 1)) (mtr-0 (1 1)) (n (0 0))) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay-rely-guar (vars (for-bank bank-conf-commit bank-conf-decommit mesg) (account acct) (cost cost-0 amount) (n ncb ncm ncm-0 data) (item item-0 merchandise) (merc-conf bank-conf btr mtr merc-conf-0 btr-0 mtr-0 text) (c m b name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 3 (for-bank for-bank) (bank-conf-commit bank-conf-commit) (bank-conf-decommit bank-conf-decommit) (cost cost-0) (n n) (ncm ncm-0) (item item-0) (merc-conf merc-conf-0) (btr btr-0) (mtr mtr-0) (c c) (m m) (b b)) (precedes ((0 0) (1 0))) (non-orig (privk "enc" b) (privk "sig" b)) (uniq-orig n mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (will-ship c m b item mtr) (will-transfer c m b cost n mtr btr) (will-transfer c m b cost-0 n mtr-0 btr-0) (buy-via c m b item-0 cost-0 n) (buy-via c m b item cost n)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-cust-1 rely-cust-2 rely-cust-3 rely-merc-3) (operation collapsed 2 1) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc n cost-0 item-0 merc-conf-0 ncm-0 bank-conf-commit (sign (order c m b cost-0 for-bank) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost-0 n) (hash ncm-0 item-0 merc-conf-0) mtr-0 (cat (sign (order c m b cost-0 for-bank) (privk "sig" c)) for-bank)) (pubk "enc" b))) (recv (enc bank-conf-decommit (sign (bconf (hash c m b n cost-0 (hash n (hash ncm-0 item-0 merc-conf-0))) btr-0 mtr-0) (privk "sig" b)) (pubk "enc" m))))) (label 97) (parent 96) (unrealized (0 1) (1 2)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay-rely-guar (vars (for-bank bank-conf-commit bank-conf-decommit for-bank-0 bank-conf-commit-0 bank-conf-decommit-0 mesg) (account account-0 acct) (cost cost-0 cost-1 amount) (n ncb ncm ncm-0 ncm-1 ncb-0 data) (item item-0 item-1 merchandise) (merc-conf bank-conf btr mtr merc-conf-0 btr-0 mtr-0 merc-conf-1 btr-1 mtr-1 bank-conf-0 text) (c m b name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 3 (for-bank for-bank) (bank-conf-commit bank-conf-commit) (bank-conf-decommit bank-conf-decommit) (cost cost-0) (n n) (ncm ncm-0) (item item-0) (merc-conf merc-conf-0) (btr btr-0) (mtr mtr-0) (c c) (m m) (b b)) (defstrand merc 3 (for-bank for-bank-0) (bank-conf-commit bank-conf-commit-0) (bank-conf-decommit bank-conf-decommit-0) (cost cost-1) (n n) (ncm ncm-1) (item item-1) (merc-conf merc-conf-1) (btr btr-1) (mtr mtr-1) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account-0) (cost cost) (n n) (ncb ncb-0) (bank-conf bank-conf-0) (btr btr) (mtr mtr) (c c) (m m) (b b)) (precedes ((0 0) (1 0)) ((0 0) (2 0)) ((0 0) (3 0)) ((3 1) (0 1))) (non-orig (privk "enc" b) (privk "sig" c) (privk "sig" b)) (uniq-orig n btr mtr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (will-ship c m b item mtr) (will-transfer c m b cost-1 n mtr-1 btr-1) (buy-via c m b item-1 cost-1 n) (will-transfer c m b cost-0 n mtr-0 btr-0) (buy-via c m b item-0 cost-0 n) (buy-via c m b item cost n) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 rely-cust-3 rely-merc-3) (operation encryption-test (added-strand bank 2) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (0 1)) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc n cost-0 item-0 merc-conf-0 ncm-0 bank-conf-commit (sign (order c m b cost-0 for-bank) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost-0 n) (hash ncm-0 item-0 merc-conf-0) mtr-0 (cat (sign (order c m b cost-0 for-bank) (privk "sig" c)) for-bank)) (pubk "enc" b))) (recv (enc bank-conf-decommit (sign (bconf (hash c m b n cost-0 (hash n (hash ncm-0 item-0 merc-conf-0))) btr-0 mtr-0) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc n cost-1 item-1 merc-conf-1 ncm-1 bank-conf-commit-0 (sign (order c m b cost-1 for-bank-0) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost-1 n) (hash ncm-1 item-1 merc-conf-1) mtr-1 (cat (sign (order c m b cost-1 for-bank-0) (privk "sig" c)) for-bank-0)) (pubk "enc" b))) (recv (enc bank-conf-decommit-0 (sign (bconf (hash c m b n cost-1 (hash n (hash ncm-1 item-1 merc-conf-1))) btr-1 mtr-1) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb-0 bank-conf-0) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))))) (label 98) (parent 96) (unrealized (1 0) (1 2) (2 0) (2 2) (3 0)) (comment "2 in cohort - 2 not yet seen")) (defskeleton minipay-rely-guar (vars (for-bank bank-conf-commit bank-conf-decommit mesg) (account account-0 acct) (cost cost-0 amount) (n ncb ncm ncm-0 ncb-0 data) (item item-0 merchandise) (merc-conf bank-conf btr mtr merc-conf-0 btr-0 mtr-0 bank-conf-0 text) (c m b name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 3 (for-bank for-bank) (bank-conf-commit bank-conf-commit) (bank-conf-decommit bank-conf-decommit) (cost cost-0) (n n) (ncm ncm-0) (item item-0) (merc-conf merc-conf-0) (btr btr-0) (mtr mtr-0) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account-0) (cost cost) (n n) (ncb ncb-0) (bank-conf bank-conf-0) (btr btr) (mtr mtr) (c c) (m m) (b b)) (precedes ((0 0) (1 0)) ((0 0) (2 0)) ((2 1) (0 1))) (non-orig (privk "enc" b) (privk "sig" c) (privk "sig" b)) (uniq-orig n btr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (will-ship c m b item mtr) (will-transfer c m b cost-0 n mtr-0 btr-0) (buy-via c m b item-0 cost-0 n) (buy-via c m b item cost n) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 rely-cust-3 rely-merc-3) (operation encryption-test (added-strand bank 2) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (0 1)) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc n cost-0 item-0 merc-conf-0 ncm-0 bank-conf-commit (sign (order c m b cost-0 for-bank) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost-0 n) (hash ncm-0 item-0 merc-conf-0) mtr-0 (cat (sign (order c m b cost-0 for-bank) (privk "sig" c)) for-bank)) (pubk "enc" b))) (recv (enc bank-conf-decommit (sign (bconf (hash c m b n cost-0 (hash n (hash ncm-0 item-0 merc-conf-0))) btr-0 mtr-0) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb-0 bank-conf-0) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))))) (label 99) (parent 97) (unrealized (1 0) (1 2) (2 0)) (origs (btr (2 1)) (mtr-0 (1 1)) (n (0 0))) (comment "2 in cohort - 2 not yet seen")) (defskeleton minipay-rely-guar (vars (bank-conf-commit bank-conf-decommit for-bank bank-conf-commit-0 bank-conf-decommit-0 mesg) (account account-0 acct) (cost cost-0 amount) (n ncb ncm ncm-0 ncm-1 ncb-0 data) (item item-0 item-1 merchandise) (merc-conf bank-conf btr mtr merc-conf-0 btr-0 mtr-0 merc-conf-1 btr-1 mtr-1 bank-conf-0 text) (c m b name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 3 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit) (bank-conf-decommit bank-conf-decommit) (cost cost) (n n) (ncm ncm-0) (item item-0) (merc-conf merc-conf-0) (btr btr-0) (mtr mtr-0) (c c) (m m) (b b)) (defstrand merc 3 (for-bank for-bank) (bank-conf-commit bank-conf-commit-0) (bank-conf-decommit bank-conf-decommit-0) (cost cost-0) (n n) (ncm ncm-1) (item item-1) (merc-conf merc-conf-1) (btr btr-1) (mtr mtr-1) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account-0) (cost cost) (n n) (ncb ncb-0) (bank-conf bank-conf-0) (btr btr) (mtr mtr) (c c) (m m) (b b)) (precedes ((0 0) (1 0)) ((0 0) (2 0)) ((0 0) (3 0)) ((3 1) (0 1))) (non-orig (privk "enc" b) (privk "sig" c) (privk "sig" b)) (uniq-orig n btr mtr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (will-ship c m b item mtr) (will-transfer c m b cost-0 n mtr-1 btr-1) (buy-via c m b item-1 cost-0 n) (will-transfer c m b cost n mtr-0 btr-0) (buy-via c m b item-0 cost n) (buy-via c m b item cost n) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 rely-cust-3 rely-merc-3) (operation encryption-test (displaced 4 0 cust 1) (sign (order c m b cost-1 (enc n-0 cost-1 account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b))) (privk "sig" c)) (1 0)) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc n cost item-0 merc-conf-0 ncm-0 bank-conf-commit (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm-0 item-0 merc-conf-0) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit (sign (bconf (hash c m b n cost (hash n (hash ncm-0 item-0 merc-conf-0))) btr-0 mtr-0) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc n cost-0 item-1 merc-conf-1 ncm-1 bank-conf-commit-0 (sign (order c m b cost-0 for-bank) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost-0 n) (hash ncm-1 item-1 merc-conf-1) mtr-1 (cat (sign (order c m b cost-0 for-bank) (privk "sig" c)) for-bank)) (pubk "enc" b))) (recv (enc bank-conf-decommit-0 (sign (bconf (hash c m b n cost-0 (hash n (hash ncm-1 item-1 merc-conf-1))) btr-1 mtr-1) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb-0 bank-conf-0) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))))) (label 100) (parent 98) (unrealized (1 2) (2 0) (2 2) (3 0)) (comment "2 in cohort - 2 not yet seen")) (defskeleton minipay-rely-guar (vars (bank-conf-commit bank-conf-decommit for-bank bank-conf-commit-0 bank-conf-decommit-0 mesg) (account account-0 account-1 acct) (cost cost-0 cost-1 amount) (n ncb ncm ncm-0 ncm-1 ncb-0 n-0 ncb-1 ncm-2 data) (item item-0 item-1 item-2 merchandise) (merc-conf bank-conf btr mtr merc-conf-0 btr-0 mtr-0 merc-conf-1 btr-1 mtr-1 bank-conf-0 merc-conf-2 bank-conf-1 text) (c m b name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 3 (for-bank (enc n-0 cost-0 account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit) (bank-conf-decommit bank-conf-decommit) (cost cost-0) (n n) (ncm ncm-0) (item item-0) (merc-conf merc-conf-0) (btr btr-0) (mtr mtr-0) (c c) (m m) (b b)) (defstrand merc 3 (for-bank for-bank) (bank-conf-commit bank-conf-commit-0) (bank-conf-decommit bank-conf-decommit-0) (cost cost-1) (n n) (ncm ncm-1) (item item-1) (merc-conf merc-conf-1) (btr btr-1) (mtr mtr-1) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account-0) (cost cost) (n n) (ncb ncb-0) (bank-conf bank-conf-0) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account-1) (cost cost-0) (n n-0) (ncb ncb-1) (ncm ncm-2) (item item-2) (merc-conf merc-conf-2) (bank-conf bank-conf-1) (c c) (m m) (b b)) (precedes ((0 0) (1 0)) ((0 0) (2 0)) ((0 0) (3 0)) ((3 1) (0 1)) ((4 0) (1 0))) (non-orig (privk "enc" b) (privk "sig" c) (privk "sig" b)) (uniq-orig n btr mtr-0 mtr-1) (facts (neq n-0 ncb-1) (neq n ncb) (neq n-0 ncm-2) (neq n ncm) (neq ncm-2 ncb-1) (neq ncm ncb) (will-ship c m b item mtr) (will-transfer c m b cost-1 n mtr-1 btr-1) (buy-via c m b item-1 cost-1 n) (will-transfer c m b cost-0 n mtr-0 btr-0) (buy-via c m b item-0 cost-0 n) (buy-via c m b item-2 cost-0 n-0) (buy-via c m b item cost n) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 rely-cust-3 rely-merc-3) (operation encryption-test (added-strand cust 1) (sign (order c m b cost-0 (enc n-0 cost-0 account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b))) (privk "sig" c)) (1 0)) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc n cost-0 item-0 merc-conf-0 ncm-0 bank-conf-commit (sign (order c m b cost-0 (enc n-0 cost-0 account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost-0 n) (hash ncm-0 item-0 merc-conf-0) mtr-0 (cat (sign (order c m b cost-0 (enc n-0 cost-0 account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b))) (privk "sig" c)) (enc n-0 cost-0 account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit (sign (bconf (hash c m b n cost-0 (hash n (hash ncm-0 item-0 merc-conf-0))) btr-0 mtr-0) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc n cost-1 item-1 merc-conf-1 ncm-1 bank-conf-commit-0 (sign (order c m b cost-1 for-bank) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost-1 n) (hash ncm-1 item-1 merc-conf-1) mtr-1 (cat (sign (order c m b cost-1 for-bank) (privk "sig" c)) for-bank)) (pubk "enc" b))) (recv (enc bank-conf-decommit-0 (sign (bconf (hash c m b n cost-1 (hash n (hash ncm-1 item-1 merc-conf-1))) btr-1 mtr-1) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb-0 bank-conf-0) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n-0 cost-0 item-2 merc-conf-2 ncm-2 (hash n-0 (hash ncb-1 bank-conf-1)) (sign (order c m b cost-0 (enc n-0 cost-0 account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))))) (label 101) (parent 98) (unrealized (1 2) (2 0) (2 2) (3 0)) (comment "2 in cohort - 2 not yet seen")) (defskeleton minipay-rely-guar (vars (bank-conf-commit bank-conf-decommit mesg) (account account-0 acct) (cost amount) (n ncb ncm ncm-0 ncb-0 data) (item item-0 merchandise) (merc-conf bank-conf btr mtr merc-conf-0 btr-0 mtr-0 bank-conf-0 text) (c m b name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 3 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit) (bank-conf-decommit bank-conf-decommit) (cost cost) (n n) (ncm ncm-0) (item item-0) (merc-conf merc-conf-0) (btr btr-0) (mtr mtr-0) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account-0) (cost cost) (n n) (ncb ncb-0) (bank-conf bank-conf-0) (btr btr) (mtr mtr) (c c) (m m) (b b)) (precedes ((0 0) (1 0)) ((0 0) (2 0)) ((2 1) (0 1))) (non-orig (privk "enc" b) (privk "sig" c) (privk "sig" b)) (uniq-orig n btr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (will-ship c m b item mtr) (will-transfer c m b cost n mtr-0 btr-0) (buy-via c m b item-0 cost n) (buy-via c m b item cost n) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 rely-cust-3 rely-merc-3) (operation encryption-test (displaced 3 0 cust 1) (sign (order c m b cost-0 (enc n-0 cost-0 account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (privk "sig" c)) (1 0)) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc n cost item-0 merc-conf-0 ncm-0 bank-conf-commit (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm-0 item-0 merc-conf-0) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit (sign (bconf (hash c m b n cost (hash n (hash ncm-0 item-0 merc-conf-0))) btr-0 mtr-0) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb-0 bank-conf-0) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))))) (label 102) (parent 99) (unrealized (1 2) (2 0)) (origs (btr (2 1)) (mtr-0 (1 1)) (n (0 0))) (comment "2 in cohort - 2 not yet seen")) (defskeleton minipay-rely-guar (vars (bank-conf-commit bank-conf-decommit mesg) (account account-0 account-1 acct) (cost cost-0 amount) (n ncb ncm ncm-0 ncb-0 n-0 ncb-1 ncm-1 data) (item item-0 item-1 merchandise) (merc-conf bank-conf btr mtr merc-conf-0 btr-0 mtr-0 bank-conf-0 merc-conf-1 bank-conf-1 text) (c m b name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 3 (for-bank (enc n-0 cost-0 account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit) (bank-conf-decommit bank-conf-decommit) (cost cost-0) (n n) (ncm ncm-0) (item item-0) (merc-conf merc-conf-0) (btr btr-0) (mtr mtr-0) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account-0) (cost cost) (n n) (ncb ncb-0) (bank-conf bank-conf-0) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account-1) (cost cost-0) (n n-0) (ncb ncb-1) (ncm ncm-1) (item item-1) (merc-conf merc-conf-1) (bank-conf bank-conf-1) (c c) (m m) (b b)) (precedes ((0 0) (1 0)) ((0 0) (2 0)) ((2 1) (0 1)) ((3 0) (1 0))) (non-orig (privk "enc" b) (privk "sig" c) (privk "sig" b)) (uniq-orig n btr mtr-0) (facts (neq n-0 ncb-1) (neq n ncb) (neq n-0 ncm-1) (neq n ncm) (neq ncm-1 ncb-1) (neq ncm ncb) (will-ship c m b item mtr) (will-transfer c m b cost-0 n mtr-0 btr-0) (buy-via c m b item-0 cost-0 n) (buy-via c m b item-1 cost-0 n-0) (buy-via c m b item cost n) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 rely-cust-3 rely-merc-3) (operation encryption-test (added-strand cust 1) (sign (order c m b cost-0 (enc n-0 cost-0 account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (privk "sig" c)) (1 0)) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc n cost-0 item-0 merc-conf-0 ncm-0 bank-conf-commit (sign (order c m b cost-0 (enc n-0 cost-0 account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost-0 n) (hash ncm-0 item-0 merc-conf-0) mtr-0 (cat (sign (order c m b cost-0 (enc n-0 cost-0 account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (privk "sig" c)) (enc n-0 cost-0 account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit (sign (bconf (hash c m b n cost-0 (hash n (hash ncm-0 item-0 merc-conf-0))) btr-0 mtr-0) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb-0 bank-conf-0) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n-0 cost-0 item-1 merc-conf-1 ncm-1 (hash n-0 (hash ncb-1 bank-conf-1)) (sign (order c m b cost-0 (enc n-0 cost-0 account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))))) (label 103) (parent 99) (unrealized (1 2) (2 0)) (comment "2 in cohort - 2 not yet seen")) (defskeleton minipay-rely-guar (vars (bank-conf-commit bank-conf-decommit for-bank bank-conf-commit-0 bank-conf-decommit-0 mesg) (account account-0 acct) (cost cost-0 amount) (n ncb ncm ncm-0 ncb-0 data) (item item-0 merchandise) (merc-conf bank-conf btr mtr merc-conf-0 btr-0 mtr-0 bank-conf-0 text) (c m b name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 3 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit) (bank-conf-decommit bank-conf-decommit) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 3 (for-bank for-bank) (bank-conf-commit bank-conf-commit-0) (bank-conf-decommit bank-conf-decommit-0) (cost cost-0) (n n) (ncm ncm-0) (item item-0) (merc-conf merc-conf-0) (btr btr-0) (mtr mtr-0) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account-0) (cost cost) (n n) (ncb ncb-0) (bank-conf bank-conf-0) (btr btr) (mtr mtr) (c c) (m m) (b b)) (precedes ((0 0) (1 0)) ((0 0) (2 0)) ((1 1) (3 0)) ((3 1) (0 1)) ((3 1) (1 2))) (non-orig (privk "enc" b) (privk "sig" c) (privk "sig" b)) (uniq-orig n btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (will-ship c m b item mtr) (will-transfer c m b cost-0 n mtr-0 btr-0) (buy-via c m b item-0 cost-0 n) (buy-via c m b item cost n) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 rely-cust-3 rely-merc-3) (operation encryption-test (displaced 4 3 bank 2) (sign (bconf (hash c m b n cost (hash n (hash ncm-1 item-1 merc-conf-1))) btr-1 mtr-1) (privk "sig" b)) (1 2)) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc n cost item merc-conf ncm bank-conf-commit (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc n cost-0 item-0 merc-conf-0 ncm-0 bank-conf-commit-0 (sign (order c m b cost-0 for-bank) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost-0 n) (hash ncm-0 item-0 merc-conf-0) mtr-0 (cat (sign (order c m b cost-0 for-bank) (privk "sig" c)) for-bank)) (pubk "enc" b))) (recv (enc bank-conf-decommit-0 (sign (bconf (hash c m b n cost-0 (hash n (hash ncm-0 item-0 merc-conf-0))) btr-0 mtr-0) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb-0 bank-conf-0) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))))) (label 104) (parent 100) (unrealized (2 0) (2 2) (3 0)) (comment "2 in cohort - 2 not yet seen")) (defskeleton minipay-rely-guar (vars (bank-conf-commit bank-conf-decommit for-bank bank-conf-commit-0 bank-conf-decommit-0 mesg) (account account-0 account-1 acct) (cost cost-0 amount) (n ncb ncm ncm-0 ncm-1 ncb-0 ncb-1 data) (item item-0 item-1 merchandise) (merc-conf bank-conf btr mtr merc-conf-0 btr-0 mtr-0 merc-conf-1 btr-1 mtr-1 bank-conf-0 bank-conf-1 text) (c m b name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 3 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit) (bank-conf-decommit bank-conf-decommit) (cost cost) (n n) (ncm ncm-0) (item item-0) (merc-conf merc-conf-0) (btr btr-0) (mtr mtr-0) (c c) (m m) (b b)) (defstrand merc 3 (for-bank for-bank) (bank-conf-commit bank-conf-commit-0) (bank-conf-decommit bank-conf-decommit-0) (cost cost-0) (n n) (ncm ncm-1) (item item-1) (merc-conf merc-conf-1) (btr btr-1) (mtr mtr-1) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account-0) (cost cost) (n n) (ncb ncb-0) (bank-conf bank-conf-0) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm-0 item-0 merc-conf-0)) (account account-1) (cost cost) (n n) (ncb ncb-1) (bank-conf bank-conf-1) (btr btr-0) (mtr mtr-0) (c c) (m m) (b b)) (precedes ((0 0) (1 0)) ((0 0) (2 0)) ((0 0) (3 0)) ((1 1) (4 0)) ((3 1) (0 1)) ((4 1) (1 2))) (non-orig (privk "enc" b) (privk "sig" c) (privk "sig" b)) (uniq-orig n btr btr-0 mtr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (will-ship c m b item mtr) (will-transfer c m b cost-0 n mtr-1 btr-1) (buy-via c m b item-1 cost-0 n) (buy-via c m b item-0 cost n) (buy-via c m b item cost n) (will-transfer c m b cost n mtr-0 btr-0) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 rely-cust-3 rely-merc-3) (operation encryption-test (added-strand bank 2) (sign (bconf (hash c m b n cost (hash n (hash ncm-0 item-0 merc-conf-0))) btr-0 mtr-0) (privk "sig" b)) (1 2)) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc n cost item-0 merc-conf-0 ncm-0 bank-conf-commit (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm-0 item-0 merc-conf-0) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit (sign (bconf (hash c m b n cost (hash n (hash ncm-0 item-0 merc-conf-0))) btr-0 mtr-0) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc n cost-0 item-1 merc-conf-1 ncm-1 bank-conf-commit-0 (sign (order c m b cost-0 for-bank) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost-0 n) (hash ncm-1 item-1 merc-conf-1) mtr-1 (cat (sign (order c m b cost-0 for-bank) (privk "sig" c)) for-bank)) (pubk "enc" b))) (recv (enc bank-conf-decommit-0 (sign (bconf (hash c m b n cost-0 (hash n (hash ncm-1 item-1 merc-conf-1))) btr-1 mtr-1) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb-0 bank-conf-0) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm-0 item-0 merc-conf-0) mtr-0 (cat (sign (order c m b cost (enc n cost account-1 bank-conf-1 ncb-1 (hash n (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-1 bank-conf-1 ncb-1 (hash n (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb-1 bank-conf-1) (sign (bconf (hash c m b n cost (hash n (hash ncm-0 item-0 merc-conf-0))) btr-0 mtr-0) (privk "sig" b)) (pubk "enc" m))))) (label 105) (parent 100) (unrealized (2 0) (2 2) (3 0) (4 0)) (comment "2 in cohort - 2 not yet seen")) (defskeleton minipay-rely-guar (vars (bank-conf-commit bank-conf-decommit for-bank bank-conf-commit-0 bank-conf-decommit-0 mesg) (account account-0 account-1 acct) (cost cost-0 amount) (n ncb ncm ncm-0 ncb-0 n-0 ncb-1 ncm-1 data) (item item-0 item-1 merchandise) (merc-conf bank-conf btr mtr merc-conf-0 btr-0 mtr-0 bank-conf-0 merc-conf-1 bank-conf-1 text) (c m b name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 3 (for-bank (enc n-0 cost account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit) (bank-conf-decommit bank-conf-decommit) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 3 (for-bank for-bank) (bank-conf-commit bank-conf-commit-0) (bank-conf-decommit bank-conf-decommit-0) (cost cost-0) (n n) (ncm ncm-0) (item item-0) (merc-conf merc-conf-0) (btr btr-0) (mtr mtr-0) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account-0) (cost cost) (n n) (ncb ncb-0) (bank-conf bank-conf-0) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account-1) (cost cost) (n n-0) (ncb ncb-1) (ncm ncm-1) (item item-1) (merc-conf merc-conf-1) (bank-conf bank-conf-1) (c c) (m m) (b b)) (precedes ((0 0) (1 0)) ((0 0) (2 0)) ((1 1) (3 0)) ((3 1) (0 1)) ((3 1) (1 2)) ((4 0) (1 0))) (non-orig (privk "enc" b) (privk "sig" c) (privk "sig" b)) (uniq-orig n btr mtr mtr-0) (facts (neq n-0 ncb-1) (neq n ncb) (neq n-0 ncm-1) (neq n ncm) (neq ncm-1 ncb-1) (neq ncm ncb) (will-ship c m b item mtr) (will-transfer c m b cost-0 n mtr-0 btr-0) (buy-via c m b item-0 cost-0 n) (buy-via c m b item-1 cost n-0) (buy-via c m b item cost n) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 rely-cust-3 rely-merc-3) (operation encryption-test (displaced 5 3 bank 2) (sign (bconf (hash c m b n cost-1 (hash n (hash ncm-2 item-2 merc-conf-2))) btr-1 mtr-1) (privk "sig" b)) (1 2)) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc n cost item merc-conf ncm bank-conf-commit (sign (order c m b cost (enc n-0 cost account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n-0 cost account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (privk "sig" c)) (enc n-0 cost account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc n cost-0 item-0 merc-conf-0 ncm-0 bank-conf-commit-0 (sign (order c m b cost-0 for-bank) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost-0 n) (hash ncm-0 item-0 merc-conf-0) mtr-0 (cat (sign (order c m b cost-0 for-bank) (privk "sig" c)) for-bank)) (pubk "enc" b))) (recv (enc bank-conf-decommit-0 (sign (bconf (hash c m b n cost-0 (hash n (hash ncm-0 item-0 merc-conf-0))) btr-0 mtr-0) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb-0 bank-conf-0) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n-0 cost item-1 merc-conf-1 ncm-1 (hash n-0 (hash ncb-1 bank-conf-1)) (sign (order c m b cost (enc n-0 cost account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))))) (label 106) (parent 101) (unrealized (2 0) (2 2) (3 0)) (comment "3 in cohort - 3 not yet seen")) (defskeleton minipay-rely-guar (vars (bank-conf-commit bank-conf-decommit for-bank bank-conf-commit-0 bank-conf-decommit-0 mesg) (account account-0 account-1 account-2 acct) (cost cost-0 cost-1 amount) (n ncb ncm ncm-0 ncm-1 ncb-0 n-0 ncb-1 ncm-2 ncb-2 data) (item item-0 item-1 item-2 merchandise) (merc-conf bank-conf btr mtr merc-conf-0 btr-0 mtr-0 merc-conf-1 btr-1 mtr-1 bank-conf-0 merc-conf-2 bank-conf-1 bank-conf-2 text) (c m b name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 3 (for-bank (enc n-0 cost-0 account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit) (bank-conf-decommit bank-conf-decommit) (cost cost-0) (n n) (ncm ncm-0) (item item-0) (merc-conf merc-conf-0) (btr btr-0) (mtr mtr-0) (c c) (m m) (b b)) (defstrand merc 3 (for-bank for-bank) (bank-conf-commit bank-conf-commit-0) (bank-conf-decommit bank-conf-decommit-0) (cost cost-1) (n n) (ncm ncm-1) (item item-1) (merc-conf merc-conf-1) (btr btr-1) (mtr mtr-1) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account-0) (cost cost) (n n) (ncb ncb-0) (bank-conf bank-conf-0) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account-1) (cost cost-0) (n n-0) (ncb ncb-1) (ncm ncm-2) (item item-2) (merc-conf merc-conf-2) (bank-conf bank-conf-1) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm-0 item-0 merc-conf-0)) (account account-2) (cost cost-0) (n n) (ncb ncb-2) (bank-conf bank-conf-2) (btr btr-0) (mtr mtr-0) (c c) (m m) (b b)) (precedes ((0 0) (1 0)) ((0 0) (2 0)) ((0 0) (3 0)) ((1 1) (5 0)) ((3 1) (0 1)) ((4 0) (1 0)) ((5 1) (1 2))) (non-orig (privk "enc" b) (privk "sig" c) (privk "sig" b)) (uniq-orig n btr btr-0 mtr-0 mtr-1) (facts (neq n-0 ncb-1) (neq n ncb) (neq n-0 ncm-2) (neq n ncm) (neq ncm-2 ncb-1) (neq ncm ncb) (will-ship c m b item mtr) (will-transfer c m b cost-1 n mtr-1 btr-1) (buy-via c m b item-1 cost-1 n) (buy-via c m b item-0 cost-0 n) (buy-via c m b item-2 cost-0 n-0) (buy-via c m b item cost n) (will-transfer c m b cost-0 n mtr-0 btr-0) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 rely-cust-3 rely-merc-3) (operation encryption-test (added-strand bank 2) (sign (bconf (hash c m b n cost-0 (hash n (hash ncm-0 item-0 merc-conf-0))) btr-0 mtr-0) (privk "sig" b)) (1 2)) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc n cost-0 item-0 merc-conf-0 ncm-0 bank-conf-commit (sign (order c m b cost-0 (enc n-0 cost-0 account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost-0 n) (hash ncm-0 item-0 merc-conf-0) mtr-0 (cat (sign (order c m b cost-0 (enc n-0 cost-0 account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b))) (privk "sig" c)) (enc n-0 cost-0 account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit (sign (bconf (hash c m b n cost-0 (hash n (hash ncm-0 item-0 merc-conf-0))) btr-0 mtr-0) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc n cost-1 item-1 merc-conf-1 ncm-1 bank-conf-commit-0 (sign (order c m b cost-1 for-bank) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost-1 n) (hash ncm-1 item-1 merc-conf-1) mtr-1 (cat (sign (order c m b cost-1 for-bank) (privk "sig" c)) for-bank)) (pubk "enc" b))) (recv (enc bank-conf-decommit-0 (sign (bconf (hash c m b n cost-1 (hash n (hash ncm-1 item-1 merc-conf-1))) btr-1 mtr-1) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb-0 bank-conf-0) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n-0 cost-0 item-2 merc-conf-2 ncm-2 (hash n-0 (hash ncb-1 bank-conf-1)) (sign (order c m b cost-0 (enc n-0 cost-0 account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost-0 n) (hash ncm-0 item-0 merc-conf-0) mtr-0 (cat (sign (order c m b cost-0 (enc n cost-0 account-2 bank-conf-2 ncb-2 (hash n (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (enc n cost-0 account-2 bank-conf-2 ncb-2 (hash n (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb-2 bank-conf-2) (sign (bconf (hash c m b n cost-0 (hash n (hash ncm-0 item-0 merc-conf-0))) btr-0 mtr-0) (privk "sig" b)) (pubk "enc" m))))) (label 107) (parent 101) (unrealized (2 0) (2 2) (3 0) (5 0)) (comment "3 in cohort - 3 not yet seen")) (defskeleton minipay-rely-guar (vars (bank-conf-commit bank-conf-decommit mesg) (account account-0 acct) (cost amount) (n ncb ncm ncb-0 data) (item merchandise) (merc-conf bank-conf btr mtr bank-conf-0 text) (c m b name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 3 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit) (bank-conf-decommit bank-conf-decommit) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account-0) (cost cost) (n n) (ncb ncb-0) (bank-conf bank-conf-0) (btr btr) (mtr mtr) (c c) (m m) (b b)) (precedes ((0 0) (1 0)) ((1 1) (2 0)) ((2 1) (0 1)) ((2 1) (1 2))) (non-orig (privk "enc" b) (privk "sig" c) (privk "sig" b)) (uniq-orig n btr mtr) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (will-ship c m b item mtr) (buy-via c m b item cost n) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 rely-cust-3) (operation encryption-test (displaced 3 2 bank 2) (sign (bconf (hash c m b n cost (hash n (hash ncm-0 item-0 merc-conf-0))) btr-0 mtr-0) (privk "sig" b)) (1 2)) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc n cost item merc-conf ncm bank-conf-commit (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb-0 bank-conf-0) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))))) (label 108) (parent 102) (unrealized (2 0)) (origs (btr (2 1)) (mtr (1 1)) (n (0 0))) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay-rely-guar (vars (bank-conf-commit bank-conf-decommit mesg) (account account-0 account-1 acct) (cost amount) (n ncb ncm ncm-0 ncb-0 ncb-1 data) (item item-0 merchandise) (merc-conf bank-conf btr mtr merc-conf-0 btr-0 mtr-0 bank-conf-0 bank-conf-1 text) (c m b name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 3 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit) (bank-conf-decommit bank-conf-decommit) (cost cost) (n n) (ncm ncm-0) (item item-0) (merc-conf merc-conf-0) (btr btr-0) (mtr mtr-0) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account-0) (cost cost) (n n) (ncb ncb-0) (bank-conf bank-conf-0) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm-0 item-0 merc-conf-0)) (account account-1) (cost cost) (n n) (ncb ncb-1) (bank-conf bank-conf-1) (btr btr-0) (mtr mtr-0) (c c) (m m) (b b)) (precedes ((0 0) (1 0)) ((0 0) (2 0)) ((1 1) (3 0)) ((2 1) (0 1)) ((3 1) (1 2))) (non-orig (privk "enc" b) (privk "sig" c) (privk "sig" b)) (uniq-orig n btr btr-0 mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (will-ship c m b item mtr) (buy-via c m b item-0 cost n) (buy-via c m b item cost n) (will-transfer c m b cost n mtr-0 btr-0) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 rely-cust-3 rely-merc-3) (operation encryption-test (added-strand bank 2) (sign (bconf (hash c m b n cost (hash n (hash ncm-0 item-0 merc-conf-0))) btr-0 mtr-0) (privk "sig" b)) (1 2)) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc n cost item-0 merc-conf-0 ncm-0 bank-conf-commit (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm-0 item-0 merc-conf-0) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit (sign (bconf (hash c m b n cost (hash n (hash ncm-0 item-0 merc-conf-0))) btr-0 mtr-0) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb-0 bank-conf-0) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm-0 item-0 merc-conf-0) mtr-0 (cat (sign (order c m b cost (enc n cost account-1 bank-conf-1 ncb-1 (hash n (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-1 bank-conf-1 ncb-1 (hash n (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb-1 bank-conf-1) (sign (bconf (hash c m b n cost (hash n (hash ncm-0 item-0 merc-conf-0))) btr-0 mtr-0) (privk "sig" b)) (pubk "enc" m))))) (label 109) (parent 102) (unrealized (2 0) (3 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay-rely-guar (vars (bank-conf-commit bank-conf-decommit mesg) (account account-0 account-1 acct) (cost amount) (n ncb ncm ncb-0 n-0 ncb-1 ncm-0 data) (item item-0 merchandise) (merc-conf bank-conf btr mtr bank-conf-0 merc-conf-0 bank-conf-1 text) (c m b name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 3 (for-bank (enc n-0 cost account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit) (bank-conf-decommit bank-conf-decommit) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account-0) (cost cost) (n n) (ncb ncb-0) (bank-conf bank-conf-0) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account-1) (cost cost) (n n-0) (ncb ncb-1) (ncm ncm-0) (item item-0) (merc-conf merc-conf-0) (bank-conf bank-conf-1) (c c) (m m) (b b)) (precedes ((0 0) (1 0)) ((1 1) (2 0)) ((2 1) (0 1)) ((2 1) (1 2)) ((3 0) (1 0))) (non-orig (privk "enc" b) (privk "sig" c) (privk "sig" b)) (uniq-orig n btr mtr) (facts (neq n-0 ncb-1) (neq n ncb) (neq n-0 ncm-0) (neq n ncm) (neq ncm-0 ncb-1) (neq ncm ncb) (will-ship c m b item mtr) (buy-via c m b item-0 cost n-0) (buy-via c m b item cost n) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 rely-cust-3) (operation encryption-test (displaced 4 2 bank 2) (sign (bconf (hash c m b n cost-0 (hash n (hash ncm-1 item-1 merc-conf-1))) btr-0 mtr-0) (privk "sig" b)) (1 2)) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc n cost item merc-conf ncm bank-conf-commit (sign (order c m b cost (enc n-0 cost account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n-0 cost account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (enc n-0 cost account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb-0 bank-conf-0) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n-0 cost item-0 merc-conf-0 ncm-0 (hash n-0 (hash ncb-1 bank-conf-1)) (sign (order c m b cost (enc n-0 cost account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))))) (label 110) (parent 103) (unrealized (2 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay-rely-guar (vars (bank-conf-commit bank-conf-decommit mesg) (account account-0 account-1 account-2 acct) (cost cost-0 amount) (n ncb ncm ncm-0 ncb-0 n-0 ncb-1 ncm-1 ncb-2 data) (item item-0 item-1 merchandise) (merc-conf bank-conf btr mtr merc-conf-0 btr-0 mtr-0 bank-conf-0 merc-conf-1 bank-conf-1 bank-conf-2 text) (c m b name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 3 (for-bank (enc n-0 cost-0 account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit) (bank-conf-decommit bank-conf-decommit) (cost cost-0) (n n) (ncm ncm-0) (item item-0) (merc-conf merc-conf-0) (btr btr-0) (mtr mtr-0) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account-0) (cost cost) (n n) (ncb ncb-0) (bank-conf bank-conf-0) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account-1) (cost cost-0) (n n-0) (ncb ncb-1) (ncm ncm-1) (item item-1) (merc-conf merc-conf-1) (bank-conf bank-conf-1) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm-0 item-0 merc-conf-0)) (account account-2) (cost cost-0) (n n) (ncb ncb-2) (bank-conf bank-conf-2) (btr btr-0) (mtr mtr-0) (c c) (m m) (b b)) (precedes ((0 0) (1 0)) ((0 0) (2 0)) ((1 1) (4 0)) ((2 1) (0 1)) ((3 0) (1 0)) ((4 1) (1 2))) (non-orig (privk "enc" b) (privk "sig" c) (privk "sig" b)) (uniq-orig n btr btr-0 mtr-0) (facts (neq n-0 ncb-1) (neq n ncb) (neq n-0 ncm-1) (neq n ncm) (neq ncm-1 ncb-1) (neq ncm ncb) (will-ship c m b item mtr) (buy-via c m b item-0 cost-0 n) (buy-via c m b item-1 cost-0 n-0) (buy-via c m b item cost n) (will-transfer c m b cost-0 n mtr-0 btr-0) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 rely-cust-3 rely-merc-3) (operation encryption-test (added-strand bank 2) (sign (bconf (hash c m b n cost-0 (hash n (hash ncm-0 item-0 merc-conf-0))) btr-0 mtr-0) (privk "sig" b)) (1 2)) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc n cost-0 item-0 merc-conf-0 ncm-0 bank-conf-commit (sign (order c m b cost-0 (enc n-0 cost-0 account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost-0 n) (hash ncm-0 item-0 merc-conf-0) mtr-0 (cat (sign (order c m b cost-0 (enc n-0 cost-0 account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (privk "sig" c)) (enc n-0 cost-0 account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit (sign (bconf (hash c m b n cost-0 (hash n (hash ncm-0 item-0 merc-conf-0))) btr-0 mtr-0) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb-0 bank-conf-0) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n-0 cost-0 item-1 merc-conf-1 ncm-1 (hash n-0 (hash ncb-1 bank-conf-1)) (sign (order c m b cost-0 (enc n-0 cost-0 account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost-0 n) (hash ncm-0 item-0 merc-conf-0) mtr-0 (cat (sign (order c m b cost-0 (enc n cost-0 account-2 bank-conf-2 ncb-2 (hash n (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (enc n cost-0 account-2 bank-conf-2 ncb-2 (hash n (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb-2 bank-conf-2) (sign (bconf (hash c m b n cost-0 (hash n (hash ncm-0 item-0 merc-conf-0))) btr-0 mtr-0) (privk "sig" b)) (pubk "enc" m))))) (label 111) (parent 103) (unrealized (2 0) (4 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay-rely-guar (vars (bank-conf-commit bank-conf-decommit bank-conf-commit-0 bank-conf-decommit-0 mesg) (account account-0 acct) (cost amount) (n ncb ncm ncm-0 ncb-0 data) (item item-0 merchandise) (merc-conf bank-conf btr mtr merc-conf-0 btr-0 mtr-0 bank-conf-0 text) (c m b name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 3 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit) (bank-conf-decommit bank-conf-decommit) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 3 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit-0) (bank-conf-decommit bank-conf-decommit-0) (cost cost) (n n) (ncm ncm-0) (item item-0) (merc-conf merc-conf-0) (btr btr-0) (mtr mtr-0) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account-0) (cost cost) (n n) (ncb ncb-0) (bank-conf bank-conf-0) (btr btr) (mtr mtr) (c c) (m m) (b b)) (precedes ((0 0) (1 0)) ((0 0) (2 0)) ((1 1) (3 0)) ((3 1) (0 1)) ((3 1) (1 2))) (non-orig (privk "enc" b) (privk "sig" c) (privk "sig" b)) (uniq-orig n btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (will-ship c m b item mtr) (will-transfer c m b cost n mtr-0 btr-0) (buy-via c m b item-0 cost n) (buy-via c m b item cost n) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 rely-cust-3 rely-merc-3) (operation encryption-test (displaced 4 0 cust 1) (sign (order c m b cost-0 (enc n-0 cost-0 account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (privk "sig" c)) (2 0)) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc n cost item merc-conf ncm bank-conf-commit (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc n cost item-0 merc-conf-0 ncm-0 bank-conf-commit-0 (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm-0 item-0 merc-conf-0) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit-0 (sign (bconf (hash c m b n cost (hash n (hash ncm-0 item-0 merc-conf-0))) btr-0 mtr-0) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb-0 bank-conf-0) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))))) (label 112) (parent 104) (unrealized (2 2) (3 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay-rely-guar (vars (bank-conf-commit bank-conf-decommit bank-conf-commit-0 bank-conf-decommit-0 mesg) (account account-0 account-1 acct) (cost cost-0 amount) (n ncb ncm ncm-0 ncb-0 n-0 ncb-1 ncm-1 data) (item item-0 item-1 merchandise) (merc-conf bank-conf btr mtr merc-conf-0 btr-0 mtr-0 bank-conf-0 merc-conf-1 bank-conf-1 text) (c m b name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 3 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit) (bank-conf-decommit bank-conf-decommit) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 3 (for-bank (enc n-0 cost-0 account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit-0) (bank-conf-decommit bank-conf-decommit-0) (cost cost-0) (n n) (ncm ncm-0) (item item-0) (merc-conf merc-conf-0) (btr btr-0) (mtr mtr-0) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account-0) (cost cost) (n n) (ncb ncb-0) (bank-conf bank-conf-0) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account-1) (cost cost-0) (n n-0) (ncb ncb-1) (ncm ncm-1) (item item-1) (merc-conf merc-conf-1) (bank-conf bank-conf-1) (c c) (m m) (b b)) (precedes ((0 0) (1 0)) ((0 0) (2 0)) ((1 1) (3 0)) ((3 1) (0 1)) ((3 1) (1 2)) ((4 0) (2 0))) (non-orig (privk "enc" b) (privk "sig" c) (privk "sig" b)) (uniq-orig n btr mtr mtr-0) (facts (neq n-0 ncb-1) (neq n ncb) (neq n-0 ncm-1) (neq n ncm) (neq ncm-1 ncb-1) (neq ncm ncb) (will-ship c m b item mtr) (will-transfer c m b cost-0 n mtr-0 btr-0) (buy-via c m b item-0 cost-0 n) (buy-via c m b item-1 cost-0 n-0) (buy-via c m b item cost n) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 rely-cust-3 rely-merc-3) (operation encryption-test (added-strand cust 1) (sign (order c m b cost-0 (enc n-0 cost-0 account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (privk "sig" c)) (2 0)) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc n cost item merc-conf ncm bank-conf-commit (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc n cost-0 item-0 merc-conf-0 ncm-0 bank-conf-commit-0 (sign (order c m b cost-0 (enc n-0 cost-0 account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost-0 n) (hash ncm-0 item-0 merc-conf-0) mtr-0 (cat (sign (order c m b cost-0 (enc n-0 cost-0 account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (privk "sig" c)) (enc n-0 cost-0 account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit-0 (sign (bconf (hash c m b n cost-0 (hash n (hash ncm-0 item-0 merc-conf-0))) btr-0 mtr-0) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb-0 bank-conf-0) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n-0 cost-0 item-1 merc-conf-1 ncm-1 (hash n-0 (hash ncb-1 bank-conf-1)) (sign (order c m b cost-0 (enc n-0 cost-0 account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))))) (label 113) (parent 104) (unrealized (2 2) (3 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay-rely-guar (vars (bank-conf-commit bank-conf-decommit bank-conf-commit-0 bank-conf-decommit-0 mesg) (account account-0 account-1 acct) (cost amount) (n ncb ncm ncm-0 ncm-1 ncb-0 ncb-1 data) (item item-0 item-1 merchandise) (merc-conf bank-conf btr mtr merc-conf-0 btr-0 mtr-0 merc-conf-1 btr-1 mtr-1 bank-conf-0 bank-conf-1 text) (c m b name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 3 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit) (bank-conf-decommit bank-conf-decommit) (cost cost) (n n) (ncm ncm-0) (item item-0) (merc-conf merc-conf-0) (btr btr-0) (mtr mtr-0) (c c) (m m) (b b)) (defstrand merc 3 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit-0) (bank-conf-decommit bank-conf-decommit-0) (cost cost) (n n) (ncm ncm-1) (item item-1) (merc-conf merc-conf-1) (btr btr-1) (mtr mtr-1) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account-0) (cost cost) (n n) (ncb ncb-0) (bank-conf bank-conf-0) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm-0 item-0 merc-conf-0)) (account account-1) (cost cost) (n n) (ncb ncb-1) (bank-conf bank-conf-1) (btr btr-0) (mtr mtr-0) (c c) (m m) (b b)) (precedes ((0 0) (1 0)) ((0 0) (2 0)) ((0 0) (3 0)) ((1 1) (4 0)) ((3 1) (0 1)) ((4 1) (1 2))) (non-orig (privk "enc" b) (privk "sig" c) (privk "sig" b)) (uniq-orig n btr btr-0 mtr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (will-ship c m b item mtr) (will-transfer c m b cost n mtr-1 btr-1) (buy-via c m b item-1 cost n) (buy-via c m b item-0 cost n) (buy-via c m b item cost n) (will-transfer c m b cost n mtr-0 btr-0) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 rely-cust-3 rely-merc-3) (operation encryption-test (displaced 5 0 cust 1) (sign (order c m b cost-0 (enc n-0 cost-0 account-2 bank-conf-2 ncb-2 (hash n-0 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b))) (privk "sig" c)) (2 0)) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc n cost item-0 merc-conf-0 ncm-0 bank-conf-commit (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm-0 item-0 merc-conf-0) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit (sign (bconf (hash c m b n cost (hash n (hash ncm-0 item-0 merc-conf-0))) btr-0 mtr-0) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc n cost item-1 merc-conf-1 ncm-1 bank-conf-commit-0 (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm-1 item-1 merc-conf-1) mtr-1 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit-0 (sign (bconf (hash c m b n cost (hash n (hash ncm-1 item-1 merc-conf-1))) btr-1 mtr-1) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb-0 bank-conf-0) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm-0 item-0 merc-conf-0) mtr-0 (cat (sign (order c m b cost (enc n cost account-1 bank-conf-1 ncb-1 (hash n (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-1 bank-conf-1 ncb-1 (hash n (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb-1 bank-conf-1) (sign (bconf (hash c m b n cost (hash n (hash ncm-0 item-0 merc-conf-0))) btr-0 mtr-0) (privk "sig" b)) (pubk "enc" m))))) (label 114) (parent 105) (seen 126) (unrealized (2 2) (3 0) (4 0)) (comment "2 in cohort - 1 not yet seen")) (defskeleton minipay-rely-guar (vars (bank-conf-commit bank-conf-decommit bank-conf-commit-0 bank-conf-decommit-0 mesg) (account account-0 account-1 account-2 acct) (cost cost-0 amount) (n ncb ncm ncm-0 ncm-1 ncb-0 ncb-1 n-0 ncb-2 ncm-2 data) (item item-0 item-1 item-2 merchandise) (merc-conf bank-conf btr mtr merc-conf-0 btr-0 mtr-0 merc-conf-1 btr-1 mtr-1 bank-conf-0 bank-conf-1 merc-conf-2 bank-conf-2 text) (c m b name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 3 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit) (bank-conf-decommit bank-conf-decommit) (cost cost) (n n) (ncm ncm-0) (item item-0) (merc-conf merc-conf-0) (btr btr-0) (mtr mtr-0) (c c) (m m) (b b)) (defstrand merc 3 (for-bank (enc n-0 cost-0 account-2 bank-conf-2 ncb-2 (hash n-0 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit-0) (bank-conf-decommit bank-conf-decommit-0) (cost cost-0) (n n) (ncm ncm-1) (item item-1) (merc-conf merc-conf-1) (btr btr-1) (mtr mtr-1) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account-0) (cost cost) (n n) (ncb ncb-0) (bank-conf bank-conf-0) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm-0 item-0 merc-conf-0)) (account account-1) (cost cost) (n n) (ncb ncb-1) (bank-conf bank-conf-1) (btr btr-0) (mtr mtr-0) (c c) (m m) (b b)) (defstrand cust 1 (account account-2) (cost cost-0) (n n-0) (ncb ncb-2) (ncm ncm-2) (item item-2) (merc-conf merc-conf-2) (bank-conf bank-conf-2) (c c) (m m) (b b)) (precedes ((0 0) (1 0)) ((0 0) (2 0)) ((0 0) (3 0)) ((1 1) (4 0)) ((3 1) (0 1)) ((4 1) (1 2)) ((5 0) (2 0))) (non-orig (privk "enc" b) (privk "sig" c) (privk "sig" b)) (uniq-orig n btr btr-0 mtr-0 mtr-1) (facts (neq n-0 ncb-2) (neq n ncb) (neq n-0 ncm-2) (neq n ncm) (neq ncm-2 ncb-2) (neq ncm ncb) (will-ship c m b item mtr) (will-transfer c m b cost-0 n mtr-1 btr-1) (buy-via c m b item-1 cost-0 n) (buy-via c m b item-0 cost n) (buy-via c m b item-2 cost-0 n-0) (buy-via c m b item cost n) (will-transfer c m b cost n mtr-0 btr-0) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 rely-cust-3 rely-merc-3) (operation encryption-test (added-strand cust 1) (sign (order c m b cost-0 (enc n-0 cost-0 account-2 bank-conf-2 ncb-2 (hash n-0 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b))) (privk "sig" c)) (2 0)) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc n cost item-0 merc-conf-0 ncm-0 bank-conf-commit (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm-0 item-0 merc-conf-0) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit (sign (bconf (hash c m b n cost (hash n (hash ncm-0 item-0 merc-conf-0))) btr-0 mtr-0) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc n cost-0 item-1 merc-conf-1 ncm-1 bank-conf-commit-0 (sign (order c m b cost-0 (enc n-0 cost-0 account-2 bank-conf-2 ncb-2 (hash n-0 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost-0 n) (hash ncm-1 item-1 merc-conf-1) mtr-1 (cat (sign (order c m b cost-0 (enc n-0 cost-0 account-2 bank-conf-2 ncb-2 (hash n-0 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b))) (privk "sig" c)) (enc n-0 cost-0 account-2 bank-conf-2 ncb-2 (hash n-0 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit-0 (sign (bconf (hash c m b n cost-0 (hash n (hash ncm-1 item-1 merc-conf-1))) btr-1 mtr-1) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb-0 bank-conf-0) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm-0 item-0 merc-conf-0) mtr-0 (cat (sign (order c m b cost (enc n cost account-1 bank-conf-1 ncb-1 (hash n (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-1 bank-conf-1 ncb-1 (hash n (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb-1 bank-conf-1) (sign (bconf (hash c m b n cost (hash n (hash ncm-0 item-0 merc-conf-0))) btr-0 mtr-0) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n-0 cost-0 item-2 merc-conf-2 ncm-2 (hash n-0 (hash ncb-2 bank-conf-2)) (sign (order c m b cost-0 (enc n-0 cost-0 account-2 bank-conf-2 ncb-2 (hash n-0 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))))) (label 115) (parent 105) (unrealized (2 2) (3 0) (4 0)) (comment "2 in cohort - 2 not yet seen")) (defskeleton minipay-rely-guar (vars (bank-conf-commit bank-conf-decommit bank-conf-commit-0 bank-conf-decommit-0 mesg) (account account-0 account-1 acct) (cost amount) (n ncb ncm ncm-0 ncb-0 n-0 ncb-1 ncm-1 data) (item item-0 item-1 merchandise) (merc-conf bank-conf btr mtr merc-conf-0 btr-0 mtr-0 bank-conf-0 merc-conf-1 bank-conf-1 text) (c m b name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 3 (for-bank (enc n-0 cost account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit) (bank-conf-decommit bank-conf-decommit) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 3 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit-0) (bank-conf-decommit bank-conf-decommit-0) (cost cost) (n n) (ncm ncm-0) (item item-0) (merc-conf merc-conf-0) (btr btr-0) (mtr mtr-0) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account-0) (cost cost) (n n) (ncb ncb-0) (bank-conf bank-conf-0) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account-1) (cost cost) (n n-0) (ncb ncb-1) (ncm ncm-1) (item item-1) (merc-conf merc-conf-1) (bank-conf bank-conf-1) (c c) (m m) (b b)) (precedes ((0 0) (1 0)) ((0 0) (2 0)) ((1 1) (3 0)) ((3 1) (0 1)) ((3 1) (1 2)) ((4 0) (1 0))) (non-orig (privk "enc" b) (privk "sig" c) (privk "sig" b)) (uniq-orig n btr mtr mtr-0) (facts (neq n-0 ncb-1) (neq n ncb) (neq n-0 ncm-1) (neq n ncm) (neq ncm-1 ncb-1) (neq ncm ncb) (will-ship c m b item mtr) (will-transfer c m b cost n mtr-0 btr-0) (buy-via c m b item-0 cost n) (buy-via c m b item-1 cost n-0) (buy-via c m b item cost n) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 rely-cust-3 rely-merc-3) (operation encryption-test (displaced 5 0 cust 1) (sign (order c m b cost-0 (enc n-1 cost-0 account-2 bank-conf-2 ncb-2 (hash n-1 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b))) (privk "sig" c)) (2 0)) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc n cost item merc-conf ncm bank-conf-commit (sign (order c m b cost (enc n-0 cost account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n-0 cost account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (privk "sig" c)) (enc n-0 cost account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc n cost item-0 merc-conf-0 ncm-0 bank-conf-commit-0 (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm-0 item-0 merc-conf-0) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit-0 (sign (bconf (hash c m b n cost (hash n (hash ncm-0 item-0 merc-conf-0))) btr-0 mtr-0) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb-0 bank-conf-0) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n-0 cost item-1 merc-conf-1 ncm-1 (hash n-0 (hash ncb-1 bank-conf-1)) (sign (order c m b cost (enc n-0 cost account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))))) (label 116) (parent 106) (seen 129) (unrealized (2 2) (3 0)) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay-rely-guar (vars (bank-conf-commit bank-conf-decommit bank-conf-commit-0 bank-conf-decommit-0 mesg) (account account-0 account-1 acct) (cost amount) (n ncb ncm ncm-0 ncb-0 n-0 ncb-1 ncm-1 data) (item item-0 item-1 merchandise) (merc-conf bank-conf btr mtr merc-conf-0 btr-0 mtr-0 bank-conf-0 merc-conf-1 bank-conf-1 text) (c m b name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 3 (for-bank (enc n-0 cost account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit) (bank-conf-decommit bank-conf-decommit) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 3 (for-bank (enc n-0 cost account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit-0) (bank-conf-decommit bank-conf-decommit-0) (cost cost) (n n) (ncm ncm-0) (item item-0) (merc-conf merc-conf-0) (btr btr-0) (mtr mtr-0) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account-0) (cost cost) (n n) (ncb ncb-0) (bank-conf bank-conf-0) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account-1) (cost cost) (n n-0) (ncb ncb-1) (ncm ncm-1) (item item-1) (merc-conf merc-conf-1) (bank-conf bank-conf-1) (c c) (m m) (b b)) (precedes ((0 0) (1 0)) ((0 0) (2 0)) ((1 1) (3 0)) ((3 1) (0 1)) ((3 1) (1 2)) ((4 0) (1 0)) ((4 0) (2 0))) (non-orig (privk "enc" b) (privk "sig" c) (privk "sig" b)) (uniq-orig n btr mtr mtr-0) (facts (neq n-0 ncb-1) (neq n ncb) (neq n-0 ncm-1) (neq n ncm) (neq ncm-1 ncb-1) (neq ncm ncb) (will-ship c m b item mtr) (will-transfer c m b cost n mtr-0 btr-0) (buy-via c m b item-0 cost n) (buy-via c m b item-1 cost n-0) (buy-via c m b item cost n) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 rely-cust-3 rely-merc-3) (operation encryption-test (displaced 5 4 cust 1) (sign (order c m b cost-0 (enc n-1 cost-0 account-2 bank-conf-2 ncb-2 (hash n-1 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b))) (privk "sig" c)) (2 0)) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc n cost item merc-conf ncm bank-conf-commit (sign (order c m b cost (enc n-0 cost account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n-0 cost account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (privk "sig" c)) (enc n-0 cost account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc n cost item-0 merc-conf-0 ncm-0 bank-conf-commit-0 (sign (order c m b cost (enc n-0 cost account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm-0 item-0 merc-conf-0) mtr-0 (cat (sign (order c m b cost (enc n-0 cost account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (privk "sig" c)) (enc n-0 cost account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit-0 (sign (bconf (hash c m b n cost (hash n (hash ncm-0 item-0 merc-conf-0))) btr-0 mtr-0) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb-0 bank-conf-0) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n-0 cost item-1 merc-conf-1 ncm-1 (hash n-0 (hash ncb-1 bank-conf-1)) (sign (order c m b cost (enc n-0 cost account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))))) (label 117) (parent 106) (unrealized (2 2) (3 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay-rely-guar (vars (bank-conf-commit bank-conf-decommit bank-conf-commit-0 bank-conf-decommit-0 mesg) (account account-0 account-1 account-2 acct) (cost cost-0 amount) (n ncb ncm ncm-0 ncb-0 n-0 ncb-1 ncm-1 n-1 ncb-2 ncm-2 data) (item item-0 item-1 item-2 merchandise) (merc-conf bank-conf btr mtr merc-conf-0 btr-0 mtr-0 bank-conf-0 merc-conf-1 bank-conf-1 merc-conf-2 bank-conf-2 text) (c m b name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 3 (for-bank (enc n-0 cost account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit) (bank-conf-decommit bank-conf-decommit) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 3 (for-bank (enc n-1 cost-0 account-2 bank-conf-2 ncb-2 (hash n-1 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit-0) (bank-conf-decommit bank-conf-decommit-0) (cost cost-0) (n n) (ncm ncm-0) (item item-0) (merc-conf merc-conf-0) (btr btr-0) (mtr mtr-0) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account-0) (cost cost) (n n) (ncb ncb-0) (bank-conf bank-conf-0) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account-1) (cost cost) (n n-0) (ncb ncb-1) (ncm ncm-1) (item item-1) (merc-conf merc-conf-1) (bank-conf bank-conf-1) (c c) (m m) (b b)) (defstrand cust 1 (account account-2) (cost cost-0) (n n-1) (ncb ncb-2) (ncm ncm-2) (item item-2) (merc-conf merc-conf-2) (bank-conf bank-conf-2) (c c) (m m) (b b)) (precedes ((0 0) (1 0)) ((0 0) (2 0)) ((1 1) (3 0)) ((3 1) (0 1)) ((3 1) (1 2)) ((4 0) (1 0)) ((5 0) (2 0))) (non-orig (privk "enc" b) (privk "sig" c) (privk "sig" b)) (uniq-orig n btr mtr mtr-0) (facts (neq n-1 ncb-2) (neq n-0 ncb-1) (neq n ncb) (neq n-1 ncm-2) (neq n-0 ncm-1) (neq n ncm) (neq ncm-2 ncb-2) (neq ncm-1 ncb-1) (neq ncm ncb) (will-ship c m b item mtr) (will-transfer c m b cost-0 n mtr-0 btr-0) (buy-via c m b item-0 cost-0 n) (buy-via c m b item-2 cost-0 n-1) (buy-via c m b item-1 cost n-0) (buy-via c m b item cost n) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 rely-cust-3 rely-merc-3) (operation encryption-test (added-strand cust 1) (sign (order c m b cost-0 (enc n-1 cost-0 account-2 bank-conf-2 ncb-2 (hash n-1 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b))) (privk "sig" c)) (2 0)) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc n cost item merc-conf ncm bank-conf-commit (sign (order c m b cost (enc n-0 cost account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n-0 cost account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (privk "sig" c)) (enc n-0 cost account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc n cost-0 item-0 merc-conf-0 ncm-0 bank-conf-commit-0 (sign (order c m b cost-0 (enc n-1 cost-0 account-2 bank-conf-2 ncb-2 (hash n-1 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost-0 n) (hash ncm-0 item-0 merc-conf-0) mtr-0 (cat (sign (order c m b cost-0 (enc n-1 cost-0 account-2 bank-conf-2 ncb-2 (hash n-1 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b))) (privk "sig" c)) (enc n-1 cost-0 account-2 bank-conf-2 ncb-2 (hash n-1 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit-0 (sign (bconf (hash c m b n cost-0 (hash n (hash ncm-0 item-0 merc-conf-0))) btr-0 mtr-0) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb-0 bank-conf-0) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n-0 cost item-1 merc-conf-1 ncm-1 (hash n-0 (hash ncb-1 bank-conf-1)) (sign (order c m b cost (enc n-0 cost account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((send (enc n-1 cost-0 item-2 merc-conf-2 ncm-2 (hash n-1 (hash ncb-2 bank-conf-2)) (sign (order c m b cost-0 (enc n-1 cost-0 account-2 bank-conf-2 ncb-2 (hash n-1 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))))) (label 118) (parent 106) (unrealized (2 2) (3 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay-rely-guar (vars (bank-conf-commit bank-conf-decommit bank-conf-commit-0 bank-conf-decommit-0 mesg) (account account-0 account-1 account-2 acct) (cost cost-0 amount) (n ncb ncm ncm-0 ncm-1 ncb-0 n-0 ncb-1 ncm-2 ncb-2 data) (item item-0 item-1 item-2 merchandise) (merc-conf bank-conf btr mtr merc-conf-0 btr-0 mtr-0 merc-conf-1 btr-1 mtr-1 bank-conf-0 merc-conf-2 bank-conf-1 bank-conf-2 text) (c m b name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 3 (for-bank (enc n-0 cost-0 account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit) (bank-conf-decommit bank-conf-decommit) (cost cost-0) (n n) (ncm ncm-0) (item item-0) (merc-conf merc-conf-0) (btr btr-0) (mtr mtr-0) (c c) (m m) (b b)) (defstrand merc 3 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit-0) (bank-conf-decommit bank-conf-decommit-0) (cost cost) (n n) (ncm ncm-1) (item item-1) (merc-conf merc-conf-1) (btr btr-1) (mtr mtr-1) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account-0) (cost cost) (n n) (ncb ncb-0) (bank-conf bank-conf-0) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account-1) (cost cost-0) (n n-0) (ncb ncb-1) (ncm ncm-2) (item item-2) (merc-conf merc-conf-2) (bank-conf bank-conf-1) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm-0 item-0 merc-conf-0)) (account account-2) (cost cost-0) (n n) (ncb ncb-2) (bank-conf bank-conf-2) (btr btr-0) (mtr mtr-0) (c c) (m m) (b b)) (precedes ((0 0) (1 0)) ((0 0) (2 0)) ((0 0) (3 0)) ((1 1) (5 0)) ((3 1) (0 1)) ((4 0) (1 0)) ((5 1) (1 2))) (non-orig (privk "enc" b) (privk "sig" c) (privk "sig" b)) (uniq-orig n btr btr-0 mtr-0 mtr-1) (facts (neq n-0 ncb-1) (neq n ncb) (neq n-0 ncm-2) (neq n ncm) (neq ncm-2 ncb-1) (neq ncm ncb) (will-ship c m b item mtr) (will-transfer c m b cost n mtr-1 btr-1) (buy-via c m b item-1 cost n) (buy-via c m b item-0 cost-0 n) (buy-via c m b item-2 cost-0 n-0) (buy-via c m b item cost n) (will-transfer c m b cost-0 n mtr-0 btr-0) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 rely-cust-3 rely-merc-3) (operation encryption-test (displaced 6 0 cust 1) (sign (order c m b cost-1 (enc n-1 cost-1 account-3 bank-conf-3 ncb-3 (hash n-1 (hash ncm-3 item-3 merc-conf-3)) (pubk "enc" b))) (privk "sig" c)) (2 0)) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc n cost-0 item-0 merc-conf-0 ncm-0 bank-conf-commit (sign (order c m b cost-0 (enc n-0 cost-0 account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost-0 n) (hash ncm-0 item-0 merc-conf-0) mtr-0 (cat (sign (order c m b cost-0 (enc n-0 cost-0 account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b))) (privk "sig" c)) (enc n-0 cost-0 account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit (sign (bconf (hash c m b n cost-0 (hash n (hash ncm-0 item-0 merc-conf-0))) btr-0 mtr-0) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc n cost item-1 merc-conf-1 ncm-1 bank-conf-commit-0 (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm-1 item-1 merc-conf-1) mtr-1 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit-0 (sign (bconf (hash c m b n cost (hash n (hash ncm-1 item-1 merc-conf-1))) btr-1 mtr-1) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb-0 bank-conf-0) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n-0 cost-0 item-2 merc-conf-2 ncm-2 (hash n-0 (hash ncb-1 bank-conf-1)) (sign (order c m b cost-0 (enc n-0 cost-0 account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost-0 n) (hash ncm-0 item-0 merc-conf-0) mtr-0 (cat (sign (order c m b cost-0 (enc n cost-0 account-2 bank-conf-2 ncb-2 (hash n (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (enc n cost-0 account-2 bank-conf-2 ncb-2 (hash n (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb-2 bank-conf-2) (sign (bconf (hash c m b n cost-0 (hash n (hash ncm-0 item-0 merc-conf-0))) btr-0 mtr-0) (privk "sig" b)) (pubk "enc" m))))) (label 119) (parent 107) (seen 127 130) (unrealized (2 2) (3 0) (5 0)) (comment "2 in cohort - 0 not yet seen")) (defskeleton minipay-rely-guar (vars (bank-conf-commit bank-conf-decommit bank-conf-commit-0 bank-conf-decommit-0 mesg) (account account-0 account-1 account-2 acct) (cost cost-0 amount) (n ncb ncm ncm-0 ncm-1 ncb-0 n-0 ncb-1 ncm-2 ncb-2 data) (item item-0 item-1 item-2 merchandise) (merc-conf bank-conf btr mtr merc-conf-0 btr-0 mtr-0 merc-conf-1 btr-1 mtr-1 bank-conf-0 merc-conf-2 bank-conf-1 bank-conf-2 text) (c m b name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 3 (for-bank (enc n-0 cost-0 account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit) (bank-conf-decommit bank-conf-decommit) (cost cost-0) (n n) (ncm ncm-0) (item item-0) (merc-conf merc-conf-0) (btr btr-0) (mtr mtr-0) (c c) (m m) (b b)) (defstrand merc 3 (for-bank (enc n-0 cost-0 account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit-0) (bank-conf-decommit bank-conf-decommit-0) (cost cost-0) (n n) (ncm ncm-1) (item item-1) (merc-conf merc-conf-1) (btr btr-1) (mtr mtr-1) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account-0) (cost cost) (n n) (ncb ncb-0) (bank-conf bank-conf-0) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account-1) (cost cost-0) (n n-0) (ncb ncb-1) (ncm ncm-2) (item item-2) (merc-conf merc-conf-2) (bank-conf bank-conf-1) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm-0 item-0 merc-conf-0)) (account account-2) (cost cost-0) (n n) (ncb ncb-2) (bank-conf bank-conf-2) (btr btr-0) (mtr mtr-0) (c c) (m m) (b b)) (precedes ((0 0) (1 0)) ((0 0) (2 0)) ((0 0) (3 0)) ((1 1) (5 0)) ((3 1) (0 1)) ((4 0) (1 0)) ((4 0) (2 0)) ((5 1) (1 2))) (non-orig (privk "enc" b) (privk "sig" c) (privk "sig" b)) (uniq-orig n btr btr-0 mtr-0 mtr-1) (facts (neq n-0 ncb-1) (neq n ncb) (neq n-0 ncm-2) (neq n ncm) (neq ncm-2 ncb-1) (neq ncm ncb) (will-ship c m b item mtr) (will-transfer c m b cost-0 n mtr-1 btr-1) (buy-via c m b item-1 cost-0 n) (buy-via c m b item-0 cost-0 n) (buy-via c m b item-2 cost-0 n-0) (buy-via c m b item cost n) (will-transfer c m b cost-0 n mtr-0 btr-0) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 rely-cust-3 rely-merc-3) (operation encryption-test (displaced 6 4 cust 1) (sign (order c m b cost-1 (enc n-1 cost-1 account-3 bank-conf-3 ncb-3 (hash n-1 (hash ncm-3 item-3 merc-conf-3)) (pubk "enc" b))) (privk "sig" c)) (2 0)) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc n cost-0 item-0 merc-conf-0 ncm-0 bank-conf-commit (sign (order c m b cost-0 (enc n-0 cost-0 account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost-0 n) (hash ncm-0 item-0 merc-conf-0) mtr-0 (cat (sign (order c m b cost-0 (enc n-0 cost-0 account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b))) (privk "sig" c)) (enc n-0 cost-0 account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit (sign (bconf (hash c m b n cost-0 (hash n (hash ncm-0 item-0 merc-conf-0))) btr-0 mtr-0) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc n cost-0 item-1 merc-conf-1 ncm-1 bank-conf-commit-0 (sign (order c m b cost-0 (enc n-0 cost-0 account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost-0 n) (hash ncm-1 item-1 merc-conf-1) mtr-1 (cat (sign (order c m b cost-0 (enc n-0 cost-0 account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b))) (privk "sig" c)) (enc n-0 cost-0 account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit-0 (sign (bconf (hash c m b n cost-0 (hash n (hash ncm-1 item-1 merc-conf-1))) btr-1 mtr-1) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb-0 bank-conf-0) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n-0 cost-0 item-2 merc-conf-2 ncm-2 (hash n-0 (hash ncb-1 bank-conf-1)) (sign (order c m b cost-0 (enc n-0 cost-0 account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost-0 n) (hash ncm-0 item-0 merc-conf-0) mtr-0 (cat (sign (order c m b cost-0 (enc n cost-0 account-2 bank-conf-2 ncb-2 (hash n (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (enc n cost-0 account-2 bank-conf-2 ncb-2 (hash n (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb-2 bank-conf-2) (sign (bconf (hash c m b n cost-0 (hash n (hash ncm-0 item-0 merc-conf-0))) btr-0 mtr-0) (privk "sig" b)) (pubk "enc" m))))) (label 120) (parent 107) (seen 131) (unrealized (2 2) (3 0) (5 0)) (comment "2 in cohort - 1 not yet seen")) (defskeleton minipay-rely-guar (vars (bank-conf-commit bank-conf-decommit bank-conf-commit-0 bank-conf-decommit-0 mesg) (account account-0 account-1 account-2 account-3 acct) (cost cost-0 cost-1 amount) (n ncb ncm ncm-0 ncm-1 ncb-0 n-0 ncb-1 ncm-2 ncb-2 n-1 ncb-3 ncm-3 data) (item item-0 item-1 item-2 item-3 merchandise) (merc-conf bank-conf btr mtr merc-conf-0 btr-0 mtr-0 merc-conf-1 btr-1 mtr-1 bank-conf-0 merc-conf-2 bank-conf-1 bank-conf-2 merc-conf-3 bank-conf-3 text) (c m b name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 3 (for-bank (enc n-0 cost-0 account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit) (bank-conf-decommit bank-conf-decommit) (cost cost-0) (n n) (ncm ncm-0) (item item-0) (merc-conf merc-conf-0) (btr btr-0) (mtr mtr-0) (c c) (m m) (b b)) (defstrand merc 3 (for-bank (enc n-1 cost-1 account-3 bank-conf-3 ncb-3 (hash n-1 (hash ncm-3 item-3 merc-conf-3)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit-0) (bank-conf-decommit bank-conf-decommit-0) (cost cost-1) (n n) (ncm ncm-1) (item item-1) (merc-conf merc-conf-1) (btr btr-1) (mtr mtr-1) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account-0) (cost cost) (n n) (ncb ncb-0) (bank-conf bank-conf-0) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account-1) (cost cost-0) (n n-0) (ncb ncb-1) (ncm ncm-2) (item item-2) (merc-conf merc-conf-2) (bank-conf bank-conf-1) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm-0 item-0 merc-conf-0)) (account account-2) (cost cost-0) (n n) (ncb ncb-2) (bank-conf bank-conf-2) (btr btr-0) (mtr mtr-0) (c c) (m m) (b b)) (defstrand cust 1 (account account-3) (cost cost-1) (n n-1) (ncb ncb-3) (ncm ncm-3) (item item-3) (merc-conf merc-conf-3) (bank-conf bank-conf-3) (c c) (m m) (b b)) (precedes ((0 0) (1 0)) ((0 0) (2 0)) ((0 0) (3 0)) ((1 1) (5 0)) ((3 1) (0 1)) ((4 0) (1 0)) ((5 1) (1 2)) ((6 0) (2 0))) (non-orig (privk "enc" b) (privk "sig" c) (privk "sig" b)) (uniq-orig n btr btr-0 mtr-0 mtr-1) (facts (neq n-1 ncb-3) (neq n-0 ncb-1) (neq n ncb) (neq n-1 ncm-3) (neq n-0 ncm-2) (neq n ncm) (neq ncm-3 ncb-3) (neq ncm-2 ncb-1) (neq ncm ncb) (will-ship c m b item mtr) (will-transfer c m b cost-1 n mtr-1 btr-1) (buy-via c m b item-1 cost-1 n) (buy-via c m b item-0 cost-0 n) (buy-via c m b item-3 cost-1 n-1) (buy-via c m b item-2 cost-0 n-0) (buy-via c m b item cost n) (will-transfer c m b cost-0 n mtr-0 btr-0) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 rely-cust-3 rely-merc-3) (operation encryption-test (added-strand cust 1) (sign (order c m b cost-1 (enc n-1 cost-1 account-3 bank-conf-3 ncb-3 (hash n-1 (hash ncm-3 item-3 merc-conf-3)) (pubk "enc" b))) (privk "sig" c)) (2 0)) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc n cost-0 item-0 merc-conf-0 ncm-0 bank-conf-commit (sign (order c m b cost-0 (enc n-0 cost-0 account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost-0 n) (hash ncm-0 item-0 merc-conf-0) mtr-0 (cat (sign (order c m b cost-0 (enc n-0 cost-0 account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b))) (privk "sig" c)) (enc n-0 cost-0 account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit (sign (bconf (hash c m b n cost-0 (hash n (hash ncm-0 item-0 merc-conf-0))) btr-0 mtr-0) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc n cost-1 item-1 merc-conf-1 ncm-1 bank-conf-commit-0 (sign (order c m b cost-1 (enc n-1 cost-1 account-3 bank-conf-3 ncb-3 (hash n-1 (hash ncm-3 item-3 merc-conf-3)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost-1 n) (hash ncm-1 item-1 merc-conf-1) mtr-1 (cat (sign (order c m b cost-1 (enc n-1 cost-1 account-3 bank-conf-3 ncb-3 (hash n-1 (hash ncm-3 item-3 merc-conf-3)) (pubk "enc" b))) (privk "sig" c)) (enc n-1 cost-1 account-3 bank-conf-3 ncb-3 (hash n-1 (hash ncm-3 item-3 merc-conf-3)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit-0 (sign (bconf (hash c m b n cost-1 (hash n (hash ncm-1 item-1 merc-conf-1))) btr-1 mtr-1) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb-0 bank-conf-0) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n-0 cost-0 item-2 merc-conf-2 ncm-2 (hash n-0 (hash ncb-1 bank-conf-1)) (sign (order c m b cost-0 (enc n-0 cost-0 account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost-0 n) (hash ncm-0 item-0 merc-conf-0) mtr-0 (cat (sign (order c m b cost-0 (enc n cost-0 account-2 bank-conf-2 ncb-2 (hash n (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (enc n cost-0 account-2 bank-conf-2 ncb-2 (hash n (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb-2 bank-conf-2) (sign (bconf (hash c m b n cost-0 (hash n (hash ncm-0 item-0 merc-conf-0))) btr-0 mtr-0) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n-1 cost-1 item-3 merc-conf-3 ncm-3 (hash n-1 (hash ncb-3 bank-conf-3)) (sign (order c m b cost-1 (enc n-1 cost-1 account-3 bank-conf-3 ncb-3 (hash n-1 (hash ncm-3 item-3 merc-conf-3)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))))) (label 121) (parent 107) (seen 132) (unrealized (2 2) (3 0) (5 0)) (comment "2 in cohort - 1 not yet seen")) (defskeleton minipay-rely-guar (vars (bank-conf-commit bank-conf-decommit mesg) (account acct) (cost amount) (n ncb ncm data) (item merchandise) (merc-conf bank-conf btr mtr text) (c m b name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 3 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit) (bank-conf-decommit bank-conf-decommit) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (precedes ((0 0) (1 0)) ((1 1) (2 0)) ((2 1) (0 1)) ((2 1) (1 2))) (non-orig (privk "enc" b) (privk "sig" c) (privk "sig" b)) (uniq-orig n btr mtr) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (will-ship c m b item mtr) (buy-via c m b item cost n) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 rely-cust-3) (operation encryption-test (displaced 3 0 cust 1) (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (2 0)) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc n cost item merc-conf ncm bank-conf-commit (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))))) (label 122) (parent 108) (realized) (shape) (maps ((0 1 1) ((c c) (m m) (b b) (n n) (cost cost) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (account account) (ncb ncb) (ncm ncm) (cost-0 cost) (item-0 item) (merc-conf-0 merc-conf) (btr-0 btr) (mtr-0 mtr) (ncm-0 ncm) (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit) (bank-conf-decommit bank-conf-decommit) (cost-1 cost) (item-1 item) (merc-conf-1 merc-conf) (btr-1 btr) (mtr-1 mtr) (ncm-1 ncm) (for-bank-0 (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit-0 bank-conf-commit) (bank-conf-decommit-0 bank-conf-decommit)))) (origs (btr (2 1)) (mtr (1 1)) (n (0 0)))) (defskeleton minipay-rely-guar (vars (bank-conf-commit bank-conf-decommit mesg) (account account-0 acct) (cost amount) (n ncb ncm ncm-0 ncb-0 data) (item item-0 merchandise) (merc-conf bank-conf btr mtr merc-conf-0 btr-0 mtr-0 bank-conf-0 text) (c m b name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 3 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit) (bank-conf-decommit bank-conf-decommit) (cost cost) (n n) (ncm ncm-0) (item item-0) (merc-conf merc-conf-0) (btr btr-0) (mtr mtr-0) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm-0 item-0 merc-conf-0)) (account account-0) (cost cost) (n n) (ncb ncb-0) (bank-conf bank-conf-0) (btr btr-0) (mtr mtr-0) (c c) (m m) (b b)) (precedes ((0 0) (1 0)) ((0 0) (2 0)) ((1 1) (3 0)) ((2 1) (0 1)) ((3 1) (1 2))) (non-orig (privk "enc" b) (privk "sig" c) (privk "sig" b)) (uniq-orig n btr btr-0 mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (will-ship c m b item mtr) (buy-via c m b item-0 cost n) (buy-via c m b item cost n) (will-transfer c m b cost n mtr-0 btr-0) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 rely-cust-3 rely-merc-3) (operation encryption-test (displaced 4 0 cust 1) (sign (order c m b cost (enc n cost account-1 bank-conf-1 ncb-1 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (2 0)) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc n cost item-0 merc-conf-0 ncm-0 bank-conf-commit (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm-0 item-0 merc-conf-0) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit (sign (bconf (hash c m b n cost (hash n (hash ncm-0 item-0 merc-conf-0))) btr-0 mtr-0) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm-0 item-0 merc-conf-0) mtr-0 (cat (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb-0 bank-conf-0) (sign (bconf (hash c m b n cost (hash n (hash ncm-0 item-0 merc-conf-0))) btr-0 mtr-0) (privk "sig" b)) (pubk "enc" m))))) (label 123) (parent 109) (unrealized (3 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay-rely-guar (vars (bank-conf-commit bank-conf-decommit mesg) (account account-0 acct) (cost amount) (n ncb ncm n-0 ncb-0 ncm-0 data) (item item-0 merchandise) (merc-conf bank-conf btr mtr merc-conf-0 bank-conf-0 text) (c m b name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 3 (for-bank (enc n-0 cost account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit) (bank-conf-decommit bank-conf-decommit) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account-0) (cost cost) (n n-0) (ncb ncb-0) (ncm ncm-0) (item item-0) (merc-conf merc-conf-0) (bank-conf bank-conf-0) (c c) (m m) (b b)) (precedes ((0 0) (1 0)) ((1 1) (2 0)) ((2 1) (0 1)) ((2 1) (1 2)) ((3 0) (1 0))) (non-orig (privk "enc" b) (privk "sig" c) (privk "sig" b)) (uniq-orig n btr mtr) (facts (neq n-0 ncb-0) (neq n ncb) (neq n-0 ncm-0) (neq n ncm) (neq ncm-0 ncb-0) (neq ncm ncb) (will-ship c m b item mtr) (buy-via c m b item-0 cost n-0) (buy-via c m b item cost n) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 rely-cust-3) (operation encryption-test (displaced 4 0 cust 1) (sign (order c m b cost (enc n cost account-1 bank-conf-1 ncb-1 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (2 0)) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc n cost item merc-conf ncm bank-conf-commit (sign (order c m b cost (enc n-0 cost account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n-0 cost account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (enc n-0 cost account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n-0 cost item-0 merc-conf-0 ncm-0 (hash n-0 (hash ncb-0 bank-conf-0)) (sign (order c m b cost (enc n-0 cost account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))))) (label 124) (parent 110) (unrealized (2 0)) (dead) (comment "empty cohort")) (defskeleton minipay-rely-guar (vars (bank-conf-commit bank-conf-decommit mesg) (account account-0 account-1 acct) (cost cost-0 amount) (n ncb ncm ncm-0 n-0 ncb-0 ncm-1 ncb-1 data) (item item-0 item-1 merchandise) (merc-conf bank-conf btr mtr merc-conf-0 btr-0 mtr-0 merc-conf-1 bank-conf-0 bank-conf-1 text) (c m b name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 3 (for-bank (enc n-0 cost-0 account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit) (bank-conf-decommit bank-conf-decommit) (cost cost-0) (n n) (ncm ncm-0) (item item-0) (merc-conf merc-conf-0) (btr btr-0) (mtr mtr-0) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account-0) (cost cost-0) (n n-0) (ncb ncb-0) (ncm ncm-1) (item item-1) (merc-conf merc-conf-1) (bank-conf bank-conf-0) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm-0 item-0 merc-conf-0)) (account account-1) (cost cost-0) (n n) (ncb ncb-1) (bank-conf bank-conf-1) (btr btr-0) (mtr mtr-0) (c c) (m m) (b b)) (precedes ((0 0) (1 0)) ((0 0) (2 0)) ((1 1) (4 0)) ((2 1) (0 1)) ((3 0) (1 0)) ((4 1) (1 2))) (non-orig (privk "enc" b) (privk "sig" c) (privk "sig" b)) (uniq-orig n btr btr-0 mtr-0) (facts (neq n-0 ncb-0) (neq n ncb) (neq n-0 ncm-1) (neq n ncm) (neq ncm-1 ncb-0) (neq ncm ncb) (will-ship c m b item mtr) (buy-via c m b item-0 cost-0 n) (buy-via c m b item-1 cost-0 n-0) (buy-via c m b item cost n) (will-transfer c m b cost-0 n mtr-0 btr-0) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 rely-cust-3 rely-merc-3) (operation encryption-test (displaced 5 0 cust 1) (sign (order c m b cost (enc n cost account-2 bank-conf-2 ncb-2 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (2 0)) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc n cost-0 item-0 merc-conf-0 ncm-0 bank-conf-commit (sign (order c m b cost-0 (enc n-0 cost-0 account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost-0 n) (hash ncm-0 item-0 merc-conf-0) mtr-0 (cat (sign (order c m b cost-0 (enc n-0 cost-0 account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (privk "sig" c)) (enc n-0 cost-0 account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit (sign (bconf (hash c m b n cost-0 (hash n (hash ncm-0 item-0 merc-conf-0))) btr-0 mtr-0) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n-0 cost-0 item-1 merc-conf-1 ncm-1 (hash n-0 (hash ncb-0 bank-conf-0)) (sign (order c m b cost-0 (enc n-0 cost-0 account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost-0 n) (hash ncm-0 item-0 merc-conf-0) mtr-0 (cat (sign (order c m b cost-0 (enc n cost-0 account-1 bank-conf-1 ncb-1 (hash n (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (enc n cost-0 account-1 bank-conf-1 ncb-1 (hash n (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb-1 bank-conf-1) (sign (bconf (hash c m b n cost-0 (hash n (hash ncm-0 item-0 merc-conf-0))) btr-0 mtr-0) (privk "sig" b)) (pubk "enc" m))))) (label 125) (parent 111) (unrealized (4 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay-rely-guar (vars (bank-conf-commit bank-conf-decommit bank-conf-commit-0 bank-conf-decommit-0 mesg) (account account-0 account-1 acct) (cost amount) (n ncb ncm ncm-0 ncb-0 ncb-1 data) (item item-0 merchandise) (merc-conf bank-conf btr mtr merc-conf-0 btr-0 mtr-0 bank-conf-0 bank-conf-1 text) (c m b name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 3 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit) (bank-conf-decommit bank-conf-decommit) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 3 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit-0) (bank-conf-decommit bank-conf-decommit-0) (cost cost) (n n) (ncm ncm-0) (item item-0) (merc-conf merc-conf-0) (btr btr-0) (mtr mtr-0) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account-0) (cost cost) (n n) (ncb ncb-0) (bank-conf bank-conf-0) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm-0 item-0 merc-conf-0)) (account account-1) (cost cost) (n n) (ncb ncb-1) (bank-conf bank-conf-1) (btr btr-0) (mtr mtr-0) (c c) (m m) (b b)) (precedes ((0 0) (1 0)) ((0 0) (2 0)) ((1 1) (3 0)) ((2 1) (4 0)) ((3 1) (0 1)) ((3 1) (1 2)) ((4 1) (2 2))) (non-orig (privk "enc" b) (privk "sig" c) (privk "sig" b)) (uniq-orig n btr mtr btr-0 mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (will-ship c m b item mtr) (buy-via c m b item-0 cost n) (buy-via c m b item cost n) (will-transfer c m b cost n mtr-0 btr-0) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 rely-cust-3 rely-merc-3) (operation encryption-test (added-strand bank 2) (sign (bconf (hash c m b n cost (hash n (hash ncm-0 item-0 merc-conf-0))) btr-0 mtr-0) (privk "sig" b)) (2 2)) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc n cost item merc-conf ncm bank-conf-commit (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc n cost item-0 merc-conf-0 ncm-0 bank-conf-commit-0 (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm-0 item-0 merc-conf-0) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit-0 (sign (bconf (hash c m b n cost (hash n (hash ncm-0 item-0 merc-conf-0))) btr-0 mtr-0) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb-0 bank-conf-0) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm-0 item-0 merc-conf-0) mtr-0 (cat (sign (order c m b cost (enc n cost account-1 bank-conf-1 ncb-1 (hash n (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-1 bank-conf-1 ncb-1 (hash n (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb-1 bank-conf-1) (sign (bconf (hash c m b n cost (hash n (hash ncm-0 item-0 merc-conf-0))) btr-0 mtr-0) (privk "sig" b)) (pubk "enc" m))))) (label 126) (parent 112) (unrealized (3 0) (4 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay-rely-guar (vars (bank-conf-commit bank-conf-decommit bank-conf-commit-0 bank-conf-decommit-0 mesg) (account account-0 account-1 account-2 acct) (cost cost-0 amount) (n ncb ncm ncm-0 ncb-0 n-0 ncb-1 ncm-1 ncb-2 data) (item item-0 item-1 merchandise) (merc-conf bank-conf btr mtr merc-conf-0 btr-0 mtr-0 bank-conf-0 merc-conf-1 bank-conf-1 bank-conf-2 text) (c m b name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 3 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit) (bank-conf-decommit bank-conf-decommit) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 3 (for-bank (enc n-0 cost-0 account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit-0) (bank-conf-decommit bank-conf-decommit-0) (cost cost-0) (n n) (ncm ncm-0) (item item-0) (merc-conf merc-conf-0) (btr btr-0) (mtr mtr-0) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account-0) (cost cost) (n n) (ncb ncb-0) (bank-conf bank-conf-0) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account-1) (cost cost-0) (n n-0) (ncb ncb-1) (ncm ncm-1) (item item-1) (merc-conf merc-conf-1) (bank-conf bank-conf-1) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm-0 item-0 merc-conf-0)) (account account-2) (cost cost-0) (n n) (ncb ncb-2) (bank-conf bank-conf-2) (btr btr-0) (mtr mtr-0) (c c) (m m) (b b)) (precedes ((0 0) (1 0)) ((0 0) (2 0)) ((1 1) (3 0)) ((2 1) (5 0)) ((3 1) (0 1)) ((3 1) (1 2)) ((4 0) (2 0)) ((5 1) (2 2))) (non-orig (privk "enc" b) (privk "sig" c) (privk "sig" b)) (uniq-orig n btr mtr btr-0 mtr-0) (facts (neq n-0 ncb-1) (neq n ncb) (neq n-0 ncm-1) (neq n ncm) (neq ncm-1 ncb-1) (neq ncm ncb) (will-ship c m b item mtr) (buy-via c m b item-0 cost-0 n) (buy-via c m b item-1 cost-0 n-0) (buy-via c m b item cost n) (will-transfer c m b cost-0 n mtr-0 btr-0) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 rely-cust-3 rely-merc-3) (operation encryption-test (added-strand bank 2) (sign (bconf (hash c m b n cost-0 (hash n (hash ncm-0 item-0 merc-conf-0))) btr-0 mtr-0) (privk "sig" b)) (2 2)) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc n cost item merc-conf ncm bank-conf-commit (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc n cost-0 item-0 merc-conf-0 ncm-0 bank-conf-commit-0 (sign (order c m b cost-0 (enc n-0 cost-0 account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost-0 n) (hash ncm-0 item-0 merc-conf-0) mtr-0 (cat (sign (order c m b cost-0 (enc n-0 cost-0 account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (privk "sig" c)) (enc n-0 cost-0 account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit-0 (sign (bconf (hash c m b n cost-0 (hash n (hash ncm-0 item-0 merc-conf-0))) btr-0 mtr-0) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb-0 bank-conf-0) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n-0 cost-0 item-1 merc-conf-1 ncm-1 (hash n-0 (hash ncb-1 bank-conf-1)) (sign (order c m b cost-0 (enc n-0 cost-0 account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost-0 n) (hash ncm-0 item-0 merc-conf-0) mtr-0 (cat (sign (order c m b cost-0 (enc n cost-0 account-2 bank-conf-2 ncb-2 (hash n (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (enc n cost-0 account-2 bank-conf-2 ncb-2 (hash n (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb-2 bank-conf-2) (sign (bconf (hash c m b n cost-0 (hash n (hash ncm-0 item-0 merc-conf-0))) btr-0 mtr-0) (privk "sig" b)) (pubk "enc" m))))) (label 127) (parent 113) (unrealized (3 0) (5 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay-rely-guar (vars (bank-conf-commit bank-conf-decommit bank-conf-commit-0 bank-conf-decommit-0 mesg) (account account-0 account-1 account-2 acct) (cost amount) (n ncb ncm ncm-0 ncm-1 ncb-0 ncb-1 ncb-2 data) (item item-0 item-1 merchandise) (merc-conf bank-conf btr mtr merc-conf-0 btr-0 mtr-0 merc-conf-1 btr-1 mtr-1 bank-conf-0 bank-conf-1 bank-conf-2 text) (c m b name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 3 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit) (bank-conf-decommit bank-conf-decommit) (cost cost) (n n) (ncm ncm-0) (item item-0) (merc-conf merc-conf-0) (btr btr-0) (mtr mtr-0) (c c) (m m) (b b)) (defstrand merc 3 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit-0) (bank-conf-decommit bank-conf-decommit-0) (cost cost) (n n) (ncm ncm-1) (item item-1) (merc-conf merc-conf-1) (btr btr-1) (mtr mtr-1) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account-0) (cost cost) (n n) (ncb ncb-0) (bank-conf bank-conf-0) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm-0 item-0 merc-conf-0)) (account account-1) (cost cost) (n n) (ncb ncb-1) (bank-conf bank-conf-1) (btr btr-0) (mtr mtr-0) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm-1 item-1 merc-conf-1)) (account account-2) (cost cost) (n n) (ncb ncb-2) (bank-conf bank-conf-2) (btr btr-1) (mtr mtr-1) (c c) (m m) (b b)) (precedes ((0 0) (1 0)) ((0 0) (2 0)) ((0 0) (3 0)) ((1 1) (4 0)) ((2 1) (5 0)) ((3 1) (0 1)) ((4 1) (1 2)) ((5 1) (2 2))) (non-orig (privk "enc" b) (privk "sig" c) (privk "sig" b)) (uniq-orig n btr btr-0 mtr-0 btr-1 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (will-ship c m b item mtr) (buy-via c m b item-1 cost n) (buy-via c m b item-0 cost n) (buy-via c m b item cost n) (will-transfer c m b cost n mtr-1 btr-1) (will-transfer c m b cost n mtr-0 btr-0) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 rely-cust-3 rely-merc-3) (operation encryption-test (added-strand bank 2) (sign (bconf (hash c m b n cost (hash n (hash ncm-1 item-1 merc-conf-1))) btr-1 mtr-1) (privk "sig" b)) (2 2)) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc n cost item-0 merc-conf-0 ncm-0 bank-conf-commit (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm-0 item-0 merc-conf-0) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit (sign (bconf (hash c m b n cost (hash n (hash ncm-0 item-0 merc-conf-0))) btr-0 mtr-0) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc n cost item-1 merc-conf-1 ncm-1 bank-conf-commit-0 (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm-1 item-1 merc-conf-1) mtr-1 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit-0 (sign (bconf (hash c m b n cost (hash n (hash ncm-1 item-1 merc-conf-1))) btr-1 mtr-1) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb-0 bank-conf-0) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm-0 item-0 merc-conf-0) mtr-0 (cat (sign (order c m b cost (enc n cost account-1 bank-conf-1 ncb-1 (hash n (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-1 bank-conf-1 ncb-1 (hash n (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb-1 bank-conf-1) (sign (bconf (hash c m b n cost (hash n (hash ncm-0 item-0 merc-conf-0))) btr-0 mtr-0) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm-1 item-1 merc-conf-1) mtr-1 (cat (sign (order c m b cost (enc n cost account-2 bank-conf-2 ncb-2 (hash n (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-2 bank-conf-2 ncb-2 (hash n (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb-2 bank-conf-2) (sign (bconf (hash c m b n cost (hash n (hash ncm-1 item-1 merc-conf-1))) btr-1 mtr-1) (privk "sig" b)) (pubk "enc" m))))) (label 128) (parent 114) (unrealized (3 0) (4 0) (5 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay-rely-guar (vars (bank-conf-commit bank-conf-decommit bank-conf-commit-0 bank-conf-decommit-0 mesg) (account account-0 account-1 account-2 acct) (cost amount) (n ncb ncm ncm-0 ncb-0 ncb-1 n-0 ncb-2 ncm-1 data) (item item-0 item-1 merchandise) (merc-conf bank-conf btr mtr merc-conf-0 btr-0 mtr-0 bank-conf-0 bank-conf-1 merc-conf-1 bank-conf-2 text) (c m b name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 3 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit) (bank-conf-decommit bank-conf-decommit) (cost cost) (n n) (ncm ncm-0) (item item-0) (merc-conf merc-conf-0) (btr btr-0) (mtr mtr-0) (c c) (m m) (b b)) (defstrand merc 3 (for-bank (enc n-0 cost account-2 bank-conf-2 ncb-2 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit-0) (bank-conf-decommit bank-conf-decommit-0) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account-0) (cost cost) (n n) (ncb ncb-0) (bank-conf bank-conf-0) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm-0 item-0 merc-conf-0)) (account account-1) (cost cost) (n n) (ncb ncb-1) (bank-conf bank-conf-1) (btr btr-0) (mtr mtr-0) (c c) (m m) (b b)) (defstrand cust 1 (account account-2) (cost cost) (n n-0) (ncb ncb-2) (ncm ncm-1) (item item-1) (merc-conf merc-conf-1) (bank-conf bank-conf-2) (c c) (m m) (b b)) (precedes ((0 0) (1 0)) ((0 0) (2 0)) ((1 1) (4 0)) ((2 1) (3 0)) ((3 1) (0 1)) ((3 1) (2 2)) ((4 1) (1 2)) ((5 0) (2 0))) (non-orig (privk "enc" b) (privk "sig" c) (privk "sig" b)) (uniq-orig n btr mtr btr-0 mtr-0) (facts (neq n-0 ncb-2) (neq n ncb) (neq n-0 ncm-1) (neq n ncm) (neq ncm-1 ncb-2) (neq ncm ncb) (will-ship c m b item mtr) (buy-via c m b item-0 cost n) (buy-via c m b item-1 cost n-0) (buy-via c m b item cost n) (will-transfer c m b cost n mtr-0 btr-0) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 rely-cust-3 rely-merc-3) (operation encryption-test (displaced 6 3 bank 2) (sign (bconf (hash c m b n cost-0 (hash n (hash ncm-2 item-2 merc-conf-2))) btr-1 mtr-1) (privk "sig" b)) (2 2)) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc n cost item-0 merc-conf-0 ncm-0 bank-conf-commit (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm-0 item-0 merc-conf-0) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit (sign (bconf (hash c m b n cost (hash n (hash ncm-0 item-0 merc-conf-0))) btr-0 mtr-0) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm bank-conf-commit-0 (sign (order c m b cost (enc n-0 cost account-2 bank-conf-2 ncb-2 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n-0 cost account-2 bank-conf-2 ncb-2 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (privk "sig" c)) (enc n-0 cost account-2 bank-conf-2 ncb-2 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit-0 (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb-0 bank-conf-0) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm-0 item-0 merc-conf-0) mtr-0 (cat (sign (order c m b cost (enc n cost account-1 bank-conf-1 ncb-1 (hash n (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-1 bank-conf-1 ncb-1 (hash n (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb-1 bank-conf-1) (sign (bconf (hash c m b n cost (hash n (hash ncm-0 item-0 merc-conf-0))) btr-0 mtr-0) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n-0 cost item-1 merc-conf-1 ncm-1 (hash n-0 (hash ncb-2 bank-conf-2)) (sign (order c m b cost (enc n-0 cost account-2 bank-conf-2 ncb-2 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))))) (label 129) (parent 115) (unrealized (3 0) (4 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay-rely-guar (vars (bank-conf-commit bank-conf-decommit bank-conf-commit-0 bank-conf-decommit-0 mesg) (account account-0 account-1 account-2 account-3 acct) (cost cost-0 amount) (n ncb ncm ncm-0 ncm-1 ncb-0 ncb-1 n-0 ncb-2 ncm-2 ncb-3 data) (item item-0 item-1 item-2 merchandise) (merc-conf bank-conf btr mtr merc-conf-0 btr-0 mtr-0 merc-conf-1 btr-1 mtr-1 bank-conf-0 bank-conf-1 merc-conf-2 bank-conf-2 bank-conf-3 text) (c m b name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 3 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit) (bank-conf-decommit bank-conf-decommit) (cost cost) (n n) (ncm ncm-0) (item item-0) (merc-conf merc-conf-0) (btr btr-0) (mtr mtr-0) (c c) (m m) (b b)) (defstrand merc 3 (for-bank (enc n-0 cost-0 account-2 bank-conf-2 ncb-2 (hash n-0 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit-0) (bank-conf-decommit bank-conf-decommit-0) (cost cost-0) (n n) (ncm ncm-1) (item item-1) (merc-conf merc-conf-1) (btr btr-1) (mtr mtr-1) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account-0) (cost cost) (n n) (ncb ncb-0) (bank-conf bank-conf-0) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm-0 item-0 merc-conf-0)) (account account-1) (cost cost) (n n) (ncb ncb-1) (bank-conf bank-conf-1) (btr btr-0) (mtr mtr-0) (c c) (m m) (b b)) (defstrand cust 1 (account account-2) (cost cost-0) (n n-0) (ncb ncb-2) (ncm ncm-2) (item item-2) (merc-conf merc-conf-2) (bank-conf bank-conf-2) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm-1 item-1 merc-conf-1)) (account account-3) (cost cost-0) (n n) (ncb ncb-3) (bank-conf bank-conf-3) (btr btr-1) (mtr mtr-1) (c c) (m m) (b b)) (precedes ((0 0) (1 0)) ((0 0) (2 0)) ((0 0) (3 0)) ((1 1) (4 0)) ((2 1) (6 0)) ((3 1) (0 1)) ((4 1) (1 2)) ((5 0) (2 0)) ((6 1) (2 2))) (non-orig (privk "enc" b) (privk "sig" c) (privk "sig" b)) (uniq-orig n btr btr-0 mtr-0 btr-1 mtr-1) (facts (neq n-0 ncb-2) (neq n ncb) (neq n-0 ncm-2) (neq n ncm) (neq ncm-2 ncb-2) (neq ncm ncb) (will-ship c m b item mtr) (buy-via c m b item-1 cost-0 n) (buy-via c m b item-0 cost n) (buy-via c m b item-2 cost-0 n-0) (buy-via c m b item cost n) (will-transfer c m b cost-0 n mtr-1 btr-1) (will-transfer c m b cost n mtr-0 btr-0) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 rely-cust-3 rely-merc-3) (operation encryption-test (added-strand bank 2) (sign (bconf (hash c m b n cost-0 (hash n (hash ncm-1 item-1 merc-conf-1))) btr-1 mtr-1) (privk "sig" b)) (2 2)) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc n cost item-0 merc-conf-0 ncm-0 bank-conf-commit (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm-0 item-0 merc-conf-0) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit (sign (bconf (hash c m b n cost (hash n (hash ncm-0 item-0 merc-conf-0))) btr-0 mtr-0) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc n cost-0 item-1 merc-conf-1 ncm-1 bank-conf-commit-0 (sign (order c m b cost-0 (enc n-0 cost-0 account-2 bank-conf-2 ncb-2 (hash n-0 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost-0 n) (hash ncm-1 item-1 merc-conf-1) mtr-1 (cat (sign (order c m b cost-0 (enc n-0 cost-0 account-2 bank-conf-2 ncb-2 (hash n-0 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b))) (privk "sig" c)) (enc n-0 cost-0 account-2 bank-conf-2 ncb-2 (hash n-0 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit-0 (sign (bconf (hash c m b n cost-0 (hash n (hash ncm-1 item-1 merc-conf-1))) btr-1 mtr-1) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb-0 bank-conf-0) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm-0 item-0 merc-conf-0) mtr-0 (cat (sign (order c m b cost (enc n cost account-1 bank-conf-1 ncb-1 (hash n (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-1 bank-conf-1 ncb-1 (hash n (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb-1 bank-conf-1) (sign (bconf (hash c m b n cost (hash n (hash ncm-0 item-0 merc-conf-0))) btr-0 mtr-0) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n-0 cost-0 item-2 merc-conf-2 ncm-2 (hash n-0 (hash ncb-2 bank-conf-2)) (sign (order c m b cost-0 (enc n-0 cost-0 account-2 bank-conf-2 ncb-2 (hash n-0 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost-0 n) (hash ncm-1 item-1 merc-conf-1) mtr-1 (cat (sign (order c m b cost-0 (enc n cost-0 account-3 bank-conf-3 ncb-3 (hash n (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (privk "sig" c)) (enc n cost-0 account-3 bank-conf-3 ncb-3 (hash n (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb-3 bank-conf-3) (sign (bconf (hash c m b n cost-0 (hash n (hash ncm-1 item-1 merc-conf-1))) btr-1 mtr-1) (privk "sig" b)) (pubk "enc" m))))) (label 130) (parent 115) (unrealized (3 0) (4 0) (6 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay-rely-guar (vars (bank-conf-commit bank-conf-decommit bank-conf-commit-0 bank-conf-decommit-0 mesg) (account account-0 account-1 account-2 acct) (cost amount) (n ncb ncm ncm-0 ncb-0 n-0 ncb-1 ncm-1 ncb-2 data) (item item-0 item-1 merchandise) (merc-conf bank-conf btr mtr merc-conf-0 btr-0 mtr-0 bank-conf-0 merc-conf-1 bank-conf-1 bank-conf-2 text) (c m b name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 3 (for-bank (enc n-0 cost account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit) (bank-conf-decommit bank-conf-decommit) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 3 (for-bank (enc n-0 cost account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit-0) (bank-conf-decommit bank-conf-decommit-0) (cost cost) (n n) (ncm ncm-0) (item item-0) (merc-conf merc-conf-0) (btr btr-0) (mtr mtr-0) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account-0) (cost cost) (n n) (ncb ncb-0) (bank-conf bank-conf-0) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account-1) (cost cost) (n n-0) (ncb ncb-1) (ncm ncm-1) (item item-1) (merc-conf merc-conf-1) (bank-conf bank-conf-1) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm-0 item-0 merc-conf-0)) (account account-2) (cost cost) (n n) (ncb ncb-2) (bank-conf bank-conf-2) (btr btr-0) (mtr mtr-0) (c c) (m m) (b b)) (precedes ((0 0) (1 0)) ((0 0) (2 0)) ((1 1) (3 0)) ((2 1) (5 0)) ((3 1) (0 1)) ((3 1) (1 2)) ((4 0) (1 0)) ((4 0) (2 0)) ((5 1) (2 2))) (non-orig (privk "enc" b) (privk "sig" c) (privk "sig" b)) (uniq-orig n btr mtr btr-0 mtr-0) (facts (neq n-0 ncb-1) (neq n ncb) (neq n-0 ncm-1) (neq n ncm) (neq ncm-1 ncb-1) (neq ncm ncb) (will-ship c m b item mtr) (buy-via c m b item-0 cost n) (buy-via c m b item-1 cost n-0) (buy-via c m b item cost n) (will-transfer c m b cost n mtr-0 btr-0) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 rely-cust-3 rely-merc-3) (operation encryption-test (added-strand bank 2) (sign (bconf (hash c m b n cost (hash n (hash ncm-0 item-0 merc-conf-0))) btr-0 mtr-0) (privk "sig" b)) (2 2)) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc n cost item merc-conf ncm bank-conf-commit (sign (order c m b cost (enc n-0 cost account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n-0 cost account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (privk "sig" c)) (enc n-0 cost account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc n cost item-0 merc-conf-0 ncm-0 bank-conf-commit-0 (sign (order c m b cost (enc n-0 cost account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm-0 item-0 merc-conf-0) mtr-0 (cat (sign (order c m b cost (enc n-0 cost account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (privk "sig" c)) (enc n-0 cost account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit-0 (sign (bconf (hash c m b n cost (hash n (hash ncm-0 item-0 merc-conf-0))) btr-0 mtr-0) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb-0 bank-conf-0) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n-0 cost item-1 merc-conf-1 ncm-1 (hash n-0 (hash ncb-1 bank-conf-1)) (sign (order c m b cost (enc n-0 cost account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm-0 item-0 merc-conf-0) mtr-0 (cat (sign (order c m b cost (enc n cost account-2 bank-conf-2 ncb-2 (hash n (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-2 bank-conf-2 ncb-2 (hash n (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb-2 bank-conf-2) (sign (bconf (hash c m b n cost (hash n (hash ncm-0 item-0 merc-conf-0))) btr-0 mtr-0) (privk "sig" b)) (pubk "enc" m))))) (label 131) (parent 117) (unrealized (3 0) (5 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay-rely-guar (vars (bank-conf-commit bank-conf-decommit bank-conf-commit-0 bank-conf-decommit-0 mesg) (account account-0 account-1 account-2 account-3 acct) (cost cost-0 amount) (n ncb ncm ncm-0 ncb-0 n-0 ncb-1 ncm-1 n-1 ncb-2 ncm-2 ncb-3 data) (item item-0 item-1 item-2 merchandise) (merc-conf bank-conf btr mtr merc-conf-0 btr-0 mtr-0 bank-conf-0 merc-conf-1 bank-conf-1 merc-conf-2 bank-conf-2 bank-conf-3 text) (c m b name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 3 (for-bank (enc n-0 cost account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit) (bank-conf-decommit bank-conf-decommit) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 3 (for-bank (enc n-1 cost-0 account-2 bank-conf-2 ncb-2 (hash n-1 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit-0) (bank-conf-decommit bank-conf-decommit-0) (cost cost-0) (n n) (ncm ncm-0) (item item-0) (merc-conf merc-conf-0) (btr btr-0) (mtr mtr-0) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account-0) (cost cost) (n n) (ncb ncb-0) (bank-conf bank-conf-0) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account-1) (cost cost) (n n-0) (ncb ncb-1) (ncm ncm-1) (item item-1) (merc-conf merc-conf-1) (bank-conf bank-conf-1) (c c) (m m) (b b)) (defstrand cust 1 (account account-2) (cost cost-0) (n n-1) (ncb ncb-2) (ncm ncm-2) (item item-2) (merc-conf merc-conf-2) (bank-conf bank-conf-2) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm-0 item-0 merc-conf-0)) (account account-3) (cost cost-0) (n n) (ncb ncb-3) (bank-conf bank-conf-3) (btr btr-0) (mtr mtr-0) (c c) (m m) (b b)) (precedes ((0 0) (1 0)) ((0 0) (2 0)) ((1 1) (3 0)) ((2 1) (6 0)) ((3 1) (0 1)) ((3 1) (1 2)) ((4 0) (1 0)) ((5 0) (2 0)) ((6 1) (2 2))) (non-orig (privk "enc" b) (privk "sig" c) (privk "sig" b)) (uniq-orig n btr mtr btr-0 mtr-0) (facts (neq n-1 ncb-2) (neq n-0 ncb-1) (neq n ncb) (neq n-1 ncm-2) (neq n-0 ncm-1) (neq n ncm) (neq ncm-2 ncb-2) (neq ncm-1 ncb-1) (neq ncm ncb) (will-ship c m b item mtr) (buy-via c m b item-0 cost-0 n) (buy-via c m b item-2 cost-0 n-1) (buy-via c m b item-1 cost n-0) (buy-via c m b item cost n) (will-transfer c m b cost-0 n mtr-0 btr-0) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 rely-cust-3 rely-merc-3) (operation encryption-test (added-strand bank 2) (sign (bconf (hash c m b n cost-0 (hash n (hash ncm-0 item-0 merc-conf-0))) btr-0 mtr-0) (privk "sig" b)) (2 2)) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc n cost item merc-conf ncm bank-conf-commit (sign (order c m b cost (enc n-0 cost account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n-0 cost account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (privk "sig" c)) (enc n-0 cost account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc n cost-0 item-0 merc-conf-0 ncm-0 bank-conf-commit-0 (sign (order c m b cost-0 (enc n-1 cost-0 account-2 bank-conf-2 ncb-2 (hash n-1 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost-0 n) (hash ncm-0 item-0 merc-conf-0) mtr-0 (cat (sign (order c m b cost-0 (enc n-1 cost-0 account-2 bank-conf-2 ncb-2 (hash n-1 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b))) (privk "sig" c)) (enc n-1 cost-0 account-2 bank-conf-2 ncb-2 (hash n-1 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit-0 (sign (bconf (hash c m b n cost-0 (hash n (hash ncm-0 item-0 merc-conf-0))) btr-0 mtr-0) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb-0 bank-conf-0) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n-0 cost item-1 merc-conf-1 ncm-1 (hash n-0 (hash ncb-1 bank-conf-1)) (sign (order c m b cost (enc n-0 cost account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((send (enc n-1 cost-0 item-2 merc-conf-2 ncm-2 (hash n-1 (hash ncb-2 bank-conf-2)) (sign (order c m b cost-0 (enc n-1 cost-0 account-2 bank-conf-2 ncb-2 (hash n-1 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost-0 n) (hash ncm-0 item-0 merc-conf-0) mtr-0 (cat (sign (order c m b cost-0 (enc n cost-0 account-3 bank-conf-3 ncb-3 (hash n (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (enc n cost-0 account-3 bank-conf-3 ncb-3 (hash n (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb-3 bank-conf-3) (sign (bconf (hash c m b n cost-0 (hash n (hash ncm-0 item-0 merc-conf-0))) btr-0 mtr-0) (privk "sig" b)) (pubk "enc" m))))) (label 132) (parent 118) (unrealized (3 0) (6 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay-rely-guar (vars (bank-conf-commit bank-conf-decommit bank-conf-commit-0 bank-conf-decommit-0 mesg) (account account-0 account-1 account-2 account-3 acct) (cost cost-0 amount) (n ncb ncm ncm-0 ncm-1 ncb-0 n-0 ncb-1 ncm-2 ncb-2 ncb-3 data) (item item-0 item-1 item-2 merchandise) (merc-conf bank-conf btr mtr merc-conf-0 btr-0 mtr-0 merc-conf-1 btr-1 mtr-1 bank-conf-0 merc-conf-2 bank-conf-1 bank-conf-2 bank-conf-3 text) (c m b name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 3 (for-bank (enc n-0 cost-0 account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit) (bank-conf-decommit bank-conf-decommit) (cost cost-0) (n n) (ncm ncm-0) (item item-0) (merc-conf merc-conf-0) (btr btr-0) (mtr mtr-0) (c c) (m m) (b b)) (defstrand merc 3 (for-bank (enc n-0 cost-0 account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit-0) (bank-conf-decommit bank-conf-decommit-0) (cost cost-0) (n n) (ncm ncm-1) (item item-1) (merc-conf merc-conf-1) (btr btr-1) (mtr mtr-1) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account-0) (cost cost) (n n) (ncb ncb-0) (bank-conf bank-conf-0) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account-1) (cost cost-0) (n n-0) (ncb ncb-1) (ncm ncm-2) (item item-2) (merc-conf merc-conf-2) (bank-conf bank-conf-1) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm-0 item-0 merc-conf-0)) (account account-2) (cost cost-0) (n n) (ncb ncb-2) (bank-conf bank-conf-2) (btr btr-0) (mtr mtr-0) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm-1 item-1 merc-conf-1)) (account account-3) (cost cost-0) (n n) (ncb ncb-3) (bank-conf bank-conf-3) (btr btr-1) (mtr mtr-1) (c c) (m m) (b b)) (precedes ((0 0) (1 0)) ((0 0) (2 0)) ((0 0) (3 0)) ((1 1) (5 0)) ((2 1) (6 0)) ((3 1) (0 1)) ((4 0) (1 0)) ((4 0) (2 0)) ((5 1) (1 2)) ((6 1) (2 2))) (non-orig (privk "enc" b) (privk "sig" c) (privk "sig" b)) (uniq-orig n btr btr-0 mtr-0 btr-1 mtr-1) (facts (neq n-0 ncb-1) (neq n ncb) (neq n-0 ncm-2) (neq n ncm) (neq ncm-2 ncb-1) (neq ncm ncb) (will-ship c m b item mtr) (buy-via c m b item-1 cost-0 n) (buy-via c m b item-0 cost-0 n) (buy-via c m b item-2 cost-0 n-0) (buy-via c m b item cost n) (will-transfer c m b cost-0 n mtr-1 btr-1) (will-transfer c m b cost-0 n mtr-0 btr-0) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 rely-cust-3 rely-merc-3) (operation encryption-test (added-strand bank 2) (sign (bconf (hash c m b n cost-0 (hash n (hash ncm-1 item-1 merc-conf-1))) btr-1 mtr-1) (privk "sig" b)) (2 2)) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc n cost-0 item-0 merc-conf-0 ncm-0 bank-conf-commit (sign (order c m b cost-0 (enc n-0 cost-0 account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost-0 n) (hash ncm-0 item-0 merc-conf-0) mtr-0 (cat (sign (order c m b cost-0 (enc n-0 cost-0 account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b))) (privk "sig" c)) (enc n-0 cost-0 account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit (sign (bconf (hash c m b n cost-0 (hash n (hash ncm-0 item-0 merc-conf-0))) btr-0 mtr-0) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc n cost-0 item-1 merc-conf-1 ncm-1 bank-conf-commit-0 (sign (order c m b cost-0 (enc n-0 cost-0 account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost-0 n) (hash ncm-1 item-1 merc-conf-1) mtr-1 (cat (sign (order c m b cost-0 (enc n-0 cost-0 account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b))) (privk "sig" c)) (enc n-0 cost-0 account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit-0 (sign (bconf (hash c m b n cost-0 (hash n (hash ncm-1 item-1 merc-conf-1))) btr-1 mtr-1) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb-0 bank-conf-0) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n-0 cost-0 item-2 merc-conf-2 ncm-2 (hash n-0 (hash ncb-1 bank-conf-1)) (sign (order c m b cost-0 (enc n-0 cost-0 account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost-0 n) (hash ncm-0 item-0 merc-conf-0) mtr-0 (cat (sign (order c m b cost-0 (enc n cost-0 account-2 bank-conf-2 ncb-2 (hash n (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (enc n cost-0 account-2 bank-conf-2 ncb-2 (hash n (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb-2 bank-conf-2) (sign (bconf (hash c m b n cost-0 (hash n (hash ncm-0 item-0 merc-conf-0))) btr-0 mtr-0) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost-0 n) (hash ncm-1 item-1 merc-conf-1) mtr-1 (cat (sign (order c m b cost-0 (enc n cost-0 account-3 bank-conf-3 ncb-3 (hash n (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (privk "sig" c)) (enc n cost-0 account-3 bank-conf-3 ncb-3 (hash n (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb-3 bank-conf-3) (sign (bconf (hash c m b n cost-0 (hash n (hash ncm-1 item-1 merc-conf-1))) btr-1 mtr-1) (privk "sig" b)) (pubk "enc" m))))) (label 133) (parent 120) (unrealized (3 0) (5 0) (6 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay-rely-guar (vars (bank-conf-commit bank-conf-decommit bank-conf-commit-0 bank-conf-decommit-0 mesg) (account account-0 account-1 account-2 account-3 account-4 acct) (cost cost-0 cost-1 amount) (n ncb ncm ncm-0 ncm-1 ncb-0 n-0 ncb-1 ncm-2 ncb-2 n-1 ncb-3 ncm-3 ncb-4 data) (item item-0 item-1 item-2 item-3 merchandise) (merc-conf bank-conf btr mtr merc-conf-0 btr-0 mtr-0 merc-conf-1 btr-1 mtr-1 bank-conf-0 merc-conf-2 bank-conf-1 bank-conf-2 merc-conf-3 bank-conf-3 bank-conf-4 text) (c m b name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 3 (for-bank (enc n-0 cost-0 account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit) (bank-conf-decommit bank-conf-decommit) (cost cost-0) (n n) (ncm ncm-0) (item item-0) (merc-conf merc-conf-0) (btr btr-0) (mtr mtr-0) (c c) (m m) (b b)) (defstrand merc 3 (for-bank (enc n-1 cost-1 account-3 bank-conf-3 ncb-3 (hash n-1 (hash ncm-3 item-3 merc-conf-3)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit-0) (bank-conf-decommit bank-conf-decommit-0) (cost cost-1) (n n) (ncm ncm-1) (item item-1) (merc-conf merc-conf-1) (btr btr-1) (mtr mtr-1) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account-0) (cost cost) (n n) (ncb ncb-0) (bank-conf bank-conf-0) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account-1) (cost cost-0) (n n-0) (ncb ncb-1) (ncm ncm-2) (item item-2) (merc-conf merc-conf-2) (bank-conf bank-conf-1) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm-0 item-0 merc-conf-0)) (account account-2) (cost cost-0) (n n) (ncb ncb-2) (bank-conf bank-conf-2) (btr btr-0) (mtr mtr-0) (c c) (m m) (b b)) (defstrand cust 1 (account account-3) (cost cost-1) (n n-1) (ncb ncb-3) (ncm ncm-3) (item item-3) (merc-conf merc-conf-3) (bank-conf bank-conf-3) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm-1 item-1 merc-conf-1)) (account account-4) (cost cost-1) (n n) (ncb ncb-4) (bank-conf bank-conf-4) (btr btr-1) (mtr mtr-1) (c c) (m m) (b b)) (precedes ((0 0) (1 0)) ((0 0) (2 0)) ((0 0) (3 0)) ((1 1) (5 0)) ((2 1) (7 0)) ((3 1) (0 1)) ((4 0) (1 0)) ((5 1) (1 2)) ((6 0) (2 0)) ((7 1) (2 2))) (non-orig (privk "enc" b) (privk "sig" c) (privk "sig" b)) (uniq-orig n btr btr-0 mtr-0 btr-1 mtr-1) (facts (neq n-1 ncb-3) (neq n-0 ncb-1) (neq n ncb) (neq n-1 ncm-3) (neq n-0 ncm-2) (neq n ncm) (neq ncm-3 ncb-3) (neq ncm-2 ncb-1) (neq ncm ncb) (will-ship c m b item mtr) (buy-via c m b item-1 cost-1 n) (buy-via c m b item-0 cost-0 n) (buy-via c m b item-3 cost-1 n-1) (buy-via c m b item-2 cost-0 n-0) (buy-via c m b item cost n) (will-transfer c m b cost-1 n mtr-1 btr-1) (will-transfer c m b cost-0 n mtr-0 btr-0) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 rely-cust-3 rely-merc-3) (operation encryption-test (added-strand bank 2) (sign (bconf (hash c m b n cost-1 (hash n (hash ncm-1 item-1 merc-conf-1))) btr-1 mtr-1) (privk "sig" b)) (2 2)) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc n cost-0 item-0 merc-conf-0 ncm-0 bank-conf-commit (sign (order c m b cost-0 (enc n-0 cost-0 account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost-0 n) (hash ncm-0 item-0 merc-conf-0) mtr-0 (cat (sign (order c m b cost-0 (enc n-0 cost-0 account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b))) (privk "sig" c)) (enc n-0 cost-0 account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit (sign (bconf (hash c m b n cost-0 (hash n (hash ncm-0 item-0 merc-conf-0))) btr-0 mtr-0) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc n cost-1 item-1 merc-conf-1 ncm-1 bank-conf-commit-0 (sign (order c m b cost-1 (enc n-1 cost-1 account-3 bank-conf-3 ncb-3 (hash n-1 (hash ncm-3 item-3 merc-conf-3)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost-1 n) (hash ncm-1 item-1 merc-conf-1) mtr-1 (cat (sign (order c m b cost-1 (enc n-1 cost-1 account-3 bank-conf-3 ncb-3 (hash n-1 (hash ncm-3 item-3 merc-conf-3)) (pubk "enc" b))) (privk "sig" c)) (enc n-1 cost-1 account-3 bank-conf-3 ncb-3 (hash n-1 (hash ncm-3 item-3 merc-conf-3)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit-0 (sign (bconf (hash c m b n cost-1 (hash n (hash ncm-1 item-1 merc-conf-1))) btr-1 mtr-1) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb-0 bank-conf-0) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n-0 cost-0 item-2 merc-conf-2 ncm-2 (hash n-0 (hash ncb-1 bank-conf-1)) (sign (order c m b cost-0 (enc n-0 cost-0 account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost-0 n) (hash ncm-0 item-0 merc-conf-0) mtr-0 (cat (sign (order c m b cost-0 (enc n cost-0 account-2 bank-conf-2 ncb-2 (hash n (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (enc n cost-0 account-2 bank-conf-2 ncb-2 (hash n (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb-2 bank-conf-2) (sign (bconf (hash c m b n cost-0 (hash n (hash ncm-0 item-0 merc-conf-0))) btr-0 mtr-0) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n-1 cost-1 item-3 merc-conf-3 ncm-3 (hash n-1 (hash ncb-3 bank-conf-3)) (sign (order c m b cost-1 (enc n-1 cost-1 account-3 bank-conf-3 ncb-3 (hash n-1 (hash ncm-3 item-3 merc-conf-3)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost-1 n) (hash ncm-1 item-1 merc-conf-1) mtr-1 (cat (sign (order c m b cost-1 (enc n cost-1 account-4 bank-conf-4 ncb-4 (hash n (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (privk "sig" c)) (enc n cost-1 account-4 bank-conf-4 ncb-4 (hash n (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb-4 bank-conf-4) (sign (bconf (hash c m b n cost-1 (hash n (hash ncm-1 item-1 merc-conf-1))) btr-1 mtr-1) (privk "sig" b)) (pubk "enc" m))))) (label 134) (parent 121) (unrealized (3 0) (5 0) (7 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay-rely-guar (vars (bank-conf-commit bank-conf-decommit mesg) (account acct) (cost amount) (n ncb ncm data) (item merchandise) (merc-conf bank-conf btr mtr btr-0 mtr-0 text) (c m b name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 3 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit) (bank-conf-decommit bank-conf-decommit) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr-0) (mtr mtr-0) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr-0) (mtr mtr-0) (c c) (m m) (b b)) (precedes ((0 0) (1 0)) ((0 0) (2 0)) ((1 1) (3 0)) ((2 1) (0 1)) ((3 1) (1 2))) (non-orig (privk "enc" b) (privk "sig" c) (privk "sig" b)) (uniq-orig n btr btr-0 mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (will-ship c m b item mtr) (buy-via c m b item cost n) (will-transfer c m b cost n mtr-0 btr-0) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 rely-cust-3) (operation encryption-test (displaced 4 0 cust 1) (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (3 0)) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc n cost item merc-conf ncm bank-conf-commit (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-0) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-0) (privk "sig" b)) (pubk "enc" m))))) (label 135) (parent 123) (realized) (shape) (maps ((0 1 1) ((c c) (m m) (b b) (n n) (cost cost) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (account account) (ncb ncb) (ncm ncm) (cost-0 cost) (item-0 item) (merc-conf-0 merc-conf) (btr-0 btr-0) (mtr-0 mtr-0) (ncm-0 ncm) (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit) (bank-conf-decommit bank-conf-decommit) (cost-1 cost) (item-1 item) (merc-conf-1 merc-conf) (btr-1 btr-0) (mtr-1 mtr-0) (ncm-1 ncm) (for-bank-0 (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit-0 bank-conf-commit) (bank-conf-decommit-0 bank-conf-decommit)))) (origs (btr-0 (3 1)) (btr (2 1)) (mtr-0 (1 1)) (n (0 0)))) (defskeleton minipay-rely-guar (vars (bank-conf-commit bank-conf-decommit mesg) (account account-0 acct) (cost amount) (n ncb ncm n-0 ncb-0 ncm-0 data) (item item-0 merchandise) (merc-conf bank-conf btr mtr btr-0 mtr-0 merc-conf-0 bank-conf-0 text) (c m b name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 3 (for-bank (enc n-0 cost account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit) (bank-conf-decommit bank-conf-decommit) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr-0) (mtr mtr-0) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account-0) (cost cost) (n n-0) (ncb ncb-0) (ncm ncm-0) (item item-0) (merc-conf merc-conf-0) (bank-conf bank-conf-0) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr-0) (mtr mtr-0) (c c) (m m) (b b)) (precedes ((0 0) (1 0)) ((0 0) (2 0)) ((1 1) (4 0)) ((2 1) (0 1)) ((3 0) (1 0)) ((4 1) (1 2))) (non-orig (privk "enc" b) (privk "sig" c) (privk "sig" b)) (uniq-orig n btr btr-0 mtr-0) (facts (neq n-0 ncb-0) (neq n ncb) (neq n-0 ncm-0) (neq n ncm) (neq ncm-0 ncb-0) (neq ncm ncb) (will-ship c m b item mtr) (buy-via c m b item-0 cost n-0) (buy-via c m b item cost n) (will-transfer c m b cost n mtr-0 btr-0) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 rely-cust-3) (operation encryption-test (displaced 5 0 cust 1) (sign (order c m b cost-0 (enc n cost-0 account-1 bank-conf-1 ncb-1 (hash n (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (privk "sig" c)) (4 0)) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc n cost item merc-conf ncm bank-conf-commit (sign (order c m b cost (enc n-0 cost account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n-0 cost account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (enc n-0 cost account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-0) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n-0 cost item-0 merc-conf-0 ncm-0 (hash n-0 (hash ncb-0 bank-conf-0)) (sign (order c m b cost (enc n-0 cost account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-0) (privk "sig" b)) (pubk "enc" m))))) (label 136) (parent 125) (unrealized (4 0)) (dead) (comment "empty cohort")) (defskeleton minipay-rely-guar (vars (bank-conf-commit bank-conf-decommit bank-conf-commit-0 bank-conf-decommit-0 mesg) (account account-0 acct) (cost amount) (n ncb ncm ncm-0 ncb-0 data) (item item-0 merchandise) (merc-conf bank-conf btr mtr merc-conf-0 btr-0 mtr-0 bank-conf-0 text) (c m b name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 3 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit) (bank-conf-decommit bank-conf-decommit) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 3 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit-0) (bank-conf-decommit bank-conf-decommit-0) (cost cost) (n n) (ncm ncm-0) (item item-0) (merc-conf merc-conf-0) (btr btr-0) (mtr mtr-0) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm-0 item-0 merc-conf-0)) (account account-0) (cost cost) (n n) (ncb ncb-0) (bank-conf bank-conf-0) (btr btr-0) (mtr mtr-0) (c c) (m m) (b b)) (precedes ((0 0) (1 0)) ((0 0) (2 0)) ((1 1) (3 0)) ((2 1) (4 0)) ((3 1) (0 1)) ((3 1) (1 2)) ((4 1) (2 2))) (non-orig (privk "enc" b) (privk "sig" c) (privk "sig" b)) (uniq-orig n btr mtr btr-0 mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (will-ship c m b item mtr) (buy-via c m b item-0 cost n) (buy-via c m b item cost n) (will-transfer c m b cost n mtr-0 btr-0) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 rely-cust-3 rely-merc-3) (operation encryption-test (displaced 5 0 cust 1) (sign (order c m b cost (enc n cost account-1 bank-conf-1 ncb-1 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (3 0)) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc n cost item merc-conf ncm bank-conf-commit (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc n cost item-0 merc-conf-0 ncm-0 bank-conf-commit-0 (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm-0 item-0 merc-conf-0) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit-0 (sign (bconf (hash c m b n cost (hash n (hash ncm-0 item-0 merc-conf-0))) btr-0 mtr-0) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm-0 item-0 merc-conf-0) mtr-0 (cat (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb-0 bank-conf-0) (sign (bconf (hash c m b n cost (hash n (hash ncm-0 item-0 merc-conf-0))) btr-0 mtr-0) (privk "sig" b)) (pubk "enc" m))))) (label 137) (parent 126) (unrealized (4 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay-rely-guar (vars (bank-conf-commit bank-conf-decommit bank-conf-commit-0 bank-conf-decommit-0 mesg) (account account-0 account-1 acct) (cost cost-0 amount) (n ncb ncm ncm-0 n-0 ncb-0 ncm-1 ncb-1 data) (item item-0 item-1 merchandise) (merc-conf bank-conf btr mtr merc-conf-0 btr-0 mtr-0 merc-conf-1 bank-conf-0 bank-conf-1 text) (c m b name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 3 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit) (bank-conf-decommit bank-conf-decommit) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 3 (for-bank (enc n-0 cost-0 account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit-0) (bank-conf-decommit bank-conf-decommit-0) (cost cost-0) (n n) (ncm ncm-0) (item item-0) (merc-conf merc-conf-0) (btr btr-0) (mtr mtr-0) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account-0) (cost cost-0) (n n-0) (ncb ncb-0) (ncm ncm-1) (item item-1) (merc-conf merc-conf-1) (bank-conf bank-conf-0) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm-0 item-0 merc-conf-0)) (account account-1) (cost cost-0) (n n) (ncb ncb-1) (bank-conf bank-conf-1) (btr btr-0) (mtr mtr-0) (c c) (m m) (b b)) (precedes ((0 0) (1 0)) ((0 0) (2 0)) ((1 1) (3 0)) ((2 1) (5 0)) ((3 1) (0 1)) ((3 1) (1 2)) ((4 0) (2 0)) ((5 1) (2 2))) (non-orig (privk "enc" b) (privk "sig" c) (privk "sig" b)) (uniq-orig n btr mtr btr-0 mtr-0) (facts (neq n-0 ncb-0) (neq n ncb) (neq n-0 ncm-1) (neq n ncm) (neq ncm-1 ncb-0) (neq ncm ncb) (will-ship c m b item mtr) (buy-via c m b item-0 cost-0 n) (buy-via c m b item-1 cost-0 n-0) (buy-via c m b item cost n) (will-transfer c m b cost-0 n mtr-0 btr-0) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 rely-cust-3 rely-merc-3) (operation encryption-test (displaced 6 0 cust 1) (sign (order c m b cost (enc n cost account-2 bank-conf-2 ncb-2 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (3 0)) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc n cost item merc-conf ncm bank-conf-commit (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc n cost-0 item-0 merc-conf-0 ncm-0 bank-conf-commit-0 (sign (order c m b cost-0 (enc n-0 cost-0 account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost-0 n) (hash ncm-0 item-0 merc-conf-0) mtr-0 (cat (sign (order c m b cost-0 (enc n-0 cost-0 account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (privk "sig" c)) (enc n-0 cost-0 account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit-0 (sign (bconf (hash c m b n cost-0 (hash n (hash ncm-0 item-0 merc-conf-0))) btr-0 mtr-0) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n-0 cost-0 item-1 merc-conf-1 ncm-1 (hash n-0 (hash ncb-0 bank-conf-0)) (sign (order c m b cost-0 (enc n-0 cost-0 account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost-0 n) (hash ncm-0 item-0 merc-conf-0) mtr-0 (cat (sign (order c m b cost-0 (enc n cost-0 account-1 bank-conf-1 ncb-1 (hash n (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (enc n cost-0 account-1 bank-conf-1 ncb-1 (hash n (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb-1 bank-conf-1) (sign (bconf (hash c m b n cost-0 (hash n (hash ncm-0 item-0 merc-conf-0))) btr-0 mtr-0) (privk "sig" b)) (pubk "enc" m))))) (label 138) (parent 127) (unrealized (5 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay-rely-guar (vars (bank-conf-commit bank-conf-decommit bank-conf-commit-0 bank-conf-decommit-0 mesg) (account account-0 account-1 acct) (cost amount) (n ncb ncm ncm-0 ncm-1 ncb-0 ncb-1 data) (item item-0 item-1 merchandise) (merc-conf bank-conf btr mtr merc-conf-0 btr-0 mtr-0 merc-conf-1 btr-1 mtr-1 bank-conf-0 bank-conf-1 text) (c m b name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 3 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit) (bank-conf-decommit bank-conf-decommit) (cost cost) (n n) (ncm ncm-0) (item item-0) (merc-conf merc-conf-0) (btr btr-0) (mtr mtr-0) (c c) (m m) (b b)) (defstrand merc 3 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit-0) (bank-conf-decommit bank-conf-decommit-0) (cost cost) (n n) (ncm ncm-1) (item item-1) (merc-conf merc-conf-1) (btr btr-1) (mtr mtr-1) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm-0 item-0 merc-conf-0)) (account account-0) (cost cost) (n n) (ncb ncb-0) (bank-conf bank-conf-0) (btr btr-0) (mtr mtr-0) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm-1 item-1 merc-conf-1)) (account account-1) (cost cost) (n n) (ncb ncb-1) (bank-conf bank-conf-1) (btr btr-1) (mtr mtr-1) (c c) (m m) (b b)) (precedes ((0 0) (1 0)) ((0 0) (2 0)) ((0 0) (3 0)) ((1 1) (4 0)) ((2 1) (5 0)) ((3 1) (0 1)) ((4 1) (1 2)) ((5 1) (2 2))) (non-orig (privk "enc" b) (privk "sig" c) (privk "sig" b)) (uniq-orig n btr btr-0 mtr-0 btr-1 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (will-ship c m b item mtr) (buy-via c m b item-1 cost n) (buy-via c m b item-0 cost n) (buy-via c m b item cost n) (will-transfer c m b cost n mtr-1 btr-1) (will-transfer c m b cost n mtr-0 btr-0) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 rely-cust-3 rely-merc-3) (operation encryption-test (displaced 6 0 cust 1) (sign (order c m b cost (enc n cost account-2 bank-conf-2 ncb-2 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (3 0)) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc n cost item-0 merc-conf-0 ncm-0 bank-conf-commit (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm-0 item-0 merc-conf-0) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit (sign (bconf (hash c m b n cost (hash n (hash ncm-0 item-0 merc-conf-0))) btr-0 mtr-0) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc n cost item-1 merc-conf-1 ncm-1 bank-conf-commit-0 (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm-1 item-1 merc-conf-1) mtr-1 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit-0 (sign (bconf (hash c m b n cost (hash n (hash ncm-1 item-1 merc-conf-1))) btr-1 mtr-1) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm-0 item-0 merc-conf-0) mtr-0 (cat (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb-0 bank-conf-0) (sign (bconf (hash c m b n cost (hash n (hash ncm-0 item-0 merc-conf-0))) btr-0 mtr-0) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm-1 item-1 merc-conf-1) mtr-1 (cat (sign (order c m b cost (enc n cost account-1 bank-conf-1 ncb-1 (hash n (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-1 bank-conf-1 ncb-1 (hash n (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb-1 bank-conf-1) (sign (bconf (hash c m b n cost (hash n (hash ncm-1 item-1 merc-conf-1))) btr-1 mtr-1) (privk "sig" b)) (pubk "enc" m))))) (label 139) (parent 128) (unrealized (4 0) (5 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay-rely-guar (vars (bank-conf-commit bank-conf-decommit bank-conf-commit-0 bank-conf-decommit-0 mesg) (account account-0 account-1 acct) (cost amount) (n ncb ncm ncm-0 ncb-0 n-0 ncb-1 ncm-1 data) (item item-0 item-1 merchandise) (merc-conf bank-conf btr mtr merc-conf-0 btr-0 mtr-0 bank-conf-0 merc-conf-1 bank-conf-1 text) (c m b name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 3 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit) (bank-conf-decommit bank-conf-decommit) (cost cost) (n n) (ncm ncm-0) (item item-0) (merc-conf merc-conf-0) (btr btr-0) (mtr mtr-0) (c c) (m m) (b b)) (defstrand merc 3 (for-bank (enc n-0 cost account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit-0) (bank-conf-decommit bank-conf-decommit-0) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm-0 item-0 merc-conf-0)) (account account-0) (cost cost) (n n) (ncb ncb-0) (bank-conf bank-conf-0) (btr btr-0) (mtr mtr-0) (c c) (m m) (b b)) (defstrand cust 1 (account account-1) (cost cost) (n n-0) (ncb ncb-1) (ncm ncm-1) (item item-1) (merc-conf merc-conf-1) (bank-conf bank-conf-1) (c c) (m m) (b b)) (precedes ((0 0) (1 0)) ((0 0) (2 0)) ((1 1) (4 0)) ((2 1) (3 0)) ((3 1) (0 1)) ((3 1) (2 2)) ((4 1) (1 2)) ((5 0) (2 0))) (non-orig (privk "enc" b) (privk "sig" c) (privk "sig" b)) (uniq-orig n btr mtr btr-0 mtr-0) (facts (neq n-0 ncb-1) (neq n ncb) (neq n-0 ncm-1) (neq n ncm) (neq ncm-1 ncb-1) (neq ncm ncb) (will-ship c m b item mtr) (buy-via c m b item-0 cost n) (buy-via c m b item-1 cost n-0) (buy-via c m b item cost n) (will-transfer c m b cost n mtr-0 btr-0) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 rely-cust-3 rely-merc-3) (operation encryption-test (displaced 6 0 cust 1) (sign (order c m b cost (enc n cost account-2 bank-conf-2 ncb-2 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (3 0)) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc n cost item-0 merc-conf-0 ncm-0 bank-conf-commit (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm-0 item-0 merc-conf-0) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit (sign (bconf (hash c m b n cost (hash n (hash ncm-0 item-0 merc-conf-0))) btr-0 mtr-0) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm bank-conf-commit-0 (sign (order c m b cost (enc n-0 cost account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n-0 cost account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (privk "sig" c)) (enc n-0 cost account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit-0 (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm-0 item-0 merc-conf-0) mtr-0 (cat (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb-0 bank-conf-0) (sign (bconf (hash c m b n cost (hash n (hash ncm-0 item-0 merc-conf-0))) btr-0 mtr-0) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n-0 cost item-1 merc-conf-1 ncm-1 (hash n-0 (hash ncb-1 bank-conf-1)) (sign (order c m b cost (enc n-0 cost account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))))) (label 140) (parent 129) (unrealized (3 0) (4 0)) (dead) (comment "empty cohort")) (defskeleton minipay-rely-guar (vars (bank-conf-commit bank-conf-decommit bank-conf-commit-0 bank-conf-decommit-0 mesg) (account account-0 account-1 account-2 acct) (cost cost-0 amount) (n ncb ncm ncm-0 ncm-1 ncb-0 n-0 ncb-1 ncm-2 ncb-2 data) (item item-0 item-1 item-2 merchandise) (merc-conf bank-conf btr mtr merc-conf-0 btr-0 mtr-0 merc-conf-1 btr-1 mtr-1 bank-conf-0 merc-conf-2 bank-conf-1 bank-conf-2 text) (c m b name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 3 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit) (bank-conf-decommit bank-conf-decommit) (cost cost) (n n) (ncm ncm-0) (item item-0) (merc-conf merc-conf-0) (btr btr-0) (mtr mtr-0) (c c) (m m) (b b)) (defstrand merc 3 (for-bank (enc n-0 cost-0 account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit-0) (bank-conf-decommit bank-conf-decommit-0) (cost cost-0) (n n) (ncm ncm-1) (item item-1) (merc-conf merc-conf-1) (btr btr-1) (mtr mtr-1) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm-0 item-0 merc-conf-0)) (account account-0) (cost cost) (n n) (ncb ncb-0) (bank-conf bank-conf-0) (btr btr-0) (mtr mtr-0) (c c) (m m) (b b)) (defstrand cust 1 (account account-1) (cost cost-0) (n n-0) (ncb ncb-1) (ncm ncm-2) (item item-2) (merc-conf merc-conf-2) (bank-conf bank-conf-1) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm-1 item-1 merc-conf-1)) (account account-2) (cost cost-0) (n n) (ncb ncb-2) (bank-conf bank-conf-2) (btr btr-1) (mtr mtr-1) (c c) (m m) (b b)) (precedes ((0 0) (1 0)) ((0 0) (2 0)) ((0 0) (3 0)) ((1 1) (4 0)) ((2 1) (6 0)) ((3 1) (0 1)) ((4 1) (1 2)) ((5 0) (2 0)) ((6 1) (2 2))) (non-orig (privk "enc" b) (privk "sig" c) (privk "sig" b)) (uniq-orig n btr btr-0 mtr-0 btr-1 mtr-1) (facts (neq n-0 ncb-1) (neq n ncb) (neq n-0 ncm-2) (neq n ncm) (neq ncm-2 ncb-1) (neq ncm ncb) (will-ship c m b item mtr) (buy-via c m b item-1 cost-0 n) (buy-via c m b item-0 cost n) (buy-via c m b item-2 cost-0 n-0) (buy-via c m b item cost n) (will-transfer c m b cost-0 n mtr-1 btr-1) (will-transfer c m b cost n mtr-0 btr-0) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 rely-cust-3 rely-merc-3) (operation encryption-test (displaced 7 0 cust 1) (sign (order c m b cost (enc n cost account-3 bank-conf-3 ncb-3 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (3 0)) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc n cost item-0 merc-conf-0 ncm-0 bank-conf-commit (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm-0 item-0 merc-conf-0) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit (sign (bconf (hash c m b n cost (hash n (hash ncm-0 item-0 merc-conf-0))) btr-0 mtr-0) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc n cost-0 item-1 merc-conf-1 ncm-1 bank-conf-commit-0 (sign (order c m b cost-0 (enc n-0 cost-0 account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost-0 n) (hash ncm-1 item-1 merc-conf-1) mtr-1 (cat (sign (order c m b cost-0 (enc n-0 cost-0 account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b))) (privk "sig" c)) (enc n-0 cost-0 account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit-0 (sign (bconf (hash c m b n cost-0 (hash n (hash ncm-1 item-1 merc-conf-1))) btr-1 mtr-1) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm-0 item-0 merc-conf-0) mtr-0 (cat (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb-0 bank-conf-0) (sign (bconf (hash c m b n cost (hash n (hash ncm-0 item-0 merc-conf-0))) btr-0 mtr-0) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n-0 cost-0 item-2 merc-conf-2 ncm-2 (hash n-0 (hash ncb-1 bank-conf-1)) (sign (order c m b cost-0 (enc n-0 cost-0 account-1 bank-conf-1 ncb-1 (hash n-0 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost-0 n) (hash ncm-1 item-1 merc-conf-1) mtr-1 (cat (sign (order c m b cost-0 (enc n cost-0 account-2 bank-conf-2 ncb-2 (hash n (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (privk "sig" c)) (enc n cost-0 account-2 bank-conf-2 ncb-2 (hash n (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb-2 bank-conf-2) (sign (bconf (hash c m b n cost-0 (hash n (hash ncm-1 item-1 merc-conf-1))) btr-1 mtr-1) (privk "sig" b)) (pubk "enc" m))))) (label 141) (parent 130) (unrealized (4 0) (6 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay-rely-guar (vars (bank-conf-commit bank-conf-decommit bank-conf-commit-0 bank-conf-decommit-0 mesg) (account account-0 account-1 acct) (cost amount) (n ncb ncm ncm-0 n-0 ncb-0 ncm-1 ncb-1 data) (item item-0 item-1 merchandise) (merc-conf bank-conf btr mtr merc-conf-0 btr-0 mtr-0 merc-conf-1 bank-conf-0 bank-conf-1 text) (c m b name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 3 (for-bank (enc n-0 cost account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit) (bank-conf-decommit bank-conf-decommit) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 3 (for-bank (enc n-0 cost account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit-0) (bank-conf-decommit bank-conf-decommit-0) (cost cost) (n n) (ncm ncm-0) (item item-0) (merc-conf merc-conf-0) (btr btr-0) (mtr mtr-0) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account-0) (cost cost) (n n-0) (ncb ncb-0) (ncm ncm-1) (item item-1) (merc-conf merc-conf-1) (bank-conf bank-conf-0) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm-0 item-0 merc-conf-0)) (account account-1) (cost cost) (n n) (ncb ncb-1) (bank-conf bank-conf-1) (btr btr-0) (mtr mtr-0) (c c) (m m) (b b)) (precedes ((0 0) (1 0)) ((0 0) (2 0)) ((1 1) (3 0)) ((2 1) (5 0)) ((3 1) (0 1)) ((3 1) (1 2)) ((4 0) (1 0)) ((4 0) (2 0)) ((5 1) (2 2))) (non-orig (privk "enc" b) (privk "sig" c) (privk "sig" b)) (uniq-orig n btr mtr btr-0 mtr-0) (facts (neq n-0 ncb-0) (neq n ncb) (neq n-0 ncm-1) (neq n ncm) (neq ncm-1 ncb-0) (neq ncm ncb) (will-ship c m b item mtr) (buy-via c m b item-0 cost n) (buy-via c m b item-1 cost n-0) (buy-via c m b item cost n) (will-transfer c m b cost n mtr-0 btr-0) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 rely-cust-3 rely-merc-3) (operation encryption-test (displaced 6 0 cust 1) (sign (order c m b cost (enc n cost account-2 bank-conf-2 ncb-2 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (3 0)) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc n cost item merc-conf ncm bank-conf-commit (sign (order c m b cost (enc n-0 cost account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n-0 cost account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (privk "sig" c)) (enc n-0 cost account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc n cost item-0 merc-conf-0 ncm-0 bank-conf-commit-0 (sign (order c m b cost (enc n-0 cost account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm-0 item-0 merc-conf-0) mtr-0 (cat (sign (order c m b cost (enc n-0 cost account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (privk "sig" c)) (enc n-0 cost account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit-0 (sign (bconf (hash c m b n cost (hash n (hash ncm-0 item-0 merc-conf-0))) btr-0 mtr-0) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n-0 cost item-1 merc-conf-1 ncm-1 (hash n-0 (hash ncb-0 bank-conf-0)) (sign (order c m b cost (enc n-0 cost account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm-0 item-0 merc-conf-0) mtr-0 (cat (sign (order c m b cost (enc n cost account-1 bank-conf-1 ncb-1 (hash n (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-1 bank-conf-1 ncb-1 (hash n (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb-1 bank-conf-1) (sign (bconf (hash c m b n cost (hash n (hash ncm-0 item-0 merc-conf-0))) btr-0 mtr-0) (privk "sig" b)) (pubk "enc" m))))) (label 142) (parent 131) (unrealized (3 0) (5 0)) (dead) (comment "empty cohort")) (defskeleton minipay-rely-guar (vars (bank-conf-commit bank-conf-decommit bank-conf-commit-0 bank-conf-decommit-0 mesg) (account account-0 account-1 account-2 acct) (cost cost-0 amount) (n ncb ncm ncm-0 n-0 ncb-0 ncm-1 n-1 ncb-1 ncm-2 ncb-2 data) (item item-0 item-1 item-2 merchandise) (merc-conf bank-conf btr mtr merc-conf-0 btr-0 mtr-0 merc-conf-1 bank-conf-0 merc-conf-2 bank-conf-1 bank-conf-2 text) (c m b name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 3 (for-bank (enc n-0 cost account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit) (bank-conf-decommit bank-conf-decommit) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 3 (for-bank (enc n-1 cost-0 account-1 bank-conf-1 ncb-1 (hash n-1 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit-0) (bank-conf-decommit bank-conf-decommit-0) (cost cost-0) (n n) (ncm ncm-0) (item item-0) (merc-conf merc-conf-0) (btr btr-0) (mtr mtr-0) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account-0) (cost cost) (n n-0) (ncb ncb-0) (ncm ncm-1) (item item-1) (merc-conf merc-conf-1) (bank-conf bank-conf-0) (c c) (m m) (b b)) (defstrand cust 1 (account account-1) (cost cost-0) (n n-1) (ncb ncb-1) (ncm ncm-2) (item item-2) (merc-conf merc-conf-2) (bank-conf bank-conf-1) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm-0 item-0 merc-conf-0)) (account account-2) (cost cost-0) (n n) (ncb ncb-2) (bank-conf bank-conf-2) (btr btr-0) (mtr mtr-0) (c c) (m m) (b b)) (precedes ((0 0) (1 0)) ((0 0) (2 0)) ((1 1) (3 0)) ((2 1) (6 0)) ((3 1) (0 1)) ((3 1) (1 2)) ((4 0) (1 0)) ((5 0) (2 0)) ((6 1) (2 2))) (non-orig (privk "enc" b) (privk "sig" c) (privk "sig" b)) (uniq-orig n btr mtr btr-0 mtr-0) (facts (neq n-1 ncb-1) (neq n-0 ncb-0) (neq n ncb) (neq n-1 ncm-2) (neq n-0 ncm-1) (neq n ncm) (neq ncm-2 ncb-1) (neq ncm-1 ncb-0) (neq ncm ncb) (will-ship c m b item mtr) (buy-via c m b item-0 cost-0 n) (buy-via c m b item-2 cost-0 n-1) (buy-via c m b item-1 cost n-0) (buy-via c m b item cost n) (will-transfer c m b cost-0 n mtr-0 btr-0) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 rely-cust-3 rely-merc-3) (operation encryption-test (displaced 7 0 cust 1) (sign (order c m b cost (enc n cost account-3 bank-conf-3 ncb-3 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (3 0)) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc n cost item merc-conf ncm bank-conf-commit (sign (order c m b cost (enc n-0 cost account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n-0 cost account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (privk "sig" c)) (enc n-0 cost account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc n cost-0 item-0 merc-conf-0 ncm-0 bank-conf-commit-0 (sign (order c m b cost-0 (enc n-1 cost-0 account-1 bank-conf-1 ncb-1 (hash n-1 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost-0 n) (hash ncm-0 item-0 merc-conf-0) mtr-0 (cat (sign (order c m b cost-0 (enc n-1 cost-0 account-1 bank-conf-1 ncb-1 (hash n-1 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b))) (privk "sig" c)) (enc n-1 cost-0 account-1 bank-conf-1 ncb-1 (hash n-1 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit-0 (sign (bconf (hash c m b n cost-0 (hash n (hash ncm-0 item-0 merc-conf-0))) btr-0 mtr-0) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n-0 cost item-1 merc-conf-1 ncm-1 (hash n-0 (hash ncb-0 bank-conf-0)) (sign (order c m b cost (enc n-0 cost account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((send (enc n-1 cost-0 item-2 merc-conf-2 ncm-2 (hash n-1 (hash ncb-1 bank-conf-1)) (sign (order c m b cost-0 (enc n-1 cost-0 account-1 bank-conf-1 ncb-1 (hash n-1 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost-0 n) (hash ncm-0 item-0 merc-conf-0) mtr-0 (cat (sign (order c m b cost-0 (enc n cost-0 account-2 bank-conf-2 ncb-2 (hash n (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (enc n cost-0 account-2 bank-conf-2 ncb-2 (hash n (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb-2 bank-conf-2) (sign (bconf (hash c m b n cost-0 (hash n (hash ncm-0 item-0 merc-conf-0))) btr-0 mtr-0) (privk "sig" b)) (pubk "enc" m))))) (label 143) (parent 132) (unrealized (3 0) (6 0)) (dead) (comment "empty cohort")) (defskeleton minipay-rely-guar (vars (bank-conf-commit bank-conf-decommit bank-conf-commit-0 bank-conf-decommit-0 mesg) (account account-0 account-1 account-2 acct) (cost cost-0 amount) (n ncb ncm ncm-0 ncm-1 n-0 ncb-0 ncm-2 ncb-1 ncb-2 data) (item item-0 item-1 item-2 merchandise) (merc-conf bank-conf btr mtr merc-conf-0 btr-0 mtr-0 merc-conf-1 btr-1 mtr-1 merc-conf-2 bank-conf-0 bank-conf-1 bank-conf-2 text) (c m b name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 3 (for-bank (enc n-0 cost-0 account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit) (bank-conf-decommit bank-conf-decommit) (cost cost-0) (n n) (ncm ncm-0) (item item-0) (merc-conf merc-conf-0) (btr btr-0) (mtr mtr-0) (c c) (m m) (b b)) (defstrand merc 3 (for-bank (enc n-0 cost-0 account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit-0) (bank-conf-decommit bank-conf-decommit-0) (cost cost-0) (n n) (ncm ncm-1) (item item-1) (merc-conf merc-conf-1) (btr btr-1) (mtr mtr-1) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account-0) (cost cost-0) (n n-0) (ncb ncb-0) (ncm ncm-2) (item item-2) (merc-conf merc-conf-2) (bank-conf bank-conf-0) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm-0 item-0 merc-conf-0)) (account account-1) (cost cost-0) (n n) (ncb ncb-1) (bank-conf bank-conf-1) (btr btr-0) (mtr mtr-0) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm-1 item-1 merc-conf-1)) (account account-2) (cost cost-0) (n n) (ncb ncb-2) (bank-conf bank-conf-2) (btr btr-1) (mtr mtr-1) (c c) (m m) (b b)) (precedes ((0 0) (1 0)) ((0 0) (2 0)) ((0 0) (3 0)) ((1 1) (5 0)) ((2 1) (6 0)) ((3 1) (0 1)) ((4 0) (1 0)) ((4 0) (2 0)) ((5 1) (1 2)) ((6 1) (2 2))) (non-orig (privk "enc" b) (privk "sig" c) (privk "sig" b)) (uniq-orig n btr btr-0 mtr-0 btr-1 mtr-1) (facts (neq n-0 ncb-0) (neq n ncb) (neq n-0 ncm-2) (neq n ncm) (neq ncm-2 ncb-0) (neq ncm ncb) (will-ship c m b item mtr) (buy-via c m b item-1 cost-0 n) (buy-via c m b item-0 cost-0 n) (buy-via c m b item-2 cost-0 n-0) (buy-via c m b item cost n) (will-transfer c m b cost-0 n mtr-1 btr-1) (will-transfer c m b cost-0 n mtr-0 btr-0) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 rely-cust-3 rely-merc-3) (operation encryption-test (displaced 7 0 cust 1) (sign (order c m b cost (enc n cost account-3 bank-conf-3 ncb-3 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (3 0)) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc n cost-0 item-0 merc-conf-0 ncm-0 bank-conf-commit (sign (order c m b cost-0 (enc n-0 cost-0 account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost-0 n) (hash ncm-0 item-0 merc-conf-0) mtr-0 (cat (sign (order c m b cost-0 (enc n-0 cost-0 account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b))) (privk "sig" c)) (enc n-0 cost-0 account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit (sign (bconf (hash c m b n cost-0 (hash n (hash ncm-0 item-0 merc-conf-0))) btr-0 mtr-0) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc n cost-0 item-1 merc-conf-1 ncm-1 bank-conf-commit-0 (sign (order c m b cost-0 (enc n-0 cost-0 account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost-0 n) (hash ncm-1 item-1 merc-conf-1) mtr-1 (cat (sign (order c m b cost-0 (enc n-0 cost-0 account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b))) (privk "sig" c)) (enc n-0 cost-0 account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit-0 (sign (bconf (hash c m b n cost-0 (hash n (hash ncm-1 item-1 merc-conf-1))) btr-1 mtr-1) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n-0 cost-0 item-2 merc-conf-2 ncm-2 (hash n-0 (hash ncb-0 bank-conf-0)) (sign (order c m b cost-0 (enc n-0 cost-0 account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost-0 n) (hash ncm-0 item-0 merc-conf-0) mtr-0 (cat (sign (order c m b cost-0 (enc n cost-0 account-1 bank-conf-1 ncb-1 (hash n (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (enc n cost-0 account-1 bank-conf-1 ncb-1 (hash n (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb-1 bank-conf-1) (sign (bconf (hash c m b n cost-0 (hash n (hash ncm-0 item-0 merc-conf-0))) btr-0 mtr-0) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost-0 n) (hash ncm-1 item-1 merc-conf-1) mtr-1 (cat (sign (order c m b cost-0 (enc n cost-0 account-2 bank-conf-2 ncb-2 (hash n (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (privk "sig" c)) (enc n cost-0 account-2 bank-conf-2 ncb-2 (hash n (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb-2 bank-conf-2) (sign (bconf (hash c m b n cost-0 (hash n (hash ncm-1 item-1 merc-conf-1))) btr-1 mtr-1) (privk "sig" b)) (pubk "enc" m))))) (label 144) (parent 133) (unrealized (5 0) (6 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay-rely-guar (vars (bank-conf-commit bank-conf-decommit bank-conf-commit-0 bank-conf-decommit-0 mesg) (account account-0 account-1 account-2 account-3 acct) (cost cost-0 cost-1 amount) (n ncb ncm ncm-0 ncm-1 n-0 ncb-0 ncm-2 ncb-1 n-1 ncb-2 ncm-3 ncb-3 data) (item item-0 item-1 item-2 item-3 merchandise) (merc-conf bank-conf btr mtr merc-conf-0 btr-0 mtr-0 merc-conf-1 btr-1 mtr-1 merc-conf-2 bank-conf-0 bank-conf-1 merc-conf-3 bank-conf-2 bank-conf-3 text) (c m b name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 3 (for-bank (enc n-0 cost-0 account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit) (bank-conf-decommit bank-conf-decommit) (cost cost-0) (n n) (ncm ncm-0) (item item-0) (merc-conf merc-conf-0) (btr btr-0) (mtr mtr-0) (c c) (m m) (b b)) (defstrand merc 3 (for-bank (enc n-1 cost-1 account-2 bank-conf-2 ncb-2 (hash n-1 (hash ncm-3 item-3 merc-conf-3)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit-0) (bank-conf-decommit bank-conf-decommit-0) (cost cost-1) (n n) (ncm ncm-1) (item item-1) (merc-conf merc-conf-1) (btr btr-1) (mtr mtr-1) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account-0) (cost cost-0) (n n-0) (ncb ncb-0) (ncm ncm-2) (item item-2) (merc-conf merc-conf-2) (bank-conf bank-conf-0) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm-0 item-0 merc-conf-0)) (account account-1) (cost cost-0) (n n) (ncb ncb-1) (bank-conf bank-conf-1) (btr btr-0) (mtr mtr-0) (c c) (m m) (b b)) (defstrand cust 1 (account account-2) (cost cost-1) (n n-1) (ncb ncb-2) (ncm ncm-3) (item item-3) (merc-conf merc-conf-3) (bank-conf bank-conf-2) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm-1 item-1 merc-conf-1)) (account account-3) (cost cost-1) (n n) (ncb ncb-3) (bank-conf bank-conf-3) (btr btr-1) (mtr mtr-1) (c c) (m m) (b b)) (precedes ((0 0) (1 0)) ((0 0) (2 0)) ((0 0) (3 0)) ((1 1) (5 0)) ((2 1) (7 0)) ((3 1) (0 1)) ((4 0) (1 0)) ((5 1) (1 2)) ((6 0) (2 0)) ((7 1) (2 2))) (non-orig (privk "enc" b) (privk "sig" c) (privk "sig" b)) (uniq-orig n btr btr-0 mtr-0 btr-1 mtr-1) (facts (neq n-1 ncb-2) (neq n-0 ncb-0) (neq n ncb) (neq n-1 ncm-3) (neq n-0 ncm-2) (neq n ncm) (neq ncm-3 ncb-2) (neq ncm-2 ncb-0) (neq ncm ncb) (will-ship c m b item mtr) (buy-via c m b item-1 cost-1 n) (buy-via c m b item-0 cost-0 n) (buy-via c m b item-3 cost-1 n-1) (buy-via c m b item-2 cost-0 n-0) (buy-via c m b item cost n) (will-transfer c m b cost-1 n mtr-1 btr-1) (will-transfer c m b cost-0 n mtr-0 btr-0) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 rely-cust-3 rely-merc-3) (operation encryption-test (displaced 8 0 cust 1) (sign (order c m b cost (enc n cost account-4 bank-conf-4 ncb-4 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (3 0)) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc n cost-0 item-0 merc-conf-0 ncm-0 bank-conf-commit (sign (order c m b cost-0 (enc n-0 cost-0 account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost-0 n) (hash ncm-0 item-0 merc-conf-0) mtr-0 (cat (sign (order c m b cost-0 (enc n-0 cost-0 account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b))) (privk "sig" c)) (enc n-0 cost-0 account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit (sign (bconf (hash c m b n cost-0 (hash n (hash ncm-0 item-0 merc-conf-0))) btr-0 mtr-0) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc n cost-1 item-1 merc-conf-1 ncm-1 bank-conf-commit-0 (sign (order c m b cost-1 (enc n-1 cost-1 account-2 bank-conf-2 ncb-2 (hash n-1 (hash ncm-3 item-3 merc-conf-3)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost-1 n) (hash ncm-1 item-1 merc-conf-1) mtr-1 (cat (sign (order c m b cost-1 (enc n-1 cost-1 account-2 bank-conf-2 ncb-2 (hash n-1 (hash ncm-3 item-3 merc-conf-3)) (pubk "enc" b))) (privk "sig" c)) (enc n-1 cost-1 account-2 bank-conf-2 ncb-2 (hash n-1 (hash ncm-3 item-3 merc-conf-3)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit-0 (sign (bconf (hash c m b n cost-1 (hash n (hash ncm-1 item-1 merc-conf-1))) btr-1 mtr-1) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n-0 cost-0 item-2 merc-conf-2 ncm-2 (hash n-0 (hash ncb-0 bank-conf-0)) (sign (order c m b cost-0 (enc n-0 cost-0 account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost-0 n) (hash ncm-0 item-0 merc-conf-0) mtr-0 (cat (sign (order c m b cost-0 (enc n cost-0 account-1 bank-conf-1 ncb-1 (hash n (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (enc n cost-0 account-1 bank-conf-1 ncb-1 (hash n (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb-1 bank-conf-1) (sign (bconf (hash c m b n cost-0 (hash n (hash ncm-0 item-0 merc-conf-0))) btr-0 mtr-0) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n-1 cost-1 item-3 merc-conf-3 ncm-3 (hash n-1 (hash ncb-2 bank-conf-2)) (sign (order c m b cost-1 (enc n-1 cost-1 account-2 bank-conf-2 ncb-2 (hash n-1 (hash ncm-3 item-3 merc-conf-3)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost-1 n) (hash ncm-1 item-1 merc-conf-1) mtr-1 (cat (sign (order c m b cost-1 (enc n cost-1 account-3 bank-conf-3 ncb-3 (hash n (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (privk "sig" c)) (enc n cost-1 account-3 bank-conf-3 ncb-3 (hash n (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb-3 bank-conf-3) (sign (bconf (hash c m b n cost-1 (hash n (hash ncm-1 item-1 merc-conf-1))) btr-1 mtr-1) (privk "sig" b)) (pubk "enc" m))))) (label 145) (parent 134) (unrealized (5 0) (7 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay-rely-guar (vars (bank-conf-commit bank-conf-decommit bank-conf-commit-0 bank-conf-decommit-0 mesg) (account acct) (cost amount) (n ncb ncm data) (item merchandise) (merc-conf bank-conf btr mtr btr-0 mtr-0 text) (c m b name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 3 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit) (bank-conf-decommit bank-conf-decommit) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 3 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit-0) (bank-conf-decommit bank-conf-decommit-0) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr-0) (mtr mtr-0) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr-0) (mtr mtr-0) (c c) (m m) (b b)) (precedes ((0 0) (1 0)) ((0 0) (2 0)) ((1 1) (3 0)) ((2 1) (4 0)) ((3 1) (0 1)) ((3 1) (1 2)) ((4 1) (2 2))) (non-orig (privk "enc" b) (privk "sig" c) (privk "sig" b)) (uniq-orig n btr mtr btr-0 mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (will-ship c m b item mtr) (buy-via c m b item cost n) (will-transfer c m b cost n mtr-0 btr-0) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 rely-cust-3) (operation encryption-test (displaced 5 0 cust 1) (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (4 0)) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc n cost item merc-conf ncm bank-conf-commit (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm bank-conf-commit-0 (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit-0 (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-0) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-0) (privk "sig" b)) (pubk "enc" m))))) (label 146) (parent 137) (realized) (shape) (maps ((0 1 2) ((c c) (m m) (b b) (n n) (cost cost) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (account account) (ncb ncb) (ncm ncm) (cost-0 cost) (item-0 item) (merc-conf-0 merc-conf) (btr-0 btr) (mtr-0 mtr) (ncm-0 ncm) (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit) (bank-conf-decommit bank-conf-decommit) (cost-1 cost) (item-1 item) (merc-conf-1 merc-conf) (btr-1 btr-0) (mtr-1 mtr-0) (ncm-1 ncm) (for-bank-0 (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit-0 bank-conf-commit-0) (bank-conf-decommit-0 bank-conf-decommit-0)))) (origs (btr-0 (4 1)) (btr (3 1)) (mtr-0 (2 1)) (mtr (1 1)) (n (0 0)))) (defskeleton minipay-rely-guar (vars (bank-conf-commit bank-conf-decommit bank-conf-commit-0 bank-conf-decommit-0 mesg) (account account-0 acct) (cost amount) (n ncb ncm n-0 ncb-0 ncm-0 data) (item item-0 merchandise) (merc-conf bank-conf btr mtr btr-0 mtr-0 merc-conf-0 bank-conf-0 text) (c m b name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 3 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit) (bank-conf-decommit bank-conf-decommit) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 3 (for-bank (enc n-0 cost account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit-0) (bank-conf-decommit bank-conf-decommit-0) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr-0) (mtr mtr-0) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account-0) (cost cost) (n n-0) (ncb ncb-0) (ncm ncm-0) (item item-0) (merc-conf merc-conf-0) (bank-conf bank-conf-0) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr-0) (mtr mtr-0) (c c) (m m) (b b)) (precedes ((0 0) (1 0)) ((0 0) (2 0)) ((1 1) (3 0)) ((2 1) (5 0)) ((3 1) (0 1)) ((3 1) (1 2)) ((4 0) (2 0)) ((5 1) (2 2))) (non-orig (privk "enc" b) (privk "sig" c) (privk "sig" b)) (uniq-orig n btr mtr btr-0 mtr-0) (facts (neq n-0 ncb-0) (neq n ncb) (neq n-0 ncm-0) (neq n ncm) (neq ncm-0 ncb-0) (neq ncm ncb) (will-ship c m b item mtr) (buy-via c m b item-0 cost n-0) (buy-via c m b item cost n) (will-transfer c m b cost n mtr-0 btr-0) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 rely-cust-3) (operation encryption-test (displaced 6 0 cust 1) (sign (order c m b cost-0 (enc n cost-0 account-1 bank-conf-1 ncb-1 (hash n (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (privk "sig" c)) (5 0)) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc n cost item merc-conf ncm bank-conf-commit (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm bank-conf-commit-0 (sign (order c m b cost (enc n-0 cost account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n-0 cost account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (enc n-0 cost account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit-0 (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-0) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n-0 cost item-0 merc-conf-0 ncm-0 (hash n-0 (hash ncb-0 bank-conf-0)) (sign (order c m b cost (enc n-0 cost account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-0) (privk "sig" b)) (pubk "enc" m))))) (label 147) (parent 138) (unrealized (5 0)) (dead) (comment "empty cohort")) (defskeleton minipay-rely-guar (vars (bank-conf-commit bank-conf-decommit bank-conf-commit-0 bank-conf-decommit-0 mesg) (account account-0 acct) (cost amount) (n ncb ncm ncm-0 ncb-0 data) (item item-0 merchandise) (merc-conf bank-conf btr mtr btr-0 mtr-0 merc-conf-0 btr-1 mtr-1 bank-conf-0 text) (c m b name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 3 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit) (bank-conf-decommit bank-conf-decommit) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr-0) (mtr mtr-0) (c c) (m m) (b b)) (defstrand merc 3 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit-0) (bank-conf-decommit bank-conf-decommit-0) (cost cost) (n n) (ncm ncm-0) (item item-0) (merc-conf merc-conf-0) (btr btr-1) (mtr mtr-1) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr-0) (mtr mtr-0) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm-0 item-0 merc-conf-0)) (account account-0) (cost cost) (n n) (ncb ncb-0) (bank-conf bank-conf-0) (btr btr-1) (mtr mtr-1) (c c) (m m) (b b)) (precedes ((0 0) (1 0)) ((0 0) (2 0)) ((0 0) (3 0)) ((1 1) (4 0)) ((2 1) (5 0)) ((3 1) (0 1)) ((4 1) (1 2)) ((5 1) (2 2))) (non-orig (privk "enc" b) (privk "sig" c) (privk "sig" b)) (uniq-orig n btr btr-0 mtr-0 btr-1 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (will-ship c m b item mtr) (buy-via c m b item-0 cost n) (buy-via c m b item cost n) (will-transfer c m b cost n mtr-1 btr-1) (will-transfer c m b cost n mtr-0 btr-0) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 rely-cust-3 rely-merc-3) (operation encryption-test (displaced 6 0 cust 1) (sign (order c m b cost (enc n cost account-1 bank-conf-1 ncb-1 (hash n (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (privk "sig" c)) (4 0)) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc n cost item merc-conf ncm bank-conf-commit (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-0) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc n cost item-0 merc-conf-0 ncm-0 bank-conf-commit-0 (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm-0 item-0 merc-conf-0) mtr-1 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit-0 (sign (bconf (hash c m b n cost (hash n (hash ncm-0 item-0 merc-conf-0))) btr-1 mtr-1) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-0) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm-0 item-0 merc-conf-0) mtr-1 (cat (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb-0 bank-conf-0) (sign (bconf (hash c m b n cost (hash n (hash ncm-0 item-0 merc-conf-0))) btr-1 mtr-1) (privk "sig" b)) (pubk "enc" m))))) (label 148) (parent 139) (unrealized (5 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay-rely-guar (vars (bank-conf-commit bank-conf-decommit bank-conf-commit-0 bank-conf-decommit-0 mesg) (account account-0 account-1 acct) (cost cost-0 amount) (n ncb ncm ncm-0 n-0 ncb-0 ncm-1 ncb-1 data) (item item-0 item-1 merchandise) (merc-conf bank-conf btr mtr btr-0 mtr-0 merc-conf-0 btr-1 mtr-1 merc-conf-1 bank-conf-0 bank-conf-1 text) (c m b name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 3 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit) (bank-conf-decommit bank-conf-decommit) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr-0) (mtr mtr-0) (c c) (m m) (b b)) (defstrand merc 3 (for-bank (enc n-0 cost-0 account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit-0) (bank-conf-decommit bank-conf-decommit-0) (cost cost-0) (n n) (ncm ncm-0) (item item-0) (merc-conf merc-conf-0) (btr btr-1) (mtr mtr-1) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr-0) (mtr mtr-0) (c c) (m m) (b b)) (defstrand cust 1 (account account-0) (cost cost-0) (n n-0) (ncb ncb-0) (ncm ncm-1) (item item-1) (merc-conf merc-conf-1) (bank-conf bank-conf-0) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm-0 item-0 merc-conf-0)) (account account-1) (cost cost-0) (n n) (ncb ncb-1) (bank-conf bank-conf-1) (btr btr-1) (mtr mtr-1) (c c) (m m) (b b)) (precedes ((0 0) (1 0)) ((0 0) (2 0)) ((0 0) (3 0)) ((1 1) (4 0)) ((2 1) (6 0)) ((3 1) (0 1)) ((4 1) (1 2)) ((5 0) (2 0)) ((6 1) (2 2))) (non-orig (privk "enc" b) (privk "sig" c) (privk "sig" b)) (uniq-orig n btr btr-0 mtr-0 btr-1 mtr-1) (facts (neq n-0 ncb-0) (neq n ncb) (neq n-0 ncm-1) (neq n ncm) (neq ncm-1 ncb-0) (neq ncm ncb) (will-ship c m b item mtr) (buy-via c m b item-0 cost-0 n) (buy-via c m b item-1 cost-0 n-0) (buy-via c m b item cost n) (will-transfer c m b cost-0 n mtr-1 btr-1) (will-transfer c m b cost n mtr-0 btr-0) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 rely-cust-3 rely-merc-3) (operation encryption-test (displaced 7 0 cust 1) (sign (order c m b cost (enc n cost account-2 bank-conf-2 ncb-2 (hash n (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b))) (privk "sig" c)) (4 0)) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc n cost item merc-conf ncm bank-conf-commit (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-0) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc n cost-0 item-0 merc-conf-0 ncm-0 bank-conf-commit-0 (sign (order c m b cost-0 (enc n-0 cost-0 account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost-0 n) (hash ncm-0 item-0 merc-conf-0) mtr-1 (cat (sign (order c m b cost-0 (enc n-0 cost-0 account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (privk "sig" c)) (enc n-0 cost-0 account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit-0 (sign (bconf (hash c m b n cost-0 (hash n (hash ncm-0 item-0 merc-conf-0))) btr-1 mtr-1) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-0) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n-0 cost-0 item-1 merc-conf-1 ncm-1 (hash n-0 (hash ncb-0 bank-conf-0)) (sign (order c m b cost-0 (enc n-0 cost-0 account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost-0 n) (hash ncm-0 item-0 merc-conf-0) mtr-1 (cat (sign (order c m b cost-0 (enc n cost-0 account-1 bank-conf-1 ncb-1 (hash n (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (enc n cost-0 account-1 bank-conf-1 ncb-1 (hash n (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb-1 bank-conf-1) (sign (bconf (hash c m b n cost-0 (hash n (hash ncm-0 item-0 merc-conf-0))) btr-1 mtr-1) (privk "sig" b)) (pubk "enc" m))))) (label 149) (parent 141) (unrealized (6 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay-rely-guar (vars (bank-conf-commit bank-conf-decommit bank-conf-commit-0 bank-conf-decommit-0 mesg) (account account-0 account-1 acct) (cost amount) (n ncb ncm ncm-0 n-0 ncb-0 ncm-1 ncb-1 data) (item item-0 item-1 merchandise) (merc-conf bank-conf btr mtr btr-0 mtr-0 merc-conf-0 btr-1 mtr-1 merc-conf-1 bank-conf-0 bank-conf-1 text) (c m b name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 3 (for-bank (enc n-0 cost account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit) (bank-conf-decommit bank-conf-decommit) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr-0) (mtr mtr-0) (c c) (m m) (b b)) (defstrand merc 3 (for-bank (enc n-0 cost account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit-0) (bank-conf-decommit bank-conf-decommit-0) (cost cost) (n n) (ncm ncm-0) (item item-0) (merc-conf merc-conf-0) (btr btr-1) (mtr mtr-1) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account-0) (cost cost) (n n-0) (ncb ncb-0) (ncm ncm-1) (item item-1) (merc-conf merc-conf-1) (bank-conf bank-conf-0) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr-0) (mtr mtr-0) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm-0 item-0 merc-conf-0)) (account account-1) (cost cost) (n n) (ncb ncb-1) (bank-conf bank-conf-1) (btr btr-1) (mtr mtr-1) (c c) (m m) (b b)) (precedes ((0 0) (1 0)) ((0 0) (2 0)) ((0 0) (3 0)) ((1 1) (5 0)) ((2 1) (6 0)) ((3 1) (0 1)) ((4 0) (1 0)) ((4 0) (2 0)) ((5 1) (1 2)) ((6 1) (2 2))) (non-orig (privk "enc" b) (privk "sig" c) (privk "sig" b)) (uniq-orig n btr btr-0 mtr-0 btr-1 mtr-1) (facts (neq n-0 ncb-0) (neq n ncb) (neq n-0 ncm-1) (neq n ncm) (neq ncm-1 ncb-0) (neq ncm ncb) (will-ship c m b item mtr) (buy-via c m b item-0 cost n) (buy-via c m b item-1 cost n-0) (buy-via c m b item cost n) (will-transfer c m b cost n mtr-1 btr-1) (will-transfer c m b cost n mtr-0 btr-0) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 rely-cust-3 rely-merc-3) (operation encryption-test (displaced 7 0 cust 1) (sign (order c m b cost-0 (enc n cost-0 account-2 bank-conf-2 ncb-2 (hash n (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b))) (privk "sig" c)) (5 0)) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc n cost item merc-conf ncm bank-conf-commit (sign (order c m b cost (enc n-0 cost account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n-0 cost account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (privk "sig" c)) (enc n-0 cost account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-0) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc n cost item-0 merc-conf-0 ncm-0 bank-conf-commit-0 (sign (order c m b cost (enc n-0 cost account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm-0 item-0 merc-conf-0) mtr-1 (cat (sign (order c m b cost (enc n-0 cost account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (privk "sig" c)) (enc n-0 cost account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit-0 (sign (bconf (hash c m b n cost (hash n (hash ncm-0 item-0 merc-conf-0))) btr-1 mtr-1) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n-0 cost item-1 merc-conf-1 ncm-1 (hash n-0 (hash ncb-0 bank-conf-0)) (sign (order c m b cost (enc n-0 cost account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-0) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm-0 item-0 merc-conf-0) mtr-1 (cat (sign (order c m b cost (enc n cost account-1 bank-conf-1 ncb-1 (hash n (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-1 bank-conf-1 ncb-1 (hash n (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb-1 bank-conf-1) (sign (bconf (hash c m b n cost (hash n (hash ncm-0 item-0 merc-conf-0))) btr-1 mtr-1) (privk "sig" b)) (pubk "enc" m))))) (label 150) (parent 144) (unrealized (5 0) (6 0)) (dead) (comment "empty cohort")) (defskeleton minipay-rely-guar (vars (bank-conf-commit bank-conf-decommit bank-conf-commit-0 bank-conf-decommit-0 mesg) (account account-0 account-1 account-2 acct) (cost cost-0 amount) (n ncb ncm ncm-0 n-0 ncb-0 ncm-1 n-1 ncb-1 ncm-2 ncb-2 data) (item item-0 item-1 item-2 merchandise) (merc-conf bank-conf btr mtr btr-0 mtr-0 merc-conf-0 btr-1 mtr-1 merc-conf-1 bank-conf-0 merc-conf-2 bank-conf-1 bank-conf-2 text) (c m b name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 3 (for-bank (enc n-0 cost account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit) (bank-conf-decommit bank-conf-decommit) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr-0) (mtr mtr-0) (c c) (m m) (b b)) (defstrand merc 3 (for-bank (enc n-1 cost-0 account-1 bank-conf-1 ncb-1 (hash n-1 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit-0) (bank-conf-decommit bank-conf-decommit-0) (cost cost-0) (n n) (ncm ncm-0) (item item-0) (merc-conf merc-conf-0) (btr btr-1) (mtr mtr-1) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account-0) (cost cost) (n n-0) (ncb ncb-0) (ncm ncm-1) (item item-1) (merc-conf merc-conf-1) (bank-conf bank-conf-0) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr-0) (mtr mtr-0) (c c) (m m) (b b)) (defstrand cust 1 (account account-1) (cost cost-0) (n n-1) (ncb ncb-1) (ncm ncm-2) (item item-2) (merc-conf merc-conf-2) (bank-conf bank-conf-1) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm-0 item-0 merc-conf-0)) (account account-2) (cost cost-0) (n n) (ncb ncb-2) (bank-conf bank-conf-2) (btr btr-1) (mtr mtr-1) (c c) (m m) (b b)) (precedes ((0 0) (1 0)) ((0 0) (2 0)) ((0 0) (3 0)) ((1 1) (5 0)) ((2 1) (7 0)) ((3 1) (0 1)) ((4 0) (1 0)) ((5 1) (1 2)) ((6 0) (2 0)) ((7 1) (2 2))) (non-orig (privk "enc" b) (privk "sig" c) (privk "sig" b)) (uniq-orig n btr btr-0 mtr-0 btr-1 mtr-1) (facts (neq n-1 ncb-1) (neq n-0 ncb-0) (neq n ncb) (neq n-1 ncm-2) (neq n-0 ncm-1) (neq n ncm) (neq ncm-2 ncb-1) (neq ncm-1 ncb-0) (neq ncm ncb) (will-ship c m b item mtr) (buy-via c m b item-0 cost-0 n) (buy-via c m b item-2 cost-0 n-1) (buy-via c m b item-1 cost n-0) (buy-via c m b item cost n) (will-transfer c m b cost-0 n mtr-1 btr-1) (will-transfer c m b cost n mtr-0 btr-0) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 rely-cust-3 rely-merc-3) (operation encryption-test (displaced 8 0 cust 1) (sign (order c m b cost-1 (enc n cost-1 account-3 bank-conf-3 ncb-3 (hash n (hash ncm-3 item-3 merc-conf-3)) (pubk "enc" b))) (privk "sig" c)) (5 0)) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc n cost item merc-conf ncm bank-conf-commit (sign (order c m b cost (enc n-0 cost account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n-0 cost account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (privk "sig" c)) (enc n-0 cost account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-0) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc n cost-0 item-0 merc-conf-0 ncm-0 bank-conf-commit-0 (sign (order c m b cost-0 (enc n-1 cost-0 account-1 bank-conf-1 ncb-1 (hash n-1 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost-0 n) (hash ncm-0 item-0 merc-conf-0) mtr-1 (cat (sign (order c m b cost-0 (enc n-1 cost-0 account-1 bank-conf-1 ncb-1 (hash n-1 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b))) (privk "sig" c)) (enc n-1 cost-0 account-1 bank-conf-1 ncb-1 (hash n-1 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit-0 (sign (bconf (hash c m b n cost-0 (hash n (hash ncm-0 item-0 merc-conf-0))) btr-1 mtr-1) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n-0 cost item-1 merc-conf-1 ncm-1 (hash n-0 (hash ncb-0 bank-conf-0)) (sign (order c m b cost (enc n-0 cost account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-0) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n-1 cost-0 item-2 merc-conf-2 ncm-2 (hash n-1 (hash ncb-1 bank-conf-1)) (sign (order c m b cost-0 (enc n-1 cost-0 account-1 bank-conf-1 ncb-1 (hash n-1 (hash ncm-2 item-2 merc-conf-2)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost-0 n) (hash ncm-0 item-0 merc-conf-0) mtr-1 (cat (sign (order c m b cost-0 (enc n cost-0 account-2 bank-conf-2 ncb-2 (hash n (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (enc n cost-0 account-2 bank-conf-2 ncb-2 (hash n (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb-2 bank-conf-2) (sign (bconf (hash c m b n cost-0 (hash n (hash ncm-0 item-0 merc-conf-0))) btr-1 mtr-1) (privk "sig" b)) (pubk "enc" m))))) (label 151) (parent 145) (unrealized (5 0) (7 0)) (dead) (comment "empty cohort")) (defskeleton minipay-rely-guar (vars (bank-conf-commit bank-conf-decommit bank-conf-commit-0 bank-conf-decommit-0 mesg) (account acct) (cost amount) (n ncb ncm data) (item merchandise) (merc-conf bank-conf btr mtr btr-0 mtr-0 btr-1 mtr-1 text) (c m b name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 3 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit) (bank-conf-decommit bank-conf-decommit) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr-0) (mtr mtr-0) (c c) (m m) (b b)) (defstrand merc 3 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit-0) (bank-conf-decommit bank-conf-decommit-0) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr-1) (mtr mtr-1) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr-0) (mtr mtr-0) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr-1) (mtr mtr-1) (c c) (m m) (b b)) (precedes ((0 0) (1 0)) ((0 0) (2 0)) ((0 0) (3 0)) ((1 1) (4 0)) ((2 1) (5 0)) ((3 1) (0 1)) ((4 1) (1 2)) ((5 1) (2 2))) (non-orig (privk "enc" b) (privk "sig" c) (privk "sig" b)) (uniq-orig n btr btr-0 mtr-0 btr-1 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (will-ship c m b item mtr) (buy-via c m b item cost n) (will-transfer c m b cost n mtr-1 btr-1) (will-transfer c m b cost n mtr-0 btr-0) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 rely-cust-3) (operation encryption-test (displaced 6 0 cust 1) (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (5 0)) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc n cost item merc-conf ncm bank-conf-commit (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-0) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm bank-conf-commit-0 (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-1 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit-0 (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-1 mtr-1) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-0) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-1 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-1 mtr-1) (privk "sig" b)) (pubk "enc" m))))) (label 152) (parent 148) (realized) (shape) (maps ((0 1 2) ((c c) (m m) (b b) (n n) (cost cost) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (account account) (ncb ncb) (ncm ncm) (cost-0 cost) (item-0 item) (merc-conf-0 merc-conf) (btr-0 btr-0) (mtr-0 mtr-0) (ncm-0 ncm) (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit) (bank-conf-decommit bank-conf-decommit) (cost-1 cost) (item-1 item) (merc-conf-1 merc-conf) (btr-1 btr-1) (mtr-1 mtr-1) (ncm-1 ncm) (for-bank-0 (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit-0 bank-conf-commit-0) (bank-conf-decommit-0 bank-conf-decommit-0)))) (origs (btr-1 (5 1)) (btr-0 (4 1)) (btr (3 1)) (mtr-1 (2 1)) (mtr-0 (1 1)) (n (0 0)))) (defskeleton minipay-rely-guar (vars (bank-conf-commit bank-conf-decommit bank-conf-commit-0 bank-conf-decommit-0 mesg) (account account-0 acct) (cost amount) (n ncb ncm n-0 ncb-0 ncm-0 data) (item item-0 merchandise) (merc-conf bank-conf btr mtr btr-0 mtr-0 btr-1 mtr-1 merc-conf-0 bank-conf-0 text) (c m b name)) (defstrand cust 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 3 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit) (bank-conf-decommit bank-conf-decommit) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr-0) (mtr mtr-0) (c c) (m m) (b b)) (defstrand merc 3 (for-bank (enc n-0 cost account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit-0) (bank-conf-decommit bank-conf-decommit-0) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr-1) (mtr mtr-1) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr-0) (mtr mtr-0) (c c) (m m) (b b)) (defstrand cust 1 (account account-0) (cost cost) (n n-0) (ncb ncb-0) (ncm ncm-0) (item item-0) (merc-conf merc-conf-0) (bank-conf bank-conf-0) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr-1) (mtr mtr-1) (c c) (m m) (b b)) (precedes ((0 0) (1 0)) ((0 0) (2 0)) ((0 0) (3 0)) ((1 1) (4 0)) ((2 1) (6 0)) ((3 1) (0 1)) ((4 1) (1 2)) ((5 0) (2 0)) ((6 1) (2 2))) (non-orig (privk "enc" b) (privk "sig" c) (privk "sig" b)) (uniq-orig n btr btr-0 mtr-0 btr-1 mtr-1) (facts (neq n-0 ncb-0) (neq n ncb) (neq n-0 ncm-0) (neq n ncm) (neq ncm-0 ncb-0) (neq ncm ncb) (will-ship c m b item mtr) (buy-via c m b item-0 cost n-0) (buy-via c m b item cost n) (will-transfer c m b cost n mtr-1 btr-1) (will-transfer c m b cost n mtr-0 btr-0) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 rely-cust-3) (operation encryption-test (displaced 7 0 cust 1) (sign (order c m b cost-0 (enc n cost-0 account-1 bank-conf-1 ncb-1 (hash n (hash ncm-1 item-1 merc-conf-1)) (pubk "enc" b))) (privk "sig" c)) (6 0)) (traces ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) ((recv (enc n cost item merc-conf ncm bank-conf-commit (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-0) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm bank-conf-commit-0 (sign (order c m b cost (enc n-0 cost account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-1 (cat (sign (order c m b cost (enc n-0 cost account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (enc n-0 cost account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit-0 (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-1 mtr-1) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-0) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n-0 cost item-0 merc-conf-0 ncm-0 (hash n-0 (hash ncb-0 bank-conf-0)) (sign (order c m b cost (enc n-0 cost account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-1 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-1 mtr-1) (privk "sig" b)) (pubk "enc" m))))) (label 153) (parent 149) (unrealized (6 0)) (dead) (comment "empty cohort")) (comment "Nothing left to do") (defprotocol minipay-rely-guar basic (defrole cust (vars (c m b name) (cost amount) (item merchandise) (merc-conf bank-conf btr mtr text) (account acct) (n ncb ncm data)) (trace (send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) (facts (neq n ncb) (neq n ncm) (neq ncm ncb))) (defrole merc (vars (c m b name) (cost amount) (item merchandise) (merc-conf btr mtr text) (n ncm data) (for-bank bank-conf-commit bank-conf-decommit mesg)) (trace (recv (enc n cost item merc-conf ncm bank-conf-commit (sign (order c m b cost for-bank) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost for-bank) (privk "sig" c)) for-bank)) (pubk "enc" b))) (recv (enc bank-conf-decommit (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n bank-conf-decommit)) btr mtr) (privk "sig" m)))) (uniq-orig mtr)) (defrole bank (vars (c m b name) (cost amount) (bank-conf btr mtr text) (merc-conf-decommit mesg) (account acct) (n ncb data)) (trace (recv (enc (payreq c m b (hash cost n) merc-conf-decommit mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n merc-conf-decommit) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n merc-conf-decommit) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n merc-conf-decommit)) btr mtr) (privk "sig" b)) (pubk "enc" m)))) (uniq-orig btr)) (defrule rely-cust-3 (forall ((z strd) (mtr text) (item merchandise) (b m c name)) (implies (and (p "cust" z (idx 3)) (p "cust" "mtr" z mtr) (p "cust" "item" z item) (p "cust" "b" z b) (p "cust" "m" z m) (p "cust" "c" z c)) (fact will-ship c m b item mtr)))) (defrule rely-cust-2 (forall ((z strd) (btr mtr text) (n data) (cost amount) (b m c name)) (implies (and (p "cust" z (idx 2)) (p "cust" "btr" z btr) (p "cust" "mtr" z mtr) (p "cust" "n" z n) (p "cust" "cost" z cost) (p "cust" "b" z b) (p "cust" "m" z m) (p "cust" "c" z c)) (fact will-transfer c m b cost n mtr btr)))) (defrule rely-merc-3 (forall ((z strd) (n data) (cost amount) (item merchandise) (b m c name) (btr mtr text)) (implies (and (p "merc" z (idx 3)) (p "merc" "n" z n) (p "merc" "cost" z cost) (p "merc" "item" z item) (p "merc" "b" z b) (p "merc" "m" z m) (p "merc" "c" z c) (p "merc" "btr" z btr) (p "merc" "mtr" z mtr)) (and (fact buy-via c m b item cost n) (fact will-transfer c m b cost n mtr btr))))) (defrule rely-bank-1 (forall ((z strd) (n data) (cost amount) (b m c name)) (implies (and (p "bank" z (idx 1)) (p "bank" "n" z n) (p "bank" "cost" z cost) (p "bank" "b" z b) (p "bank" "m" z m) (p "bank" "c" z c)) (exists ((item merchandise)) (fact buy-via c m b item cost n))))) (defrule guar-cust-1 (forall ((z strd) (n data) (cost amount) (item merchandise) (b m c name)) (implies (and (p "cust" z (idx 1)) (p "cust" "n" z n) (p "cust" "cost" z cost) (p "cust" "item" z item) (p "cust" "b" z b) (p "cust" "m" z m) (p "cust" "c" z c)) (fact buy-via c m b item cost n)))) (defrule guar-merc-4 (forall ((z strd) (mtr text) (item merchandise) (b m c name)) (implies (and (p "merc" z (idx 4)) (p "merc" "mtr" z mtr) (p "merc" "item" z item) (p "merc" "b" z b) (p "merc" "m" z m) (p "merc" "c" z c)) (fact will-ship c m b item mtr)))) (defrule guar-bank-2 (forall ((z strd) (btr mtr text) (n data) (cost amount) (c b m name)) (implies (and (p "bank" z (idx 2)) (p "bank" "btr" z btr) (p "bank" "mtr" z mtr) (p "bank" "n" z n) (p "bank" "cost" z cost) (p "bank" "c" z c) (p "bank" "b" z b) (p "bank" "m" z m)) (and (non (privk "sig" c)) (fact will-transfer c m b cost n mtr btr))))) (defrule cheq-merc-4 (forall ((z strd) (n data) (bank-conf-decommit bank-conf-commit mesg)) (implies (and (p "merc" z (idx 4)) (p "merc" "n" z n) (p "merc" "bank-conf-decommit" z bank-conf-decommit) (p "merc" "bank-conf-commit" z bank-conf-commit)) (= bank-conf-commit (hash n bank-conf-decommit))))) (defgenrule neqRl_indx (forall ((x indx)) (implies (fact neq x x) (false)))) (defgenrule neqRl_strd (forall ((x strd)) (implies (fact neq x x) (false)))) (defgenrule neqRl_mesg (forall ((x mesg)) (implies (fact neq x x) (false)))) (defgenrule fact-cust-neq2 (forall ((z strd) (ncb n data)) (implies (and (p "cust" z (idx 1)) (p "cust" "ncb" z ncb) (p "cust" "n" z n)) (fact neq n ncb)))) (defgenrule fact-cust-neq1 (forall ((z strd) (ncm n data)) (implies (and (p "cust" z (idx 1)) (p "cust" "ncm" z ncm) (p "cust" "n" z n)) (fact neq n ncm)))) (defgenrule fact-cust-neq0 (forall ((z strd) (ncb ncm data)) (implies (and (p "cust" z (idx 1)) (p "cust" "ncb" z ncb) (p "cust" "ncm" z ncm)) (fact neq ncm ncb)))) (lang (acct atom) (amount atom) (merchandise atom) (sign sign) (order (tuple 5)) (bconf (tuple 3)) (mconf (tuple 3)) (payreq (tuple 7)))) (defskeleton minipay-rely-guar (vars (for-bank bank-conf-commit bank-conf-decommit mesg) (cost amount) (n ncm data) (item merchandise) (merc-conf btr mtr text) (c m b name)) (defstrand merc 4 (for-bank for-bank) (bank-conf-commit bank-conf-commit) (bank-conf-decommit bank-conf-decommit) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig mtr) (traces ((recv (enc n cost item merc-conf ncm bank-conf-commit (sign (order c m b cost for-bank) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost for-bank) (privk "sig" c)) for-bank)) (pubk "enc" b))) (recv (enc bank-conf-decommit (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))))) (label 154) (unrealized (0 2)) (origs (mtr (0 1))) (comment "Not closed under rules")) (defskeleton minipay-rely-guar (vars (for-bank bank-conf-decommit mesg) (cost amount) (n ncm data) (item merchandise) (merc-conf btr mtr text) (c m b name)) (defstrand merc 4 (for-bank for-bank) (bank-conf-commit (hash n bank-conf-decommit)) (bank-conf-decommit bank-conf-decommit) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig mtr) (facts (will-transfer c m b cost n mtr btr) (buy-via c m b item cost n) (will-ship c m b item mtr)) (rule cheq-merc-4 guar-merc-4 rely-merc-3) (traces ((recv (enc n cost item merc-conf ncm (hash n bank-conf-decommit) (sign (order c m b cost for-bank) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost for-bank) (privk "sig" c)) for-bank)) (pubk "enc" b))) (recv (enc bank-conf-decommit (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))))) (label 155) (parent 154) (unrealized (0 2)) (origs (mtr (0 1))) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay-rely-guar (vars (for-bank bank-conf-decommit mesg) (account acct) (cost amount) (n ncm ncb data) (item merchandise) (merc-conf btr mtr bank-conf text) (c m b name)) (defstrand merc 4 (for-bank for-bank) (bank-conf-commit (hash n bank-conf-decommit)) (bank-conf-decommit bank-conf-decommit) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (precedes ((0 1) (1 0)) ((1 1) (0 2))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig btr mtr) (facts (buy-via c m b item cost n) (will-ship c m b item mtr) (will-transfer c m b cost n mtr btr)) (rule guar-bank-2 guar-merc-4 rely-merc-3) (operation encryption-test (added-strand bank 2) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (0 2)) (traces ((recv (enc n cost item merc-conf ncm (hash n bank-conf-decommit) (sign (order c m b cost for-bank) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost for-bank) (privk "sig" c)) for-bank)) (pubk "enc" b))) (recv (enc bank-conf-decommit (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))))) (label 156) (parent 155) (unrealized (0 0) (0 2) (1 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay-rely-guar (vars (bank-conf-decommit mesg) (account account-0 acct) (cost amount) (n ncm ncb n-0 ncb-0 ncm-0 data) (item item-0 merchandise) (merc-conf btr mtr bank-conf merc-conf-0 bank-conf-0 text) (c m b name)) (defstrand merc 4 (for-bank (enc n-0 cost account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (bank-conf-commit (hash n bank-conf-decommit)) (bank-conf-decommit bank-conf-decommit) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account-0) (cost cost) (n n-0) (ncb ncb-0) (ncm ncm-0) (item item-0) (merc-conf merc-conf-0) (bank-conf bank-conf-0) (c c) (m m) (b b)) (precedes ((0 1) (1 0)) ((1 1) (0 2)) ((2 0) (0 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig btr mtr) (facts (neq n-0 ncb-0) (neq n-0 ncm-0) (neq ncm-0 ncb-0) (buy-via c m b item cost n) (buy-via c m b item-0 cost n-0) (will-ship c m b item mtr) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 guar-merc-4 rely-merc-3) (operation encryption-test (added-strand cust 1) (sign (order c m b cost (enc n-0 cost account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (0 0)) (traces ((recv (enc n cost item merc-conf ncm (hash n bank-conf-decommit) (sign (order c m b cost (enc n-0 cost account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n-0 cost account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (enc n-0 cost account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n-0 cost item-0 merc-conf-0 ncm-0 (hash n-0 (hash ncb-0 bank-conf-0)) (sign (order c m b cost (enc n-0 cost account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))))) (label 157) (parent 156) (unrealized (0 0) (0 2) (1 0)) (comment "2 in cohort - 2 not yet seen")) (defskeleton minipay-rely-guar (vars (account account-0 acct) (cost amount) (ncb n ncb-0 ncm data) (item merchandise) (btr mtr bank-conf merc-conf bank-conf-0 text) (c m b name)) (defstrand merc 4 (for-bank (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb-0 bank-conf-0))) (bank-conf-decommit (hash ncb-0 bank-conf-0)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account-0) (cost cost) (n n) (ncb ncb-0) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf-0) (c c) (m m) (b b)) (precedes ((0 1) (1 0)) ((1 1) (0 2)) ((2 0) (0 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig btr mtr) (facts (neq n ncb-0) (neq n ncm) (neq ncm ncb-0) (buy-via c m b item cost n) (will-ship c m b item mtr) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 guar-merc-4) (operation encryption-test (contracted (item-0 item) (merc-conf-0 merc-conf) (n-0 n) (ncm-0 ncm) (bank-conf-decommit (hash ncb-0 bank-conf-0))) (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (0 0) (enc n cost item merc-conf ncm (hash n (hash ncb-0 bank-conf-0)) (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (traces ((recv (enc n cost item merc-conf ncm (hash n (hash ncb-0 bank-conf-0)) (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb-0 bank-conf-0) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb-0 bank-conf-0)) (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))))) (label 158) (parent 157) (unrealized (0 2) (1 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay-rely-guar (vars (bank-conf-decommit mesg) (account account-0 acct) (cost amount) (n ncm ncb n-0 ncb-0 ncm-0 data) (item item-0 merchandise) (merc-conf btr mtr bank-conf merc-conf-0 bank-conf-0 mtr-0 text) (c m b name)) (defstrand merc 4 (for-bank (enc n-0 cost account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (bank-conf-commit (hash n bank-conf-decommit)) (bank-conf-decommit bank-conf-decommit) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account-0) (cost cost) (n n-0) (ncb ncb-0) (ncm ncm-0) (item item-0) (merc-conf merc-conf-0) (bank-conf bank-conf-0) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n-0 cost account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (bank-conf-commit (hash n-0 (hash ncb-0 bank-conf-0))) (cost cost) (n n-0) (ncm ncm-0) (item item-0) (merc-conf merc-conf-0) (mtr mtr-0) (c c) (m m) (b b)) (precedes ((0 1) (1 0)) ((1 1) (0 2)) ((2 0) (0 0)) ((3 1) (0 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig btr mtr mtr-0) (facts (neq n-0 ncb-0) (neq n-0 ncm-0) (neq ncm-0 ncb-0) (buy-via c m b item cost n) (buy-via c m b item-0 cost n-0) (will-ship c m b item mtr) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 guar-merc-4 rely-merc-3) (operation encryption-test (added-strand merc 2) (sign (order c m b cost (enc n-0 cost account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (0 0) (enc n-0 cost item-0 merc-conf-0 ncm-0 (hash n-0 (hash ncb-0 bank-conf-0)) (sign (order c m b cost (enc n-0 cost account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (traces ((recv (enc n cost item merc-conf ncm (hash n bank-conf-decommit) (sign (order c m b cost (enc n-0 cost account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n-0 cost account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (enc n-0 cost account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n-0 cost item-0 merc-conf-0 ncm-0 (hash n-0 (hash ncb-0 bank-conf-0)) (sign (order c m b cost (enc n-0 cost account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n-0 cost item-0 merc-conf-0 ncm-0 (hash n-0 (hash ncb-0 bank-conf-0)) (sign (order c m b cost (enc n-0 cost account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n-0) (hash ncm-0 item-0 merc-conf-0) mtr-0 (cat (sign (order c m b cost (enc n-0 cost account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (enc n-0 cost account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b)))) (pubk "enc" b))))) (label 159) (parent 157) (unrealized (0 0) (0 2) (1 0) (3 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay-rely-guar (vars (account account-0 acct) (cost amount) (ncb n ncm data) (item merchandise) (btr mtr bank-conf merc-conf text) (c m b name)) (defstrand merc 4 (for-bank (enc n cost account-0 bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account-0) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (precedes ((0 1) (1 0)) ((1 1) (0 2)) ((2 0) (0 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig btr mtr) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-ship c m b item mtr) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 guar-merc-4) (operation encryption-test (contracted (bank-conf-0 bank-conf) (ncb-0 ncb)) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (0 2) (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (traces ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account-0 bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account-0 bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-0 bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account-0 bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))))) (label 160) (parent 158) (unrealized (1 0)) (comment "2 in cohort - 2 not yet seen")) (defskeleton minipay-rely-guar (vars (account account-0 acct) (cost amount) (ncb n ncb-0 ncm data) (item merchandise) (btr mtr bank-conf merc-conf bank-conf-0 mtr-0 text) (c m b name)) (defstrand merc 4 (for-bank (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb-0 bank-conf-0))) (bank-conf-decommit (hash ncb-0 bank-conf-0)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account-0) (cost cost) (n n) (ncb ncb-0) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf-0) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb-0 bank-conf-0))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-0) (c c) (m m) (b b)) (precedes ((0 1) (1 0)) ((1 1) (0 2)) ((2 0) (0 0)) ((3 1) (0 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig btr mtr mtr-0) (facts (neq n ncb-0) (neq n ncm) (neq ncm ncb-0) (buy-via c m b item cost n) (will-ship c m b item mtr) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 guar-merc-4) (operation encryption-test (contracted (item-0 item) (merc-conf-0 merc-conf) (n-0 n) (ncm-0 ncm) (bank-conf-decommit (hash ncb-0 bank-conf-0))) (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (0 0) (enc n cost item merc-conf ncm (hash n (hash ncb-0 bank-conf-0)) (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)) (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (traces ((recv (enc n cost item merc-conf ncm (hash n (hash ncb-0 bank-conf-0)) (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb-0 bank-conf-0) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb-0 bank-conf-0)) (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb-0 bank-conf-0)) (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-0 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))))) (label 161) (parent 159) (unrealized (0 2) (1 0) (3 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay-rely-guar (vars (account acct) (cost amount) (ncb n ncm data) (item merchandise) (btr mtr bank-conf merc-conf text) (c m b name)) (defstrand merc 4 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (precedes ((0 1) (1 0)) ((1 1) (0 2)) ((2 0) (0 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig btr mtr) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-ship c m b item mtr) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 guar-merc-4) (operation encryption-test (displaced 3 2 cust 1) (sign (order c m b cost (enc n cost account-0 bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (1 0)) (traces ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))))) (label 162) (parent 160) (realized) (shape) (maps ((0) ((c c) (m m) (b b) (cost cost) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (n n) (ncm ncm) (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf))))) (origs (btr (1 1)) (mtr (0 1)))) (defskeleton minipay-rely-guar (vars (account account-0 acct) (cost amount) (ncb n ncm data) (item merchandise) (btr mtr bank-conf merc-conf text) (c m b name)) (defstrand merc 4 (for-bank (enc n cost account-0 bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account-0) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (precedes ((0 1) (1 0)) ((1 1) (0 2)) ((2 0) (0 0)) ((3 0) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig btr mtr) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-ship c m b item mtr) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 guar-merc-4) (operation encryption-test (added-strand cust 1) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (1 0)) (traces ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account-0 bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account-0 bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-0 bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account-0 bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))))) (label 163) (parent 160) (unrealized (1 0)) (comment "2 in cohort - 2 not yet seen")) (defskeleton minipay-rely-guar (vars (account account-0 acct) (cost amount) (ncb n ncm data) (item merchandise) (btr mtr bank-conf merc-conf mtr-0 text) (c m b name)) (defstrand merc 4 (for-bank (enc n cost account-0 bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account-0) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account-0 bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-0) (c c) (m m) (b b)) (precedes ((0 1) (1 0)) ((1 1) (0 2)) ((2 0) (0 0)) ((3 1) (0 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-ship c m b item mtr) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 guar-merc-4) (operation encryption-test (contracted (bank-conf-0 bank-conf) (ncb-0 ncb)) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (0 2) (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (traces ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account-0 bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account-0 bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-0 bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account-0 bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account-0 bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account-0 bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-0 bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))))) (label 164) (parent 161) (unrealized (1 0) (3 0)) (comment "2 in cohort - 2 not yet seen")) (defskeleton minipay-rely-guar (vars (account acct) (cost amount) (ncb n ncm data) (item merchandise) (btr mtr bank-conf merc-conf text) (c m b name)) (defstrand merc 4 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (precedes ((0 1) (1 0)) ((1 1) (0 2)) ((2 0) (0 0)) ((3 0) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig btr mtr) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-ship c m b item mtr) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 guar-merc-4) (operation encryption-test (displaced 4 0 merc 2) (sign (order c m b cost (enc n cost account-0 bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (1 0) (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account-0 bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (traces ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))))) (label 165) (parent 163) (seen 162) (realized) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay-rely-guar (vars (account account-0 acct) (cost amount) (ncb n ncm data) (item merchandise) (btr mtr bank-conf merc-conf mtr-0 text) (c m b name)) (defstrand merc 4 (for-bank (enc n cost account-0 bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account-0) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-0) (c c) (m m) (b b)) (precedes ((0 1) (1 0)) ((1 1) (0 2)) ((2 0) (0 0)) ((3 0) (1 0)) ((4 1) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-ship c m b item mtr) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 guar-merc-4) (operation encryption-test (added-strand merc 2) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (1 0) (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (traces ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account-0 bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account-0 bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-0 bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account-0 bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))))) (label 166) (parent 163) (unrealized (1 0) (4 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay-rely-guar (vars (account acct) (cost amount) (ncb n ncm data) (item merchandise) (btr mtr bank-conf merc-conf mtr-0 text) (c m b name)) (defstrand merc 4 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-0) (c c) (m m) (b b)) (precedes ((0 1) (1 0)) ((1 1) (0 2)) ((2 0) (0 0)) ((3 1) (0 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-ship c m b item mtr) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 guar-merc-4) (operation encryption-test (displaced 4 2 cust 1) (sign (order c m b cost (enc n cost account-0 bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (1 0)) (traces ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))))) (label 167) (parent 164) (unrealized (3 0)) (comment "2 in cohort - 2 not yet seen")) (defskeleton minipay-rely-guar (vars (account account-0 acct) (cost amount) (ncb n ncm data) (item merchandise) (btr mtr bank-conf merc-conf mtr-0 text) (c m b name)) (defstrand merc 4 (for-bank (enc n cost account-0 bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account-0) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account-0 bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-0) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (precedes ((0 1) (1 0)) ((1 1) (0 2)) ((2 0) (0 0)) ((3 1) (0 0)) ((4 0) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-ship c m b item mtr) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 guar-merc-4) (operation encryption-test (added-strand cust 1) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (1 0)) (traces ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account-0 bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account-0 bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-0 bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account-0 bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account-0 bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account-0 bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-0 bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))))) (label 168) (parent 164) (unrealized (1 0) (3 0)) (comment "2 in cohort - 2 not yet seen")) (defskeleton minipay-rely-guar (vars (account acct) (cost amount) (ncb n ncm data) (item merchandise) (btr mtr bank-conf merc-conf mtr-0 text) (c m b name)) (defstrand merc 4 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-0) (c c) (m m) (b b)) (precedes ((0 1) (1 0)) ((1 1) (0 2)) ((2 0) (0 0)) ((3 0) (1 0)) ((4 1) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-ship c m b item mtr) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 guar-merc-4) (operation encryption-test (displaced 5 0 merc 2) (sign (order c m b cost (enc n cost account-0 bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (1 0) (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account-0 bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)) (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account-0 bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-0 bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (traces ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))))) (label 169) (parent 166) (unrealized (4 0)) (comment "3 in cohort - 3 not yet seen")) (defskeleton minipay-rely-guar (vars (account acct) (cost amount) (ncb n ncm data) (item merchandise) (btr mtr bank-conf merc-conf mtr-0 text) (c m b name)) (defstrand merc 4 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-0) (c c) (m m) (b b)) (precedes ((0 1) (1 0)) ((1 1) (0 2)) ((2 0) (3 0)) ((3 1) (0 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-ship c m b item mtr) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 guar-merc-4) (operation encryption-test (displaced 4 2 cust 1) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (3 0)) (traces ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))))) (label 170) (parent 167) (seen 162) (realized) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay-rely-guar (vars (account acct) (cost amount) (ncb n ncm data) (item merchandise) (btr mtr bank-conf merc-conf mtr-0 text) (c m b name)) (defstrand merc 4 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-0) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (precedes ((0 1) (1 0)) ((1 1) (0 2)) ((2 0) (0 0)) ((3 1) (0 0)) ((4 0) (3 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-ship c m b item mtr) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 guar-merc-4) (operation encryption-test (added-strand cust 1) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (3 0)) (traces ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))))) (label 171) (parent 167) (seen 170) (realized) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay-rely-guar (vars (account acct) (cost amount) (ncb n ncm data) (item merchandise) (btr mtr bank-conf merc-conf mtr-0 text) (c m b name)) (defstrand merc 4 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-0) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (precedes ((0 1) (1 0)) ((1 1) (0 2)) ((2 0) (0 0)) ((3 1) (0 0)) ((4 0) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-ship c m b item mtr) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 guar-merc-4) (operation encryption-test (displaced 5 3 merc 2) (sign (order c m b cost (enc n cost account-0 bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (1 0) (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account-0 bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (traces ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))))) (label 172) (parent 168) (seen 171) (unrealized (3 0)) (comment "3 in cohort - 2 not yet seen")) (defskeleton minipay-rely-guar (vars (account account-0 acct) (cost amount) (ncb n ncm data) (item merchandise) (btr mtr bank-conf merc-conf mtr-0 mtr-1 text) (c m b name)) (defstrand merc 4 (for-bank (enc n cost account-0 bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account-0) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account-0 bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-0) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-1) (c c) (m m) (b b)) (precedes ((0 1) (1 0)) ((1 1) (0 2)) ((2 0) (0 0)) ((3 1) (0 0)) ((4 0) (1 0)) ((5 1) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig btr mtr mtr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-ship c m b item mtr) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 guar-merc-4) (operation encryption-test (added-strand merc 2) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (1 0) (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (traces ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account-0 bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account-0 bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-0 bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account-0 bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account-0 bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account-0 bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-0 bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-1 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))))) (label 173) (parent 168) (unrealized (1 0) (3 0) (5 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay-rely-guar (vars (account acct) (cost amount) (ncb n ncm data) (item merchandise) (btr mtr bank-conf merc-conf mtr-0 text) (c m b name)) (defstrand merc 4 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-0) (c c) (m m) (b b)) (precedes ((0 1) (1 0)) ((1 1) (0 2)) ((2 0) (0 0)) ((2 0) (4 0)) ((3 0) (1 0)) ((4 1) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-ship c m b item mtr) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 guar-merc-4) (operation encryption-test (displaced 5 2 cust 1) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (4 0)) (traces ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))))) (label 174) (parent 169) (realized) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay-rely-guar (vars (account acct) (cost amount) (ncb n ncm data) (item merchandise) (btr mtr bank-conf merc-conf mtr-0 text) (c m b name)) (defstrand merc 4 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-0) (c c) (m m) (b b)) (precedes ((0 1) (1 0)) ((1 1) (0 2)) ((2 0) (0 0)) ((3 0) (4 0)) ((4 1) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-ship c m b item mtr) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 guar-merc-4) (operation encryption-test (displaced 5 3 cust 1) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (4 0)) (traces ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))))) (label 175) (parent 169) (seen 165) (realized) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay-rely-guar (vars (account acct) (cost amount) (ncb n ncm data) (item merchandise) (btr mtr bank-conf merc-conf mtr-0 text) (c m b name)) (defstrand merc 4 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-0) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (precedes ((0 1) (1 0)) ((1 1) (0 2)) ((2 0) (0 0)) ((3 0) (1 0)) ((4 1) (1 0)) ((5 0) (4 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-ship c m b item mtr) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 guar-merc-4) (operation encryption-test (added-strand cust 1) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (4 0)) (traces ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))))) (label 176) (parent 169) (seen 175) (realized) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay-rely-guar (vars (account acct) (cost amount) (ncb n ncm data) (item merchandise) (btr mtr bank-conf merc-conf mtr-0 text) (c m b name)) (defstrand merc 4 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-0) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (precedes ((0 1) (1 0)) ((1 1) (0 2)) ((2 0) (3 0)) ((3 1) (0 0)) ((4 0) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-ship c m b item mtr) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 guar-merc-4) (operation encryption-test (displaced 5 2 cust 1) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (3 0)) (traces ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))))) (label 177) (parent 172) (seen 165) (realized) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay-rely-guar (vars (account acct) (cost amount) (ncb n ncm data) (item merchandise) (btr mtr bank-conf merc-conf mtr-0 text) (c m b name)) (defstrand merc 4 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-0) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (precedes ((0 1) (1 0)) ((1 1) (0 2)) ((2 0) (0 0)) ((3 1) (0 0)) ((4 0) (1 0)) ((5 0) (3 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-ship c m b item mtr) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 guar-merc-4) (operation encryption-test (added-strand cust 1) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (3 0)) (traces ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))))) (label 178) (parent 172) (seen 177) (realized) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay-rely-guar (vars (account acct) (cost amount) (ncb n ncm data) (item merchandise) (btr mtr bank-conf merc-conf mtr-0 mtr-1 text) (c m b name)) (defstrand merc 4 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-0) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-1) (c c) (m m) (b b)) (precedes ((0 1) (1 0)) ((1 1) (0 2)) ((2 0) (0 0)) ((3 1) (0 0)) ((4 0) (1 0)) ((5 1) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig btr mtr mtr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-ship c m b item mtr) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 guar-merc-4) (operation encryption-test (displaced 6 3 merc 2) (sign (order c m b cost (enc n cost account-0 bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (1 0) (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account-0 bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)) (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-1 (cat (sign (order c m b cost (enc n cost account-0 bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-0 bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (traces ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-1 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))))) (label 179) (parent 173) (unrealized (3 0) (5 0)) (comment "3 in cohort - 3 not yet seen")) (defskeleton minipay-rely-guar (vars (account acct) (cost amount) (ncb n ncm data) (item merchandise) (btr mtr bank-conf merc-conf mtr-0 text) (c m b name)) (defstrand merc 4 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-0) (c c) (m m) (b b)) (precedes ((0 1) (1 0)) ((1 1) (0 2)) ((2 0) (0 0)) ((2 0) (3 0)) ((3 1) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-ship c m b item mtr) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 guar-merc-4) (operation generalization deleted (3 0)) (traces ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))))) (label 180) (parent 174) (seen 162) (realized) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay-rely-guar (vars (account acct) (cost amount) (ncb n ncm data) (item merchandise) (btr mtr bank-conf merc-conf mtr-0 mtr-1 text) (c m b name)) (defstrand merc 4 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-0) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-1) (c c) (m m) (b b)) (precedes ((0 1) (1 0)) ((1 1) (0 2)) ((2 0) (3 0)) ((3 1) (0 0)) ((4 0) (1 0)) ((5 1) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig btr mtr mtr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-ship c m b item mtr) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 guar-merc-4) (operation encryption-test (displaced 6 2 cust 1) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (3 0)) (traces ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-1 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))))) (label 181) (parent 179) (unrealized (5 0)) (comment "3 in cohort - 3 not yet seen")) (defskeleton minipay-rely-guar (vars (account acct) (cost amount) (ncb n ncm data) (item merchandise) (btr mtr bank-conf merc-conf mtr-0 mtr-1 text) (c m b name)) (defstrand merc 4 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-0) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-1) (c c) (m m) (b b)) (precedes ((0 1) (1 0)) ((1 1) (0 2)) ((2 0) (0 0)) ((3 1) (0 0)) ((4 0) (3 0)) ((5 1) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig btr mtr mtr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-ship c m b item mtr) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 guar-merc-4) (operation encryption-test (displaced 6 4 cust 1) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (3 0)) (traces ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-1 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))))) (label 182) (parent 179) (unrealized (5 0)) (comment "3 in cohort - 3 not yet seen")) (defskeleton minipay-rely-guar (vars (account acct) (cost amount) (ncb n ncm data) (item merchandise) (btr mtr bank-conf merc-conf mtr-0 mtr-1 text) (c m b name)) (defstrand merc 4 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-0) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-1) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (precedes ((0 1) (1 0)) ((1 1) (0 2)) ((2 0) (0 0)) ((3 1) (0 0)) ((4 0) (1 0)) ((5 1) (1 0)) ((6 0) (3 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig btr mtr mtr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-ship c m b item mtr) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 guar-merc-4) (operation encryption-test (added-strand cust 1) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (3 0)) (traces ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-1 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))))) (label 183) (parent 179) (seen 189) (unrealized (5 0)) (comment "4 in cohort - 3 not yet seen")) (defskeleton minipay-rely-guar (vars (account acct) (cost amount) (ncb n ncm data) (item merchandise) (btr mtr bank-conf merc-conf mtr-0 mtr-1 text) (c m b name)) (defstrand merc 4 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-0) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-1) (c c) (m m) (b b)) (precedes ((0 1) (1 0)) ((1 1) (0 2)) ((2 0) (3 0)) ((2 0) (5 0)) ((3 1) (0 0)) ((4 0) (1 0)) ((5 1) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig btr mtr mtr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-ship c m b item mtr) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 guar-merc-4) (operation encryption-test (displaced 6 2 cust 1) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (5 0)) (traces ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-1 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))))) (label 184) (parent 181) (seen 174) (realized) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay-rely-guar (vars (account acct) (cost amount) (ncb n ncm data) (item merchandise) (btr mtr bank-conf merc-conf mtr-0 mtr-1 text) (c m b name)) (defstrand merc 4 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-0) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-1) (c c) (m m) (b b)) (precedes ((0 1) (1 0)) ((1 1) (0 2)) ((2 0) (3 0)) ((3 1) (0 0)) ((4 0) (5 0)) ((5 1) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig btr mtr mtr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-ship c m b item mtr) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 guar-merc-4) (operation encryption-test (displaced 6 4 cust 1) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (5 0)) (traces ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-1 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))))) (label 185) (parent 181) (seen 175) (realized) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay-rely-guar (vars (account acct) (cost amount) (ncb n ncm data) (item merchandise) (btr mtr bank-conf merc-conf mtr-0 mtr-1 text) (c m b name)) (defstrand merc 4 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-0) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-1) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (precedes ((0 1) (1 0)) ((1 1) (0 2)) ((2 0) (3 0)) ((3 1) (0 0)) ((4 0) (1 0)) ((5 1) (1 0)) ((6 0) (5 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig btr mtr mtr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-ship c m b item mtr) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 guar-merc-4) (operation encryption-test (added-strand cust 1) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (5 0)) (traces ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-1 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))))) (label 186) (parent 181) (seen 176) (realized) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay-rely-guar (vars (account acct) (cost amount) (ncb n ncm data) (item merchandise) (btr mtr bank-conf merc-conf mtr-0 mtr-1 text) (c m b name)) (defstrand merc 4 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-0) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-1) (c c) (m m) (b b)) (precedes ((0 1) (1 0)) ((1 1) (0 2)) ((2 0) (0 0)) ((2 0) (5 0)) ((3 1) (0 0)) ((4 0) (3 0)) ((5 1) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig btr mtr mtr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-ship c m b item mtr) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 guar-merc-4) (operation encryption-test (displaced 6 2 cust 1) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (5 0)) (traces ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-1 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))))) (label 187) (parent 182) (realized) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay-rely-guar (vars (account acct) (cost amount) (ncb n ncm data) (item merchandise) (btr mtr bank-conf merc-conf mtr-0 mtr-1 text) (c m b name)) (defstrand merc 4 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-0) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-1) (c c) (m m) (b b)) (precedes ((0 1) (1 0)) ((1 1) (0 2)) ((2 0) (0 0)) ((3 1) (0 0)) ((4 0) (3 0)) ((4 0) (5 0)) ((5 1) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig btr mtr mtr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-ship c m b item mtr) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 guar-merc-4) (operation encryption-test (displaced 6 4 cust 1) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (5 0)) (traces ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-1 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))))) (label 188) (parent 182) (realized) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay-rely-guar (vars (account acct) (cost amount) (ncb n ncm data) (item merchandise) (btr mtr bank-conf merc-conf mtr-0 mtr-1 text) (c m b name)) (defstrand merc 4 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-0) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-1) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (precedes ((0 1) (1 0)) ((1 1) (0 2)) ((2 0) (0 0)) ((3 1) (0 0)) ((4 0) (3 0)) ((5 1) (1 0)) ((6 0) (5 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig btr mtr mtr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-ship c m b item mtr) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 guar-merc-4) (operation encryption-test (added-strand cust 1) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (5 0)) (traces ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-1 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))))) (label 189) (parent 182) (seen 185) (realized) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay-rely-guar (vars (account acct) (cost amount) (ncb n ncm data) (item merchandise) (btr mtr bank-conf merc-conf mtr-0 mtr-1 text) (c m b name)) (defstrand merc 4 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-0) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-1) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (precedes ((0 1) (1 0)) ((1 1) (0 2)) ((2 0) (0 0)) ((2 0) (5 0)) ((3 1) (0 0)) ((4 0) (1 0)) ((5 1) (1 0)) ((6 0) (3 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig btr mtr mtr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-ship c m b item mtr) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 guar-merc-4) (operation encryption-test (displaced 7 2 cust 1) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (5 0)) (traces ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-1 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))))) (label 190) (parent 183) (realized) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay-rely-guar (vars (account acct) (cost amount) (ncb n ncm data) (item merchandise) (btr mtr bank-conf merc-conf mtr-0 mtr-1 text) (c m b name)) (defstrand merc 4 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-0) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-1) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (precedes ((0 1) (1 0)) ((1 1) (0 2)) ((2 0) (0 0)) ((3 1) (0 0)) ((4 0) (1 0)) ((5 1) (1 0)) ((6 0) (3 0)) ((6 0) (5 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig btr mtr mtr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-ship c m b item mtr) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 guar-merc-4) (operation encryption-test (displaced 7 6 cust 1) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (5 0)) (traces ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-1 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))))) (label 191) (parent 183) (seen 184) (realized) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay-rely-guar (vars (account acct) (cost amount) (ncb n ncm data) (item merchandise) (btr mtr bank-conf merc-conf mtr-0 mtr-1 text) (c m b name)) (defstrand merc 4 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-0) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-1) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (precedes ((0 1) (1 0)) ((1 1) (0 2)) ((2 0) (0 0)) ((3 1) (0 0)) ((4 0) (1 0)) ((5 1) (1 0)) ((6 0) (3 0)) ((7 0) (5 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig btr mtr mtr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-ship c m b item mtr) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 guar-merc-4) (operation encryption-test (added-strand cust 1) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (5 0)) (traces ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-1 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))))) (label 192) (parent 183) (seen 186) (realized) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay-rely-guar (vars (account acct) (cost amount) (ncb n ncm data) (item merchandise) (btr mtr bank-conf merc-conf mtr-0 text) (c m b name)) (defstrand merc 4 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-0) (c c) (m m) (b b)) (precedes ((0 1) (1 0)) ((1 1) (0 2)) ((2 0) (0 0)) ((2 0) (4 0)) ((3 0) (0 0)) ((4 1) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-ship c m b item mtr) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 guar-merc-4) (operation generalization deleted (3 0)) (traces ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))))) (label 193) (parent 187) (seen 180) (realized) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay-rely-guar (vars (account acct) (cost amount) (ncb n ncm data) (item merchandise) (btr mtr bank-conf merc-conf mtr-0 mtr-1 text) (c m b name)) (defstrand merc 4 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-0) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-1) (c c) (m m) (b b)) (precedes ((0 1) (1 0)) ((1 1) (0 2)) ((2 1) (0 0)) ((3 0) (2 0)) ((3 0) (4 0)) ((4 1) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig btr mtr mtr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-ship c m b item mtr) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 guar-merc-4) (operation generalization deleted (2 0)) (traces ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-1 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))))) (label 194) (parent 188) (seen 180) (realized) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay-rely-guar (vars (account acct) (cost amount) (ncb n ncm data) (item merchandise) (btr mtr bank-conf merc-conf mtr-0 text) (c m b name)) (defstrand merc 4 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (bank-conf-decommit (hash ncb bank-conf)) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr-0) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (precedes ((0 1) (1 0)) ((1 1) (0 2)) ((2 0) (0 0)) ((2 0) (4 0)) ((3 0) (1 0)) ((4 1) (1 0)) ((5 0) (0 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-ship c m b item mtr) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 guar-merc-4) (operation generalization deleted (3 0)) (traces ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-0 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))))) (label 195) (parent 190) (seen 193) (realized) (comment "1 in cohort - 0 not yet seen")) (comment "Nothing left to do") (defprotocol minipay-rely-guar basic (defrole cust (vars (c m b name) (cost amount) (item merchandise) (merc-conf bank-conf btr mtr text) (account acct) (n ncb ncm data)) (trace (send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) (facts (neq n ncb) (neq n ncm) (neq ncm ncb))) (defrole merc (vars (c m b name) (cost amount) (item merchandise) (merc-conf btr mtr text) (n ncm data) (for-bank bank-conf-commit bank-conf-decommit mesg)) (trace (recv (enc n cost item merc-conf ncm bank-conf-commit (sign (order c m b cost for-bank) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost for-bank) (privk "sig" c)) for-bank)) (pubk "enc" b))) (recv (enc bank-conf-decommit (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n bank-conf-decommit)) btr mtr) (privk "sig" m)))) (uniq-orig mtr)) (defrole bank (vars (c m b name) (cost amount) (bank-conf btr mtr text) (merc-conf-decommit mesg) (account acct) (n ncb data)) (trace (recv (enc (payreq c m b (hash cost n) merc-conf-decommit mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n merc-conf-decommit) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n merc-conf-decommit) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n merc-conf-decommit)) btr mtr) (privk "sig" b)) (pubk "enc" m)))) (uniq-orig btr)) (defrule rely-cust-3 (forall ((z strd) (mtr text) (item merchandise) (b m c name)) (implies (and (p "cust" z (idx 3)) (p "cust" "mtr" z mtr) (p "cust" "item" z item) (p "cust" "b" z b) (p "cust" "m" z m) (p "cust" "c" z c)) (fact will-ship c m b item mtr)))) (defrule rely-cust-2 (forall ((z strd) (btr mtr text) (n data) (cost amount) (b m c name)) (implies (and (p "cust" z (idx 2)) (p "cust" "btr" z btr) (p "cust" "mtr" z mtr) (p "cust" "n" z n) (p "cust" "cost" z cost) (p "cust" "b" z b) (p "cust" "m" z m) (p "cust" "c" z c)) (fact will-transfer c m b cost n mtr btr)))) (defrule rely-merc-3 (forall ((z strd) (n data) (cost amount) (item merchandise) (b m c name) (btr mtr text)) (implies (and (p "merc" z (idx 3)) (p "merc" "n" z n) (p "merc" "cost" z cost) (p "merc" "item" z item) (p "merc" "b" z b) (p "merc" "m" z m) (p "merc" "c" z c) (p "merc" "btr" z btr) (p "merc" "mtr" z mtr)) (and (fact buy-via c m b item cost n) (fact will-transfer c m b cost n mtr btr))))) (defrule rely-bank-1 (forall ((z strd) (n data) (cost amount) (b m c name)) (implies (and (p "bank" z (idx 1)) (p "bank" "n" z n) (p "bank" "cost" z cost) (p "bank" "b" z b) (p "bank" "m" z m) (p "bank" "c" z c)) (exists ((item merchandise)) (fact buy-via c m b item cost n))))) (defrule guar-cust-1 (forall ((z strd) (n data) (cost amount) (item merchandise) (b m c name)) (implies (and (p "cust" z (idx 1)) (p "cust" "n" z n) (p "cust" "cost" z cost) (p "cust" "item" z item) (p "cust" "b" z b) (p "cust" "m" z m) (p "cust" "c" z c)) (fact buy-via c m b item cost n)))) (defrule guar-merc-4 (forall ((z strd) (mtr text) (item merchandise) (b m c name)) (implies (and (p "merc" z (idx 4)) (p "merc" "mtr" z mtr) (p "merc" "item" z item) (p "merc" "b" z b) (p "merc" "m" z m) (p "merc" "c" z c)) (fact will-ship c m b item mtr)))) (defrule guar-bank-2 (forall ((z strd) (btr mtr text) (n data) (cost amount) (c b m name)) (implies (and (p "bank" z (idx 2)) (p "bank" "btr" z btr) (p "bank" "mtr" z mtr) (p "bank" "n" z n) (p "bank" "cost" z cost) (p "bank" "c" z c) (p "bank" "b" z b) (p "bank" "m" z m)) (and (non (privk "sig" c)) (fact will-transfer c m b cost n mtr btr))))) (defrule cheq-merc-4 (forall ((z strd) (n data) (bank-conf-decommit bank-conf-commit mesg)) (implies (and (p "merc" z (idx 4)) (p "merc" "n" z n) (p "merc" "bank-conf-decommit" z bank-conf-decommit) (p "merc" "bank-conf-commit" z bank-conf-commit)) (= bank-conf-commit (hash n bank-conf-decommit))))) (defgenrule neqRl_indx (forall ((x indx)) (implies (fact neq x x) (false)))) (defgenrule neqRl_strd (forall ((x strd)) (implies (fact neq x x) (false)))) (defgenrule neqRl_mesg (forall ((x mesg)) (implies (fact neq x x) (false)))) (defgenrule fact-cust-neq2 (forall ((z strd) (ncb n data)) (implies (and (p "cust" z (idx 1)) (p "cust" "ncb" z ncb) (p "cust" "n" z n)) (fact neq n ncb)))) (defgenrule fact-cust-neq1 (forall ((z strd) (ncm n data)) (implies (and (p "cust" z (idx 1)) (p "cust" "ncm" z ncm) (p "cust" "n" z n)) (fact neq n ncm)))) (defgenrule fact-cust-neq0 (forall ((z strd) (ncb ncm data)) (implies (and (p "cust" z (idx 1)) (p "cust" "ncb" z ncb) (p "cust" "ncm" z ncm)) (fact neq ncm ncb)))) (lang (acct atom) (amount atom) (merchandise atom) (sign sign) (order (tuple 5)) (bconf (tuple 3)) (mconf (tuple 3)) (payreq (tuple 7)))) (defskeleton minipay-rely-guar (vars (for-bank bank-conf-commit bank-conf-decommit mesg) (cost amount) (n ncm data) (item merchandise) (merc-conf btr mtr text) (c m b name)) (defstrand merc 4 (for-bank for-bank) (bank-conf-commit bank-conf-commit) (bank-conf-decommit bank-conf-decommit) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (non-orig (privk "sig" b)) (uniq-orig mtr) (traces ((recv (enc n cost item merc-conf ncm bank-conf-commit (sign (order c m b cost for-bank) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost for-bank) (privk "sig" c)) for-bank)) (pubk "enc" b))) (recv (enc bank-conf-decommit (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))))) (label 196) (unrealized (0 2)) (origs (mtr (0 1))) (comment "Not closed under rules")) (defskeleton minipay-rely-guar (vars (for-bank bank-conf-decommit mesg) (cost amount) (n ncm data) (item merchandise) (merc-conf btr mtr text) (c m b name)) (defstrand merc 4 (for-bank for-bank) (bank-conf-commit (hash n bank-conf-decommit)) (bank-conf-decommit bank-conf-decommit) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (non-orig (privk "sig" b)) (uniq-orig mtr) (facts (will-transfer c m b cost n mtr btr) (buy-via c m b item cost n) (will-ship c m b item mtr)) (rule cheq-merc-4 guar-merc-4 rely-merc-3) (traces ((recv (enc n cost item merc-conf ncm (hash n bank-conf-decommit) (sign (order c m b cost for-bank) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost for-bank) (privk "sig" c)) for-bank)) (pubk "enc" b))) (recv (enc bank-conf-decommit (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))))) (label 197) (parent 196) (unrealized (0 2)) (origs (mtr (0 1))) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay-rely-guar (vars (for-bank bank-conf-decommit mesg) (account acct) (cost amount) (n ncm ncb data) (item merchandise) (merc-conf btr mtr bank-conf text) (c m b name)) (defstrand merc 4 (for-bank for-bank) (bank-conf-commit (hash n bank-conf-decommit)) (bank-conf-decommit bank-conf-decommit) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (precedes ((0 1) (1 0)) ((1 1) (0 2))) (non-orig (privk "sig" c) (privk "sig" b)) (uniq-orig btr mtr) (facts (buy-via c m b item cost n) (will-ship c m b item mtr) (will-transfer c m b cost n mtr btr)) (rule guar-bank-2 guar-merc-4 rely-merc-3) (operation encryption-test (added-strand bank 2) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (0 2)) (traces ((recv (enc n cost item merc-conf ncm (hash n bank-conf-decommit) (sign (order c m b cost for-bank) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost for-bank) (privk "sig" c)) for-bank)) (pubk "enc" b))) (recv (enc bank-conf-decommit (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))))) (label 198) (parent 197) (unrealized (0 0) (1 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay-rely-guar (vars (bank-conf-decommit mesg) (account account-0 acct) (cost amount) (n ncm ncb n-0 ncb-0 ncm-0 data) (item item-0 merchandise) (merc-conf btr mtr bank-conf merc-conf-0 bank-conf-0 text) (c m b name)) (defstrand merc 4 (for-bank (enc n-0 cost account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (bank-conf-commit (hash n bank-conf-decommit)) (bank-conf-decommit bank-conf-decommit) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account-0) (cost cost) (n n-0) (ncb ncb-0) (ncm ncm-0) (item item-0) (merc-conf merc-conf-0) (bank-conf bank-conf-0) (c c) (m m) (b b)) (precedes ((0 1) (1 0)) ((1 1) (0 2)) ((2 0) (0 0))) (non-orig (privk "sig" c) (privk "sig" b)) (uniq-orig btr mtr) (facts (neq n-0 ncb-0) (neq n-0 ncm-0) (neq ncm-0 ncb-0) (buy-via c m b item cost n) (buy-via c m b item-0 cost n-0) (will-ship c m b item mtr) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 guar-merc-4 rely-merc-3) (operation encryption-test (added-strand cust 1) (sign (order c m b cost (enc n-0 cost account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (0 0)) (traces ((recv (enc n cost item merc-conf ncm (hash n bank-conf-decommit) (sign (order c m b cost (enc n-0 cost account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n-0 cost account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (enc n-0 cost account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n-0 cost item-0 merc-conf-0 ncm-0 (hash n-0 (hash ncb-0 bank-conf-0)) (sign (order c m b cost (enc n-0 cost account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))))) (label 199) (parent 198) (unrealized (1 0)) (comment "2 in cohort - 2 not yet seen")) (defskeleton minipay-rely-guar (vars (bank-conf-decommit mesg) (account acct) (cost amount) (n ncb ncm data) (item merchandise) (btr mtr merc-conf bank-conf text) (c m b name)) (defstrand merc 4 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n bank-conf-decommit)) (bank-conf-decommit bank-conf-decommit) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (precedes ((0 1) (1 0)) ((1 1) (0 2)) ((2 0) (0 0))) (non-orig (privk "sig" c) (privk "sig" b)) (uniq-orig btr mtr) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n) (will-ship c m b item mtr) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 guar-merc-4) (operation encryption-test (displaced 3 2 cust 1) (sign (order c m b cost (enc n-0 cost account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (1 0)) (traces ((recv (enc n cost item merc-conf ncm (hash n bank-conf-decommit) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))))) (label 200) (parent 199) (realized) (shape) (maps ((0) ((c c) (m m) (b b) (cost cost) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (n n) (ncm ncm) (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n bank-conf-decommit)) (bank-conf-decommit bank-conf-decommit)))) (origs (btr (1 1)) (mtr (0 1)))) (defskeleton minipay-rely-guar (vars (bank-conf-decommit mesg) (account account-0 acct) (cost amount) (n ncm ncb n-0 ncb-0 ncm-0 data) (item item-0 merchandise) (merc-conf btr mtr bank-conf merc-conf-0 bank-conf-0 text) (c m b name)) (defstrand merc 4 (for-bank (enc n-0 cost account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (bank-conf-commit (hash n bank-conf-decommit)) (bank-conf-decommit bank-conf-decommit) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account-0) (cost cost) (n n-0) (ncb ncb-0) (ncm ncm-0) (item item-0) (merc-conf merc-conf-0) (bank-conf bank-conf-0) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (precedes ((0 1) (1 0)) ((1 1) (0 2)) ((2 0) (0 0)) ((3 0) (1 0))) (non-orig (privk "sig" c) (privk "sig" b)) (uniq-orig btr mtr) (facts (neq n ncb) (neq n-0 ncb-0) (neq n ncm) (neq n-0 ncm-0) (neq ncm ncb) (neq ncm-0 ncb-0) (buy-via c m b item cost n) (buy-via c m b item-0 cost n-0) (will-ship c m b item mtr) (will-transfer c m b cost n mtr btr)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-bank-2 guar-cust-1 guar-merc-4) (operation encryption-test (added-strand cust 1) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (1 0)) (traces ((recv (enc n cost item merc-conf ncm (hash n bank-conf-decommit) (sign (order c m b cost (enc n-0 cost account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n-0 cost account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (enc n-0 cost account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b)))) (pubk "enc" b))) (recv (enc bank-conf-decommit (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)))) ((recv (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m)))) ((send (enc n-0 cost item-0 merc-conf-0 ncm-0 (hash n-0 (hash ncb-0 bank-conf-0)) (sign (order c m b cost (enc n-0 cost account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))))) (label 201) (parent 199) (realized) (shape) (maps ((0) ((c c) (m m) (b b) (cost cost) (item item) (merc-conf merc-conf) (btr btr) (mtr mtr) (n n) (ncm ncm) (for-bank (enc n-0 cost account-0 bank-conf-0 ncb-0 (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (bank-conf-commit (hash n bank-conf-decommit)) (bank-conf-decommit bank-conf-decommit)))) (origs (btr (1 1)) (mtr (0 1)))) (comment "Nothing left to do") (defprotocol minipay-rely-guar basic (defrole cust (vars (c m b name) (cost amount) (item merchandise) (merc-conf bank-conf btr mtr text) (account acct) (n ncb ncm data)) (trace (send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) (facts (neq n ncb) (neq n ncm) (neq ncm ncb))) (defrole merc (vars (c m b name) (cost amount) (item merchandise) (merc-conf btr mtr text) (n ncm data) (for-bank bank-conf-commit bank-conf-decommit mesg)) (trace (recv (enc n cost item merc-conf ncm bank-conf-commit (sign (order c m b cost for-bank) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost for-bank) (privk "sig" c)) for-bank)) (pubk "enc" b))) (recv (enc bank-conf-decommit (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n bank-conf-decommit)) btr mtr) (privk "sig" m)))) (uniq-orig mtr)) (defrole bank (vars (c m b name) (cost amount) (bank-conf btr mtr text) (merc-conf-decommit mesg) (account acct) (n ncb data)) (trace (recv (enc (payreq c m b (hash cost n) merc-conf-decommit mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n merc-conf-decommit) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n merc-conf-decommit) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n merc-conf-decommit)) btr mtr) (privk "sig" b)) (pubk "enc" m)))) (uniq-orig btr)) (defrule rely-cust-3 (forall ((z strd) (mtr text) (item merchandise) (b m c name)) (implies (and (p "cust" z (idx 3)) (p "cust" "mtr" z mtr) (p "cust" "item" z item) (p "cust" "b" z b) (p "cust" "m" z m) (p "cust" "c" z c)) (fact will-ship c m b item mtr)))) (defrule rely-cust-2 (forall ((z strd) (btr mtr text) (n data) (cost amount) (b m c name)) (implies (and (p "cust" z (idx 2)) (p "cust" "btr" z btr) (p "cust" "mtr" z mtr) (p "cust" "n" z n) (p "cust" "cost" z cost) (p "cust" "b" z b) (p "cust" "m" z m) (p "cust" "c" z c)) (fact will-transfer c m b cost n mtr btr)))) (defrule rely-merc-3 (forall ((z strd) (n data) (cost amount) (item merchandise) (b m c name) (btr mtr text)) (implies (and (p "merc" z (idx 3)) (p "merc" "n" z n) (p "merc" "cost" z cost) (p "merc" "item" z item) (p "merc" "b" z b) (p "merc" "m" z m) (p "merc" "c" z c) (p "merc" "btr" z btr) (p "merc" "mtr" z mtr)) (and (fact buy-via c m b item cost n) (fact will-transfer c m b cost n mtr btr))))) (defrule rely-bank-1 (forall ((z strd) (n data) (cost amount) (b m c name)) (implies (and (p "bank" z (idx 1)) (p "bank" "n" z n) (p "bank" "cost" z cost) (p "bank" "b" z b) (p "bank" "m" z m) (p "bank" "c" z c)) (exists ((item merchandise)) (fact buy-via c m b item cost n))))) (defrule guar-cust-1 (forall ((z strd) (n data) (cost amount) (item merchandise) (b m c name)) (implies (and (p "cust" z (idx 1)) (p "cust" "n" z n) (p "cust" "cost" z cost) (p "cust" "item" z item) (p "cust" "b" z b) (p "cust" "m" z m) (p "cust" "c" z c)) (fact buy-via c m b item cost n)))) (defrule guar-merc-4 (forall ((z strd) (mtr text) (item merchandise) (b m c name)) (implies (and (p "merc" z (idx 4)) (p "merc" "mtr" z mtr) (p "merc" "item" z item) (p "merc" "b" z b) (p "merc" "m" z m) (p "merc" "c" z c)) (fact will-ship c m b item mtr)))) (defrule guar-bank-2 (forall ((z strd) (btr mtr text) (n data) (cost amount) (c b m name)) (implies (and (p "bank" z (idx 2)) (p "bank" "btr" z btr) (p "bank" "mtr" z mtr) (p "bank" "n" z n) (p "bank" "cost" z cost) (p "bank" "c" z c) (p "bank" "b" z b) (p "bank" "m" z m)) (and (non (privk "sig" c)) (fact will-transfer c m b cost n mtr btr))))) (defrule cheq-merc-4 (forall ((z strd) (n data) (bank-conf-decommit bank-conf-commit mesg)) (implies (and (p "merc" z (idx 4)) (p "merc" "n" z n) (p "merc" "bank-conf-decommit" z bank-conf-decommit) (p "merc" "bank-conf-commit" z bank-conf-commit)) (= bank-conf-commit (hash n bank-conf-decommit))))) (defgenrule neqRl_indx (forall ((x indx)) (implies (fact neq x x) (false)))) (defgenrule neqRl_strd (forall ((x strd)) (implies (fact neq x x) (false)))) (defgenrule neqRl_mesg (forall ((x mesg)) (implies (fact neq x x) (false)))) (defgenrule fact-cust-neq2 (forall ((z strd) (ncb n data)) (implies (and (p "cust" z (idx 1)) (p "cust" "ncb" z ncb) (p "cust" "n" z n)) (fact neq n ncb)))) (defgenrule fact-cust-neq1 (forall ((z strd) (ncm n data)) (implies (and (p "cust" z (idx 1)) (p "cust" "ncm" z ncm) (p "cust" "n" z n)) (fact neq n ncm)))) (defgenrule fact-cust-neq0 (forall ((z strd) (ncb ncm data)) (implies (and (p "cust" z (idx 1)) (p "cust" "ncb" z ncb) (p "cust" "ncm" z ncm)) (fact neq ncm ncb)))) (lang (acct atom) (amount atom) (merchandise atom) (sign sign) (order (tuple 5)) (bconf (tuple 3)) (mconf (tuple 3)) (payreq (tuple 7)))) (defskeleton minipay-rely-guar (vars (for-bank bank-conf-commit mesg) (cost amount) (n ncm data) (item merchandise) (merc-conf text) (c m b name)) (defstrand merc 1 (for-bank for-bank) (bank-conf-commit bank-conf-commit) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (c c) (m m) (b b)) (non-orig (privk "enc" m) (privk "sig" c)) (traces ((recv (enc n cost item merc-conf ncm bank-conf-commit (sign (order c m b cost for-bank) (privk "sig" c)) (pubk "enc" m))))) (label 202) (unrealized (0 0)) (origs) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay-rely-guar (vars (bank-conf-commit mesg) (account acct) (cost amount) (n ncm n-0 ncb ncm-0 data) (item item-0 merchandise) (merc-conf merc-conf-0 bank-conf text) (c m b name)) (defstrand merc 1 (for-bank (enc n-0 cost account bank-conf ncb (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n-0) (ncb ncb) (ncm ncm-0) (item item-0) (merc-conf merc-conf-0) (bank-conf bank-conf) (c c) (m m) (b b)) (precedes ((1 0) (0 0))) (non-orig (privk "enc" m) (privk "sig" c)) (facts (neq n-0 ncb) (neq n-0 ncm-0) (neq ncm-0 ncb) (buy-via c m b item-0 cost n-0)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-cust-1) (operation encryption-test (added-strand cust 1) (sign (order c m b cost (enc n-0 cost account bank-conf ncb (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (0 0)) (traces ((recv (enc n cost item merc-conf ncm bank-conf-commit (sign (order c m b cost (enc n-0 cost account bank-conf ncb (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((send (enc n-0 cost item-0 merc-conf-0 ncm-0 (hash n-0 (hash ncb bank-conf)) (sign (order c m b cost (enc n-0 cost account bank-conf ncb (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))))) (label 203) (parent 202) (unrealized (0 0)) (comment "2 in cohort - 2 not yet seen")) (defskeleton minipay-rely-guar (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (merc-conf bank-conf text) (c m b name)) (defstrand merc 1 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (precedes ((1 0) (0 0))) (non-orig (privk "enc" m) (privk "sig" c)) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-cust-1) (operation encryption-test (contracted (item-0 item) (merc-conf-0 merc-conf) (n-0 n) (ncm-0 ncm) (bank-conf-commit (hash n (hash ncb bank-conf)))) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (0 0) (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (traces ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))))) (label 204) (parent 203) (realized) (shape) (maps ((0) ((c c) (m m) (b b) (cost cost) (item item) (merc-conf merc-conf) (n n) (ncm ncm) (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf)))))) (origs)) (defskeleton minipay-rely-guar (vars (bank-conf-commit mesg) (account acct) (cost amount) (n ncm n-0 ncb ncm-0 data) (item item-0 merchandise) (merc-conf merc-conf-0 bank-conf mtr text) (c m b name)) (defstrand merc 1 (for-bank (enc n-0 cost account bank-conf ncb (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n-0) (ncb ncb) (ncm ncm-0) (item item-0) (merc-conf merc-conf-0) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n-0 cost account bank-conf ncb (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (bank-conf-commit (hash n-0 (hash ncb bank-conf))) (cost cost) (n n-0) (ncm ncm-0) (item item-0) (merc-conf merc-conf-0) (mtr mtr) (c c) (m m) (b b)) (precedes ((1 0) (0 0)) ((2 1) (0 0))) (non-orig (privk "enc" m) (privk "sig" c)) (uniq-orig mtr) (facts (neq n-0 ncb) (neq n-0 ncm-0) (neq ncm-0 ncb) (buy-via c m b item-0 cost n-0)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-cust-1) (operation encryption-test (added-strand merc 2) (sign (order c m b cost (enc n-0 cost account bank-conf ncb (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (0 0) (enc n-0 cost item-0 merc-conf-0 ncm-0 (hash n-0 (hash ncb bank-conf)) (sign (order c m b cost (enc n-0 cost account bank-conf ncb (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (traces ((recv (enc n cost item merc-conf ncm bank-conf-commit (sign (order c m b cost (enc n-0 cost account bank-conf ncb (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((send (enc n-0 cost item-0 merc-conf-0 ncm-0 (hash n-0 (hash ncb bank-conf)) (sign (order c m b cost (enc n-0 cost account bank-conf ncb (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n-0 cost item-0 merc-conf-0 ncm-0 (hash n-0 (hash ncb bank-conf)) (sign (order c m b cost (enc n-0 cost account bank-conf ncb (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n-0) (hash ncm-0 item-0 merc-conf-0) mtr (cat (sign (order c m b cost (enc n-0 cost account bank-conf ncb (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (enc n-0 cost account bank-conf ncb (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b)))) (pubk "enc" b))))) (label 205) (parent 203) (unrealized (2 0)) (comment "2 in cohort - 2 not yet seen")) (defskeleton minipay-rely-guar (vars (bank-conf-commit mesg) (account acct) (cost amount) (n ncm n-0 ncb ncm-0 data) (item item-0 merchandise) (merc-conf merc-conf-0 bank-conf mtr text) (c m b name)) (defstrand merc 1 (for-bank (enc n-0 cost account bank-conf ncb (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n-0) (ncb ncb) (ncm ncm-0) (item item-0) (merc-conf merc-conf-0) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n-0 cost account bank-conf ncb (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (bank-conf-commit (hash n-0 (hash ncb bank-conf))) (cost cost) (n n-0) (ncm ncm-0) (item item-0) (merc-conf merc-conf-0) (mtr mtr) (c c) (m m) (b b)) (precedes ((1 0) (2 0)) ((2 1) (0 0))) (non-orig (privk "enc" m) (privk "sig" c)) (uniq-orig mtr) (facts (neq n-0 ncb) (neq n-0 ncm-0) (neq ncm-0 ncb) (buy-via c m b item-0 cost n-0)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-cust-1) (operation encryption-test (displaced 3 1 cust 1) (sign (order c m b cost (enc n-0 cost account bank-conf ncb (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (2 0)) (traces ((recv (enc n cost item merc-conf ncm bank-conf-commit (sign (order c m b cost (enc n-0 cost account bank-conf ncb (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((send (enc n-0 cost item-0 merc-conf-0 ncm-0 (hash n-0 (hash ncb bank-conf)) (sign (order c m b cost (enc n-0 cost account bank-conf ncb (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n-0 cost item-0 merc-conf-0 ncm-0 (hash n-0 (hash ncb bank-conf)) (sign (order c m b cost (enc n-0 cost account bank-conf ncb (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n-0) (hash ncm-0 item-0 merc-conf-0) mtr (cat (sign (order c m b cost (enc n-0 cost account bank-conf ncb (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (enc n-0 cost account bank-conf ncb (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b)))) (pubk "enc" b))))) (label 206) (parent 205) (realized) (shape) (maps ((0) ((c c) (m m) (b b) (cost cost) (item item) (merc-conf merc-conf) (n n) (ncm ncm) (for-bank (enc n-0 cost account bank-conf ncb (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit)))) (origs (mtr (2 1)))) (defskeleton minipay-rely-guar (vars (bank-conf-commit mesg) (account acct) (cost amount) (n ncm n-0 ncb ncm-0 data) (item item-0 merchandise) (merc-conf merc-conf-0 bank-conf mtr text) (c m b name)) (defstrand merc 1 (for-bank (enc n-0 cost account bank-conf ncb (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n-0) (ncb ncb) (ncm ncm-0) (item item-0) (merc-conf merc-conf-0) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n-0 cost account bank-conf ncb (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (bank-conf-commit (hash n-0 (hash ncb bank-conf))) (cost cost) (n n-0) (ncm ncm-0) (item item-0) (merc-conf merc-conf-0) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n-0) (ncb ncb) (ncm ncm-0) (item item-0) (merc-conf merc-conf-0) (bank-conf bank-conf) (c c) (m m) (b b)) (precedes ((1 0) (0 0)) ((2 1) (0 0)) ((3 0) (2 0))) (non-orig (privk "enc" m) (privk "sig" c)) (uniq-orig mtr) (facts (neq n-0 ncb) (neq n-0 ncm-0) (neq ncm-0 ncb) (buy-via c m b item-0 cost n-0)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-cust-1) (operation encryption-test (added-strand cust 1) (sign (order c m b cost (enc n-0 cost account bank-conf ncb (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (2 0)) (traces ((recv (enc n cost item merc-conf ncm bank-conf-commit (sign (order c m b cost (enc n-0 cost account bank-conf ncb (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((send (enc n-0 cost item-0 merc-conf-0 ncm-0 (hash n-0 (hash ncb bank-conf)) (sign (order c m b cost (enc n-0 cost account bank-conf ncb (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n-0 cost item-0 merc-conf-0 ncm-0 (hash n-0 (hash ncb bank-conf)) (sign (order c m b cost (enc n-0 cost account bank-conf ncb (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n-0) (hash ncm-0 item-0 merc-conf-0) mtr (cat (sign (order c m b cost (enc n-0 cost account bank-conf ncb (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (enc n-0 cost account bank-conf ncb (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b)))) (pubk "enc" b)))) ((send (enc n-0 cost item-0 merc-conf-0 ncm-0 (hash n-0 (hash ncb bank-conf)) (sign (order c m b cost (enc n-0 cost account bank-conf ncb (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))))) (label 207) (parent 205) (seen 206) (realized) (comment "1 in cohort - 0 not yet seen")) (comment "Nothing left to do") (defprotocol minipay-rely-guar basic (defrole cust (vars (c m b name) (cost amount) (item merchandise) (merc-conf bank-conf btr mtr text) (account acct) (n ncb ncm data)) (trace (send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (recv (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)))) (facts (neq n ncb) (neq n ncm) (neq ncm ncb))) (defrole merc (vars (c m b name) (cost amount) (item merchandise) (merc-conf btr mtr text) (n ncm data) (for-bank bank-conf-commit bank-conf-decommit mesg)) (trace (recv (enc n cost item merc-conf ncm bank-conf-commit (sign (order c m b cost for-bank) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost for-bank) (privk "sig" c)) for-bank)) (pubk "enc" b))) (recv (enc bank-conf-decommit (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n bank-conf-decommit)) btr mtr) (privk "sig" m)))) (uniq-orig mtr)) (defrole bank (vars (c m b name) (cost amount) (bank-conf btr mtr text) (merc-conf-decommit mesg) (account acct) (n ncb data)) (trace (recv (enc (payreq c m b (hash cost n) merc-conf-decommit mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n merc-conf-decommit) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n merc-conf-decommit) (pubk "enc" b)))) (pubk "enc" b))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n merc-conf-decommit)) btr mtr) (privk "sig" b)) (pubk "enc" m)))) (uniq-orig btr)) (defrule rely-cust-3 (forall ((z strd) (mtr text) (item merchandise) (b m c name)) (implies (and (p "cust" z (idx 3)) (p "cust" "mtr" z mtr) (p "cust" "item" z item) (p "cust" "b" z b) (p "cust" "m" z m) (p "cust" "c" z c)) (fact will-ship c m b item mtr)))) (defrule rely-cust-2 (forall ((z strd) (btr mtr text) (n data) (cost amount) (b m c name)) (implies (and (p "cust" z (idx 2)) (p "cust" "btr" z btr) (p "cust" "mtr" z mtr) (p "cust" "n" z n) (p "cust" "cost" z cost) (p "cust" "b" z b) (p "cust" "m" z m) (p "cust" "c" z c)) (fact will-transfer c m b cost n mtr btr)))) (defrule rely-merc-3 (forall ((z strd) (n data) (cost amount) (item merchandise) (b m c name) (btr mtr text)) (implies (and (p "merc" z (idx 3)) (p "merc" "n" z n) (p "merc" "cost" z cost) (p "merc" "item" z item) (p "merc" "b" z b) (p "merc" "m" z m) (p "merc" "c" z c) (p "merc" "btr" z btr) (p "merc" "mtr" z mtr)) (and (fact buy-via c m b item cost n) (fact will-transfer c m b cost n mtr btr))))) (defrule rely-bank-1 (forall ((z strd) (n data) (cost amount) (b m c name)) (implies (and (p "bank" z (idx 1)) (p "bank" "n" z n) (p "bank" "cost" z cost) (p "bank" "b" z b) (p "bank" "m" z m) (p "bank" "c" z c)) (exists ((item merchandise)) (fact buy-via c m b item cost n))))) (defrule guar-cust-1 (forall ((z strd) (n data) (cost amount) (item merchandise) (b m c name)) (implies (and (p "cust" z (idx 1)) (p "cust" "n" z n) (p "cust" "cost" z cost) (p "cust" "item" z item) (p "cust" "b" z b) (p "cust" "m" z m) (p "cust" "c" z c)) (fact buy-via c m b item cost n)))) (defrule guar-merc-4 (forall ((z strd) (mtr text) (item merchandise) (b m c name)) (implies (and (p "merc" z (idx 4)) (p "merc" "mtr" z mtr) (p "merc" "item" z item) (p "merc" "b" z b) (p "merc" "m" z m) (p "merc" "c" z c)) (fact will-ship c m b item mtr)))) (defrule guar-bank-2 (forall ((z strd) (btr mtr text) (n data) (cost amount) (c b m name)) (implies (and (p "bank" z (idx 2)) (p "bank" "btr" z btr) (p "bank" "mtr" z mtr) (p "bank" "n" z n) (p "bank" "cost" z cost) (p "bank" "c" z c) (p "bank" "b" z b) (p "bank" "m" z m)) (and (non (privk "sig" c)) (fact will-transfer c m b cost n mtr btr))))) (defrule cheq-merc-4 (forall ((z strd) (n data) (bank-conf-decommit bank-conf-commit mesg)) (implies (and (p "merc" z (idx 4)) (p "merc" "n" z n) (p "merc" "bank-conf-decommit" z bank-conf-decommit) (p "merc" "bank-conf-commit" z bank-conf-commit)) (= bank-conf-commit (hash n bank-conf-decommit))))) (defgenrule neqRl_indx (forall ((x indx)) (implies (fact neq x x) (false)))) (defgenrule neqRl_strd (forall ((x strd)) (implies (fact neq x x) (false)))) (defgenrule neqRl_mesg (forall ((x mesg)) (implies (fact neq x x) (false)))) (defgenrule fact-cust-neq2 (forall ((z strd) (ncb n data)) (implies (and (p "cust" z (idx 1)) (p "cust" "ncb" z ncb) (p "cust" "n" z n)) (fact neq n ncb)))) (defgenrule fact-cust-neq1 (forall ((z strd) (ncm n data)) (implies (and (p "cust" z (idx 1)) (p "cust" "ncm" z ncm) (p "cust" "n" z n)) (fact neq n ncm)))) (defgenrule fact-cust-neq0 (forall ((z strd) (ncb ncm data)) (implies (and (p "cust" z (idx 1)) (p "cust" "ncb" z ncb) (p "cust" "ncm" z ncm)) (fact neq ncm ncb)))) (lang (acct atom) (amount atom) (merchandise atom) (sign sign) (order (tuple 5)) (bconf (tuple 3)) (mconf (tuple 3)) (payreq (tuple 7)))) (defskeleton minipay-rely-guar (vars (for-bank bank-conf-commit mesg) (cost amount) (n ncm data) (item merchandise) (merc-conf text) (c m b name)) (defstrand merc 1 (for-bank for-bank) (bank-conf-commit bank-conf-commit) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (c c) (m m) (b b)) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c)) (traces ((recv (enc n cost item merc-conf ncm bank-conf-commit (sign (order c m b cost for-bank) (privk "sig" c)) (pubk "enc" m))))) (label 208) (unrealized (0 0)) (origs) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay-rely-guar (vars (bank-conf-commit mesg) (account acct) (cost amount) (n ncm n-0 ncb ncm-0 data) (item item-0 merchandise) (merc-conf merc-conf-0 bank-conf text) (c m b name)) (defstrand merc 1 (for-bank (enc n-0 cost account bank-conf ncb (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n-0) (ncb ncb) (ncm ncm-0) (item item-0) (merc-conf merc-conf-0) (bank-conf bank-conf) (c c) (m m) (b b)) (precedes ((1 0) (0 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c)) (facts (neq n-0 ncb) (neq n-0 ncm-0) (neq ncm-0 ncb) (buy-via c m b item-0 cost n-0)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-cust-1) (operation encryption-test (added-strand cust 1) (sign (order c m b cost (enc n-0 cost account bank-conf ncb (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (0 0)) (traces ((recv (enc n cost item merc-conf ncm bank-conf-commit (sign (order c m b cost (enc n-0 cost account bank-conf ncb (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((send (enc n-0 cost item-0 merc-conf-0 ncm-0 (hash n-0 (hash ncb bank-conf)) (sign (order c m b cost (enc n-0 cost account bank-conf ncb (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))))) (label 209) (parent 208) (unrealized (0 0)) (comment "2 in cohort - 2 not yet seen")) (defskeleton minipay-rely-guar (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (merc-conf bank-conf text) (c m b name)) (defstrand merc 1 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (precedes ((1 0) (0 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c)) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-cust-1) (operation encryption-test (contracted (item-0 item) (merc-conf-0 merc-conf) (n-0 n) (ncm-0 ncm) (bank-conf-commit (hash n (hash ncb bank-conf)))) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (0 0) (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (traces ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))))) (label 210) (parent 209) (realized) (shape) (maps ((0) ((c c) (m m) (b b) (cost cost) (item item) (merc-conf merc-conf) (n n) (ncm ncm) (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf)))))) (origs)) (defskeleton minipay-rely-guar (vars (bank-conf-commit mesg) (account acct) (cost amount) (n ncm n-0 ncb ncm-0 data) (item item-0 merchandise) (merc-conf merc-conf-0 bank-conf mtr text) (c m b name)) (defstrand merc 1 (for-bank (enc n-0 cost account bank-conf ncb (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (bank-conf-commit bank-conf-commit) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n-0) (ncb ncb) (ncm ncm-0) (item item-0) (merc-conf merc-conf-0) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n-0 cost account bank-conf ncb (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (bank-conf-commit (hash n-0 (hash ncb bank-conf))) (cost cost) (n n-0) (ncm ncm-0) (item item-0) (merc-conf merc-conf-0) (mtr mtr) (c c) (m m) (b b)) (precedes ((1 0) (0 0)) ((2 1) (0 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c)) (uniq-orig mtr) (facts (neq n-0 ncb) (neq n-0 ncm-0) (neq ncm-0 ncb) (buy-via c m b item-0 cost n-0)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-cust-1) (operation encryption-test (added-strand merc 2) (sign (order c m b cost (enc n-0 cost account bank-conf ncb (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (0 0) (enc n-0 cost item-0 merc-conf-0 ncm-0 (hash n-0 (hash ncb bank-conf)) (sign (order c m b cost (enc n-0 cost account bank-conf ncb (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (traces ((recv (enc n cost item merc-conf ncm bank-conf-commit (sign (order c m b cost (enc n-0 cost account bank-conf ncb (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((send (enc n-0 cost item-0 merc-conf-0 ncm-0 (hash n-0 (hash ncb bank-conf)) (sign (order c m b cost (enc n-0 cost account bank-conf ncb (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n-0 cost item-0 merc-conf-0 ncm-0 (hash n-0 (hash ncb bank-conf)) (sign (order c m b cost (enc n-0 cost account bank-conf ncb (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n-0) (hash ncm-0 item-0 merc-conf-0) mtr (cat (sign (order c m b cost (enc n-0 cost account bank-conf ncb (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b))) (privk "sig" c)) (enc n-0 cost account bank-conf ncb (hash n-0 (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b)))) (pubk "enc" b))))) (label 211) (parent 209) (unrealized (0 0) (2 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay-rely-guar (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (merc-conf bank-conf mtr text) (c m b name)) (defstrand merc 1 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr) (c c) (m m) (b b)) (precedes ((1 0) (0 0)) ((2 1) (0 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c)) (uniq-orig mtr) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-cust-1) (operation encryption-test (contracted (item-0 item) (merc-conf-0 merc-conf) (n-0 n) (ncm-0 ncm) (bank-conf-commit (hash n (hash ncb bank-conf)))) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (0 0) (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)) (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))) (traces ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))))) (label 212) (parent 211) (unrealized (2 0)) (comment "2 in cohort - 2 not yet seen")) (defskeleton minipay-rely-guar (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (merc-conf bank-conf mtr text) (c m b name)) (defstrand merc 1 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr) (c c) (m m) (b b)) (precedes ((1 0) (2 0)) ((2 1) (0 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c)) (uniq-orig mtr) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-cust-1) (operation encryption-test (displaced 3 1 cust 1) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (2 0)) (traces ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b))))) (label 213) (parent 212) (seen 210) (realized) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay-rely-guar (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (merc-conf bank-conf mtr text) (c m b name)) (defstrand merc 1 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (defstrand merc 2 (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (bank-conf-commit (hash n (hash ncb bank-conf))) (cost cost) (n n) (ncm ncm) (item item) (merc-conf merc-conf) (mtr mtr) (c c) (m m) (b b)) (defstrand cust 1 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (c c) (m m) (b b)) (precedes ((1 0) (0 0)) ((2 1) (0 0)) ((3 0) (2 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" c)) (uniq-orig mtr) (facts (neq n ncb) (neq n ncm) (neq ncm ncb) (buy-via c m b item cost n)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2 guar-cust-1) (operation encryption-test (added-strand cust 1) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (2 0)) (traces ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m)))) ((recv (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))) (send (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (pubk "enc" b)))) ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (pubk "enc" m))))) (label 214) (parent 212) (seen 213) (realized) (comment "1 in cohort - 0 not yet seen")) (comment "Nothing left to do")