(herald minipay (try-old-strands) (bound 16) (limit 5000)) (comment "CPSA 4.4.0") (comment "All input read from minipay.scm") (comment "Step count limited to 5000") (comment "Strand count bounded at 16") (comment "Old strands tried first") (defprotocol minipay 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 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 (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 (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)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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 (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" m) (privk "sig" b)) (uniq-orig n btr) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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 (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" m) (privk "sig" b)) (uniq-orig n btr mtr) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule cheq-merc-4 fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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 (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" m) (privk "sig" b)) (uniq-orig n btr mtr) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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 (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" m) (privk "sig" b)) (uniq-orig n btr mtr) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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 (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" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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 "4 in cohort - 4 not yet seen")) (defskeleton minipay (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" m) (privk "sig" b)) (uniq-orig n btr mtr) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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 "2 in cohort - 2 not yet seen")) (defskeleton minipay (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" m) (privk "sig" b)) (uniq-orig n btr mtr) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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 (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" m) (privk "sig" b)) (uniq-orig n btr mtr) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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 (3 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (vars (for-bank mesg) (account account-0 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-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 (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" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation encryption-test (displaced 4 3 merc 2) (hash n (hash ncm-0 item-0 merc-conf-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-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 merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc 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 10) (parent 6) (seen 12) (unrealized (1 0) (2 0)) (comment "3 in cohort - 2 not yet seen")) (defskeleton minipay (vars (for-bank 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 (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" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation encryption-test (displaced 4 2 merc 2) (hash n (hash ncm item merc-conf)) (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-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 bank-conf ncb (hash n (hash 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 11) (parent 6) (unrealized (1 0) (3 0)) (comment "4 in cohort - 4 not yet seen")) (defskeleton minipay (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 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-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)) (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" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation encryption-test (added-strand merc 2) (hash n (hash ncm item merc-conf)) (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-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)))) ((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 12) (parent 6) (seen 21) (unrealized (1 0) (2 0) (3 0)) (comment "2 in cohort - 1 not yet seen")) (defskeleton minipay (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)) (deflistener (cat n (hash ncm item merc-conf))) (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" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation encryption-test (added-listener (cat n (hash ncm item merc-conf))) (hash n (hash ncm item merc-conf)) (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-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)))) ((recv (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf))))) (label 13) (parent 6) (unrealized (1 0) (2 0) (3 0) (4 0)) (comment "2 in cohort - 2 not yet seen")) (defskeleton minipay (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 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" m) (privk "sig" b)) (uniq-orig n btr mtr) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (contracted (for-bank (enc n cost account-0 bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) mtr (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)))) ((recv (cat cost n)) (send (cat cost n)))) (label 14) (parent 7) (unrealized (2 0) (3 0)) (comment "2 in cohort - 2 not yet seen")) (defskeleton minipay (vars (account account-0 account-1 acct) (cost amount) (n ncb ncm ncb-0 data) (item merchandise) (bank-conf btr mtr merc-conf bank-conf-0 btr-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) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 5 (for-bank (enc n cost account-1 bank-conf-0 ncb-0 (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 bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account-1) (cost cost) (n n) (ncb ncb-0) (bank-conf bank-conf-0) (btr btr-0) (mtr mtr) (c c) (m m) (b b)) (precedes ((0 0) (2 0)) ((0 0) (3 0)) ((1 1) (2 2)) ((2 1) (4 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" m) (privk "sig" b)) (uniq-orig n btr mtr btr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand bank 2) mtr (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-1 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-1 bank-conf-0 ncb-0 (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-1 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-1 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-1 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))) (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 (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account-1 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-1 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-0 mtr) (privk "sig" b)) (pubk "enc" m))))) (label 15) (parent 7) (unrealized (1 0) (2 0) (3 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (vars (account account-0 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-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))) (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" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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-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)))) ((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 16) (parent 9) (unrealized (3 0)) (dead) (comment "empty cohort")) (defskeleton minipay (vars (account account-0 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-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)) (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" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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)) (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-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 (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc 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 10) (unrealized (2 0)) (comment "2 in cohort - 2 not yet seen")) (defskeleton minipay (vars (for-bank mesg) (account account-0 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-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 (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)) (deflistener (cat cost n)) (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" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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)) (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-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 merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc 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 (cat cost n)) (send (cat cost n)))) (label 18) (parent 10) (unrealized (1 0) (2 0) (4 0)) (comment "2 in cohort - 2 not yet seen")) (defskeleton minipay (vars (account account-0 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-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 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" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation encryption-test (displaced 4 3 merc 2) (hash n (hash ncm-0 item-0 merc-conf-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)) (enc (payreq c-0 m-0 b-0 (hash cost n) (hash ncm-0 item-0 merc-conf-0) mtr (cat (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)) (enc n cost account bank-conf ncb (hash n (hash ncm-0 item-0 merc-conf-0)) (pubk "enc" b-0)))) (pubk "enc" b-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-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 bank-conf ncb (hash n (hash 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 11) (seen 21 29) (unrealized (1 0)) (comment "3 in cohort - 1 not yet seen")) (defskeleton minipay (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" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation encryption-test (contracted (account-0 account)) (hash n (hash ncm item merc-conf)) (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 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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))))) (label 20) (parent 11) (seen 29) (unrealized (3 0)) (comment "3 in cohort - 2 not yet seen")) (defskeleton minipay (vars (for-bank 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 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-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 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" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation encryption-test (added-strand merc 2) (hash n (hash ncm item merc-conf)) (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 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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-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 bank-conf ncb (hash n (hash 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 11) (unrealized (1 0) (3 0)) (comment "2 in cohort - 2 not yet seen")) (defskeleton minipay (vars (for-bank 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 (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)) (deflistener (cat n (hash ncm item merc-conf))) (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" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation encryption-test (added-listener (cat n (hash ncm item merc-conf))) (hash n (hash ncm item merc-conf)) (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 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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-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 bank-conf ncb (hash n (hash 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf))))) (label 22) (parent 11) (unrealized (1 0) (3 0) (4 0)) (comment "2 in cohort - 2 not yet seen")) (defskeleton minipay (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 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-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)) (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)) (deflistener (cat n (hash ncm item merc-conf))) (precedes ((0 0) (2 0)) ((0 0) (3 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) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (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)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation encryption-test (added-listener (cat n (hash ncm item merc-conf))) (hash n (hash ncm item merc-conf)) (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-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)))) ((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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf))))) (label 23) (parent 12) (unrealized (1 0) (2 0) (3 0) (5 0)) (comment "2 in cohort - 2 not yet seen")) (defskeleton minipay (vars (for-bank 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 (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 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)) (deflistener (cat n (hash ncm item merc-conf))) (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" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (contracted (for-bank-0 (enc n cost account-0 bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) mtr (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)))) ((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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf))))) (label 24) (parent 13) (seen 38) (unrealized (2 0) (3 0) (4 0)) (comment "2 in cohort - 1 not yet seen")) (defskeleton minipay (vars (for-bank bank-conf-commit mesg) (account account-0 account-1 acct) (cost amount) (n ncb ncm ncm-0 ncb-0 data) (item item-0 merchandise) (bank-conf btr mtr merc-conf merc-conf-0 mtr-0 bank-conf-0 btr-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 (enc n cost account-1 bank-conf-0 ncb-0 (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)) (deflistener (cat n (hash ncm item merc-conf))) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account-1) (cost cost) (n n) (ncb ncb-0) (bank-conf bank-conf-0) (btr btr-0) (mtr mtr) (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) (5 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 btr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand bank 2) mtr (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-1 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-1 bank-conf-0 ncb-0 (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-1 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-1 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-1 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))) (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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-1 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-1 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-0 mtr) (privk "sig" b)) (pubk "enc" m))))) (label 25) (parent 13) (unrealized (1 0) (2 0) (3 0) (4 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (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" m) (privk "sig" b)) (uniq-orig n btr mtr) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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)))) ((recv (cat cost n)) (send (cat cost n)))) (label 26) (parent 14) (unrealized (3 0)) (comment "2 in cohort - 2 not yet seen")) (defskeleton minipay (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 cost n)) (deflistener (cat n (hash ncb bank-conf))) (precedes ((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) (2 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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 cost n)) (send (cat cost n))) ((recv (cat n (hash ncb bank-conf))) (send (cat n (hash ncb bank-conf))))) (label 27) (parent 14) (unrealized (3 0) (4 0)) (comment "2 in cohort - 2 not yet seen")) (defskeleton minipay (vars (account account-0 acct) (cost amount) (n ncm ncb data) (item merchandise) (btr mtr merc-conf bank-conf btr-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) (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 cost n)) (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-0) (mtr mtr) (c c) (m m) (b b)) (precedes ((0 0) (2 0)) ((0 0) (3 0)) ((1 1) (2 2)) ((2 1) (4 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" m) (privk "sig" b)) (uniq-orig n btr mtr btr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (contracted (bank-conf-0 bank-conf) (ncb-0 ncb) (account-1 account-0)) mtr (1 0) (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr) (privk "sig" b)) (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-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)))) ((recv (cat cost n)) (send (cat cost n))) ((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-0 mtr) (privk "sig" b)) (pubk "enc" m))))) (label 28) (parent 15) (unrealized (2 0) (3 0)) (comment "2 in cohort - 2 not yet seen")) (defskeleton minipay (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" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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)))) ((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 29) (parent 17) (seen 8) (realized) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay (vars (account account-0 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-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)) (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)) (deflistener (cat n (hash ncb bank-conf))) (precedes ((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) (2 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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 (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc 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 (cat n (hash ncb bank-conf))) (send (cat n (hash ncb bank-conf))))) (label 30) (parent 17) (seen 16) (unrealized (4 0)) (comment "2 in cohort - 1 not yet seen")) (defskeleton minipay (vars (account account-0 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-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)) (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)) (deflistener (cat cost n)) (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" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (contracted (for-bank (enc n cost account-0 bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) mtr (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)))) ((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 (cat cost n)) (send (cat cost n)))) (label 31) (parent 18) (unrealized (2 0) (4 0)) (comment "2 in cohort - 2 not yet seen")) (defskeleton minipay (vars (account account-0 account-1 acct) (cost amount) (n ncb ncm ncb-0 data) (item merchandise) (bank-conf btr mtr merc-conf mtr-0 bank-conf-0 btr-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) (bank-conf bank-conf) (btr btr) (mtr mtr) (c c) (m m) (b b)) (defstrand merc 5 (for-bank (enc n cost account-1 bank-conf-0 ncb-0 (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)) (deflistener (cat cost n)) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account-1) (cost cost) (n n) (ncb ncb-0) (bank-conf bank-conf-0) (btr btr-0) (mtr mtr) (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) (5 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 btr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand bank 2) mtr (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-1 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-1 bank-conf-0 ncb-0 (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-1 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-1 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-1 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))) (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 (cat cost n)) (send (cat cost n))) ((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-1 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-1 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-0 mtr) (privk "sig" b)) (pubk "enc" m))))) (label 32) (parent 18) (unrealized (1 0) (2 0) (4 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (vars (account account-0 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-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 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)) (deflistener (cat cost n)) (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" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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 (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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-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-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 bank-conf ncb (hash n (hash 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 (cat cost n)) (send (cat cost n)))) (label 33) (parent 19) (seen 51) (unrealized (1 0) (4 0)) (comment "2 in cohort - 1 not yet seen")) (defskeleton minipay (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" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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 34) (parent 20) (unrealized (3 0)) (comment "2 in cohort - 2 not yet seen")) (defskeleton minipay (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" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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 35) (parent 20) (seen 56) (unrealized (3 0)) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay (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" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation encryption-test (contracted (account-0 account)) (hash n (hash ncm item merc-conf)) (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 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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-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 36) (parent 21) (seen 35) (unrealized (3 0)) (comment "3 in cohort - 2 not yet seen")) (defskeleton minipay (vars (for-bank 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 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-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 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)) (deflistener (cat n (hash ncm item merc-conf))) (precedes ((0 0) (2 0)) ((0 0) (3 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) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (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)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation encryption-test (added-listener (cat n (hash ncm item merc-conf))) (hash n (hash ncm item merc-conf)) (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 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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-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 bank-conf ncb (hash n (hash 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf))))) (label 37) (parent 21) (unrealized (1 0) (3 0) (5 0)) (comment "2 in cohort - 2 not yet seen")) (defskeleton minipay (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)) (deflistener (cat n (hash ncm item merc-conf))) (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" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (contracted (account-0 account)) mtr (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 bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf))))) (label 38) (parent 22) (unrealized (3 0) (4 0)) (comment "3 in cohort - 3 not yet seen")) (defskeleton minipay (vars (for-bank 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 btr-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 (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)) (deflistener (cat n (hash ncm item merc-conf))) (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) (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) (5 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 btr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand bank 2) mtr (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 bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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-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 bank-conf ncb (hash n (hash 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 mtr) (privk "sig" b)) (pubk "enc" m))))) (label 39) (parent 22) (unrealized (1 0) (3 0) (4 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (vars (for-bank 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 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-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)) (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)) (deflistener (cat n (hash ncm item merc-conf))) (precedes ((0 0) (2 0)) ((0 0) (3 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) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (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)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (contracted (for-bank-0 (enc n cost account-0 bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) mtr (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)))) ((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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf))))) (label 40) (parent 23) (seen 59) (unrealized (2 0) (3 0) (5 0)) (comment "2 in cohort - 1 not yet seen")) (defskeleton minipay (vars (for-bank bank-conf-commit mesg) (account account-0 account-1 acct) (cost amount) (n ncb ncm ncm-0 ncb-0 data) (item item-0 merchandise) (bank-conf btr mtr merc-conf merc-conf-0 mtr-0 mtr-1 bank-conf-0 btr-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 (enc n cost account-1 bank-conf-0 ncb-0 (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)) (deflistener (cat n (hash ncm item merc-conf))) (defstrand bank 2 (merc-conf-decommit (hash ncm item merc-conf)) (account account-1) (cost cost) (n n) (ncb ncb-0) (bank-conf bank-conf-0) (btr btr-0) (mtr mtr) (c c) (m m) (b b)) (precedes ((0 0) (2 0)) ((0 0) (3 0)) ((0 0) (4 0)) ((0 0) (5 0)) ((1 1) (2 2)) ((2 1) (6 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 mtr-1 btr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand bank 2) mtr (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-1 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-1 bank-conf-0 ncb-0 (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-1 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-1 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-1 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))) (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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-1 bank-conf-0 ncb-0 (hash n (hash ncm item merc-conf)) (pubk "enc" b))) (privk "sig" c)) (enc n cost account-1 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-0 mtr) (privk "sig" b)) (pubk "enc" m))))) (label 41) (parent 23) (unrealized (1 0) (2 0) (3 0) (5 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (vars (for-bank 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 (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 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)) (deflistener (cat n (hash ncm item merc-conf))) (deflistener (cat n (hash ncb bank-conf))) (precedes ((0 0) (3 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) (2 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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 (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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((recv (cat n (hash ncb bank-conf))) (send (cat n (hash ncb bank-conf))))) (label 42) (parent 24) (unrealized (3 0) (4 0) (5 0)) (comment "3 in cohort - 3 not yet seen")) (defskeleton minipay (vars (for-bank bank-conf-commit mesg) (account account-0 acct) (cost amount) (n ncm ncm-0 ncb data) (item item-0 merchandise) (btr mtr merc-conf merc-conf-0 mtr-0 bank-conf btr-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 (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 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)) (deflistener (cat n (hash ncm item merc-conf))) (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-0) (mtr mtr) (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) (5 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 btr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (contracted (bank-conf-0 bank-conf) (ncb-0 ncb) (account-1 account-0)) mtr (1 0) (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr) (privk "sig" b)) (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-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)))) ((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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 mtr) (privk "sig" b)) (pubk "enc" m))))) (label 43) (parent 25) (seen 64) (unrealized (2 0) (3 0) (4 0)) (comment "2 in cohort - 1 not yet seen")) (defskeleton minipay (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" m) (privk "sig" b)) (uniq-orig n btr mtr) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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 44) (parent 26) (unrealized (3 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (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" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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 45) (parent 26) (seen 71) (unrealized (3 0)) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay (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)) (deflistener (cat n (hash ncb bank-conf))) (precedes ((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) (2 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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-0 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 (cat n (hash ncb bank-conf))) (send (cat n (hash ncb bank-conf))))) (label 46) (parent 27) (unrealized (4 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (vars (account account-0 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-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 cost n)) (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)) ((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) (2 0)) ((5 1) (3 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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-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 cost n)) (send (cat cost n))) ((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 47) (parent 27) (unrealized (3 0) (4 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncm ncb data) (item merchandise) (btr mtr merc-conf bank-conf btr-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 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) (c c) (m m) (b b)) (precedes ((0 0) (2 0)) ((0 0) (3 0)) ((1 1) (2 2)) ((2 1) (4 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" m) (privk "sig" b)) (uniq-orig n btr mtr btr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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)))) ((recv (cat cost n)) (send (cat cost n))) ((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-0 mtr) (privk "sig" b)) (pubk "enc" m))))) (label 48) (parent 28) (unrealized (3 0)) (comment "2 in cohort - 2 not yet seen")) (defskeleton minipay (vars (account account-0 acct) (cost amount) (n ncm ncb data) (item merchandise) (btr mtr merc-conf bank-conf btr-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) (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 cost n)) (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-0) (mtr mtr) (c c) (m m) (b b)) (deflistener (cat n (hash ncb bank-conf))) (precedes ((0 0) (3 0)) ((0 0) (5 0)) ((1 1) (2 2)) ((2 1) (4 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (2 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr btr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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 cost n)) (send (cat cost n))) ((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-0 mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (cat n (hash ncb bank-conf))) (send (cat n (hash ncb bank-conf))))) (label 49) (parent 28) (unrealized (3 0) (5 0)) (comment "2 in cohort - 2 not yet seen")) (defskeleton minipay (vars (account account-0 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-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)) (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)) (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-1) (c c) (m m) (b b)) (precedes ((0 0) (3 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) (2 0)) ((5 1) (4 0))) (non-orig (privk "enc" m) (privk "enc" b) (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)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand merc 2) n (4 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 (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc 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 (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-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 50) (parent 30) (unrealized (4 0)) (dead) (comment "empty cohort")) (defskeleton minipay (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)) (deflistener (cat cost n)) (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" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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)))) ((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 (cat cost n)) (send (cat cost n)))) (label 51) (parent 31) (seen 45) (unrealized (4 0)) (comment "3 in cohort - 2 not yet seen")) (defskeleton minipay (vars (account account-0 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-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)) (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)) (deflistener (cat cost n)) (deflistener (cat n (hash ncb bank-conf))) (precedes ((0 0) (3 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) (2 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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 (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc 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 (cat cost n)) (send (cat cost n))) ((recv (cat n (hash ncb bank-conf))) (send (cat n (hash ncb bank-conf))))) (label 52) (parent 31) (seen 47) (unrealized (4 0) (5 0)) (comment "3 in cohort - 2 not yet seen")) (defskeleton minipay (vars (account account-0 acct) (cost amount) (n ncm ncb data) (item merchandise) (btr mtr merc-conf mtr-0 bank-conf btr-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) (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)) (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)) (deflistener (cat cost n)) (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-0) (mtr mtr) (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) (5 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 btr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (contracted (bank-conf-0 bank-conf) (ncb-0 ncb) (account-1 account-0)) mtr (1 0) (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr) (privk "sig" b)) (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-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)))) ((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 (cat cost n)) (send (cat cost n))) ((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-0 mtr) (privk "sig" b)) (pubk "enc" m))))) (label 53) (parent 32) (unrealized (2 0) (4 0)) (comment "2 in cohort - 2 not yet seen")) (defskeleton minipay (vars (account account-0 acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr merc-conf mtr-0 btr-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) (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)) (deflistener (cat cost n)) (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) (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) (5 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 btr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand bank 2) mtr (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 bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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-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 bank-conf ncb (hash n (hash 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 (cat cost n)) (send (cat cost n))) ((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-0 mtr) (privk "sig" b)) (pubk "enc" m))))) (label 54) (parent 33) (seen 82) (unrealized (1 0) (4 0)) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay (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" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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 55) (parent 34) (seen 8) (realized) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay (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" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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 56) (parent 34) (unrealized (3 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (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" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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 57) (parent 36) (seen 56) (unrealized (3 0)) (comment "3 in cohort - 2 not yet seen")) (defskeleton minipay (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" 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)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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 58) (parent 36) (seen 86) (unrealized (3 0)) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay (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)) (deflistener (cat n (hash ncm item merc-conf))) (precedes ((0 0) (2 0)) ((0 0) (3 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) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (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)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (contracted (account-0 account)) mtr (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 bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf))))) (label 59) (parent 37) (seen 63) (unrealized (3 0) (5 0)) (comment "3 in cohort - 2 not yet seen")) (defskeleton minipay (vars (for-bank 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 mtr-1 btr-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 (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)) (deflistener (cat n (hash ncm item merc-conf))) (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) (c c) (m m) (b b)) (precedes ((0 0) (2 0)) ((0 0) (3 0)) ((0 0) (4 0)) ((0 0) (5 0)) ((1 1) (2 2)) ((2 1) (6 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 mtr-1 btr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand bank 2) mtr (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 bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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-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 bank-conf ncb (hash n (hash 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 mtr) (privk "sig" b)) (pubk "enc" m))))) (label 60) (parent 37) (unrealized (1 0) (3 0) (5 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (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)) (deflistener (cat n (hash ncm item merc-conf))) (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" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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)))) ((recv (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf))))) (label 61) (parent 38) (unrealized (4 0)) (comment "3 in cohort - 3 not yet seen")) (defskeleton minipay (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)) (deflistener (cat n (hash ncm item merc-conf))) (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" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf))))) (label 62) (parent 38) (unrealized (3 0) (4 0)) (comment "2 in cohort - 2 not yet seen")) (defskeleton minipay (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)) (deflistener (cat n (hash ncm item merc-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-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" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-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-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 63) (parent 38) (seen 94) (unrealized (3 0) (4 0)) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay (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 btr-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)) (deflistener (cat n (hash ncm item merc-conf))) (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) (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) (5 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 btr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (contracted (account-0 account)) mtr (1 0) (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr) (privk "sig" b)) (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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 mtr) (privk "sig" b)) (pubk "enc" m))))) (label 64) (parent 39) (unrealized (3 0) (4 0)) (comment "3 in cohort - 3 not yet seen")) (defskeleton minipay (vars (for-bank 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 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-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)) (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)) (deflistener (cat n (hash ncm item merc-conf))) (deflistener (cat n (hash ncb bank-conf))) (precedes ((0 0) (3 0)) ((0 0) (4 0)) ((0 0) (5 0)) ((0 0) (6 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) (1 0)) ((6 1) (2 0))) (non-orig (privk "enc" m) (privk "enc" b) (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)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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 (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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((recv (cat n (hash ncb bank-conf))) (send (cat n (hash ncb bank-conf))))) (label 65) (parent 40) (seen 69) (unrealized (3 0) (5 0) (6 0)) (comment "3 in cohort - 2 not yet seen")) (defskeleton minipay (vars (for-bank bank-conf-commit mesg) (account account-0 acct) (cost amount) (n ncm ncm-0 ncb data) (item item-0 merchandise) (btr mtr merc-conf merc-conf-0 mtr-0 mtr-1 bank-conf btr-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 (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 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)) (deflistener (cat n (hash ncm item merc-conf))) (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-0) (mtr mtr) (c c) (m m) (b b)) (precedes ((0 0) (2 0)) ((0 0) (3 0)) ((0 0) (4 0)) ((0 0) (5 0)) ((1 1) (2 2)) ((2 1) (6 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 mtr-1 btr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (contracted (bank-conf-0 bank-conf) (ncb-0 ncb) (account-1 account-0)) mtr (1 0) (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr) (privk "sig" b)) (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-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)))) ((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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 mtr) (privk "sig" b)) (pubk "enc" m))))) (label 66) (parent 41) (seen 89) (unrealized (2 0) (3 0) (5 0)) (comment "2 in cohort - 1 not yet seen")) (defskeleton minipay (vars (account account-0 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-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)) (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)) (deflistener (cat n (hash ncm item merc-conf))) (deflistener (cat n (hash ncb bank-conf))) (precedes ((0 0) (3 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) (2 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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-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 (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((recv (cat n (hash ncb bank-conf))) (send (cat n (hash ncb bank-conf))))) (label 67) (parent 42) (unrealized (4 0) (5 0)) (comment "3 in cohort - 3 not yet seen")) (defskeleton minipay (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)) (deflistener (cat n (hash ncm item merc-conf))) (deflistener (cat n (hash ncb bank-conf))) (precedes ((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) (2 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (displaced 6 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-0 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((recv (cat n (hash ncb bank-conf))) (send (cat n (hash ncb bank-conf))))) (label 68) (parent 42) (unrealized (4 0) (5 0)) (comment "2 in cohort - 2 not yet seen")) (defskeleton minipay (vars (for-bank 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 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-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)) (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)) (deflistener (cat n (hash ncm item merc-conf))) (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-1) (c c) (m m) (b b)) (precedes ((0 0) (4 0)) ((0 0) (5 0)) ((0 0) (6 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) (2 0)) ((6 1) (3 0))) (non-orig (privk "enc" m) (privk "enc" b) (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)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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-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 (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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-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 42) (unrealized (3 0) (4 0) (5 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (vars (for-bank bank-conf-commit mesg) (account account-0 acct) (cost amount) (n ncm ncm-0 ncb data) (item item-0 merchandise) (btr mtr merc-conf merc-conf-0 mtr-0 bank-conf btr-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 (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 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)) (deflistener (cat n (hash ncm item merc-conf))) (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-0) (mtr mtr) (c c) (m m) (b b)) (deflistener (cat n (hash ncb bank-conf))) (precedes ((0 0) (3 0)) ((0 0) (4 0)) ((0 0) (6 0)) ((1 1) (2 2)) ((2 1) (5 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (2 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 btr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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 (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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (cat n (hash ncb bank-conf))) (send (cat n (hash ncb bank-conf))))) (label 70) (parent 43) (unrealized (3 0) (4 0) (6 0)) (comment "3 in cohort - 3 not yet seen")) (defskeleton minipay (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" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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 71) (parent 44) (unrealized (3 0)) (dead) (comment "empty cohort")) (defskeleton minipay (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)) (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) (5 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (2 0)) ((5 1) (4 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand merc 2) n (4 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 (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 72) (parent 46) (unrealized (4 0)) (dead) (comment "empty cohort")) (defskeleton minipay (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)) (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)) ((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) (2 0)) ((5 1) (3 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (displaced 6 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-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 ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b 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 (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 73) (parent 47) (seen 72) (unrealized (4 0)) (comment "2 in cohort - 1 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncm ncb data) (item merchandise) (btr mtr merc-conf bank-conf btr-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 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) (c c) (m m) (b b)) (precedes ((0 0) (2 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (4 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" m) (privk "sig" b)) (uniq-orig n btr mtr btr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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 (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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) (privk "sig" b)) (pubk "enc" m))))) (label 74) (parent 48) (unrealized (3 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncm ncb data) (item merchandise) (btr mtr merc-conf bank-conf 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 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 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) (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) (5 0)) ((1 1) (2 2)) ((2 1) (4 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" m) (privk "sig" b)) (uniq-orig n btr mtr btr-0 mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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 (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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) (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))))) (label 75) (parent 48) (seen 111) (unrealized (3 0)) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncm ncb data) (item merchandise) (btr mtr merc-conf bank-conf btr-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 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) (c c) (m m) (b b)) (deflistener (cat n (hash ncb bank-conf))) (precedes ((0 0) (5 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (4 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (2 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr btr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (displaced 6 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-0 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 (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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) (privk "sig" b)) (pubk "enc" m)))) ((recv (cat n (hash ncb bank-conf))) (send (cat n (hash ncb bank-conf))))) (label 76) (parent 49) (unrealized (5 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (vars (account account-0 acct) (cost amount) (n ncm ncb data) (item merchandise) (btr mtr merc-conf bank-conf 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 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 cost n)) (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-0) (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) (5 0)) ((0 0) (6 0)) ((1 1) (2 2)) ((2 1) (4 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (2 0)) ((6 1) (3 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr btr-0 mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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-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 cost n)) (send (cat cost n))) ((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-0 mtr) (privk "sig" b)) (pubk "enc" 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 77) (parent 49) (unrealized (3 0) (5 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (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)) (deflistener (cat cost n)) (precedes ((0 0) (2 0)) ((0 0) (3 0)) ((1 1) (2 2)) ((2 1) (4 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" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (displaced 5 2 merc 2) n (4 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)))) ((recv (cat cost n)) (send (cat cost n)))) (label 78) (parent 51) (seen 71) (unrealized (4 0)) (comment "2 in cohort - 1 not yet seen")) (defskeleton minipay (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)) (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-1) (c c) (m m) (b b)) (precedes ((0 0) (2 0)) ((0 0) (3 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) (4 0))) (non-orig (privk "enc" m) (privk "enc" b) (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)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand merc 2) n (4 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)))) ((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-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 51) (seen 114) (unrealized (4 0)) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay (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)) (deflistener (cat cost n)) (deflistener (cat n (hash ncb bank-conf))) (precedes ((0 0) (3 0)) ((0 0) (5 0)) ((1 1) (2 2)) ((2 1) (4 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (2 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (displaced 6 2 merc 2) n (4 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 ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b 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 (cat cost n)) (send (cat cost n))) ((recv (cat n (hash ncb bank-conf))) (send (cat n (hash ncb bank-conf))))) (label 80) (parent 52) (seen 72) (unrealized (5 0)) (comment "2 in cohort - 1 not yet seen")) (defskeleton minipay (vars (account account-0 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-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)) (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)) (deflistener (cat cost n)) (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-1) (c c) (m m) (b b)) (precedes ((0 0) (3 0)) ((0 0) (5 0)) ((0 0) (6 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) (2 0)) ((6 1) (4 0))) (non-orig (privk "enc" m) (privk "enc" b) (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)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand merc 2) n (4 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 (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc 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 (cat cost n)) (send (cat cost n))) ((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-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 81) (parent 52) (unrealized (4 0) (5 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncm ncb data) (item merchandise) (btr mtr merc-conf mtr-0 bank-conf btr-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)) (deflistener (cat cost n)) (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) (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) (5 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 btr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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)))) ((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 (cat cost n)) (send (cat cost n))) ((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-0 mtr) (privk "sig" b)) (pubk "enc" m))))) (label 82) (parent 53) (seen 75) (unrealized (4 0)) (comment "3 in cohort - 2 not yet seen")) (defskeleton minipay (vars (account account-0 acct) (cost amount) (n ncm ncb data) (item merchandise) (btr mtr merc-conf mtr-0 bank-conf btr-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) (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)) (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)) (deflistener (cat cost n)) (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-0) (mtr mtr) (c c) (m m) (b b)) (deflistener (cat n (hash ncb bank-conf))) (precedes ((0 0) (3 0)) ((0 0) (4 0)) ((0 0) (6 0)) ((1 1) (2 2)) ((2 1) (5 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (2 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 btr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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 (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc 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 (cat cost n)) (send (cat cost n))) ((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-0 mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (cat n (hash ncb bank-conf))) (send (cat n (hash ncb bank-conf))))) (label 83) (parent 53) (seen 77) (unrealized (4 0) (6 0)) (comment "3 in cohort - 2 not yet seen")) (defskeleton minipay (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" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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 84) (parent 56) (seen 29) (realized) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay (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" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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 85) (parent 57) (seen 29) (realized) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay (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" 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)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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 86) (parent 57) (unrealized (3 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (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)) (deflistener (cat n (hash ncm item merc-conf))) (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) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (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)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (displaced 6 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)))) ((recv (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf))))) (label 87) (parent 59) (seen 94) (unrealized (3 0) (5 0)) (comment "3 in cohort - 2 not yet seen")) (defskeleton minipay (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)) (deflistener (cat n (hash ncm item merc-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-2) (c c) (m m) (b b)) (precedes ((0 0) (2 0)) ((0 0) (4 0)) ((0 0) (5 0)) ((0 0) (6 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) (1 0)) ((6 1) (3 0))) (non-orig (privk "enc" m) (privk "enc" b) (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)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-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-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 88) (parent 59) (seen 123) (unrealized (3 0) (5 0)) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay (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 btr-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)) (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)) (deflistener (cat n (hash ncm item merc-conf))) (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) (c c) (m m) (b b)) (precedes ((0 0) (2 0)) ((0 0) (3 0)) ((0 0) (4 0)) ((0 0) (5 0)) ((1 1) (2 2)) ((2 1) (6 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 mtr-1 btr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (contracted (account-0 account)) mtr (1 0) (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr) (privk "sig" b)) (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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 mtr) (privk "sig" b)) (pubk "enc" m))))) (label 89) (parent 60) (seen 97) (unrealized (3 0) (5 0)) (comment "3 in cohort - 2 not yet seen")) (defskeleton minipay (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)) (deflistener (cat n (hash ncm item merc-conf))) (precedes ((0 0) (2 0)) ((0 0) (3 0)) ((1 1) (2 2)) ((2 1) (4 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" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (displaced 5 2 merc 2) n (4 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)))) ((recv (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf))))) (label 90) (parent 61) (unrealized (4 0)) (comment "2 in cohort - 2 not yet seen")) (defskeleton minipay (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)) (deflistener (cat n (hash ncm item merc-conf))) (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) (4 0)) ((4 1) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (displaced 5 3 merc 2) n (4 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)))) ((recv (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf))))) (label 91) (parent 61) (seen 126) (unrealized (4 0)) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay (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)) (deflistener (cat n (hash ncm item merc-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-1) (c c) (m m) (b b)) (precedes ((0 0) (2 0)) ((0 0) (3 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) (4 0))) (non-orig (privk "enc" m) (privk "enc" b) (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)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand merc 2) n (4 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)))) ((recv (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-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-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 92) (parent 61) (seen 127) (unrealized (4 0)) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay (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)) (deflistener (cat n (hash ncm item merc-conf))) (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" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf))))) (label 93) (parent 62) (unrealized (4 0)) (comment "2 in cohort - 2 not yet seen")) (defskeleton minipay (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)) (deflistener (cat n (hash ncm item merc-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-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" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-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-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 94) (parent 62) (unrealized (3 0) (4 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr merc-conf mtr-0 btr-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)) (deflistener (cat n (hash ncm item merc-conf))) (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) (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) (5 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 btr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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)))) ((recv (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 mtr) (privk "sig" b)) (pubk "enc" m))))) (label 95) (parent 64) (unrealized (4 0)) (comment "3 in cohort - 3 not yet seen")) (defskeleton minipay (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 btr-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)) (deflistener (cat n (hash ncm item merc-conf))) (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) (c c) (m m) (b b)) (precedes ((0 0) (2 0)) ((0 0) (4 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (5 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 btr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (displaced 6 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 mtr) (privk "sig" b)) (pubk "enc" m))))) (label 96) (parent 64) (unrealized (3 0) (4 0)) (comment "2 in cohort - 2 not yet seen")) (defskeleton minipay (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 btr-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)) (deflistener (cat n (hash ncm item merc-conf))) (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) (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) (6 0)) ((1 1) (2 2)) ((2 1) (5 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (3 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 btr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 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-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 97) (parent 64) (seen 135) (unrealized (3 0) (4 0)) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay (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)) (deflistener (cat n (hash ncm item merc-conf))) (deflistener (cat n (hash ncb bank-conf))) (precedes ((0 0) (4 0)) ((0 0) (5 0)) ((0 0) (6 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) (1 0)) ((6 1) (2 0))) (non-orig (privk "enc" m) (privk "enc" b) (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)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (displaced 7 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-0 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((recv (cat n (hash ncb bank-conf))) (send (cat n (hash ncb bank-conf))))) (label 98) (parent 65) (seen 105) (unrealized (5 0) (6 0)) (comment "3 in cohort - 2 not yet seen")) (defskeleton minipay (vars (for-bank 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 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-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)) (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)) (deflistener (cat n (hash ncm item merc-conf))) (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-2) (c c) (m m) (b b)) (precedes ((0 0) (4 0)) ((0 0) (5 0)) ((0 0) (6 0)) ((0 0) (7 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) (1 0)) ((6 1) (2 0)) ((7 1) (3 0))) (non-orig (privk "enc" m) (privk "enc" b) (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)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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-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 (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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-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 99) (parent 65) (unrealized (3 0) (5 0) (6 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (vars (for-bank bank-conf-commit mesg) (account account-0 acct) (cost amount) (n ncm ncm-0 ncb data) (item item-0 merchandise) (btr mtr merc-conf merc-conf-0 mtr-0 mtr-1 bank-conf btr-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 (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 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)) (deflistener (cat n (hash ncm item merc-conf))) (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-0) (mtr mtr) (c c) (m m) (b b)) (deflistener (cat n (hash ncb bank-conf))) (precedes ((0 0) (3 0)) ((0 0) (4 0)) ((0 0) (5 0)) ((0 0) (7 0)) ((1 1) (2 2)) ((2 1) (6 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (1 0)) ((7 1) (2 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 mtr-1 btr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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 (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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (cat n (hash ncb bank-conf))) (send (cat n (hash ncb bank-conf))))) (label 100) (parent 66) (seen 109) (unrealized (3 0) (5 0) (7 0)) (comment "3 in cohort - 2 not yet seen")) (defskeleton minipay (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)) (deflistener (cat n (hash ncm item merc-conf))) (deflistener (cat n (hash ncb bank-conf))) (precedes ((0 0) (3 0)) ((0 0) (5 0)) ((1 1) (2 2)) ((2 1) (4 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (2 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (displaced 6 2 merc 2) n (4 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 ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((recv (cat n (hash ncb bank-conf))) (send (cat n (hash ncb bank-conf))))) (label 101) (parent 67) (unrealized (5 0)) (comment "2 in cohort - 2 not yet seen")) (defskeleton minipay (vars (account account-0 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-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)) (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)) (deflistener (cat n (hash ncm item merc-conf))) (deflistener (cat n (hash ncb bank-conf))) (precedes ((0 0) (3 0)) ((0 0) (5 0)) ((1 1) (2 2)) ((2 1) (1 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (4 0)) ((4 1) (1 0)) ((5 1) (2 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (displaced 6 3 merc 2) n (4 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 (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((recv (cat n (hash ncb bank-conf))) (send (cat n (hash ncb bank-conf))))) (label 102) (parent 67) (unrealized (4 0) (5 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (vars (account account-0 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-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)) (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)) (deflistener (cat n (hash ncm item merc-conf))) (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-1) (c c) (m m) (b b)) (precedes ((0 0) (3 0)) ((0 0) (5 0)) ((0 0) (6 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) (2 0)) ((6 1) (4 0))) (non-orig (privk "enc" m) (privk "enc" b) (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)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand merc 2) n (4 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 (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-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 103) (parent 67) (unrealized (4 0) (5 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (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)) (deflistener (cat n (hash ncm item merc-conf))) (deflistener (cat n (hash ncb bank-conf))) (precedes ((0 0) (5 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (4 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (2 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (displaced 6 2 merc 2) n (4 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((recv (cat n (hash ncb bank-conf))) (send (cat n (hash ncb bank-conf))))) (label 104) (parent 68) (unrealized (5 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (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)) (deflistener (cat n (hash ncm item merc-conf))) (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-1) (c c) (m m) (b b)) (precedes ((0 0) (5 0)) ((0 0) (6 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) (2 0)) ((6 1) (4 0))) (non-orig (privk "enc" m) (privk "enc" b) (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)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand merc 2) n (4 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-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 105) (parent 68) (unrealized (4 0) (5 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (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)) (deflistener (cat n (hash ncm item merc-conf))) (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-1) (c c) (m m) (b b)) (precedes ((0 0) (4 0)) ((0 0) (5 0)) ((0 0) (6 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) (2 0)) ((6 1) (3 0))) (non-orig (privk "enc" m) (privk "enc" b) (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)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (displaced 7 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-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 ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-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 106) (parent 69) (unrealized (4 0) (5 0)) (comment "3 in cohort - 3 not yet seen")) (defskeleton minipay (vars (account account-0 acct) (cost amount) (n ncm ncb data) (item merchandise) (btr mtr merc-conf mtr-0 bank-conf btr-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) (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)) (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)) (deflistener (cat n (hash ncm item merc-conf))) (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-0) (mtr mtr) (c c) (m m) (b b)) (deflistener (cat n (hash ncb bank-conf))) (precedes ((0 0) (3 0)) ((0 0) (4 0)) ((0 0) (6 0)) ((1 1) (2 2)) ((2 1) (5 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (2 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 btr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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-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 (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (cat n (hash ncb bank-conf))) (send (cat n (hash ncb bank-conf))))) (label 107) (parent 70) (unrealized (4 0) (6 0)) (comment "3 in cohort - 3 not yet seen")) (defskeleton minipay (vars (for-bank bank-conf-commit mesg) (account acct) (cost amount) (n ncm ncm-0 ncb data) (item item-0 merchandise) (btr mtr merc-conf merc-conf-0 mtr-0 bank-conf btr-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)) (deflistener (cat n (hash ncm item merc-conf))) (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) (c c) (m m) (b b)) (deflistener (cat n (hash ncb bank-conf))) (precedes ((0 0) (4 0)) ((0 0) (6 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (5 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (2 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 btr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (displaced 7 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-0 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (cat n (hash ncb bank-conf))) (send (cat n (hash ncb bank-conf))))) (label 108) (parent 70) (unrealized (4 0) (6 0)) (comment "2 in cohort - 2 not yet seen")) (defskeleton minipay (vars (for-bank bank-conf-commit mesg) (account account-0 acct) (cost amount) (n ncm ncm-0 ncb data) (item item-0 merchandise) (btr mtr merc-conf merc-conf-0 mtr-0 bank-conf btr-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-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)) (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)) (deflistener (cat n (hash ncm item merc-conf))) (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-0) (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-1) (c c) (m m) (b b)) (precedes ((0 0) (4 0)) ((0 0) (6 0)) ((0 0) (7 0)) ((1 1) (2 2)) ((2 1) (5 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (2 0)) ((7 1) (3 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 btr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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-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 (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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 mtr) (privk "sig" b)) (pubk "enc" 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-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 109) (parent 70) (unrealized (3 0) (4 0) (6 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (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)) (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)) (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) (5 0)) ((0 0) (6 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (2 0)) ((5 1) (3 0)) ((6 1) (4 0))) (non-orig (privk "enc" m) (privk "enc" b) (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)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand merc 2) n (4 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 (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)))) ((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 110) (parent 73) (unrealized (4 0)) (dead) (comment "empty cohort")) (defskeleton minipay (vars (account acct) (cost amount) (n ncm ncb data) (item merchandise) (btr mtr merc-conf bank-conf 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 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 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) (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) (5 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (4 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" m) (privk "sig" b)) (uniq-orig n btr mtr btr-0 mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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 (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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) (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))))) (label 111) (parent 74) (unrealized (3 0)) (dead) (comment "empty cohort")) (defskeleton minipay (vars (account acct) (cost amount) (n ncm ncb data) (item merchandise) (btr mtr merc-conf bank-conf 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 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 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) (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) (6 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (4 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (2 0)) ((6 1) (5 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr btr-0 mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand merc 2) n (5 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 (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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) (privk "sig" b)) (pubk "enc" 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 112) (parent 76) (unrealized (5 0)) (dead) (comment "empty cohort")) (defskeleton minipay (vars (account acct) (cost amount) (n ncm ncb data) (item merchandise) (btr mtr merc-conf bank-conf 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 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 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) (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) (5 0)) ((0 0) (6 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (4 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (2 0)) ((6 1) (3 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr btr-0 mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (displaced 7 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-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 ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b 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 (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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) (privk "sig" b)) (pubk "enc" 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 113) (parent 77) (seen 112) (unrealized (5 0)) (comment "2 in cohort - 1 not yet seen")) (defskeleton minipay (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)) (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-1) (c c) (m m) (b b)) (precedes ((0 0) (2 0)) ((0 0) (3 0)) ((0 0) (5 0)) ((1 1) (2 2)) ((2 1) (4 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (4 0))) (non-orig (privk "enc" m) (privk "enc" b) (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)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand merc 2) n (4 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 (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-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 114) (parent 78) (unrealized (4 0)) (dead) (comment "empty cohort")) (defskeleton minipay (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)) (deflistener (cat cost n)) (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-1) (c c) (m m) (b b)) (precedes ((0 0) (3 0)) ((0 0) (6 0)) ((1 1) (2 2)) ((2 1) (4 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (2 0)) ((6 1) (5 0))) (non-orig (privk "enc" m) (privk "enc" b) (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)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand merc 2) n (5 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)))) ((recv (cat cost n)) (send (cat cost n))) ((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-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 115) (parent 80) (unrealized (5 0)) (dead) (comment "empty cohort")) (defskeleton minipay (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)) (deflistener (cat cost n)) (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-1) (c c) (m m) (b b)) (precedes ((0 0) (3 0)) ((0 0) (5 0)) ((0 0) (6 0)) ((1 1) (2 2)) ((2 1) (4 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (2 0)) ((6 1) (4 0))) (non-orig (privk "enc" m) (privk "enc" b) (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)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (displaced 7 2 merc 2) n (4 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 ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b 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 (cat cost n)) (send (cat cost n))) ((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-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 116) (parent 81) (seen 110 115) (unrealized (5 0)) (comment "3 in cohort - 1 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncm ncb data) (item merchandise) (btr mtr merc-conf mtr-0 bank-conf btr-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)) (deflistener (cat cost n)) (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) (c c) (m m) (b b)) (precedes ((0 0) (2 0)) ((0 0) (3 0)) ((1 1) (2 2)) ((2 1) (4 0)) ((2 1) (5 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 btr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (displaced 6 2 merc 2) n (4 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)))) ((recv (cat cost n)) (send (cat cost n))) ((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-0 mtr) (privk "sig" b)) (pubk "enc" m))))) (label 117) (parent 82) (seen 111) (unrealized (4 0)) (comment "2 in cohort - 1 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncm ncb data) (item merchandise) (btr mtr merc-conf mtr-0 bank-conf btr-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)) (deflistener (cat cost n)) (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) (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) (6 0)) ((1 1) (2 2)) ((2 1) (5 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (4 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 btr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand merc 2) n (4 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)))) ((recv (cat cost n)) (send (cat cost n))) ((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-0 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-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 118) (parent 82) (seen 158) (unrealized (4 0)) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncm ncb data) (item merchandise) (btr mtr merc-conf mtr-0 bank-conf btr-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)) (deflistener (cat cost n)) (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) (c c) (m m) (b b)) (deflistener (cat n (hash ncb bank-conf))) (precedes ((0 0) (3 0)) ((0 0) (6 0)) ((1 1) (2 2)) ((2 1) (4 0)) ((2 1) (5 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (2 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 btr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (displaced 7 2 merc 2) n (4 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 ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b 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 (cat cost n)) (send (cat cost n))) ((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-0 mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (cat n (hash ncb bank-conf))) (send (cat n (hash ncb bank-conf))))) (label 119) (parent 83) (seen 112) (unrealized (6 0)) (comment "2 in cohort - 1 not yet seen")) (defskeleton minipay (vars (account account-0 acct) (cost amount) (n ncm ncb data) (item merchandise) (btr mtr merc-conf mtr-0 bank-conf btr-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-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)) (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)) (deflistener (cat cost n)) (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-0) (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-1) (c c) (m m) (b b)) (precedes ((0 0) (3 0)) ((0 0) (6 0)) ((0 0) (7 0)) ((1 1) (2 2)) ((2 1) (5 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (2 0)) ((7 1) (4 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 btr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand merc 2) n (4 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 (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc 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 (cat cost n)) (send (cat cost n))) ((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-0 mtr) (privk "sig" b)) (pubk "enc" 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-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 120) (parent 83) (unrealized (4 0) (6 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (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" 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)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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 121) (parent 86) (realized) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (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)) (deflistener (cat n (hash ncm item merc-conf))) (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) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (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)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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)))) ((recv (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf))))) (label 122) (parent 87) (seen 129) (unrealized (5 0)) (comment "3 in cohort - 2 not yet seen")) (defskeleton minipay (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)) (deflistener (cat n (hash ncm item merc-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-2) (c c) (m m) (b b)) (precedes ((0 0) (2 0)) ((0 0) (4 0)) ((0 0) (5 0)) ((0 0) (6 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) (1 0)) ((6 1) (3 0))) (non-orig (privk "enc" m) (privk "enc" b) (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)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-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-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 123) (parent 87) (unrealized (3 0) (5 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (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 btr-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)) (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)) (deflistener (cat n (hash ncm item merc-conf))) (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) (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 1) (6 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 mtr-1 btr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (displaced 7 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)))) ((recv (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 mtr) (privk "sig" b)) (pubk "enc" m))))) (label 124) (parent 89) (seen 135) (unrealized (3 0) (5 0)) (comment "3 in cohort - 2 not yet seen")) (defskeleton minipay (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 btr-0 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)) (deflistener (cat n (hash ncm item merc-conf))) (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) (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)) ((0 0) (7 0)) ((1 1) (2 2)) ((2 1) (6 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (1 0)) ((7 1) (3 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 mtr-1 btr-0 mtr-2) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 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-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 125) (parent 89) (seen 166) (unrealized (3 0) (5 0)) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay (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)) (deflistener (cat n (hash ncm item merc-conf))) (precedes ((0 0) (2 0)) ((0 0) (3 0)) ((1 1) (2 2)) ((2 1) (4 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (4 0)) ((4 1) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (displaced 5 3 merc 2) n (4 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf))))) (label 126) (parent 90) (unrealized (4 0)) (dead) (comment "empty cohort")) (defskeleton minipay (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)) (deflistener (cat n (hash ncm item merc-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-1) (c c) (m m) (b b)) (precedes ((0 0) (2 0)) ((0 0) (3 0)) ((0 0) (5 0)) ((1 1) (2 2)) ((2 1) (4 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (4 0))) (non-orig (privk "enc" m) (privk "enc" b) (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)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand merc 2) n (4 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-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-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 127) (parent 90) (unrealized (4 0)) (dead) (comment "empty cohort")) (defskeleton minipay (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)) (deflistener (cat n (hash ncm item merc-conf))) (precedes ((0 0) (2 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (4 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" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (displaced 5 2 merc 2) n (4 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)))) ((recv (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf))))) (label 128) (parent 93) (unrealized (4 0)) (comment "2 in cohort - 2 not yet seen")) (defskeleton minipay (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)) (deflistener (cat n (hash ncm item merc-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-1) (c c) (m m) (b b)) (precedes ((0 0) (2 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) (4 0))) (non-orig (privk "enc" m) (privk "enc" b) (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)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand merc 2) n (4 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)))) ((recv (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-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-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 129) (parent 93) (seen 168) (unrealized (4 0)) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay (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)) (deflistener (cat n (hash ncm item merc-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-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" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-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-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 130) (parent 94) (unrealized (4 0)) (comment "3 in cohort - 3 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr merc-conf mtr-0 btr-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)) (deflistener (cat n (hash ncm item merc-conf))) (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) (c c) (m m) (b b)) (precedes ((0 0) (2 0)) ((0 0) (3 0)) ((1 1) (2 2)) ((2 1) (4 0)) ((2 1) (5 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 btr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (displaced 6 2 merc 2) n (4 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)))) ((recv (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 mtr) (privk "sig" b)) (pubk "enc" m))))) (label 131) (parent 95) (unrealized (4 0)) (comment "2 in cohort - 2 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr merc-conf mtr-0 btr-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)) (deflistener (cat n (hash ncm item merc-conf))) (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) (c c) (m m) (b b)) (precedes ((0 0) (2 0)) ((0 0) (3 0)) ((1 1) (2 2)) ((2 1) (5 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (4 0)) ((4 1) (1 0)) ((5 1) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 btr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (displaced 6 3 merc 2) n (4 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)))) ((recv (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 mtr) (privk "sig" b)) (pubk "enc" m))))) (label 132) (parent 95) (seen 172) (unrealized (4 0)) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr merc-conf mtr-0 btr-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)) (deflistener (cat n (hash ncm item merc-conf))) (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) (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) (6 0)) ((1 1) (2 2)) ((2 1) (5 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (4 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 btr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand merc 2) n (4 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)))) ((recv (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 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-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 133) (parent 95) (seen 173) (unrealized (4 0)) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr merc-conf mtr-0 btr-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)) (deflistener (cat n (hash ncm item merc-conf))) (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) (c c) (m m) (b b)) (precedes ((0 0) (2 0)) ((0 0) (4 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (5 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 btr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 mtr) (privk "sig" b)) (pubk "enc" m))))) (label 134) (parent 96) (unrealized (4 0)) (comment "2 in cohort - 2 not yet seen")) (defskeleton minipay (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 btr-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)) (deflistener (cat n (hash ncm item merc-conf))) (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) (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) (6 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (5 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (3 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 btr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 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-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 135) (parent 96) (unrealized (3 0) (4 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (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)) (deflistener (cat n (hash ncm item merc-conf))) (deflistener (cat n (hash ncb bank-conf))) (precedes ((0 0) (4 0)) ((0 0) (6 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (5 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (2 0))) (non-orig (privk "enc" m) (privk "enc" b) (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)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (displaced 7 2 merc 2) n (5 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((recv (cat n (hash ncb bank-conf))) (send (cat n (hash ncb bank-conf))))) (label 136) (parent 98) (seen 145) (unrealized (6 0)) (comment "2 in cohort - 1 not yet seen")) (defskeleton minipay (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)) (deflistener (cat n (hash ncm item merc-conf))) (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-2) (c c) (m m) (b b)) (precedes ((0 0) (4 0)) ((0 0) (6 0)) ((0 0) (7 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) (1 0)) ((6 1) (2 0)) ((7 1) (5 0))) (non-orig (privk "enc" m) (privk "enc" b) (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)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand merc 2) n (5 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-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 137) (parent 98) (unrealized (5 0) (6 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (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)) (deflistener (cat n (hash ncm item merc-conf))) (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-2) (c c) (m m) (b b)) (precedes ((0 0) (4 0)) ((0 0) (5 0)) ((0 0) (6 0)) ((0 0) (7 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) (1 0)) ((6 1) (2 0)) ((7 1) (3 0))) (non-orig (privk "enc" m) (privk "enc" b) (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)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (displaced 8 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-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-2 (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 bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-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 138) (parent 99) (seen 149) (unrealized (5 0) (6 0)) (comment "4 in cohort - 3 not yet seen")) (defskeleton minipay (vars (for-bank bank-conf-commit mesg) (account acct) (cost amount) (n ncm ncm-0 ncb data) (item item-0 merchandise) (btr mtr merc-conf merc-conf-0 mtr-0 mtr-1 bank-conf btr-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)) (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)) (deflistener (cat n (hash ncm item merc-conf))) (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) (c c) (m m) (b b)) (deflistener (cat n (hash ncb bank-conf))) (precedes ((0 0) (4 0)) ((0 0) (5 0)) ((0 0) (7 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (6 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (1 0)) ((7 1) (2 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 mtr-1 btr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (displaced 8 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-0 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (cat n (hash ncb bank-conf))) (send (cat n (hash ncb bank-conf))))) (label 139) (parent 100) (seen 154) (unrealized (5 0) (7 0)) (comment "3 in cohort - 2 not yet seen")) (defskeleton minipay (vars (for-bank bank-conf-commit mesg) (account account-0 acct) (cost amount) (n ncm ncm-0 ncb data) (item item-0 merchandise) (btr mtr merc-conf merc-conf-0 mtr-0 mtr-1 bank-conf btr-0 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-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)) (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)) (deflistener (cat n (hash ncm item merc-conf))) (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-0) (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-2) (c c) (m m) (b b)) (precedes ((0 0) (4 0)) ((0 0) (5 0)) ((0 0) (7 0)) ((0 0) (8 0)) ((1 1) (2 2)) ((2 1) (6 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (1 0)) ((7 1) (2 0)) ((8 1) (3 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 mtr-1 btr-0 mtr-2) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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-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 (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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 mtr) (privk "sig" b)) (pubk "enc" 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-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 140) (parent 100) (unrealized (3 0) (5 0) (7 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (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)) (deflistener (cat n (hash ncm item merc-conf))) (deflistener (cat n (hash ncb bank-conf))) (precedes ((0 0) (3 0)) ((1 1) (2 2)) ((2 1) (4 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (5 0)) ((4 1) (1 0)) ((5 1) (2 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (displaced 6 3 merc 2) n (5 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)))) ((recv (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((recv (cat n (hash ncb bank-conf))) (send (cat n (hash ncb bank-conf))))) (label 141) (parent 101) (unrealized (5 0)) (dead) (comment "empty cohort")) (defskeleton minipay (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)) (deflistener (cat n (hash ncm item merc-conf))) (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-1) (c c) (m m) (b b)) (precedes ((0 0) (3 0)) ((0 0) (6 0)) ((1 1) (2 2)) ((2 1) (4 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (2 0)) ((6 1) (5 0))) (non-orig (privk "enc" m) (privk "enc" b) (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)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand merc 2) n (5 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)))) ((recv (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-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 142) (parent 101) (unrealized (5 0)) (dead) (comment "empty cohort")) (defskeleton minipay (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)) (deflistener (cat n (hash ncm item merc-conf))) (deflistener (cat n (hash ncb bank-conf))) (precedes ((0 0) (3 0)) ((0 0) (5 0)) ((1 1) (2 2)) ((2 1) (4 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (4 0)) ((4 1) (1 0)) ((5 1) (2 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (displaced 6 2 merc 2) n (4 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 ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((recv (cat n (hash ncb bank-conf))) (send (cat n (hash ncb bank-conf))))) (label 143) (parent 102) (seen 141) (unrealized (5 0)) (comment "2 in cohort - 1 not yet seen")) (defskeleton minipay (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)) (deflistener (cat n (hash ncm item merc-conf))) (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-1) (c c) (m m) (b b)) (precedes ((0 0) (3 0)) ((0 0) (5 0)) ((0 0) (6 0)) ((1 1) (2 2)) ((2 1) (4 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (2 0)) ((6 1) (4 0))) (non-orig (privk "enc" m) (privk "enc" b) (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)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (displaced 7 2 merc 2) n (4 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 ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-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 144) (parent 103) (seen 142 185) (unrealized (5 0)) (comment "3 in cohort - 1 not yet seen")) (defskeleton minipay (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)) (deflistener (cat n (hash ncm item merc-conf))) (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-1) (c c) (m m) (b b)) (precedes ((0 0) (6 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (4 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (2 0)) ((6 1) (5 0))) (non-orig (privk "enc" m) (privk "enc" b) (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)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand merc 2) n (5 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-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 145) (parent 104) (unrealized (5 0)) (dead) (comment "empty cohort")) (defskeleton minipay (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)) (deflistener (cat n (hash ncm item merc-conf))) (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-1) (c c) (m m) (b b)) (precedes ((0 0) (5 0)) ((0 0) (6 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (4 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (2 0)) ((6 1) (4 0))) (non-orig (privk "enc" m) (privk "enc" b) (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)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (displaced 7 2 merc 2) n (4 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-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 146) (parent 105) (seen 145) (unrealized (5 0)) (comment "2 in cohort - 1 not yet seen")) (defskeleton minipay (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)) (deflistener (cat n (hash ncm item merc-conf))) (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-1) (c c) (m m) (b b)) (precedes ((0 0) (5 0)) ((0 0) (6 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (4 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (2 0)) ((6 1) (3 0))) (non-orig (privk "enc" m) (privk "enc" b) (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)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (displaced 7 2 merc 2) n (4 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-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 147) (parent 106) (seen 145) (unrealized (5 0)) (comment "2 in cohort - 1 not yet seen")) (defskeleton minipay (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)) (deflistener (cat n (hash ncm item merc-conf))) (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-1) (c c) (m m) (b b)) (precedes ((0 0) (5 0)) ((0 0) (6 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) (2 0)) ((6 1) (3 0)) ((6 1) (4 0))) (non-orig (privk "enc" m) (privk "enc" b) (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)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (displaced 7 6 merc 2) n (4 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-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 148) (parent 106) (unrealized (4 0) (5 0)) (comment "2 in cohort - 2 not yet seen")) (defskeleton minipay (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)) (deflistener (cat n (hash ncm item merc-conf))) (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-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) (5 0)) ((0 0) (6 0)) ((0 0) (7 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) (2 0)) ((6 1) (3 0)) ((7 1) (4 0))) (non-orig (privk "enc" m) (privk "enc" b) (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)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand merc 2) n (4 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-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 149) (parent 106) (seen 190) (unrealized (4 0) (5 0)) (comment "2 in cohort - 1 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncm ncb data) (item merchandise) (btr mtr merc-conf mtr-0 bank-conf btr-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)) (deflistener (cat n (hash ncm item merc-conf))) (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) (c c) (m m) (b b)) (deflistener (cat n (hash ncb bank-conf))) (precedes ((0 0) (3 0)) ((0 0) (6 0)) ((1 1) (2 2)) ((2 1) (4 0)) ((2 1) (5 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (2 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 btr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (displaced 7 2 merc 2) n (4 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 ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (cat n (hash ncb bank-conf))) (send (cat n (hash ncb bank-conf))))) (label 150) (parent 107) (unrealized (6 0)) (comment "2 in cohort - 2 not yet seen")) (defskeleton minipay (vars (account account-0 acct) (cost amount) (n ncm ncb data) (item merchandise) (btr mtr merc-conf mtr-0 bank-conf btr-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) (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)) (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)) (deflistener (cat n (hash ncm item merc-conf))) (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-0) (mtr mtr) (c c) (m m) (b b)) (deflistener (cat n (hash ncb bank-conf))) (precedes ((0 0) (3 0)) ((0 0) (6 0)) ((1 1) (2 2)) ((2 1) (5 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (4 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (2 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 btr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (displaced 7 3 merc 2) n (4 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 (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (cat n (hash ncb bank-conf))) (send (cat n (hash ncb bank-conf))))) (label 151) (parent 107) (unrealized (4 0) (6 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (vars (account account-0 acct) (cost amount) (n ncm ncb data) (item merchandise) (btr mtr merc-conf mtr-0 bank-conf btr-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-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)) (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)) (deflistener (cat n (hash ncm item merc-conf))) (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-0) (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-1) (c c) (m m) (b b)) (precedes ((0 0) (3 0)) ((0 0) (6 0)) ((0 0) (7 0)) ((1 1) (2 2)) ((2 1) (5 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (2 0)) ((7 1) (4 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 btr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand merc 2) n (4 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 (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 mtr) (privk "sig" b)) (pubk "enc" 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-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 152) (parent 107) (unrealized (4 0) (6 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (vars (for-bank bank-conf-commit mesg) (account acct) (cost amount) (n ncm ncm-0 ncb data) (item item-0 merchandise) (btr mtr merc-conf merc-conf-0 mtr-0 bank-conf btr-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)) (deflistener (cat n (hash ncm item merc-conf))) (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) (c c) (m m) (b b)) (deflistener (cat n (hash ncb bank-conf))) (precedes ((0 0) (6 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (4 0)) ((2 1) (5 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (2 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 btr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (displaced 7 2 merc 2) n (4 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (cat n (hash ncb bank-conf))) (send (cat n (hash ncb bank-conf))))) (label 153) (parent 108) (unrealized (6 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (vars (for-bank bank-conf-commit mesg) (account acct) (cost amount) (n ncm ncm-0 ncb data) (item item-0 merchandise) (btr mtr merc-conf merc-conf-0 mtr-0 bank-conf btr-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)) (deflistener (cat n (hash ncm item merc-conf))) (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) (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-1) (c c) (m m) (b b)) (precedes ((0 0) (6 0)) ((0 0) (7 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (5 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (2 0)) ((7 1) (4 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 btr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand merc 2) n (4 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 mtr) (privk "sig" b)) (pubk "enc" 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-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 154) (parent 108) (unrealized (4 0) (6 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (vars (for-bank bank-conf-commit mesg) (account acct) (cost amount) (n ncm ncm-0 ncb data) (item item-0 merchandise) (btr mtr merc-conf merc-conf-0 mtr-0 bank-conf btr-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)) (deflistener (cat n (hash ncm item merc-conf))) (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) (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-1) (c c) (m m) (b b)) (precedes ((0 0) (4 0)) ((0 0) (6 0)) ((0 0) (7 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (5 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (2 0)) ((7 1) (3 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 btr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (displaced 8 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-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 ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 mtr) (privk "sig" b)) (pubk "enc" 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-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 155) (parent 109) (unrealized (4 0) (6 0)) (comment "3 in cohort - 3 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncm ncb data) (item merchandise) (btr mtr merc-conf bank-conf btr-0 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 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) (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)) (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) (6 0)) ((0 0) (7 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (4 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (2 0)) ((6 1) (3 0)) ((7 1) (5 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr btr-0 mtr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand merc 2) n (5 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 (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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) (privk "sig" b)) (pubk "enc" 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)))) ((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 156) (parent 113) (unrealized (5 0)) (dead) (comment "empty cohort")) (defskeleton minipay (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)) (deflistener (cat cost n)) (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-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) (3 0)) ((0 0) (6 0)) ((0 0) (7 0)) ((1 1) (2 2)) ((2 1) (4 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (2 0)) ((6 1) (4 0)) ((7 1) (5 0))) (non-orig (privk "enc" m) (privk "enc" b) (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)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand merc 2) n (5 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)))) ((recv (cat cost n)) (send (cat cost n))) ((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-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 157) (parent 116) (unrealized (5 0)) (dead) (comment "empty cohort")) (defskeleton minipay (vars (account acct) (cost amount) (n ncm ncb data) (item merchandise) (btr mtr merc-conf mtr-0 bank-conf btr-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)) (deflistener (cat cost n)) (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) (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) (6 0)) ((1 1) (2 2)) ((2 1) (4 0)) ((2 1) (5 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (4 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 btr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand merc 2) n (4 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 (cat cost n)) (send (cat cost n))) ((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-0 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-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 158) (parent 117) (unrealized (4 0)) (dead) (comment "empty cohort")) (defskeleton minipay (vars (account acct) (cost amount) (n ncm ncb data) (item merchandise) (btr mtr merc-conf mtr-0 bank-conf btr-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)) (deflistener (cat cost n)) (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) (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-1) (c c) (m m) (b b)) (precedes ((0 0) (3 0)) ((0 0) (7 0)) ((1 1) (2 2)) ((2 1) (4 0)) ((2 1) (5 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (2 0)) ((7 1) (6 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 btr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand merc 2) n (6 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)))) ((recv (cat cost n)) (send (cat cost n))) ((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-0 mtr) (privk "sig" b)) (pubk "enc" 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-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 159) (parent 119) (unrealized (6 0)) (dead) (comment "empty cohort")) (defskeleton minipay (vars (account acct) (cost amount) (n ncm ncb data) (item merchandise) (btr mtr merc-conf mtr-0 bank-conf btr-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)) (deflistener (cat cost n)) (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) (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-1) (c c) (m m) (b b)) (precedes ((0 0) (3 0)) ((0 0) (6 0)) ((0 0) (7 0)) ((1 1) (2 2)) ((2 1) (4 0)) ((2 1) (5 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (2 0)) ((7 1) (4 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 btr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (displaced 8 2 merc 2) n (4 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 ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b 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 (cat cost n)) (send (cat cost n))) ((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-0 mtr) (privk "sig" b)) (pubk "enc" 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-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 160) (parent 120) (seen 156 159) (unrealized (6 0)) (comment "3 in cohort - 1 not yet seen")) (defskeleton minipay (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" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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 161) (parent 121) (seen 29) (realized) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay (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)) (deflistener (cat n (hash ncm item merc-conf))) (precedes ((0 0) (2 0)) ((0 0) (4 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (5 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (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)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (displaced 6 2 merc 2) n (5 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)))) ((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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf))))) (label 162) (parent 122) (seen 168) (unrealized (5 0)) (comment "3 in cohort - 2 not yet seen")) (defskeleton minipay (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)) (deflistener (cat n (hash ncm item merc-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-2) (c c) (m m) (b b)) (precedes ((0 0) (2 0)) ((0 0) (4 0)) ((0 0) (6 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) (1 0)) ((6 1) (5 0))) (non-orig (privk "enc" m) (privk "enc" b) (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)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand merc 2) n (5 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)))) ((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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-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-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 163) (parent 122) (seen 203) (unrealized (5 0)) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay (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)) (deflistener (cat n (hash ncm item merc-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-2) (c c) (m m) (b b)) (precedes ((0 0) (2 0)) ((0 0) (4 0)) ((0 0) (5 0)) ((0 0) (6 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) (1 0)) ((6 1) (3 0))) (non-orig (privk "enc" m) (privk "enc" b) (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)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-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-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 164) (parent 123) (seen 171) (unrealized (5 0)) (comment "4 in cohort - 3 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr merc-conf mtr-0 mtr-1 btr-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)) (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)) (deflistener (cat n (hash ncm item merc-conf))) (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) (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 1) (6 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 mtr-1 btr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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)))) ((recv (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 mtr) (privk "sig" b)) (pubk "enc" m))))) (label 165) (parent 124) (seen 175) (unrealized (5 0)) (comment "3 in cohort - 2 not yet seen")) (defskeleton minipay (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 btr-0 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)) (deflistener (cat n (hash ncm item merc-conf))) (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) (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)) ((0 0) (7 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (6 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (1 0)) ((7 1) (3 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 mtr-1 btr-0 mtr-2) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 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-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 166) (parent 124) (unrealized (3 0) (5 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (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)) (deflistener (cat n (hash ncm item merc-conf))) (precedes ((0 0) (2 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (4 0)) ((4 1) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (displaced 5 3 merc 2) n (4 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf))))) (label 167) (parent 128) (unrealized (4 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (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)) (deflistener (cat n (hash ncm item merc-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-1) (c c) (m m) (b b)) (precedes ((0 0) (2 0)) ((0 0) (5 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (4 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (4 0))) (non-orig (privk "enc" m) (privk "enc" b) (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)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand merc 2) n (4 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-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-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 168) (parent 128) (seen 210) (unrealized (4 0)) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay (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)) (deflistener (cat n (hash ncm item merc-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-1) (c c) (m m) (b b)) (precedes ((0 0) (2 0)) ((0 0) (5 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (4 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" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (displaced 6 2 merc 2) n (4 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)))) ((recv (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-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-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 169) (parent 130) (unrealized (4 0)) (comment "2 in cohort - 2 not yet seen")) (defskeleton minipay (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)) (deflistener (cat n (hash ncm item merc-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-1) (c c) (m m) (b b)) (precedes ((0 0) (2 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)) ((5 1) (4 0))) (non-orig (privk "enc" m) (privk "enc" b) (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)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (displaced 6 5 merc 2) n (4 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)))) ((recv (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-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-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 170) (parent 130) (seen 211) (unrealized (4 0)) (comment "2 in cohort - 1 not yet seen")) (defskeleton minipay (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)) (deflistener (cat n (hash ncm item merc-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-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) (5 0)) ((0 0) (6 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)) ((6 1) (4 0))) (non-orig (privk "enc" m) (privk "enc" b) (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)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand merc 2) n (4 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)))) ((recv (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-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-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 171) (parent 130) (seen 212 213) (unrealized (4 0)) (comment "2 in cohort - 0 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr merc-conf mtr-0 btr-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)) (deflistener (cat n (hash ncm item merc-conf))) (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) (c c) (m m) (b b)) (precedes ((0 0) (2 0)) ((0 0) (3 0)) ((1 1) (2 2)) ((2 1) (4 0)) ((2 1) (5 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (4 0)) ((4 1) (1 0)) ((5 1) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 btr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (displaced 6 3 merc 2) n (4 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 mtr) (privk "sig" b)) (pubk "enc" m))))) (label 172) (parent 131) (unrealized (4 0)) (dead) (comment "empty cohort")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr merc-conf mtr-0 btr-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)) (deflistener (cat n (hash ncm item merc-conf))) (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) (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) (6 0)) ((1 1) (2 2)) ((2 1) (4 0)) ((2 1) (5 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (4 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 btr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand merc 2) n (4 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 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-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 131) (unrealized (4 0)) (dead) (comment "empty cohort")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr merc-conf mtr-0 btr-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)) (deflistener (cat n (hash ncm item merc-conf))) (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) (c c) (m m) (b b)) (precedes ((0 0) (2 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (4 0)) ((2 1) (5 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 btr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (displaced 6 2 merc 2) n (4 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)))) ((recv (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 mtr) (privk "sig" b)) (pubk "enc" m))))) (label 174) (parent 134) (unrealized (4 0)) (comment "2 in cohort - 2 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr merc-conf mtr-0 btr-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)) (deflistener (cat n (hash ncm item merc-conf))) (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) (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) (6 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (5 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (4 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 btr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand merc 2) n (4 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)))) ((recv (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 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-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 175) (parent 134) (seen 215) (unrealized (4 0)) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr merc-conf mtr-0 btr-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)) (deflistener (cat n (hash ncm item merc-conf))) (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) (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) (6 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (5 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (3 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 btr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 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-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 176) (parent 135) (unrealized (4 0)) (comment "3 in cohort - 3 not yet seen")) (defskeleton minipay (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)) (deflistener (cat n (hash ncm item merc-conf))) (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-2) (c c) (m m) (b b)) (precedes ((0 0) (4 0)) ((0 0) (7 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (5 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (2 0)) ((7 1) (6 0))) (non-orig (privk "enc" m) (privk "enc" b) (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)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand merc 2) n (6 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-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 177) (parent 136) (unrealized (6 0)) (dead) (comment "empty cohort")) (defskeleton minipay (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)) (deflistener (cat n (hash ncm item merc-conf))) (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-2) (c c) (m m) (b b)) (precedes ((0 0) (4 0)) ((0 0) (6 0)) ((0 0) (7 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (5 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (2 0)) ((7 1) (5 0))) (non-orig (privk "enc" m) (privk "enc" b) (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)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (displaced 8 2 merc 2) n (5 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-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-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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-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 178) (parent 137) (seen 177 187) (unrealized (6 0)) (comment "3 in cohort - 1 not yet seen")) (defskeleton minipay (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)) (deflistener (cat n (hash ncm item merc-conf))) (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-2) (c c) (m m) (b b)) (precedes ((0 0) (4 0)) ((0 0) (6 0)) ((0 0) (7 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (5 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (2 0)) ((7 1) (3 0))) (non-orig (privk "enc" m) (privk "enc" b) (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)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (displaced 8 2 merc 2) n (5 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-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 179) (parent 138) (seen 177 188) (unrealized (6 0)) (comment "3 in cohort - 1 not yet seen")) (defskeleton minipay (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)) (deflistener (cat n (hash ncm item merc-conf))) (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-2) (c c) (m m) (b b)) (precedes ((0 0) (4 0)) ((0 0) (6 0)) ((0 0) (7 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) (1 0)) ((6 1) (2 0)) ((7 1) (3 0)) ((7 1) (5 0))) (non-orig (privk "enc" m) (privk "enc" b) (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)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (displaced 8 7 merc 2) n (5 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-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 180) (parent 138) (seen 190) (unrealized (5 0) (6 0)) (comment "3 in cohort - 2 not yet seen")) (defskeleton minipay (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 mtr-3 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)) (deflistener (cat n (hash ncm item merc-conf))) (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-2) (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-3) (c c) (m m) (b b)) (precedes ((0 0) (4 0)) ((0 0) (6 0)) ((0 0) (7 0)) ((0 0) (8 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) (1 0)) ((6 1) (2 0)) ((7 1) (3 0)) ((8 1) (5 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 mtr-1 mtr-2 mtr-3) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand merc 2) n (5 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-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)))) ((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-3 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 138) (seen 222) (unrealized (5 0) (6 0)) (comment "2 in cohort - 1 not yet seen")) (defskeleton minipay (vars (for-bank bank-conf-commit mesg) (account acct) (cost amount) (n ncm ncm-0 ncb data) (item item-0 merchandise) (btr mtr merc-conf merc-conf-0 mtr-0 mtr-1 bank-conf btr-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)) (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)) (deflistener (cat n (hash ncm item merc-conf))) (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) (c c) (m m) (b b)) (deflistener (cat n (hash ncb bank-conf))) (precedes ((0 0) (4 0)) ((0 0) (7 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (5 0)) ((2 1) (6 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (1 0)) ((7 1) (2 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 mtr-1 btr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (displaced 8 2 merc 2) n (5 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (cat n (hash ncb bank-conf))) (send (cat n (hash ncb bank-conf))))) (label 182) (parent 139) (seen 196) (unrealized (7 0)) (comment "2 in cohort - 1 not yet seen")) (defskeleton minipay (vars (for-bank bank-conf-commit mesg) (account acct) (cost amount) (n ncm ncm-0 ncb data) (item item-0 merchandise) (btr mtr merc-conf merc-conf-0 mtr-0 mtr-1 bank-conf btr-0 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)) (deflistener (cat n (hash ncm item merc-conf))) (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) (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-2) (c c) (m m) (b b)) (precedes ((0 0) (4 0)) ((0 0) (7 0)) ((0 0) (8 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (6 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (1 0)) ((7 1) (2 0)) ((8 1) (5 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 mtr-1 btr-0 mtr-2) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand merc 2) n (5 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 mtr) (privk "sig" b)) (pubk "enc" 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-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 183) (parent 139) (unrealized (5 0) (7 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (vars (for-bank bank-conf-commit mesg) (account acct) (cost amount) (n ncm ncm-0 ncb data) (item item-0 merchandise) (btr mtr merc-conf merc-conf-0 mtr-0 mtr-1 bank-conf btr-0 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)) (deflistener (cat n (hash ncm item merc-conf))) (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) (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-2) (c c) (m m) (b b)) (precedes ((0 0) (4 0)) ((0 0) (5 0)) ((0 0) (7 0)) ((0 0) (8 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (6 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (1 0)) ((7 1) (2 0)) ((8 1) (3 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 mtr-1 btr-0 mtr-2) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (displaced 9 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-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-2 (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 bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 mtr) (privk "sig" b)) (pubk "enc" 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-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 184) (parent 140) (seen 200) (unrealized (5 0) (7 0)) (comment "4 in cohort - 3 not yet seen")) (defskeleton minipay (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)) (deflistener (cat n (hash ncm item merc-conf))) (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-1) (c c) (m m) (b b)) (precedes ((0 0) (3 0)) ((0 0) (6 0)) ((1 1) (2 2)) ((2 1) (4 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (4 0)) ((4 1) (1 0)) ((5 1) (2 0)) ((6 1) (5 0))) (non-orig (privk "enc" m) (privk "enc" b) (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)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand merc 2) n (5 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)))) ((recv (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-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 143) (unrealized (5 0)) (dead) (comment "empty cohort")) (defskeleton minipay (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)) (deflistener (cat n (hash ncm item merc-conf))) (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-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) (3 0)) ((0 0) (6 0)) ((0 0) (7 0)) ((1 1) (2 2)) ((2 1) (4 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (2 0)) ((6 1) (4 0)) ((7 1) (5 0))) (non-orig (privk "enc" m) (privk "enc" b) (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)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand merc 2) n (5 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)))) ((recv (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-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 186) (parent 144) (unrealized (5 0)) (dead) (comment "empty cohort")) (defskeleton minipay (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)) (deflistener (cat n (hash ncm item merc-conf))) (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-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) (6 0)) ((0 0) (7 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (4 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (2 0)) ((6 1) (4 0)) ((7 1) (5 0))) (non-orig (privk "enc" m) (privk "enc" b) (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)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand merc 2) n (5 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-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 187) (parent 146) (unrealized (5 0)) (dead) (comment "empty cohort")) (defskeleton minipay (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)) (deflistener (cat n (hash ncm item merc-conf))) (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-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) (6 0)) ((0 0) (7 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (4 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (2 0)) ((6 1) (3 0)) ((7 1) (5 0))) (non-orig (privk "enc" m) (privk "enc" b) (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)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand merc 2) n (5 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-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 188) (parent 147) (unrealized (5 0)) (dead) (comment "empty cohort")) (defskeleton minipay (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)) (deflistener (cat n (hash ncm item merc-conf))) (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-1) (c c) (m m) (b b)) (precedes ((0 0) (5 0)) ((0 0) (6 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (4 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (2 0)) ((6 1) (3 0)) ((6 1) (4 0))) (non-orig (privk "enc" m) (privk "enc" b) (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)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (displaced 7 2 merc 2) n (4 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-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 189) (parent 148) (seen 145) (unrealized (5 0)) (comment "2 in cohort - 1 not yet seen")) (defskeleton minipay (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)) (deflistener (cat n (hash ncm item merc-conf))) (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-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) (5 0)) ((0 0) (6 0)) ((0 0) (7 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) (2 0)) ((6 1) (3 0)) ((6 1) (4 0)) ((7 1) (4 0))) (non-orig (privk "enc" m) (privk "enc" b) (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)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand merc 2) n (4 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-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 190) (parent 148) (unrealized (4 0) (5 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (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)) (deflistener (cat n (hash ncm item merc-conf))) (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-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) (5 0)) ((0 0) (6 0)) ((0 0) (7 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (4 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (2 0)) ((6 1) (3 0)) ((7 1) (4 0))) (non-orig (privk "enc" m) (privk "enc" b) (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)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (displaced 8 2 merc 2) n (4 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-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-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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-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 191) (parent 149) (seen 187 188) (unrealized (5 0)) (comment "3 in cohort - 1 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncm ncb data) (item merchandise) (btr mtr merc-conf mtr-0 bank-conf btr-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)) (deflistener (cat n (hash ncm item merc-conf))) (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) (c c) (m m) (b b)) (deflistener (cat n (hash ncb bank-conf))) (precedes ((0 0) (3 0)) ((1 1) (2 2)) ((2 1) (4 0)) ((2 1) (5 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (6 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (2 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 btr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (displaced 7 3 merc 2) n (6 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)))) ((recv (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (cat n (hash ncb bank-conf))) (send (cat n (hash ncb bank-conf))))) (label 192) (parent 150) (unrealized (6 0)) (dead) (comment "empty cohort")) (defskeleton minipay (vars (account acct) (cost amount) (n ncm ncb data) (item merchandise) (btr mtr merc-conf mtr-0 bank-conf btr-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)) (deflistener (cat n (hash ncm item merc-conf))) (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) (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-1) (c c) (m m) (b b)) (precedes ((0 0) (3 0)) ((0 0) (7 0)) ((1 1) (2 2)) ((2 1) (4 0)) ((2 1) (5 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (2 0)) ((7 1) (6 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 btr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand merc 2) n (6 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)))) ((recv (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 mtr) (privk "sig" b)) (pubk "enc" 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-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 193) (parent 150) (unrealized (6 0)) (dead) (comment "empty cohort")) (defskeleton minipay (vars (account acct) (cost amount) (n ncm ncb data) (item merchandise) (btr mtr merc-conf mtr-0 bank-conf btr-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)) (deflistener (cat n (hash ncm item merc-conf))) (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) (c c) (m m) (b b)) (deflistener (cat n (hash ncb bank-conf))) (precedes ((0 0) (3 0)) ((0 0) (6 0)) ((1 1) (2 2)) ((2 1) (4 0)) ((2 1) (5 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (4 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (2 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 btr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (displaced 7 2 merc 2) n (4 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 ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 mtr) (privk "sig" b)) (pubk "enc" m)))) ((recv (cat n (hash ncb bank-conf))) (send (cat n (hash ncb bank-conf))))) (label 194) (parent 151) (seen 192) (unrealized (6 0)) (comment "2 in cohort - 1 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncm ncb data) (item merchandise) (btr mtr merc-conf mtr-0 bank-conf btr-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)) (deflistener (cat n (hash ncm item merc-conf))) (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) (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-1) (c c) (m m) (b b)) (precedes ((0 0) (3 0)) ((0 0) (6 0)) ((0 0) (7 0)) ((1 1) (2 2)) ((2 1) (4 0)) ((2 1) (5 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (2 0)) ((7 1) (4 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 btr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (displaced 8 2 merc 2) n (4 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 ((send (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 mtr) (privk "sig" b)) (pubk "enc" 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-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 195) (parent 152) (seen 193 232) (unrealized (6 0)) (comment "3 in cohort - 1 not yet seen")) (defskeleton minipay (vars (for-bank bank-conf-commit mesg) (account acct) (cost amount) (n ncm ncm-0 ncb data) (item item-0 merchandise) (btr mtr merc-conf merc-conf-0 mtr-0 bank-conf btr-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)) (deflistener (cat n (hash ncm item merc-conf))) (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) (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-1) (c c) (m m) (b b)) (precedes ((0 0) (7 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (4 0)) ((2 1) (5 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (2 0)) ((7 1) (6 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 btr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand merc 2) n (6 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 mtr) (privk "sig" b)) (pubk "enc" 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-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 196) (parent 153) (unrealized (6 0)) (dead) (comment "empty cohort")) (defskeleton minipay (vars (for-bank bank-conf-commit mesg) (account acct) (cost amount) (n ncm ncm-0 ncb data) (item item-0 merchandise) (btr mtr merc-conf merc-conf-0 mtr-0 bank-conf btr-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)) (deflistener (cat n (hash ncm item merc-conf))) (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) (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-1) (c c) (m m) (b b)) (precedes ((0 0) (6 0)) ((0 0) (7 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (4 0)) ((2 1) (5 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (2 0)) ((7 1) (4 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 btr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (displaced 8 2 merc 2) n (4 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 mtr) (privk "sig" b)) (pubk "enc" 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-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 197) (parent 154) (seen 196) (unrealized (6 0)) (comment "2 in cohort - 1 not yet seen")) (defskeleton minipay (vars (for-bank bank-conf-commit mesg) (account acct) (cost amount) (n ncm ncm-0 ncb data) (item item-0 merchandise) (btr mtr merc-conf merc-conf-0 mtr-0 bank-conf btr-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)) (deflistener (cat n (hash ncm item merc-conf))) (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) (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-1) (c c) (m m) (b b)) (precedes ((0 0) (6 0)) ((0 0) (7 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (4 0)) ((2 1) (5 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (2 0)) ((7 1) (3 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 btr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (displaced 8 2 merc 2) n (4 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 mtr) (privk "sig" b)) (pubk "enc" 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-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 198) (parent 155) (seen 196) (unrealized (6 0)) (comment "2 in cohort - 1 not yet seen")) (defskeleton minipay (vars (for-bank bank-conf-commit mesg) (account acct) (cost amount) (n ncm ncm-0 ncb data) (item item-0 merchandise) (btr mtr merc-conf merc-conf-0 mtr-0 bank-conf btr-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)) (deflistener (cat n (hash ncm item merc-conf))) (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) (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-1) (c c) (m m) (b b)) (precedes ((0 0) (6 0)) ((0 0) (7 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (5 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (2 0)) ((7 1) (3 0)) ((7 1) (4 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 btr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (displaced 8 7 merc 2) n (4 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 mtr) (privk "sig" b)) (pubk "enc" 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-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 199) (parent 155) (unrealized (4 0) (6 0)) (comment "2 in cohort - 2 not yet seen")) (defskeleton minipay (vars (for-bank bank-conf-commit mesg) (account acct) (cost amount) (n ncm ncm-0 ncb data) (item item-0 merchandise) (btr mtr merc-conf merc-conf-0 mtr-0 bank-conf btr-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)) (deflistener (cat n (hash ncm item merc-conf))) (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) (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-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) (6 0)) ((0 0) (7 0)) ((0 0) (8 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (5 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (2 0)) ((7 1) (3 0)) ((8 1) (4 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 btr-0 mtr-1 mtr-2) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand merc 2) n (4 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 mtr) (privk "sig" b)) (pubk "enc" 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-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 200) (parent 155) (seen 237) (unrealized (4 0) (6 0)) (comment "2 in cohort - 1 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncm ncb data) (item merchandise) (btr mtr merc-conf mtr-0 bank-conf btr-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)) (deflistener (cat cost n)) (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) (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-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) (3 0)) ((0 0) (7 0)) ((0 0) (8 0)) ((1 1) (2 2)) ((2 1) (4 0)) ((2 1) (5 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (2 0)) ((7 1) (4 0)) ((8 1) (6 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 btr-0 mtr-1 mtr-2) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand merc 2) n (6 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)))) ((recv (cat cost n)) (send (cat cost n))) ((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-0 mtr) (privk "sig" b)) (pubk "enc" 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-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 201) (parent 160) (unrealized (6 0)) (dead) (comment "empty cohort")) (defskeleton minipay (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)) (deflistener (cat n (hash ncm item merc-conf))) (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) (5 0)) ((4 1) (1 0)) ((5 1) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (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)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (displaced 6 3 merc 2) n (5 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)))) ((recv (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf))))) (label 202) (parent 162) (seen 210) (unrealized (5 0)) (comment "2 in cohort - 1 not yet seen")) (defskeleton minipay (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)) (deflistener (cat n (hash ncm item merc-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-2) (c c) (m m) (b b)) (precedes ((0 0) (2 0)) ((0 0) (4 0)) ((0 0) (6 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (5 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (5 0))) (non-orig (privk "enc" m) (privk "enc" b) (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)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand merc 2) n (5 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)))) ((recv (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-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-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 203) (parent 162) (seen 239) (unrealized (5 0)) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay (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)) (deflistener (cat n (hash ncm item merc-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-2) (c c) (m m) (b b)) (precedes ((0 0) (2 0)) ((0 0) (4 0)) ((0 0) (6 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (5 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (3 0))) (non-orig (privk "enc" m) (privk "enc" b) (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)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (displaced 7 2 merc 2) n (5 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)))) ((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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-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-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 204) (parent 164) (seen 212) (unrealized (5 0)) (comment "3 in cohort - 2 not yet seen")) (defskeleton minipay (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)) (deflistener (cat n (hash ncm item merc-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-2) (c c) (m m) (b b)) (precedes ((0 0) (2 0)) ((0 0) (4 0)) ((0 0) (6 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) (1 0)) ((6 1) (3 0)) ((6 1) (5 0))) (non-orig (privk "enc" m) (privk "enc" b) (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)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (displaced 7 6 merc 2) n (5 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)))) ((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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-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-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 205) (parent 164) (seen 213 240) (unrealized (5 0)) (comment "3 in cohort - 1 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr merc-conf mtr-0 mtr-1 mtr-2 mtr-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 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)) (deflistener (cat n (hash ncm item merc-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-2) (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-3) (c c) (m m) (b b)) (precedes ((0 0) (2 0)) ((0 0) (4 0)) ((0 0) (6 0)) ((0 0) (7 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) (1 0)) ((6 1) (3 0)) ((7 1) (5 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 mtr-1 mtr-2 mtr-3) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand merc 2) n (5 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)))) ((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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-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-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)))) ((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-3 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 206) (parent 164) (seen 241 242) (unrealized (5 0)) (comment "2 in cohort - 0 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr merc-conf mtr-0 mtr-1 btr-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)) (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)) (deflistener (cat n (hash ncm item merc-conf))) (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) (c c) (m m) (b b)) (precedes ((0 0) (2 0)) ((0 0) (4 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (5 0)) ((2 1) (6 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 mtr-1 btr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (displaced 7 2 merc 2) n (5 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)))) ((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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 mtr) (privk "sig" b)) (pubk "enc" m))))) (label 207) (parent 165) (seen 215) (unrealized (5 0)) (comment "3 in cohort - 2 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr merc-conf mtr-0 mtr-1 btr-0 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)) (deflistener (cat n (hash ncm item merc-conf))) (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) (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) (7 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (6 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (1 0)) ((7 1) (5 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 mtr-1 btr-0 mtr-2) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand merc 2) n (5 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)))) ((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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 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-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 208) (parent 165) (seen 244) (unrealized (5 0)) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr merc-conf mtr-0 mtr-1 btr-0 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)) (deflistener (cat n (hash ncm item merc-conf))) (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) (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)) ((0 0) (7 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (6 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (1 0)) ((7 1) (3 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 mtr-1 btr-0 mtr-2) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 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-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 209) (parent 166) (seen 218) (unrealized (5 0)) (comment "4 in cohort - 3 not yet seen")) (defskeleton minipay (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)) (deflistener (cat n (hash ncm item merc-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-1) (c c) (m m) (b b)) (precedes ((0 0) (2 0)) ((0 0) (5 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (4 0)) ((4 1) (1 0)) ((5 1) (4 0))) (non-orig (privk "enc" m) (privk "enc" b) (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)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand merc 2) n (4 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-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 (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-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-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 210) (parent 167) (unrealized (4 0)) (dead) (comment "empty cohort")) (defskeleton minipay (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)) (deflistener (cat n (hash ncm item merc-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-1) (c c) (m m) (b b)) (precedes ((0 0) (2 0)) ((0 0) (5 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (4 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (3 0)) ((5 1) (4 0))) (non-orig (privk "enc" m) (privk "enc" b) (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)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (displaced 6 5 merc 2) n (4 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-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-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 211) (parent 169) (unrealized (4 0)) (comment "2 in cohort - 2 not yet seen")) (defskeleton minipay (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)) (deflistener (cat n (hash ncm item merc-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-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) (5 0)) ((0 0) (6 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (4 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (3 0)) ((6 1) (4 0))) (non-orig (privk "enc" m) (privk "enc" b) (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)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand merc 2) n (4 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-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-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 212) (parent 169) (seen 249) (unrealized (4 0)) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay (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)) (deflistener (cat n (hash ncm item merc-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-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) (5 0)) ((0 0) (6 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)) ((5 1) (4 0)) ((6 1) (4 0))) (non-orig (privk "enc" m) (privk "enc" b) (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)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand merc 2) n (4 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 merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-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-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 213) (parent 170) (seen 249) (unrealized (4 0)) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr merc-conf mtr-0 btr-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)) (deflistener (cat n (hash ncm item merc-conf))) (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) (c c) (m m) (b b)) (precedes ((0 0) (2 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (5 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (4 0)) ((4 1) (1 0)) ((5 1) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 btr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (displaced 6 3 merc 2) n (4 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 mtr) (privk "sig" b)) (pubk "enc" m))))) (label 214) (parent 174) (unrealized (4 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr merc-conf mtr-0 btr-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)) (deflistener (cat n (hash ncm item merc-conf))) (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) (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) (6 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (4 0)) ((2 1) (5 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (4 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 btr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand merc 2) n (4 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 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-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 215) (parent 174) (seen 250) (unrealized (4 0)) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr merc-conf mtr-0 btr-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)) (deflistener (cat n (hash ncm item merc-conf))) (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) (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) (6 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (4 0)) ((2 1) (5 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (3 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 btr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (displaced 7 2 merc 2) n (4 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)))) ((recv (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 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-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 216) (parent 176) (unrealized (4 0)) (comment "2 in cohort - 2 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr merc-conf mtr-0 btr-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)) (deflistener (cat n (hash ncm item merc-conf))) (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) (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) (6 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (5 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (3 0)) ((6 1) (4 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 btr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (displaced 7 6 merc 2) n (4 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)))) ((recv (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 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-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 217) (parent 176) (seen 251) (unrealized (4 0)) (comment "2 in cohort - 1 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr merc-conf mtr-0 btr-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)) (deflistener (cat n (hash ncm item merc-conf))) (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) (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) (6 0)) ((0 0) (7 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (5 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (3 0)) ((7 1) (4 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 btr-0 mtr-1 mtr-2) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand merc 2) n (4 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)))) ((recv (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 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-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 218) (parent 176) (seen 252 253) (unrealized (4 0)) (comment "2 in cohort - 0 not yet seen")) (defskeleton minipay (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 mtr-3 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)) (deflistener (cat n (hash ncm item merc-conf))) (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-2) (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-3) (c c) (m m) (b b)) (precedes ((0 0) (4 0)) ((0 0) (7 0)) ((0 0) (8 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (5 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (2 0)) ((7 1) (5 0)) ((8 1) (6 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 mtr-1 mtr-2 mtr-3) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand merc 2) n (6 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-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)))) ((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-3 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 219) (parent 178) (unrealized (6 0)) (dead) (comment "empty cohort")) (defskeleton minipay (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 mtr-3 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)) (deflistener (cat n (hash ncm item merc-conf))) (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-2) (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-3) (c c) (m m) (b b)) (precedes ((0 0) (4 0)) ((0 0) (7 0)) ((0 0) (8 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (5 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (2 0)) ((7 1) (3 0)) ((8 1) (6 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 mtr-1 mtr-2 mtr-3) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand merc 2) n (6 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-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)))) ((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-3 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 220) (parent 179) (unrealized (6 0)) (dead) (comment "empty cohort")) (defskeleton minipay (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)) (deflistener (cat n (hash ncm item merc-conf))) (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-2) (c c) (m m) (b b)) (precedes ((0 0) (4 0)) ((0 0) (6 0)) ((0 0) (7 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (5 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (2 0)) ((7 1) (3 0)) ((7 1) (5 0))) (non-orig (privk "enc" m) (privk "enc" b) (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)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (displaced 8 2 merc 2) n (5 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-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-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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-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 221) (parent 180) (seen 177 229) (unrealized (6 0)) (comment "3 in cohort - 1 not yet seen")) (defskeleton minipay (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 mtr-3 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)) (deflistener (cat n (hash ncm item merc-conf))) (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-2) (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-3) (c c) (m m) (b b)) (precedes ((0 0) (4 0)) ((0 0) (6 0)) ((0 0) (7 0)) ((0 0) (8 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) (1 0)) ((6 1) (2 0)) ((7 1) (3 0)) ((7 1) (5 0)) ((8 1) (5 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 mtr-1 mtr-2 mtr-3) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand merc 2) n (5 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-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-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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-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)))) ((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-3 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 222) (parent 180) (unrealized (5 0) (6 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (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 mtr-3 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)) (deflistener (cat n (hash ncm item merc-conf))) (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-2) (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-3) (c c) (m m) (b b)) (precedes ((0 0) (4 0)) ((0 0) (6 0)) ((0 0) (7 0)) ((0 0) (8 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (5 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (2 0)) ((7 1) (3 0)) ((8 1) (5 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 mtr-1 mtr-2 mtr-3) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (displaced 9 2 merc 2) n (5 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-3 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-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)))) ((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-3 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 223) (parent 181) (seen 219 220 231) (unrealized (6 0)) (comment "4 in cohort - 1 not yet seen")) (defskeleton minipay (vars (for-bank bank-conf-commit mesg) (account acct) (cost amount) (n ncm ncm-0 ncb data) (item item-0 merchandise) (btr mtr merc-conf merc-conf-0 mtr-0 mtr-1 bank-conf btr-0 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)) (deflistener (cat n (hash ncm item merc-conf))) (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) (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-2) (c c) (m m) (b b)) (precedes ((0 0) (4 0)) ((0 0) (8 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (5 0)) ((2 1) (6 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (1 0)) ((7 1) (2 0)) ((8 1) (7 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 mtr-1 btr-0 mtr-2) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand merc 2) n (7 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 mtr) (privk "sig" b)) (pubk "enc" 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-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 224) (parent 182) (unrealized (7 0)) (dead) (comment "empty cohort")) (defskeleton minipay (vars (for-bank bank-conf-commit mesg) (account acct) (cost amount) (n ncm ncm-0 ncb data) (item item-0 merchandise) (btr mtr merc-conf merc-conf-0 mtr-0 mtr-1 bank-conf btr-0 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)) (deflistener (cat n (hash ncm item merc-conf))) (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) (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-2) (c c) (m m) (b b)) (precedes ((0 0) (4 0)) ((0 0) (7 0)) ((0 0) (8 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (5 0)) ((2 1) (6 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (1 0)) ((7 1) (2 0)) ((8 1) (5 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 mtr-1 btr-0 mtr-2) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (displaced 9 2 merc 2) n (5 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-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-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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 mtr) (privk "sig" b)) (pubk "enc" 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-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 225) (parent 183) (seen 224 234) (unrealized (7 0)) (comment "3 in cohort - 1 not yet seen")) (defskeleton minipay (vars (for-bank bank-conf-commit mesg) (account acct) (cost amount) (n ncm ncm-0 ncb data) (item item-0 merchandise) (btr mtr merc-conf merc-conf-0 mtr-0 mtr-1 bank-conf btr-0 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)) (deflistener (cat n (hash ncm item merc-conf))) (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) (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-2) (c c) (m m) (b b)) (precedes ((0 0) (4 0)) ((0 0) (7 0)) ((0 0) (8 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (5 0)) ((2 1) (6 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (1 0)) ((7 1) (2 0)) ((8 1) (3 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 mtr-1 btr-0 mtr-2) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (displaced 9 2 merc 2) n (5 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 mtr) (privk "sig" b)) (pubk "enc" 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-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 226) (parent 184) (seen 224 235) (unrealized (7 0)) (comment "3 in cohort - 1 not yet seen")) (defskeleton minipay (vars (for-bank bank-conf-commit mesg) (account acct) (cost amount) (n ncm ncm-0 ncb data) (item item-0 merchandise) (btr mtr merc-conf merc-conf-0 mtr-0 mtr-1 bank-conf btr-0 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)) (deflistener (cat n (hash ncm item merc-conf))) (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) (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-2) (c c) (m m) (b b)) (precedes ((0 0) (4 0)) ((0 0) (7 0)) ((0 0) (8 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (6 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (1 0)) ((7 1) (2 0)) ((8 1) (3 0)) ((8 1) (5 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 mtr-1 btr-0 mtr-2) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (displaced 9 8 merc 2) n (5 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 mtr) (privk "sig" b)) (pubk "enc" 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-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 227) (parent 184) (seen 237) (unrealized (5 0) (7 0)) (comment "3 in cohort - 2 not yet seen")) (defskeleton minipay (vars (for-bank bank-conf-commit mesg) (account acct) (cost amount) (n ncm ncm-0 ncb data) (item item-0 merchandise) (btr mtr merc-conf merc-conf-0 mtr-0 mtr-1 bank-conf btr-0 mtr-2 mtr-3 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)) (deflistener (cat n (hash ncm item merc-conf))) (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) (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-2) (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-3) (c c) (m m) (b b)) (precedes ((0 0) (4 0)) ((0 0) (7 0)) ((0 0) (8 0)) ((0 0) (9 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (6 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (1 0)) ((7 1) (2 0)) ((8 1) (3 0)) ((9 1) (5 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 mtr-1 btr-0 mtr-2 mtr-3) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand merc 2) n (5 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 mtr) (privk "sig" b)) (pubk "enc" 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-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)))) ((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-3 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 228) (parent 184) (seen 260) (unrealized (5 0) (7 0)) (comment "2 in cohort - 1 not yet seen")) (defskeleton minipay (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)) (deflistener (cat n (hash ncm item merc-conf))) (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-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) (6 0)) ((0 0) (7 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (4 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (2 0)) ((6 1) (3 0)) ((6 1) (4 0)) ((7 1) (5 0))) (non-orig (privk "enc" m) (privk "enc" b) (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)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand merc 2) n (5 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-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 229) (parent 189) (unrealized (5 0)) (dead) (comment "empty cohort")) (defskeleton minipay (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)) (deflistener (cat n (hash ncm item merc-conf))) (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-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) (5 0)) ((0 0) (6 0)) ((0 0) (7 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (4 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (2 0)) ((6 1) (3 0)) ((6 1) (4 0)) ((7 1) (4 0))) (non-orig (privk "enc" m) (privk "enc" b) (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)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (displaced 8 2 merc 2) n (4 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)) (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-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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-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 230) (parent 190) (seen 187 229) (unrealized (5 0)) (comment "3 in cohort - 1 not yet seen")) (defskeleton minipay (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 mtr-3 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)) (deflistener (cat n (hash ncm item merc-conf))) (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-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)) (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-3) (c c) (m m) (b b)) (precedes ((0 0) (6 0)) ((0 0) (7 0)) ((0 0) (8 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (4 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (2 0)) ((6 1) (3 0)) ((7 1) (4 0)) ((8 1) (5 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 mtr-1 mtr-2 mtr-3) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand merc 2) n (5 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-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)))) ((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-3 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 231) (parent 191) (unrealized (5 0)) (dead) (comment "empty cohort")) (defskeleton minipay (vars (account acct) (cost amount) (n ncm ncb data) (item merchandise) (btr mtr merc-conf mtr-0 bank-conf btr-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)) (deflistener (cat n (hash ncm item merc-conf))) (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) (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-1) (c c) (m m) (b b)) (precedes ((0 0) (3 0)) ((0 0) (7 0)) ((1 1) (2 2)) ((2 1) (4 0)) ((2 1) (5 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (4 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (2 0)) ((7 1) (6 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 btr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand merc 2) n (6 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)))) ((recv (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 mtr) (privk "sig" b)) (pubk "enc" 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-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 232) (parent 194) (unrealized (6 0)) (dead) (comment "empty cohort")) (defskeleton minipay (vars (account acct) (cost amount) (n ncm ncb data) (item merchandise) (btr mtr merc-conf mtr-0 bank-conf btr-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)) (deflistener (cat n (hash ncm item merc-conf))) (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) (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-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) (3 0)) ((0 0) (7 0)) ((0 0) (8 0)) ((1 1) (2 2)) ((2 1) (4 0)) ((2 1) (5 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (2 0)) ((7 1) (4 0)) ((8 1) (6 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 btr-0 mtr-1 mtr-2) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand merc 2) n (6 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)))) ((recv (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 mtr) (privk "sig" b)) (pubk "enc" 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-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 233) (parent 195) (unrealized (6 0)) (dead) (comment "empty cohort")) (defskeleton minipay (vars (for-bank bank-conf-commit mesg) (account acct) (cost amount) (n ncm ncm-0 ncb data) (item item-0 merchandise) (btr mtr merc-conf merc-conf-0 mtr-0 bank-conf btr-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)) (deflistener (cat n (hash ncm item merc-conf))) (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) (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-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) (7 0)) ((0 0) (8 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (4 0)) ((2 1) (5 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (2 0)) ((7 1) (4 0)) ((8 1) (6 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 btr-0 mtr-1 mtr-2) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand merc 2) n (6 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 mtr) (privk "sig" b)) (pubk "enc" 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-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 234) (parent 197) (unrealized (6 0)) (dead) (comment "empty cohort")) (defskeleton minipay (vars (for-bank bank-conf-commit mesg) (account acct) (cost amount) (n ncm ncm-0 ncb data) (item item-0 merchandise) (btr mtr merc-conf merc-conf-0 mtr-0 bank-conf btr-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)) (deflistener (cat n (hash ncm item merc-conf))) (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) (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-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) (7 0)) ((0 0) (8 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (4 0)) ((2 1) (5 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (2 0)) ((7 1) (3 0)) ((8 1) (6 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 btr-0 mtr-1 mtr-2) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand merc 2) n (6 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 mtr) (privk "sig" b)) (pubk "enc" 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-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 235) (parent 198) (unrealized (6 0)) (dead) (comment "empty cohort")) (defskeleton minipay (vars (for-bank bank-conf-commit mesg) (account acct) (cost amount) (n ncm ncm-0 ncb data) (item item-0 merchandise) (btr mtr merc-conf merc-conf-0 mtr-0 bank-conf btr-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)) (deflistener (cat n (hash ncm item merc-conf))) (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) (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-1) (c c) (m m) (b b)) (precedes ((0 0) (6 0)) ((0 0) (7 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (4 0)) ((2 1) (5 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (2 0)) ((7 1) (3 0)) ((7 1) (4 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 btr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (displaced 8 2 merc 2) n (4 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 mtr) (privk "sig" b)) (pubk "enc" 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-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 236) (parent 199) (seen 196) (unrealized (6 0)) (comment "2 in cohort - 1 not yet seen")) (defskeleton minipay (vars (for-bank bank-conf-commit mesg) (account acct) (cost amount) (n ncm ncm-0 ncb data) (item item-0 merchandise) (btr mtr merc-conf merc-conf-0 mtr-0 bank-conf btr-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)) (deflistener (cat n (hash ncm item merc-conf))) (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) (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-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) (6 0)) ((0 0) (7 0)) ((0 0) (8 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (5 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (2 0)) ((7 1) (3 0)) ((7 1) (4 0)) ((8 1) (4 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 btr-0 mtr-1 mtr-2) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand merc 2) n (4 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 mtr) (privk "sig" b)) (pubk "enc" 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-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 237) (parent 199) (unrealized (4 0) (6 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (vars (for-bank bank-conf-commit mesg) (account acct) (cost amount) (n ncm ncm-0 ncb data) (item item-0 merchandise) (btr mtr merc-conf merc-conf-0 mtr-0 bank-conf btr-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)) (deflistener (cat n (hash ncm item merc-conf))) (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) (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-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) (6 0)) ((0 0) (7 0)) ((0 0) (8 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (4 0)) ((2 1) (5 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (2 0)) ((7 1) (3 0)) ((8 1) (4 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 btr-0 mtr-1 mtr-2) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (displaced 9 2 merc 2) n (4 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-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-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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 mtr) (privk "sig" b)) (pubk "enc" 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-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 238) (parent 200) (seen 234 235) (unrealized (6 0)) (comment "3 in cohort - 1 not yet seen")) (defskeleton minipay (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)) (deflistener (cat n (hash ncm item merc-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-2) (c c) (m m) (b b)) (precedes ((0 0) (2 0)) ((0 0) (4 0)) ((0 0) (6 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (5 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (5 0))) (non-orig (privk "enc" m) (privk "enc" b) (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)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand merc 2) n (5 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-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 (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-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-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 239) (parent 202) (unrealized (5 0)) (dead) (comment "empty cohort")) (defskeleton minipay (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)) (deflistener (cat n (hash ncm item merc-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-2) (c c) (m m) (b b)) (precedes ((0 0) (2 0)) ((0 0) (4 0)) ((0 0) (6 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (5 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (3 0)) ((6 1) (5 0))) (non-orig (privk "enc" m) (privk "enc" b) (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)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (displaced 7 6 merc 2) n (5 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)))) ((recv (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-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-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 240) (parent 204) (seen 249) (unrealized (5 0)) (comment "3 in cohort - 2 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr merc-conf mtr-0 mtr-1 mtr-2 mtr-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 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)) (deflistener (cat n (hash ncm item merc-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-2) (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-3) (c c) (m m) (b b)) (precedes ((0 0) (2 0)) ((0 0) (4 0)) ((0 0) (6 0)) ((0 0) (7 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (5 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (3 0)) ((7 1) (5 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 mtr-1 mtr-2 mtr-3) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand merc 2) n (5 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)))) ((recv (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-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-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)))) ((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-3 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 241) (parent 204) (seen 267) (unrealized (5 0)) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr merc-conf mtr-0 mtr-1 mtr-2 mtr-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 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)) (deflistener (cat n (hash ncm item merc-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-2) (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-3) (c c) (m m) (b b)) (precedes ((0 0) (2 0)) ((0 0) (4 0)) ((0 0) (6 0)) ((0 0) (7 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) (1 0)) ((6 1) (3 0)) ((6 1) (5 0)) ((7 1) (5 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 mtr-1 mtr-2 mtr-3) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand merc 2) n (5 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-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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-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-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)))) ((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-3 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 242) (parent 205) (seen 267) (unrealized (5 0)) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr merc-conf mtr-0 mtr-1 btr-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)) (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)) (deflistener (cat n (hash ncm item merc-conf))) (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) (c c) (m m) (b b)) (precedes ((0 0) (2 0)) ((0 0) (4 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (6 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (5 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 mtr-1 btr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (displaced 7 3 merc 2) n (5 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)))) ((recv (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 mtr) (privk "sig" b)) (pubk "enc" m))))) (label 243) (parent 207) (seen 250) (unrealized (5 0)) (comment "2 in cohort - 1 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr merc-conf mtr-0 mtr-1 btr-0 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)) (deflistener (cat n (hash ncm item merc-conf))) (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) (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) (7 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (5 0)) ((2 1) (6 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (1 0)) ((7 1) (5 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 mtr-1 btr-0 mtr-2) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand merc 2) n (5 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)))) ((recv (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 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-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 244) (parent 207) (seen 268) (unrealized (5 0)) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr merc-conf mtr-0 mtr-1 btr-0 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)) (deflistener (cat n (hash ncm item merc-conf))) (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) (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) (7 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (5 0)) ((2 1) (6 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (1 0)) ((7 1) (3 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 mtr-1 btr-0 mtr-2) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (displaced 8 2 merc 2) n (5 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)))) ((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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 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-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 245) (parent 209) (seen 252) (unrealized (5 0)) (comment "3 in cohort - 2 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr merc-conf mtr-0 mtr-1 btr-0 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)) (deflistener (cat n (hash ncm item merc-conf))) (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) (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) (7 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (6 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (1 0)) ((7 1) (3 0)) ((7 1) (5 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 mtr-1 btr-0 mtr-2) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (displaced 8 7 merc 2) n (5 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)))) ((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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 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-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 246) (parent 209) (seen 253 269) (unrealized (5 0)) (comment "3 in cohort - 1 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr merc-conf mtr-0 mtr-1 btr-0 mtr-2 mtr-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 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)) (deflistener (cat n (hash ncm item merc-conf))) (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) (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)) (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-3) (c c) (m m) (b b)) (precedes ((0 0) (2 0)) ((0 0) (4 0)) ((0 0) (7 0)) ((0 0) (8 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (6 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (1 0)) ((7 1) (3 0)) ((8 1) (5 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 mtr-1 btr-0 mtr-2 mtr-3) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand merc 2) n (5 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)))) ((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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 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-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)))) ((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-3 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 247) (parent 209) (seen 270 271) (unrealized (5 0)) (comment "2 in cohort - 0 not yet seen")) (defskeleton minipay (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)) (deflistener (cat n (hash ncm item merc-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-1) (c c) (m m) (b b)) (precedes ((0 0) (2 0)) ((0 0) (5 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (4 0)) ((4 1) (1 0)) ((5 1) (3 0))) (non-orig (privk "enc" m) (privk "enc" b) (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)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (displaced 6 3 merc 2) n (4 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-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-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 248) (parent 211) (unrealized (4 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (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)) (deflistener (cat n (hash ncm item merc-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-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) (5 0)) ((0 0) (6 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (4 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (3 0)) ((5 1) (4 0)) ((6 1) (4 0))) (non-orig (privk "enc" m) (privk "enc" b) (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)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand merc 2) n (4 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-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-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 249) (parent 211) (seen 272) (unrealized (4 0)) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr merc-conf mtr-0 btr-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)) (deflistener (cat n (hash ncm item merc-conf))) (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) (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) (6 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (5 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (4 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (4 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 btr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand merc 2) n (4 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-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 (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 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-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 250) (parent 214) (unrealized (4 0)) (dead) (comment "empty cohort")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr merc-conf mtr-0 btr-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)) (deflistener (cat n (hash ncm item merc-conf))) (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) (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) (6 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (4 0)) ((2 1) (5 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (3 0)) ((6 1) (4 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 btr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (displaced 7 6 merc 2) n (4 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 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-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 251) (parent 216) (unrealized (4 0)) (comment "2 in cohort - 2 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr merc-conf mtr-0 btr-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)) (deflistener (cat n (hash ncm item merc-conf))) (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) (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) (6 0)) ((0 0) (7 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (4 0)) ((2 1) (5 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (3 0)) ((7 1) (4 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 btr-0 mtr-1 mtr-2) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand merc 2) n (4 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 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-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 252) (parent 216) (seen 274) (unrealized (4 0)) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr merc-conf mtr-0 btr-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)) (deflistener (cat n (hash ncm item merc-conf))) (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) (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) (6 0)) ((0 0) (7 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (5 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (3 0)) ((6 1) (4 0)) ((7 1) (4 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 btr-0 mtr-1 mtr-2) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand merc 2) n (4 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 merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 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-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 253) (parent 217) (seen 274) (unrealized (4 0)) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay (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 mtr-3 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)) (deflistener (cat n (hash ncm item merc-conf))) (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-2) (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-3) (c c) (m m) (b b)) (precedes ((0 0) (4 0)) ((0 0) (7 0)) ((0 0) (8 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (5 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (2 0)) ((7 1) (3 0)) ((7 1) (5 0)) ((8 1) (6 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 mtr-1 mtr-2 mtr-3) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand merc 2) n (6 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-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)))) ((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-3 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 254) (parent 221) (unrealized (6 0)) (dead) (comment "empty cohort")) (defskeleton minipay (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 mtr-3 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)) (deflistener (cat n (hash ncm item merc-conf))) (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-2) (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-3) (c c) (m m) (b b)) (precedes ((0 0) (4 0)) ((0 0) (6 0)) ((0 0) (7 0)) ((0 0) (8 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (5 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (2 0)) ((7 1) (3 0)) ((7 1) (5 0)) ((8 1) (5 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 mtr-1 mtr-2 mtr-3) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (displaced 9 2 merc 2) n (5 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-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)) (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-3 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-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)))) ((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-3 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 255) (parent 222) (seen 219 254 262) (unrealized (6 0)) (comment "4 in cohort - 1 not yet seen")) (defskeleton minipay (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 mtr-3 mtr-4 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)) (deflistener (cat n (hash ncm item merc-conf))) (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-2) (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-3) (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-4) (c c) (m m) (b b)) (precedes ((0 0) (4 0)) ((0 0) (7 0)) ((0 0) (8 0)) ((0 0) (9 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (5 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (2 0)) ((7 1) (3 0)) ((8 1) (5 0)) ((9 1) (6 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 mtr-1 mtr-2 mtr-3 mtr-4) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand merc 2) n (6 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-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)))) ((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-3 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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-4 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 256) (parent 223) (unrealized (6 0)) (dead) (comment "empty cohort")) (defskeleton minipay (vars (for-bank bank-conf-commit mesg) (account acct) (cost amount) (n ncm ncm-0 ncb data) (item item-0 merchandise) (btr mtr merc-conf merc-conf-0 mtr-0 mtr-1 bank-conf btr-0 mtr-2 mtr-3 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)) (deflistener (cat n (hash ncm item merc-conf))) (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) (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-2) (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-3) (c c) (m m) (b b)) (precedes ((0 0) (4 0)) ((0 0) (8 0)) ((0 0) (9 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (5 0)) ((2 1) (6 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (1 0)) ((7 1) (2 0)) ((8 1) (5 0)) ((9 1) (7 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 mtr-1 btr-0 mtr-2 mtr-3) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand merc 2) n (7 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 mtr) (privk "sig" b)) (pubk "enc" 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-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)))) ((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-3 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 257) (parent 225) (unrealized (7 0)) (dead) (comment "empty cohort")) (defskeleton minipay (vars (for-bank bank-conf-commit mesg) (account acct) (cost amount) (n ncm ncm-0 ncb data) (item item-0 merchandise) (btr mtr merc-conf merc-conf-0 mtr-0 mtr-1 bank-conf btr-0 mtr-2 mtr-3 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)) (deflistener (cat n (hash ncm item merc-conf))) (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) (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-2) (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-3) (c c) (m m) (b b)) (precedes ((0 0) (4 0)) ((0 0) (8 0)) ((0 0) (9 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (5 0)) ((2 1) (6 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (1 0)) ((7 1) (2 0)) ((8 1) (3 0)) ((9 1) (7 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 mtr-1 btr-0 mtr-2 mtr-3) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand merc 2) n (7 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 mtr) (privk "sig" b)) (pubk "enc" 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-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)))) ((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-3 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 258) (parent 226) (unrealized (7 0)) (dead) (comment "empty cohort")) (defskeleton minipay (vars (for-bank bank-conf-commit mesg) (account acct) (cost amount) (n ncm ncm-0 ncb data) (item item-0 merchandise) (btr mtr merc-conf merc-conf-0 mtr-0 mtr-1 bank-conf btr-0 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)) (deflistener (cat n (hash ncm item merc-conf))) (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) (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-2) (c c) (m m) (b b)) (precedes ((0 0) (4 0)) ((0 0) (7 0)) ((0 0) (8 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (5 0)) ((2 1) (6 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (1 0)) ((7 1) (2 0)) ((8 1) (3 0)) ((8 1) (5 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 mtr-1 btr-0 mtr-2) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (displaced 9 2 merc 2) n (5 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-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-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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 mtr) (privk "sig" b)) (pubk "enc" 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-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 259) (parent 227) (seen 224 263) (unrealized (7 0)) (comment "3 in cohort - 1 not yet seen")) (defskeleton minipay (vars (for-bank bank-conf-commit mesg) (account acct) (cost amount) (n ncm ncm-0 ncb data) (item item-0 merchandise) (btr mtr merc-conf merc-conf-0 mtr-0 mtr-1 bank-conf btr-0 mtr-2 mtr-3 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)) (deflistener (cat n (hash ncm item merc-conf))) (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) (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-2) (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-3) (c c) (m m) (b b)) (precedes ((0 0) (4 0)) ((0 0) (7 0)) ((0 0) (8 0)) ((0 0) (9 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (6 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (1 0)) ((7 1) (2 0)) ((8 1) (3 0)) ((8 1) (5 0)) ((9 1) (5 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 mtr-1 btr-0 mtr-2 mtr-3) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand merc 2) n (5 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-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-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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 mtr) (privk "sig" b)) (pubk "enc" 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-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)))) ((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-3 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 260) (parent 227) (unrealized (5 0) (7 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (vars (for-bank bank-conf-commit mesg) (account acct) (cost amount) (n ncm ncm-0 ncb data) (item item-0 merchandise) (btr mtr merc-conf merc-conf-0 mtr-0 mtr-1 bank-conf btr-0 mtr-2 mtr-3 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)) (deflistener (cat n (hash ncm item merc-conf))) (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) (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-2) (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-3) (c c) (m m) (b b)) (precedes ((0 0) (4 0)) ((0 0) (7 0)) ((0 0) (8 0)) ((0 0) (9 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (5 0)) ((2 1) (6 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (1 0)) ((7 1) (2 0)) ((8 1) (3 0)) ((9 1) (5 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 mtr-1 btr-0 mtr-2 mtr-3) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (displaced 10 2 merc 2) n (5 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-3 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 mtr) (privk "sig" b)) (pubk "enc" 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-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)))) ((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-3 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 261) (parent 228) (seen 257 258 265) (unrealized (7 0)) (comment "4 in cohort - 1 not yet seen")) (defskeleton minipay (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 mtr-3 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)) (deflistener (cat n (hash ncm item merc-conf))) (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-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)) (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-3) (c c) (m m) (b b)) (precedes ((0 0) (6 0)) ((0 0) (7 0)) ((0 0) (8 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (4 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (2 0)) ((6 1) (3 0)) ((6 1) (4 0)) ((7 1) (4 0)) ((8 1) (5 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 mtr-1 mtr-2 mtr-3) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand merc 2) n (5 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-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)))) ((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-3 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 262) (parent 230) (unrealized (5 0)) (dead) (comment "empty cohort")) (defskeleton minipay (vars (for-bank bank-conf-commit mesg) (account acct) (cost amount) (n ncm ncm-0 ncb data) (item item-0 merchandise) (btr mtr merc-conf merc-conf-0 mtr-0 bank-conf btr-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)) (deflistener (cat n (hash ncm item merc-conf))) (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) (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-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) (7 0)) ((0 0) (8 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (4 0)) ((2 1) (5 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (2 0)) ((7 1) (3 0)) ((7 1) (4 0)) ((8 1) (6 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 btr-0 mtr-1 mtr-2) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand merc 2) n (6 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 mtr) (privk "sig" b)) (pubk "enc" 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-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 263) (parent 236) (unrealized (6 0)) (dead) (comment "empty cohort")) (defskeleton minipay (vars (for-bank bank-conf-commit mesg) (account acct) (cost amount) (n ncm ncm-0 ncb data) (item item-0 merchandise) (btr mtr merc-conf merc-conf-0 mtr-0 bank-conf btr-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)) (deflistener (cat n (hash ncm item merc-conf))) (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) (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-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) (6 0)) ((0 0) (7 0)) ((0 0) (8 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (4 0)) ((2 1) (5 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (2 0)) ((7 1) (3 0)) ((7 1) (4 0)) ((8 1) (4 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 btr-0 mtr-1 mtr-2) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (displaced 9 2 merc 2) n (4 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)) (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-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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 mtr) (privk "sig" b)) (pubk "enc" 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-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 264) (parent 237) (seen 234 263) (unrealized (6 0)) (comment "3 in cohort - 1 not yet seen")) (defskeleton minipay (vars (for-bank bank-conf-commit mesg) (account acct) (cost amount) (n ncm ncm-0 ncb data) (item item-0 merchandise) (btr mtr merc-conf merc-conf-0 mtr-0 bank-conf btr-0 mtr-1 mtr-2 mtr-3 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)) (deflistener (cat n (hash ncm item merc-conf))) (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) (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-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)) (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-3) (c c) (m m) (b b)) (precedes ((0 0) (7 0)) ((0 0) (8 0)) ((0 0) (9 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (4 0)) ((2 1) (5 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (2 0)) ((7 1) (3 0)) ((8 1) (4 0)) ((9 1) (6 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 btr-0 mtr-1 mtr-2 mtr-3) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand merc 2) n (6 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 mtr) (privk "sig" b)) (pubk "enc" 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-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)))) ((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-3 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 265) (parent 238) (unrealized (6 0)) (dead) (comment "empty cohort")) (defskeleton minipay (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)) (deflistener (cat n (hash ncm item merc-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-2) (c c) (m m) (b b)) (precedes ((0 0) (2 0)) ((0 0) (4 0)) ((0 0) (6 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (5 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (3 0))) (non-orig (privk "enc" m) (privk "enc" b) (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)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (displaced 7 3 merc 2) n (5 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-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-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 266) (parent 240) (seen 272) (unrealized (5 0)) (comment "2 in cohort - 1 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr merc-conf mtr-0 mtr-1 mtr-2 mtr-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 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)) (deflistener (cat n (hash ncm item merc-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-2) (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-3) (c c) (m m) (b b)) (precedes ((0 0) (2 0)) ((0 0) (4 0)) ((0 0) (6 0)) ((0 0) (7 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (5 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (3 0)) ((6 1) (5 0)) ((7 1) (5 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 mtr-1 mtr-2 mtr-3) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand merc 2) n (5 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-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-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)))) ((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-3 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 267) (parent 240) (seen 280) (unrealized (5 0)) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr merc-conf mtr-0 mtr-1 btr-0 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)) (deflistener (cat n (hash ncm item merc-conf))) (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) (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) (7 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (6 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (5 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (1 0)) ((7 1) (5 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 mtr-1 btr-0 mtr-2) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand merc 2) n (5 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-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 (enc n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 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-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 268) (parent 243) (unrealized (5 0)) (dead) (comment "empty cohort")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr merc-conf mtr-0 mtr-1 btr-0 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)) (deflistener (cat n (hash ncm item merc-conf))) (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) (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) (7 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (5 0)) ((2 1) (6 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (1 0)) ((7 1) (3 0)) ((7 1) (5 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 mtr-1 btr-0 mtr-2) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (displaced 8 7 merc 2) n (5 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)))) ((recv (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 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-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 269) (parent 245) (seen 274) (unrealized (5 0)) (comment "3 in cohort - 2 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr merc-conf mtr-0 mtr-1 btr-0 mtr-2 mtr-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 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)) (deflistener (cat n (hash ncm item merc-conf))) (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) (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)) (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-3) (c c) (m m) (b b)) (precedes ((0 0) (2 0)) ((0 0) (4 0)) ((0 0) (7 0)) ((0 0) (8 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (5 0)) ((2 1) (6 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (1 0)) ((7 1) (3 0)) ((8 1) (5 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 mtr-1 btr-0 mtr-2 mtr-3) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand merc 2) n (5 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)))) ((recv (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 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-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)))) ((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-3 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 270) (parent 245) (seen 282) (unrealized (5 0)) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr merc-conf mtr-0 mtr-1 btr-0 mtr-2 mtr-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 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)) (deflistener (cat n (hash ncm item merc-conf))) (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) (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)) (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-3) (c c) (m m) (b b)) (precedes ((0 0) (2 0)) ((0 0) (4 0)) ((0 0) (7 0)) ((0 0) (8 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (6 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (1 0)) ((7 1) (3 0)) ((7 1) (5 0)) ((8 1) (5 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 mtr-1 btr-0 mtr-2 mtr-3) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand merc 2) n (5 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-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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 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-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)))) ((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-3 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 271) (parent 246) (seen 282) (unrealized (5 0)) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay (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)) (deflistener (cat n (hash ncm item merc-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-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) (5 0)) ((0 0) (6 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (4 0)) ((4 1) (1 0)) ((5 1) (3 0)) ((6 1) (4 0))) (non-orig (privk "enc" m) (privk "enc" b) (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)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand merc 2) n (4 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-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)) (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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-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-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 272) (parent 248) (unrealized (4 0)) (dead) (comment "empty cohort")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr merc-conf mtr-0 btr-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)) (deflistener (cat n (hash ncm item merc-conf))) (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) (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) (6 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (5 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (4 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (3 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 btr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (displaced 7 3 merc 2) n (4 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 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-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 273) (parent 251) (unrealized (4 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr merc-conf mtr-0 btr-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)) (deflistener (cat n (hash ncm item merc-conf))) (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) (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) (6 0)) ((0 0) (7 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (4 0)) ((2 1) (5 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (3 0)) ((6 1) (4 0)) ((7 1) (4 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 btr-0 mtr-1 mtr-2) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand merc 2) n (4 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 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-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 274) (parent 251) (seen 283) (unrealized (4 0)) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay (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 mtr-3 mtr-4 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)) (deflistener (cat n (hash ncm item merc-conf))) (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-2) (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-3) (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-4) (c c) (m m) (b b)) (precedes ((0 0) (4 0)) ((0 0) (7 0)) ((0 0) (8 0)) ((0 0) (9 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (5 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (2 0)) ((7 1) (3 0)) ((7 1) (5 0)) ((8 1) (5 0)) ((9 1) (6 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 mtr-1 mtr-2 mtr-3 mtr-4) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand merc 2) n (6 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-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)))) ((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-3 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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-4 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 275) (parent 255) (unrealized (6 0)) (dead) (comment "empty cohort")) (defskeleton minipay (vars (for-bank bank-conf-commit mesg) (account acct) (cost amount) (n ncm ncm-0 ncb data) (item item-0 merchandise) (btr mtr merc-conf merc-conf-0 mtr-0 mtr-1 bank-conf btr-0 mtr-2 mtr-3 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)) (deflistener (cat n (hash ncm item merc-conf))) (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) (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-2) (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-3) (c c) (m m) (b b)) (precedes ((0 0) (4 0)) ((0 0) (8 0)) ((0 0) (9 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (5 0)) ((2 1) (6 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (1 0)) ((7 1) (2 0)) ((8 1) (3 0)) ((8 1) (5 0)) ((9 1) (7 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 mtr-1 btr-0 mtr-2 mtr-3) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand merc 2) n (7 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 mtr) (privk "sig" b)) (pubk "enc" 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-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)))) ((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-3 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 276) (parent 259) (unrealized (7 0)) (dead) (comment "empty cohort")) (defskeleton minipay (vars (for-bank bank-conf-commit mesg) (account acct) (cost amount) (n ncm ncm-0 ncb data) (item item-0 merchandise) (btr mtr merc-conf merc-conf-0 mtr-0 mtr-1 bank-conf btr-0 mtr-2 mtr-3 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)) (deflistener (cat n (hash ncm item merc-conf))) (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) (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-2) (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-3) (c c) (m m) (b b)) (precedes ((0 0) (4 0)) ((0 0) (7 0)) ((0 0) (8 0)) ((0 0) (9 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (5 0)) ((2 1) (6 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (1 0)) ((7 1) (2 0)) ((8 1) (3 0)) ((8 1) (5 0)) ((9 1) (5 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 mtr-1 btr-0 mtr-2 mtr-3) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (displaced 10 2 merc 2) n (5 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-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)) (enc (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr-3 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 mtr) (privk "sig" b)) (pubk "enc" 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-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)))) ((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-3 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 277) (parent 260) (seen 257 276 279) (unrealized (7 0)) (comment "4 in cohort - 1 not yet seen")) (defskeleton minipay (vars (for-bank bank-conf-commit mesg) (account acct) (cost amount) (n ncm ncm-0 ncb data) (item item-0 merchandise) (btr mtr merc-conf merc-conf-0 mtr-0 mtr-1 bank-conf btr-0 mtr-2 mtr-3 mtr-4 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)) (deflistener (cat n (hash ncm item merc-conf))) (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) (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-2) (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-3) (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-4) (c c) (m m) (b b)) (precedes ((0 0) (4 0)) ((0 0) (8 0)) ((0 0) (9 0)) ((0 0) (10 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (5 0)) ((2 1) (6 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (1 0)) ((7 1) (2 0)) ((8 1) (3 0)) ((9 1) (5 0)) ((10 1) (7 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 mtr-1 btr-0 mtr-2 mtr-3 mtr-4) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand merc 2) n (7 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 mtr) (privk "sig" b)) (pubk "enc" 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-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)))) ((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-3 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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-4 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 278) (parent 261) (unrealized (7 0)) (dead) (comment "empty cohort")) (defskeleton minipay (vars (for-bank bank-conf-commit mesg) (account acct) (cost amount) (n ncm ncm-0 ncb data) (item item-0 merchandise) (btr mtr merc-conf merc-conf-0 mtr-0 bank-conf btr-0 mtr-1 mtr-2 mtr-3 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)) (deflistener (cat n (hash ncm item merc-conf))) (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) (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-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)) (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-3) (c c) (m m) (b b)) (precedes ((0 0) (7 0)) ((0 0) (8 0)) ((0 0) (9 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (4 0)) ((2 1) (5 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (2 0)) ((7 1) (3 0)) ((7 1) (4 0)) ((8 1) (4 0)) ((9 1) (6 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 btr-0 mtr-1 mtr-2 mtr-3) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand merc 2) n (6 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 mtr) (privk "sig" b)) (pubk "enc" 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-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)))) ((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-3 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 279) (parent 264) (unrealized (6 0)) (dead) (comment "empty cohort")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr merc-conf mtr-0 mtr-1 mtr-2 mtr-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 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)) (deflistener (cat n (hash ncm item merc-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-2) (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-3) (c c) (m m) (b b)) (precedes ((0 0) (2 0)) ((0 0) (4 0)) ((0 0) (6 0)) ((0 0) (7 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (5 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (3 0)) ((7 1) (5 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 mtr-1 mtr-2 mtr-3) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand merc 2) n (5 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-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)) (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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-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-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)))) ((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-3 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 280) (parent 266) (unrealized (5 0)) (dead) (comment "empty cohort")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr merc-conf mtr-0 mtr-1 btr-0 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)) (deflistener (cat n (hash ncm item merc-conf))) (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) (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) (7 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (6 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (5 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (1 0)) ((7 1) (3 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 mtr-1 btr-0 mtr-2) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (displaced 8 3 merc 2) n (5 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 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-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 281) (parent 269) (seen 283) (unrealized (5 0)) (comment "2 in cohort - 1 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr merc-conf mtr-0 mtr-1 btr-0 mtr-2 mtr-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 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)) (deflistener (cat n (hash ncm item merc-conf))) (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) (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)) (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-3) (c c) (m m) (b b)) (precedes ((0 0) (2 0)) ((0 0) (4 0)) ((0 0) (7 0)) ((0 0) (8 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (5 0)) ((2 1) (6 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (1 0)) ((7 1) (3 0)) ((7 1) (5 0)) ((8 1) (5 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 mtr-1 btr-0 mtr-2 mtr-3) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand merc 2) n (5 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 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-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)))) ((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-3 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 282) (parent 269) (seen 285) (unrealized (5 0)) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr merc-conf mtr-0 btr-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)) (deflistener (cat n (hash ncm item merc-conf))) (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) (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) (6 0)) ((0 0) (7 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (5 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (4 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (3 0)) ((7 1) (4 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 btr-0 mtr-1 mtr-2) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand merc 2) n (4 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-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)) (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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 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-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 283) (parent 273) (unrealized (4 0)) (dead) (comment "empty cohort")) (defskeleton minipay (vars (for-bank bank-conf-commit mesg) (account acct) (cost amount) (n ncm ncm-0 ncb data) (item item-0 merchandise) (btr mtr merc-conf merc-conf-0 mtr-0 mtr-1 bank-conf btr-0 mtr-2 mtr-3 mtr-4 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)) (deflistener (cat n (hash ncm item merc-conf))) (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) (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-2) (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-3) (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-4) (c c) (m m) (b b)) (precedes ((0 0) (4 0)) ((0 0) (8 0)) ((0 0) (9 0)) ((0 0) (10 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (5 0)) ((2 1) (6 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (1 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (1 0)) ((7 1) (2 0)) ((8 1) (3 0)) ((8 1) (5 0)) ((9 1) (5 0)) ((10 1) (7 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 mtr-1 btr-0 mtr-2 mtr-3 mtr-4) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand merc 2) n (7 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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 mtr) (privk "sig" b)) (pubk "enc" 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-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)))) ((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-3 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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-4 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 284) (parent 277) (unrealized (7 0)) (dead) (comment "empty cohort")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr merc-conf mtr-0 mtr-1 btr-0 mtr-2 mtr-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 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)) (deflistener (cat n (hash ncm item merc-conf))) (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) (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)) (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-3) (c c) (m m) (b b)) (precedes ((0 0) (2 0)) ((0 0) (4 0)) ((0 0) (7 0)) ((0 0) (8 0)) ((1 1) (2 2)) ((2 1) (3 0)) ((2 1) (6 0)) ((2 3) (0 1)) ((2 4) (0 2)) ((3 1) (5 0)) ((4 1) (1 0)) ((5 1) (1 0)) ((6 1) (1 0)) ((7 1) (3 0)) ((8 1) (5 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig n btr mtr mtr-0 mtr-1 btr-0 mtr-2 mtr-3) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (operation nonce-test (added-strand merc 2) n (5 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-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)) (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 (cat n (hash ncm item merc-conf))) (send (cat n (hash ncm item merc-conf)))) ((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-0 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-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)))) ((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-3 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 285) (parent 281) (unrealized (5 0)) (dead) (comment "empty cohort")) (comment "Nothing left to do") (defprotocol minipay 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 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 (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 286) (unrealized (0 2)) (origs (mtr (0 1))) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (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" m) (privk "sig" b)) (uniq-orig btr mtr) (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 287) (parent 286) (unrealized (0 2) (1 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (vars (for-bank bank-conf-commit 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 (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)) (precedes ((0 1) (1 0)) ((1 1) (0 2))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig btr mtr) (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 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 (hash ncb bank-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))))) (label 288) (parent 287) (unrealized (1 0)) (comment "2 in cohort - 2 not yet seen")) (defskeleton minipay (vars (bank-conf-commit 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 (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 (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)) (precedes ((0 1) (1 0)) ((1 1) (0 2))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig btr mtr) (operation nonce-test (contracted (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) mtr (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 bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 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 (hash ncb bank-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))))) (label 289) (parent 288) (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 bank-conf-commit) (bank-conf-decommit (hash ncb bank-conf))))) (origs (btr (1 1)) (mtr (0 1)))) (defskeleton minipay (vars (bank-conf-commit mesg) (account account-0 acct) (cost amount) (n ncm ncb ncb-0 data) (item merchandise) (merc-conf btr mtr bank-conf bank-conf-0 btr-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 bank-conf-commit) (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 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-0) (mtr mtr) (c c) (m m) (b b)) (precedes ((0 1) (2 0)) ((1 1) (0 2)) ((2 1) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig btr mtr btr-0) (operation nonce-test (added-strand bank 2) mtr (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-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 bank-conf-commit (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)))) ((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-0 mtr) (privk "sig" b)) (pubk "enc" m))))) (label 290) (parent 288) (unrealized (1 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (vars (bank-conf-commit mesg) (account acct) (cost amount) (n ncm ncb data) (item merchandise) (merc-conf btr mtr bank-conf btr-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 bank-conf-commit) (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 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) (c c) (m m) (b b)) (precedes ((0 1) (2 0)) ((1 1) (0 2)) ((2 1) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig btr mtr btr-0) (operation nonce-test (contracted (bank-conf-0 bank-conf) (account-0 account) (ncb-0 ncb)) mtr (1 0) (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr) (privk "sig" b)) (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 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 (hash ncb bank-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 (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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) (privk "sig" b)) (pubk "enc" m))))) (label 291) (parent 290) (seen 289) (realized) (comment "1 in cohort - 0 not yet seen")) (comment "Nothing left to do") (defprotocol minipay 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 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 (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 292) (unrealized (0 0)) (origs (btr (0 1))) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (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)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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 293) (parent 292) (unrealized (0 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (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)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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 294) (parent 293) (unrealized (0 0) (2 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (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)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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 295) (parent 294) (unrealized (2 0)) (comment "2 in cohort - 2 not yet seen")) (defskeleton minipay (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)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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 296) (parent 295) (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 (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)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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 297) (parent 295) (seen 296) (realized) (comment "1 in cohort - 0 not yet seen")) (comment "Nothing left to do") (defprotocol minipay 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 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 (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 298) (unrealized (0 0)) (origs (btr (0 1))) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (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)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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 299) (parent 298) (unrealized (0 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (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)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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 300) (parent 299) (unrealized (2 0)) (comment "2 in cohort - 2 not yet seen")) (defskeleton minipay (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)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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 301) (parent 300) (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 (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)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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 302) (parent 300) (seen 301) (realized) (comment "1 in cohort - 0 not yet seen")) (comment "Nothing left to do") (defprotocol minipay 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 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 (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr merc-conf mtr-0 btr-0 mtr-1 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 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr-0) (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-0) (c c) (m m) (b b)) (precedes ((1 0) (2 0)) ((2 1) (0 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (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 (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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 303) (unrealized (1 1) (1 2)) (origs (btr (0 1)) (mtr-0 (2 1)) (ncm (1 0)) (n (1 0)) (ncb (1 0))) (comment "2 in cohort - 2 not yet seen")) (defskeleton minipay (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 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 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 1)) ((1 0) (2 0)) ((2 1) (0 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation encryption-test (displaced 3 0 bank 2) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b)) (1 1)) (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 (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 (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc 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 304) (parent 303) (unrealized (1 1) (1 2)) (origs (btr (0 1)) (mtr-0 (2 1)) (ncm (1 0)) (n (1 0)) (ncb (1 0))) (comment "2 in cohort - 2 not yet seen")) (defskeleton minipay (vars (account account-0 acct) (cost amount) (n ncb ncm ncb-0 data) (item merchandise) (bank-conf btr mtr merc-conf mtr-0 btr-0 mtr-1 bank-conf-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 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr-0) (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-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-0) (mtr mtr-1) (c c) (m m) (b b)) (precedes ((1 0) (2 0)) ((1 0) (3 0)) ((2 1) (0 0)) ((3 1) (1 1))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr-0 btr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation encryption-test (added-strand bank 2) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b)) (1 1)) (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 (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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 (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))) (send (enc (hash ncb-0 bank-conf-0) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b)) (pubk "enc" m))))) (label 305) (parent 303) (unrealized (1 1) (1 2) (3 0)) (comment "2 in cohort - 2 not yet seen")) (defskeleton minipay (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 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 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)) (precedes ((0 1) (2 2)) ((1 0) (2 0)) ((2 1) (0 0)) ((2 3) (1 1))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation encryption-test (displaced 2 3 merc 4) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr mtr) (privk "sig" b)) (1 1) (enc (hash ncb bank-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 (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 (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 (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc 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))))) (label 306) (parent 304) (unrealized (1 2)) (origs (mtr (2 1)) (btr (0 1)) (ncm (1 0)) (n (1 0)) (ncb (1 0))) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (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 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 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 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 4 (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 1) (3 2)) ((1 0) (2 0)) ((1 0) (3 0)) ((2 1) (0 0)) ((3 1) (0 0)) ((3 3) (1 1))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule cheq-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)) (1 1) (enc (hash ncb bank-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 (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 (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 (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc 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 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))))) (label 307) (parent 304) (unrealized (1 2) (3 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (vars (account account-0 acct) (cost amount) (n ncm ncb data) (item merchandise) (btr mtr merc-conf btr-0 mtr-0 bank-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 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (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-0) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr-0) (mtr mtr-0) (c c) (m m) (b b)) (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-0) (mtr mtr-0) (c c) (m m) (b b)) (precedes ((1 0) (3 0)) ((2 1) (3 2)) ((3 1) (0 0)) ((3 1) (2 0)) ((3 3) (1 1))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncm ncb btr btr-0 mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule cheq-merc-4) (operation encryption-test (displaced 2 4 merc 4) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-0) (privk "sig" b)) (1 1) (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))) (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 (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-0) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-0) (privk "sig" 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-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-0 mtr-0) (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))) (recv (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 (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-0) (privk "sig" b))))) (label 308) (parent 305) (unrealized (1 2) (2 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (vars (for-bank mesg) (account account-0 acct) (cost amount) (n ncb ncm ncb-0 data) (item merchandise) (bank-conf btr mtr merc-conf mtr-0 btr-0 mtr-1 bank-conf-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 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr-0) (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-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-0) (mtr mtr-1) (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-0) (mtr mtr-1) (c c) (m m) (b b)) (precedes ((1 0) (2 0)) ((1 0) (4 0)) ((2 1) (0 0)) ((3 1) (4 2)) ((4 1) (3 0)) ((4 3) (1 1))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr-0 btr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule cheq-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-0 mtr-1) (privk "sig" b)) (1 1) (enc (hash ncb-0 bank-conf-0) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b)) (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 (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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 (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))) (send (enc (hash ncb-0 bank-conf-0) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (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-1 (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-0 mtr-1) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))))) (label 309) (parent 305) (unrealized (1 2) (3 0) (4 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (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 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 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 1) (2 2)) ((1 0) (2 0)) ((2 1) (0 0)) ((2 3) (1 1)) ((2 4) (1 2))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (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)) (1 2)) (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 (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 (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc 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 310) (parent 306) (realized) (shape) (maps ((0 1 2) ((account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (bank-conf bank-conf) (btr btr) (mtr mtr) (merc-conf merc-conf) (mtr-0 mtr) (c c) (m m) (b b) (btr-0 btr) (mtr-1 mtr)))) (origs (mtr (2 1)) (btr (0 1)) (ncm (1 0)) (n (1 0)) (ncb (1 0)))) (defskeleton minipay (vars (for-bank mesg) (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr mtr-0 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 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 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 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 1) (3 2)) ((1 0) (2 0)) ((1 0) (3 0)) ((2 1) (0 0)) ((3 1) (0 0)) ((3 3) (1 1)) ((3 4) (1 2))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation encryption-test (displaced 3 4 merc 5) (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr mtr) (privk "sig" m)) (1 2)) (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 (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 (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc 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 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 311) (parent 307) (unrealized (3 0)) (comment "2 in cohort - 2 not yet seen")) (defskeleton minipay (vars (account account-0 acct) (cost amount) (n ncb ncm data) (item merchandise) (btr mtr btr-0 mtr-0 bank-conf 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 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (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-0) (cost cost) (n n) (ncb ncb) (bank-conf bank-conf) (btr btr-0) (mtr mtr-0) (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-0) (mtr mtr-0) (c c) (m m) (b b)) (precedes ((1 0) (3 0)) ((2 1) (3 2)) ((3 1) (0 0)) ((3 1) (2 0)) ((3 3) (1 1)) ((3 4) (1 2))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr btr-0 mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation encryption-test (displaced 3 4 merc 5) (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-0) (privk "sig" m)) (1 2)) (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 (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-0) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-0) (privk "sig" 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-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-0 mtr-0) (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))) (recv (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 (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-0) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-0) (privk "sig" m))))) (label 312) (parent 308) (unrealized (2 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (vars (for-bank mesg) (account account-0 acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr mtr-0 btr-0 mtr-1 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 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr-0) (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-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) (bank-conf bank-conf) (btr btr-0) (mtr mtr-1) (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-0) (mtr mtr-1) (c c) (m m) (b b)) (precedes ((1 0) (2 0)) ((1 0) (4 0)) ((2 1) (0 0)) ((3 1) (4 2)) ((4 1) (3 0)) ((4 3) (1 1)) ((4 4) (1 2))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr-0 btr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation encryption-test (displaced 4 5 merc 5) (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (privk "sig" m)) (1 2)) (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 (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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 (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))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (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-1 (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-0 mtr-1) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (privk "sig" m))))) (label 313) (parent 309) (unrealized (3 0) (4 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr mtr-0 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 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 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 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 1) (3 2)) ((1 0) (2 0)) ((1 0) (3 0)) ((2 1) (0 0)) ((3 1) (0 0)) ((3 3) (1 1)) ((3 4) (1 2))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation encryption-test (contracted (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (hash n (hash ncb bank-conf)) (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 ((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 (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 (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc 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 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 314) (parent 311) (realized) (shape) (maps ((0 1 2) ((account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (bank-conf bank-conf) (btr btr) (mtr mtr) (merc-conf merc-conf) (mtr-0 mtr-0) (c c) (m m) (b b) (btr-0 btr) (mtr-1 mtr)))) (origs (mtr (3 1)) (btr (0 1)) (mtr-0 (2 1)) (ncm (1 0)) (n (1 0)) (ncb (1 0)))) (defskeleton minipay (vars (for-bank mesg) (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr mtr-0 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 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 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 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 n (hash ncb bank-conf))) (precedes ((0 1) (3 2)) ((1 0) (2 0)) ((1 0) (4 0)) ((2 1) (0 0)) ((3 1) (0 0)) ((3 3) (1 1)) ((3 4) (1 2)) ((4 1) (3 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation encryption-test (added-listener (cat n (hash ncb bank-conf))) (hash n (hash ncb bank-conf)) (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 ((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 (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 (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc 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 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 n (hash ncb bank-conf))) (send (cat n (hash ncb bank-conf))))) (label 315) (parent 311) (unrealized (3 0) (4 0)) (comment "2 in cohort - 2 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (btr mtr btr-0 mtr-0 bank-conf 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 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (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-0) (mtr mtr-0) (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-0) (mtr mtr-0) (c c) (m m) (b b)) (precedes ((1 0) (3 0)) ((2 1) (3 2)) ((3 1) (0 0)) ((3 1) (2 0)) ((3 3) (1 1)) ((3 4) (1 2))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr btr-0 mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation encryption-test (displaced 4 1 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 ((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 (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-0) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-0) (privk "sig" 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 n cost item merc-conf ncm (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc 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 (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 (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-0) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-0) (privk "sig" m))))) (label 316) (parent 312) (realized) (shape) (maps ((0 1 3) ((account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (bank-conf bank-conf) (btr btr) (mtr mtr) (merc-conf merc-conf) (mtr-0 mtr-0) (c c) (m m) (b b) (btr-0 btr-0) (mtr-1 mtr-0)))) (origs (mtr-0 (3 1)) (btr-0 (2 1)) (btr (0 1)) (ncm (1 0)) (n (1 0)) (ncb (1 0)))) (defskeleton minipay (vars (for-bank mesg) (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr mtr-0 btr-0 mtr-1 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 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr-0) (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-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-1) (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-0) (mtr mtr-1) (c c) (m m) (b b)) (precedes ((1 0) (2 0)) ((1 0) (4 0)) ((2 1) (0 0)) ((3 1) (4 2)) ((4 1) (3 0)) ((4 3) (1 1)) ((4 4) (1 2))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr-0 btr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation encryption-test (displaced 5 1 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)) (3 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 (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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 (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-0 mtr-1) (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-1 (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-0 mtr-1) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (privk "sig" m))))) (label 317) (parent 313) (unrealized (3 0) (4 0)) (comment "3 in cohort - 3 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr mtr-0 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 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 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 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 1) (3 2)) ((1 0) (2 0)) ((1 0) (4 0)) ((2 1) (0 0)) ((3 1) (0 0)) ((3 3) (1 1)) ((3 4) (1 2)) ((4 1) (3 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation encryption-test (displaced 5 1 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)) (3 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 (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 (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc 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 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 318) (parent 315) (unrealized (4 0)) (comment "2 in cohort - 2 not yet seen")) (defskeleton minipay (vars (account account-0 acct) (cost amount) (n ncb ncm n-0 ncb-0 ncm-0 data) (item item-0 merchandise) (bank-conf btr mtr mtr-0 merc-conf merc-conf-0 bank-conf-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 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 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 5 (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 (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 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) (3 2)) ((1 0) (2 0)) ((1 0) (4 0)) ((2 1) (0 0)) ((3 1) (0 0)) ((3 3) (1 1)) ((3 4) (1 2)) ((4 1) (3 0)) ((5 0) (3 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr mtr-0) (facts (neq n-0 ncb-0) (neq n-0 ncm-0) (neq ncm-0 ncb-0) (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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)) (3 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 (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 (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc 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-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 (hash ncb bank-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)))) ((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 319) (parent 315) (unrealized (3 0) (4 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (vars (for-bank mesg) (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr mtr-0 btr-0 mtr-1 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 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr-0) (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-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-1) (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-0) (mtr mtr-1) (c c) (m m) (b b)) (precedes ((1 0) (2 0)) ((1 0) (4 0)) ((2 1) (0 0)) ((2 1) (3 0)) ((3 1) (4 2)) ((4 1) (3 0)) ((4 3) (1 1)) ((4 4) (1 2))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr-0 btr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (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)) (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 ((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 (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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 (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-0 mtr-1) (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-1 (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-0 mtr-1) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (privk "sig" m))))) (label 320) (parent 317) (unrealized (4 0)) (comment "2 in cohort - 2 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr mtr-0 btr-0 mtr-1 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 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr-0) (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-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-1) (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-0) (mtr mtr-1) (c c) (m m) (b b)) (precedes ((1 0) (2 0)) ((1 0) (4 0)) ((2 1) (0 0)) ((3 1) (4 2)) ((4 1) (3 0)) ((4 3) (1 1)) ((4 4) (1 2))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr-0 btr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation encryption-test (displaced 5 4 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)) (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 ((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 (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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 (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-0 mtr-1) (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-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 (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (privk "sig" m))))) (label 321) (parent 317) (realized) (shape) (maps ((0 1 2) ((account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (bank-conf bank-conf) (btr btr) (mtr mtr) (merc-conf merc-conf) (mtr-0 mtr-0) (c c) (m m) (b b) (btr-0 btr-0) (mtr-1 mtr-1)))) (origs (mtr-1 (4 1)) (btr-0 (3 1)) (btr (0 1)) (mtr-0 (2 1)) (ncm (1 0)) (n (1 0)) (ncb (1 0)))) (defskeleton minipay (vars (for-bank mesg) (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr mtr-0 btr-0 mtr-1 merc-conf mtr-2 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 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr-0) (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-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-1) (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-0) (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 ((1 0) (2 0)) ((1 0) (4 0)) ((1 0) (5 0)) ((2 1) (0 0)) ((3 1) (4 2)) ((4 1) (3 0)) ((4 3) (1 1)) ((4 4) (1 2)) ((5 1) (3 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr-0 btr-0 mtr-1 mtr-2) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (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)) (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 ((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 (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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 (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-0 mtr-1) (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-1 (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-0 mtr-1) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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-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 322) (parent 317) (unrealized (4 0)) (comment "2 in cohort - 2 not yet seen")) (defskeleton minipay (vars (merc-conf-decommit mesg) (account account-0 acct) (cost cost-0 amount) (n ncb ncm n-0 data) (item merchandise) (bank-conf btr mtr mtr-0 merc-conf btr-0 mtr-1 text) (c m b c-0 m-0 b-0 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 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 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 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 bank 2 (merc-conf-decommit merc-conf-decommit) (account account-0) (cost cost-0) (n n-0) (ncb ncb) (bank-conf bank-conf) (btr btr-0) (mtr mtr-1) (c c-0) (m m-0) (b b-0)) (precedes ((0 1) (3 2)) ((1 0) (2 0)) ((1 0) (5 0)) ((2 1) (0 0)) ((3 1) (0 0)) ((3 3) (1 1)) ((3 4) (1 2)) ((4 1) (3 0)) ((5 1) (4 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr mtr-0 btr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation encryption-test (added-strand bank 2) (hash ncb bank-conf) (4 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 (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 (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc 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 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 (payreq c-0 m-0 b-0 (hash cost-0 n-0) merc-conf-decommit mtr-1 (cat (sign (order c-0 m-0 b-0 cost-0 (enc n-0 cost-0 account-0 bank-conf ncb (hash n-0 merc-conf-decommit) (pubk "enc" b-0))) (privk "sig" c-0)) (enc n-0 cost-0 account-0 bank-conf ncb (hash n-0 merc-conf-decommit) (pubk "enc" b-0)))) (pubk "enc" b-0))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c-0 m-0 b-0 n-0 cost-0 (hash n-0 merc-conf-decommit)) btr-0 mtr-1) (privk "sig" b-0)) (pubk "enc" m-0))))) (label 323) (parent 318) (unrealized (4 0) (5 0)) (comment "2 in cohort - 2 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr mtr-0 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 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 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 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))) (deflistener (cat ncb bank-conf)) (precedes ((0 1) (3 2)) ((1 0) (2 0)) ((1 0) (5 0)) ((2 1) (0 0)) ((3 1) (0 0)) ((3 3) (1 1)) ((3 4) (1 2)) ((4 1) (3 0)) ((5 1) (4 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation encryption-test (added-listener (cat ncb bank-conf)) (hash ncb bank-conf) (4 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 (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 (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc 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 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 (cat ncb bank-conf)) (send (cat ncb bank-conf)))) (label 324) (parent 318) (unrealized (4 0) (5 0)) (comment "2 in cohort - 2 not yet seen")) (defskeleton minipay (vars (account account-0 acct) (cost amount) (n ncb ncm n-0 ncb-0 ncm-0 data) (item item-0 merchandise) (bank-conf btr mtr mtr-0 merc-conf merc-conf-0 bank-conf-0 mtr-1 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 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 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 5 (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 (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 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-1) (c c) (m m) (b b)) (precedes ((0 1) (3 2)) ((1 0) (2 0)) ((1 0) (4 0)) ((2 1) (0 0)) ((3 1) (0 0)) ((3 3) (1 1)) ((3 4) (1 2)) ((4 1) (3 0)) ((5 0) (3 0)) ((6 1) (3 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr mtr-0 mtr-1) (facts (neq n-0 ncb-0) (neq n-0 ncm-0) (neq ncm-0 ncb-0) (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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)) (3 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 (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 (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 (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc 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-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 (hash ncb bank-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)))) ((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-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))))) (label 325) (parent 319) (unrealized (3 0) (4 0) (6 0)) (dead) (comment "empty cohort")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr mtr-0 btr-0 mtr-1 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 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr-0) (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-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-1) (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-0) (mtr mtr-1) (c c) (m m) (b b)) (precedes ((1 0) (2 0)) ((1 0) (4 0)) ((2 1) (0 0)) ((2 1) (3 0)) ((3 1) (4 2)) ((4 1) (3 0)) ((4 3) (1 1)) ((4 4) (1 2))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr-0 btr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation encryption-test (contracted (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (hash n (hash ncb bank-conf)) (4 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 (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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 (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-0 mtr-1) (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-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 (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (privk "sig" m))))) (label 326) (parent 320) (realized) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (vars (for-bank mesg) (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr mtr-0 btr-0 mtr-1 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 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr-0) (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-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-1) (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-0) (mtr mtr-1) (c c) (m m) (b b)) (deflistener (cat n (hash ncb bank-conf))) (precedes ((1 0) (2 0)) ((1 0) (5 0)) ((2 1) (0 0)) ((2 1) (3 0)) ((3 1) (4 2)) ((4 1) (3 0)) ((4 3) (1 1)) ((4 4) (1 2)) ((5 1) (4 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr-0 btr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation encryption-test (added-listener (cat n (hash ncb bank-conf))) (hash n (hash ncb bank-conf)) (4 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 (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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 (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-0 mtr-1) (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-1 (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-0 mtr-1) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (privk "sig" m)))) ((recv (cat n (hash ncb bank-conf))) (send (cat n (hash ncb bank-conf))))) (label 327) (parent 320) (unrealized (4 0) (5 0)) (comment "2 in cohort - 2 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr mtr-0 btr-0 mtr-1 merc-conf mtr-2 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 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr-0) (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-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-1) (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-0) (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 ((1 0) (2 0)) ((1 0) (4 0)) ((1 0) (5 0)) ((2 1) (0 0)) ((3 1) (4 2)) ((4 1) (3 0)) ((4 3) (1 1)) ((4 4) (1 2)) ((5 1) (3 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr-0 btr-0 mtr-1 mtr-2) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation encryption-test (contracted (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) (hash n (hash ncb bank-conf)) (4 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 (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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 (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-0 mtr-1) (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-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 (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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-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 328) (parent 322) (seen 321) (realized) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay (vars (for-bank mesg) (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr mtr-0 btr-0 mtr-1 merc-conf mtr-2 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 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr-0) (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-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-1) (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-0) (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)) (deflistener (cat n (hash ncb bank-conf))) (precedes ((1 0) (2 0)) ((1 0) (5 0)) ((1 0) (6 0)) ((2 1) (0 0)) ((3 1) (4 2)) ((4 1) (3 0)) ((4 3) (1 1)) ((4 4) (1 2)) ((5 1) (3 0)) ((6 1) (4 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr-0 btr-0 mtr-1 mtr-2) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation encryption-test (added-listener (cat n (hash ncb bank-conf))) (hash n (hash ncb bank-conf)) (4 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 (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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 (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-0 mtr-1) (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-1 (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-0 mtr-1) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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-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)))) ((recv (cat n (hash ncb bank-conf))) (send (cat n (hash ncb bank-conf))))) (label 329) (parent 322) (unrealized (4 0) (6 0)) (comment "2 in cohort - 2 not yet seen")) (defskeleton minipay (vars (merc-conf-decommit mesg) (account account-0 acct) (cost cost-0 amount) (n ncb ncm n-0 data) (item merchandise) (bank-conf btr mtr mtr-0 merc-conf btr-0 mtr-1 text) (c m b c-0 m-0 b-0 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 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 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 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 bank 2 (merc-conf-decommit merc-conf-decommit) (account account-0) (cost cost-0) (n n-0) (ncb ncb) (bank-conf bank-conf) (btr btr-0) (mtr mtr-1) (c c-0) (m m-0) (b b-0)) (precedes ((0 1) (3 2)) ((1 0) (2 0)) ((1 0) (5 0)) ((2 1) (4 0)) ((3 1) (0 0)) ((3 3) (1 1)) ((3 4) (1 2)) ((4 1) (3 0)) ((5 1) (4 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr mtr-0 btr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation nonce-test (displaced 6 2 merc 2) n (4 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 (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 (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc 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 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 (payreq c-0 m-0 b-0 (hash cost-0 n-0) merc-conf-decommit mtr-1 (cat (sign (order c-0 m-0 b-0 cost-0 (enc n-0 cost-0 account-0 bank-conf ncb (hash n-0 merc-conf-decommit) (pubk "enc" b-0))) (privk "sig" c-0)) (enc n-0 cost-0 account-0 bank-conf ncb (hash n-0 merc-conf-decommit) (pubk "enc" b-0)))) (pubk "enc" b-0))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c-0 m-0 b-0 n-0 cost-0 (hash n-0 merc-conf-decommit)) btr-0 mtr-1) (privk "sig" b-0)) (pubk "enc" m-0))))) (label 330) (parent 323) (unrealized (5 0)) (comment "2 in cohort - 2 not yet seen")) (defskeleton minipay (vars (merc-conf-decommit mesg) (account account-0 acct) (cost cost-0 amount) (n ncb ncm n-0 data) (item merchandise) (bank-conf btr mtr mtr-0 merc-conf btr-0 mtr-1 mtr-2 text) (c m b c-0 m-0 b-0 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 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 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 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 bank 2 (merc-conf-decommit merc-conf-decommit) (account account-0) (cost cost-0) (n n-0) (ncb ncb) (bank-conf bank-conf) (btr btr-0) (mtr mtr-1) (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-2) (c c) (m m) (b b)) (precedes ((0 1) (3 2)) ((1 0) (2 0)) ((1 0) (5 0)) ((1 0) (6 0)) ((2 1) (0 0)) ((3 1) (0 0)) ((3 3) (1 1)) ((3 4) (1 2)) ((4 1) (3 0)) ((5 1) (4 0)) ((6 1) (4 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr mtr-0 btr-0 mtr-2) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation nonce-test (added-strand merc 2) n (4 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 (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 (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc 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 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 (payreq c-0 m-0 b-0 (hash cost-0 n-0) merc-conf-decommit mtr-1 (cat (sign (order c-0 m-0 b-0 cost-0 (enc n-0 cost-0 account-0 bank-conf ncb (hash n-0 merc-conf-decommit) (pubk "enc" b-0))) (privk "sig" c-0)) (enc n-0 cost-0 account-0 bank-conf ncb (hash n-0 merc-conf-decommit) (pubk "enc" b-0)))) (pubk "enc" b-0))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c-0 m-0 b-0 n-0 cost-0 (hash n-0 merc-conf-decommit)) btr-0 mtr-1) (privk "sig" b-0)) (pubk "enc" m-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-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 331) (parent 323) (seen 340) (unrealized (5 0)) (comment "3 in cohort - 2 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr mtr-0 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 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 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 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))) (deflistener (cat ncb bank-conf)) (precedes ((0 1) (3 2)) ((1 0) (2 0)) ((1 0) (5 0)) ((2 1) (4 0)) ((3 1) (0 0)) ((3 3) (1 1)) ((3 4) (1 2)) ((4 1) (3 0)) ((5 1) (4 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation nonce-test (displaced 6 2 merc 2) n (4 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 (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 (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc 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 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 (cat ncb bank-conf)) (send (cat ncb bank-conf)))) (label 332) (parent 324) (unrealized (5 0)) (comment "2 in cohort - 2 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr mtr-0 merc-conf mtr-1 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 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 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 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))) (deflistener (cat 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-1) (c c) (m m) (b b)) (precedes ((0 1) (3 2)) ((1 0) (2 0)) ((1 0) (5 0)) ((1 0) (6 0)) ((2 1) (0 0)) ((3 1) (0 0)) ((3 3) (1 1)) ((3 4) (1 2)) ((4 1) (3 0)) ((5 1) (4 0)) ((6 1) (4 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr mtr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation nonce-test (added-strand merc 2) n (4 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 (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 (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc 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 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 (cat ncb bank-conf)) (send (cat 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-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 333) (parent 324) (seen 344) (unrealized (5 0)) (comment "3 in cohort - 2 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr mtr-0 btr-0 mtr-1 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 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr-0) (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-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-1) (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-0) (mtr mtr-1) (c c) (m m) (b b)) (precedes ((1 0) (2 0)) ((1 0) (4 0)) ((2 1) (0 0)) ((2 1) (4 2)) ((3 1) (4 2)) ((4 1) (3 0)) ((4 3) (1 1)) ((4 4) (1 2))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr-0 btr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation generalization weakened ((2 1) (3 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 (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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 (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-0 mtr-1) (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-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 (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (privk "sig" m))))) (label 334) (parent 326) (realized) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr mtr-0 btr-0 mtr-1 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 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr-0) (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-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-1) (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-0) (mtr mtr-1) (c c) (m m) (b b)) (deflistener (cat n (hash ncb bank-conf))) (precedes ((1 0) (2 0)) ((1 0) (5 0)) ((2 1) (0 0)) ((2 1) (3 0)) ((3 1) (4 2)) ((4 1) (3 0)) ((4 3) (1 1)) ((4 4) (1 2)) ((5 1) (4 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr-0 btr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation encryption-test (displaced 6 1 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)) (4 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 (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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 (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-0 mtr-1) (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-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 (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (privk "sig" m)))) ((recv (cat n (hash ncb bank-conf))) (send (cat n (hash ncb bank-conf))))) (label 335) (parent 327) (unrealized (5 0)) (comment "3 in cohort - 3 not yet seen")) (defskeleton minipay (vars (account account-0 acct) (cost amount) (n ncb ncm n-0 ncb-0 ncm-0 data) (item item-0 merchandise) (bank-conf btr mtr mtr-0 btr-0 mtr-1 merc-conf merc-conf-0 bank-conf-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 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr-0) (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-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-1) (c c) (m m) (b b)) (defstrand merc 5 (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 (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-0) (mtr mtr-1) (c c) (m m) (b b)) (deflistener (cat n (hash ncb bank-conf))) (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 ((1 0) (2 0)) ((1 0) (5 0)) ((2 1) (0 0)) ((2 1) (3 0)) ((3 1) (4 2)) ((4 1) (3 0)) ((4 3) (1 1)) ((4 4) (1 2)) ((5 1) (4 0)) ((6 0) (4 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr-0 btr-0 mtr-1) (facts (neq n-0 ncb-0) (neq n-0 ncm-0) (neq ncm-0 ncb-0) (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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)) (4 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 (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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 (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-0 mtr-1) (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-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 (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (privk "sig" m)))) ((recv (cat n (hash ncb bank-conf))) (send (cat n (hash ncb bank-conf)))) ((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 336) (parent 327) (unrealized (4 0) (5 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr mtr-0 btr-0 mtr-1 merc-conf mtr-2 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 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr-0) (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-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-1) (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-0) (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)) (deflistener (cat n (hash ncb bank-conf))) (precedes ((1 0) (2 0)) ((1 0) (5 0)) ((1 0) (6 0)) ((2 1) (0 0)) ((3 1) (4 2)) ((4 1) (3 0)) ((4 3) (1 1)) ((4 4) (1 2)) ((5 1) (3 0)) ((6 1) (4 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr-0 btr-0 mtr-1 mtr-2) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation encryption-test (displaced 7 1 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)) (4 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 (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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 (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-0 mtr-1) (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-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 (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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-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)))) ((recv (cat n (hash ncb bank-conf))) (send (cat n (hash ncb bank-conf))))) (label 337) (parent 329) (unrealized (6 0)) (comment "3 in cohort - 3 not yet seen")) (defskeleton minipay (vars (account account-0 acct) (cost amount) (n ncb ncm n-0 ncb-0 ncm-0 data) (item item-0 merchandise) (bank-conf btr mtr mtr-0 btr-0 mtr-1 merc-conf mtr-2 merc-conf-0 bank-conf-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 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr-0) (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-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-1) (c c) (m m) (b b)) (defstrand merc 5 (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 (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-0) (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)) (deflistener (cat n (hash ncb bank-conf))) (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 ((1 0) (2 0)) ((1 0) (5 0)) ((1 0) (6 0)) ((2 1) (0 0)) ((3 1) (4 2)) ((4 1) (3 0)) ((4 3) (1 1)) ((4 4) (1 2)) ((5 1) (3 0)) ((6 1) (4 0)) ((7 0) (4 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr-0 btr-0 mtr-1 mtr-2) (facts (neq n-0 ncb-0) (neq n-0 ncm-0) (neq ncm-0 ncb-0) (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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)) (4 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 (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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 (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-0 mtr-1) (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-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 (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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-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)))) ((recv (cat n (hash ncb bank-conf))) (send (cat n (hash ncb bank-conf)))) ((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 338) (parent 329) (unrealized (4 0) (6 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (vars (merc-conf-decommit mesg) (account account-0 acct) (cost cost-0 amount) (n ncb ncm n-0 data) (item merchandise) (bank-conf btr mtr mtr-0 merc-conf btr-0 mtr-1 text) (c m b c-0 m-0 b-0 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 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 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 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 bank 2 (merc-conf-decommit merc-conf-decommit) (account account-0) (cost cost-0) (n n-0) (ncb ncb) (bank-conf bank-conf) (btr btr-0) (mtr mtr-1) (c c-0) (m m-0) (b b-0)) (precedes ((0 1) (3 2)) ((1 0) (2 0)) ((2 1) (5 0)) ((3 1) (0 0)) ((3 3) (1 1)) ((3 4) (1 2)) ((4 1) (3 0)) ((5 1) (4 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr mtr-0 btr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation nonce-test (displaced 6 2 merc 2) ncb (5 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 (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 (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc 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 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 (payreq c-0 m-0 b-0 (hash cost-0 n-0) merc-conf-decommit mtr-1 (cat (sign (order c-0 m-0 b-0 cost-0 (enc n-0 cost-0 account-0 bank-conf ncb (hash n-0 merc-conf-decommit) (pubk "enc" b-0))) (privk "sig" c-0)) (enc n-0 cost-0 account-0 bank-conf ncb (hash n-0 merc-conf-decommit) (pubk "enc" b-0)))) (pubk "enc" b-0))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c-0 m-0 b-0 n-0 cost-0 (hash n-0 merc-conf-decommit)) btr-0 mtr-1) (privk "sig" b-0)) (pubk "enc" m-0))))) (label 339) (parent 330) (realized) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (vars (merc-conf-decommit mesg) (account account-0 acct) (cost cost-0 amount) (n ncb ncm n-0 data) (item merchandise) (bank-conf btr mtr mtr-0 merc-conf btr-0 mtr-1 mtr-2 text) (c m b c-0 m-0 b-0 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 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 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 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 bank 2 (merc-conf-decommit merc-conf-decommit) (account account-0) (cost cost-0) (n n-0) (ncb ncb) (bank-conf bank-conf) (btr btr-0) (mtr mtr-1) (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-2) (c c) (m m) (b b)) (precedes ((0 1) (3 2)) ((1 0) (2 0)) ((1 0) (6 0)) ((2 1) (4 0)) ((3 1) (0 0)) ((3 3) (1 1)) ((3 4) (1 2)) ((4 1) (3 0)) ((5 1) (4 0)) ((6 1) (5 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr mtr-0 btr-0 mtr-2) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation nonce-test (added-strand merc 2) ncb (5 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 (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 (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc 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 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 (payreq c-0 m-0 b-0 (hash cost-0 n-0) merc-conf-decommit mtr-1 (cat (sign (order c-0 m-0 b-0 cost-0 (enc n-0 cost-0 account-0 bank-conf ncb (hash n-0 merc-conf-decommit) (pubk "enc" b-0))) (privk "sig" c-0)) (enc n-0 cost-0 account-0 bank-conf ncb (hash n-0 merc-conf-decommit) (pubk "enc" b-0)))) (pubk "enc" b-0))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c-0 m-0 b-0 n-0 cost-0 (hash n-0 merc-conf-decommit)) btr-0 mtr-1) (privk "sig" b-0)) (pubk "enc" m-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-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 340) (parent 330) (realized) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (vars (merc-conf-decommit mesg) (account account-0 acct) (cost cost-0 amount) (n ncb ncm n-0 data) (item merchandise) (bank-conf btr mtr mtr-0 merc-conf btr-0 mtr-1 mtr-2 text) (c m b c-0 m-0 b-0 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 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 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 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 bank 2 (merc-conf-decommit merc-conf-decommit) (account account-0) (cost cost-0) (n n-0) (ncb ncb) (bank-conf bank-conf) (btr btr-0) (mtr mtr-1) (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-2) (c c) (m m) (b b)) (precedes ((0 1) (3 2)) ((1 0) (2 0)) ((1 0) (6 0)) ((2 1) (0 0)) ((3 1) (0 0)) ((3 3) (1 1)) ((3 4) (1 2)) ((4 1) (3 0)) ((5 1) (4 0)) ((6 1) (5 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr mtr-0 btr-0 mtr-2) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation nonce-test (displaced 7 6 merc 2) ncb (5 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 (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 (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc 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 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 (payreq c-0 m-0 b-0 (hash cost-0 n-0) merc-conf-decommit mtr-1 (cat (sign (order c-0 m-0 b-0 cost-0 (enc n-0 cost-0 account-0 bank-conf ncb (hash n-0 merc-conf-decommit) (pubk "enc" b-0))) (privk "sig" c-0)) (enc n-0 cost-0 account-0 bank-conf ncb (hash n-0 merc-conf-decommit) (pubk "enc" b-0)))) (pubk "enc" b-0))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c-0 m-0 b-0 n-0 cost-0 (hash n-0 merc-conf-decommit)) btr-0 mtr-1) (privk "sig" b-0)) (pubk "enc" m-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-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 341) (parent 331) (realized) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (vars (merc-conf-decommit mesg) (account account-0 acct) (cost cost-0 amount) (n ncb ncm n-0 data) (item merchandise) (bank-conf btr mtr mtr-0 merc-conf btr-0 mtr-1 mtr-2 mtr-3 text) (c m b c-0 m-0 b-0 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 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 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 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 bank 2 (merc-conf-decommit merc-conf-decommit) (account account-0) (cost cost-0) (n n-0) (ncb ncb) (bank-conf bank-conf) (btr btr-0) (mtr mtr-1) (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-2) (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-3) (c c) (m m) (b b)) (precedes ((0 1) (3 2)) ((1 0) (2 0)) ((1 0) (6 0)) ((1 0) (7 0)) ((2 1) (0 0)) ((3 1) (0 0)) ((3 3) (1 1)) ((3 4) (1 2)) ((4 1) (3 0)) ((5 1) (4 0)) ((6 1) (4 0)) ((7 1) (5 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr mtr-0 btr-0 mtr-2 mtr-3) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation nonce-test (added-strand merc 2) ncb (5 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 (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 (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc 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 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 (payreq c-0 m-0 b-0 (hash cost-0 n-0) merc-conf-decommit mtr-1 (cat (sign (order c-0 m-0 b-0 cost-0 (enc n-0 cost-0 account-0 bank-conf ncb (hash n-0 merc-conf-decommit) (pubk "enc" b-0))) (privk "sig" c-0)) (enc n-0 cost-0 account-0 bank-conf ncb (hash n-0 merc-conf-decommit) (pubk "enc" b-0)))) (pubk "enc" b-0))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c-0 m-0 b-0 n-0 cost-0 (hash n-0 merc-conf-decommit)) btr-0 mtr-1) (privk "sig" b-0)) (pubk "enc" m-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-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)))) ((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-3 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 342) (parent 331) (realized) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr mtr-0 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 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 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 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))) (deflistener (cat ncb bank-conf)) (precedes ((0 1) (3 2)) ((1 0) (2 0)) ((2 1) (5 0)) ((3 1) (0 0)) ((3 3) (1 1)) ((3 4) (1 2)) ((4 1) (3 0)) ((5 1) (4 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation nonce-test (displaced 6 2 merc 2) ncb (5 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 (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 (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc 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 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 (cat ncb bank-conf)) (send (cat ncb bank-conf)))) (label 343) (parent 332) (realized) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr mtr-0 merc-conf mtr-1 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 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 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 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))) (deflistener (cat 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-1) (c c) (m m) (b b)) (precedes ((0 1) (3 2)) ((1 0) (2 0)) ((1 0) (6 0)) ((2 1) (4 0)) ((3 1) (0 0)) ((3 3) (1 1)) ((3 4) (1 2)) ((4 1) (3 0)) ((5 1) (4 0)) ((6 1) (5 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr mtr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation nonce-test (added-strand merc 2) ncb (5 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 (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 (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc 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 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 (cat ncb bank-conf)) (send (cat 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-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 344) (parent 332) (realized) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr mtr-0 merc-conf mtr-1 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 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 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 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))) (deflistener (cat 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-1) (c c) (m m) (b b)) (precedes ((0 1) (3 2)) ((1 0) (2 0)) ((1 0) (6 0)) ((2 1) (0 0)) ((3 1) (0 0)) ((3 3) (1 1)) ((3 4) (1 2)) ((4 1) (3 0)) ((5 1) (4 0)) ((6 1) (5 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr mtr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation nonce-test (displaced 7 6 merc 2) ncb (5 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 (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 (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc 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 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 (cat ncb bank-conf)) (send (cat 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-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 345) (parent 333) (realized) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr mtr-0 merc-conf mtr-1 mtr-2 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 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 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 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))) (deflistener (cat 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-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 1) (3 2)) ((1 0) (2 0)) ((1 0) (6 0)) ((1 0) (7 0)) ((2 1) (0 0)) ((3 1) (0 0)) ((3 3) (1 1)) ((3 4) (1 2)) ((4 1) (3 0)) ((5 1) (4 0)) ((6 1) (4 0)) ((7 1) (5 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr mtr-0 mtr-1 mtr-2) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation nonce-test (added-strand merc 2) ncb (5 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 (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 (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc 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 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 (cat ncb bank-conf)) (send (cat 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-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 346) (parent 333) (realized) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr mtr-0 btr-0 mtr-1 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 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr-0) (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-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-1) (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-0) (mtr mtr-1) (c c) (m m) (b b)) (precedes ((1 0) (2 0)) ((1 0) (4 0)) ((2 1) (0 0)) ((2 1) (1 1)) ((3 1) (4 2)) ((4 1) (3 0)) ((4 3) (1 1)) ((4 4) (1 2))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr-0 btr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation generalization weakened ((2 1) (4 2))) (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 (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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 (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-0 mtr-1) (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-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 (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (privk "sig" m))))) (label 347) (parent 334) (realized) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr mtr-0 btr-0 mtr-1 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 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr-0) (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-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-1) (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-0) (mtr mtr-1) (c c) (m m) (b b)) (deflistener (cat n (hash ncb bank-conf))) (precedes ((0 1) (5 0)) ((1 0) (2 0)) ((2 1) (0 0)) ((3 1) (4 2)) ((4 1) (3 0)) ((4 3) (1 1)) ((4 4) (1 2)) ((5 1) (4 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr-0 btr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation encryption-test (displaced 6 0 bank 2) (hash ncb bank-conf) (5 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 (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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 (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-0 mtr-1) (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-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 (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (privk "sig" m)))) ((recv (cat n (hash ncb bank-conf))) (send (cat n (hash ncb bank-conf))))) (label 348) (parent 335) (realized) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (vars (merc-conf-decommit mesg) (account account-0 acct) (cost cost-0 amount) (n ncb ncm n-0 data) (item merchandise) (bank-conf btr mtr mtr-0 btr-0 mtr-1 merc-conf btr-1 mtr-2 text) (c m b c-0 m-0 b-0 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 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr-0) (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-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-1) (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-0) (mtr mtr-1) (c c) (m m) (b b)) (deflistener (cat n (hash ncb bank-conf))) (defstrand bank 2 (merc-conf-decommit merc-conf-decommit) (account account-0) (cost cost-0) (n n-0) (ncb ncb) (bank-conf bank-conf) (btr btr-1) (mtr mtr-2) (c c-0) (m m-0) (b b-0)) (precedes ((1 0) (2 0)) ((1 0) (6 0)) ((2 1) (0 0)) ((2 1) (3 0)) ((3 1) (4 2)) ((4 1) (3 0)) ((4 3) (1 1)) ((4 4) (1 2)) ((5 1) (4 0)) ((6 1) (5 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr-0 btr-0 mtr-1 btr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation encryption-test (added-strand bank 2) (hash ncb bank-conf) (5 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 (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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 (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-0 mtr-1) (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-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 (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (privk "sig" m)))) ((recv (cat n (hash ncb bank-conf))) (send (cat n (hash ncb bank-conf)))) ((recv (enc (payreq c-0 m-0 b-0 (hash cost-0 n-0) merc-conf-decommit mtr-2 (cat (sign (order c-0 m-0 b-0 cost-0 (enc n-0 cost-0 account-0 bank-conf ncb (hash n-0 merc-conf-decommit) (pubk "enc" b-0))) (privk "sig" c-0)) (enc n-0 cost-0 account-0 bank-conf ncb (hash n-0 merc-conf-decommit) (pubk "enc" b-0)))) (pubk "enc" b-0))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c-0 m-0 b-0 n-0 cost-0 (hash n-0 merc-conf-decommit)) btr-1 mtr-2) (privk "sig" b-0)) (pubk "enc" m-0))))) (label 349) (parent 335) (unrealized (5 0) (6 0)) (comment "2 in cohort - 2 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr mtr-0 btr-0 mtr-1 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 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr-0) (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-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-1) (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-0) (mtr mtr-1) (c c) (m m) (b b)) (deflistener (cat n (hash ncb bank-conf))) (deflistener (cat ncb bank-conf)) (precedes ((1 0) (2 0)) ((1 0) (6 0)) ((2 1) (0 0)) ((2 1) (3 0)) ((3 1) (4 2)) ((4 1) (3 0)) ((4 3) (1 1)) ((4 4) (1 2)) ((5 1) (4 0)) ((6 1) (5 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr-0 btr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation encryption-test (added-listener (cat ncb bank-conf)) (hash ncb bank-conf) (5 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 (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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 (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-0 mtr-1) (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-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 (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (privk "sig" m)))) ((recv (cat n (hash ncb bank-conf))) (send (cat n (hash ncb bank-conf)))) ((recv (cat ncb bank-conf)) (send (cat ncb bank-conf)))) (label 350) (parent 335) (unrealized (5 0) (6 0)) (comment "2 in cohort - 2 not yet seen")) (defskeleton minipay (vars (account account-0 acct) (cost amount) (n ncb ncm n-0 ncb-0 ncm-0 data) (item item-0 merchandise) (bank-conf btr mtr mtr-0 btr-0 mtr-1 merc-conf merc-conf-0 bank-conf-0 mtr-2 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 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr-0) (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-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-1) (c c) (m m) (b b)) (defstrand merc 5 (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 (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-0) (mtr mtr-1) (c c) (m m) (b b)) (deflistener (cat n (hash ncb bank-conf))) (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-2) (c c) (m m) (b b)) (precedes ((1 0) (2 0)) ((1 0) (5 0)) ((2 1) (0 0)) ((2 1) (3 0)) ((3 1) (4 2)) ((4 1) (3 0)) ((4 3) (1 1)) ((4 4) (1 2)) ((5 1) (4 0)) ((6 0) (4 0)) ((7 1) (4 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr-0 btr-0 mtr-1 mtr-2) (facts (neq n-0 ncb-0) (neq n-0 ncm-0) (neq ncm-0 ncb-0) (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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)) (4 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 (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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 (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-0 mtr-1) (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-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 (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (privk "sig" m)))) ((recv (cat n (hash ncb bank-conf))) (send (cat n (hash ncb bank-conf)))) ((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-2 (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 351) (parent 336) (unrealized (4 0) (5 0) (7 0)) (dead) (comment "empty cohort")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr mtr-0 btr-0 mtr-1 merc-conf mtr-2 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 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr-0) (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-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-1) (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-0) (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)) (deflistener (cat n (hash ncb bank-conf))) (precedes ((0 1) (6 0)) ((1 0) (2 0)) ((1 0) (5 0)) ((2 1) (0 0)) ((3 1) (4 2)) ((4 1) (3 0)) ((4 3) (1 1)) ((4 4) (1 2)) ((5 1) (3 0)) ((6 1) (4 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr-0 btr-0 mtr-1 mtr-2) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation encryption-test (displaced 7 0 bank 2) (hash ncb bank-conf) (6 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 (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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 (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-0 mtr-1) (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-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 (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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-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)))) ((recv (cat n (hash ncb bank-conf))) (send (cat n (hash ncb bank-conf))))) (label 352) (parent 337) (seen 348) (realized) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay (vars (merc-conf-decommit mesg) (account account-0 acct) (cost cost-0 amount) (n ncb ncm n-0 data) (item merchandise) (bank-conf btr mtr mtr-0 btr-0 mtr-1 merc-conf mtr-2 btr-1 mtr-3 text) (c m b c-0 m-0 b-0 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 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr-0) (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-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-1) (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-0) (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)) (deflistener (cat n (hash ncb bank-conf))) (defstrand bank 2 (merc-conf-decommit merc-conf-decommit) (account account-0) (cost cost-0) (n n-0) (ncb ncb) (bank-conf bank-conf) (btr btr-1) (mtr mtr-3) (c c-0) (m m-0) (b b-0)) (precedes ((1 0) (2 0)) ((1 0) (5 0)) ((1 0) (7 0)) ((2 1) (0 0)) ((3 1) (4 2)) ((4 1) (3 0)) ((4 3) (1 1)) ((4 4) (1 2)) ((5 1) (3 0)) ((6 1) (4 0)) ((7 1) (6 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr-0 btr-0 mtr-1 mtr-2 btr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation encryption-test (added-strand bank 2) (hash ncb bank-conf) (6 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 (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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 (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-0 mtr-1) (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-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 (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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-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)))) ((recv (cat n (hash ncb bank-conf))) (send (cat n (hash ncb bank-conf)))) ((recv (enc (payreq c-0 m-0 b-0 (hash cost-0 n-0) merc-conf-decommit mtr-3 (cat (sign (order c-0 m-0 b-0 cost-0 (enc n-0 cost-0 account-0 bank-conf ncb (hash n-0 merc-conf-decommit) (pubk "enc" b-0))) (privk "sig" c-0)) (enc n-0 cost-0 account-0 bank-conf ncb (hash n-0 merc-conf-decommit) (pubk "enc" b-0)))) (pubk "enc" b-0))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c-0 m-0 b-0 n-0 cost-0 (hash n-0 merc-conf-decommit)) btr-1 mtr-3) (privk "sig" b-0)) (pubk "enc" m-0))))) (label 353) (parent 337) (unrealized (6 0) (7 0)) (comment "3 in cohort - 3 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr mtr-0 btr-0 mtr-1 merc-conf mtr-2 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 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr-0) (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-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-1) (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-0) (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)) (deflistener (cat n (hash ncb bank-conf))) (deflistener (cat ncb bank-conf)) (precedes ((1 0) (2 0)) ((1 0) (5 0)) ((1 0) (7 0)) ((2 1) (0 0)) ((3 1) (4 2)) ((4 1) (3 0)) ((4 3) (1 1)) ((4 4) (1 2)) ((5 1) (3 0)) ((6 1) (4 0)) ((7 1) (6 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr-0 btr-0 mtr-1 mtr-2) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation encryption-test (added-listener (cat ncb bank-conf)) (hash ncb bank-conf) (6 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 (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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 (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-0 mtr-1) (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-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 (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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-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)))) ((recv (cat n (hash ncb bank-conf))) (send (cat n (hash ncb bank-conf)))) ((recv (cat ncb bank-conf)) (send (cat ncb bank-conf)))) (label 354) (parent 337) (unrealized (6 0) (7 0)) (comment "3 in cohort - 3 not yet seen")) (defskeleton minipay (vars (account account-0 acct) (cost amount) (n ncb ncm n-0 ncb-0 ncm-0 data) (item item-0 merchandise) (bank-conf btr mtr mtr-0 btr-0 mtr-1 merc-conf mtr-2 merc-conf-0 bank-conf-0 mtr-3 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 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr-0) (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-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-1) (c c) (m m) (b b)) (defstrand merc 5 (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 (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-0) (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)) (deflistener (cat n (hash ncb bank-conf))) (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-3) (c c) (m m) (b b)) (precedes ((1 0) (2 0)) ((1 0) (5 0)) ((1 0) (6 0)) ((2 1) (0 0)) ((3 1) (4 2)) ((4 1) (3 0)) ((4 3) (1 1)) ((4 4) (1 2)) ((5 1) (3 0)) ((6 1) (4 0)) ((7 0) (4 0)) ((8 1) (4 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr-0 btr-0 mtr-1 mtr-2 mtr-3) (facts (neq n-0 ncb-0) (neq n-0 ncm-0) (neq ncm-0 ncb-0) (neq n ncb) (neq n ncm) (neq ncm ncb)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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)) (4 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 (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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 (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-0 mtr-1) (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-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 (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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-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)))) ((recv (cat n (hash ncb bank-conf))) (send (cat n (hash ncb bank-conf)))) ((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-3 (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 355) (parent 338) (unrealized (4 0) (6 0) (8 0)) (dead) (comment "empty cohort")) (defskeleton minipay (vars (merc-conf-decommit mesg) (account account-0 acct) (cost cost-0 amount) (n ncb ncm n-0 data) (item merchandise) (bank-conf btr mtr mtr-0 merc-conf btr-0 mtr-1 text) (c m b c-0 m-0 b-0 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 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 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 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 bank 2 (merc-conf-decommit merc-conf-decommit) (account account-0) (cost cost-0) (n n-0) (ncb ncb) (bank-conf bank-conf) (btr btr-0) (mtr mtr-1) (c c-0) (m m-0) (b b-0)) (precedes ((0 1) (3 2)) ((1 0) (2 0)) ((2 1) (4 0)) ((3 1) (0 0)) ((3 3) (1 1)) ((3 4) (1 2)) ((4 1) (3 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr mtr-0 btr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation generalization deleted (4 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 (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 (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc 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 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 (payreq c-0 m-0 b-0 (hash cost-0 n-0) merc-conf-decommit mtr-1 (cat (sign (order c-0 m-0 b-0 cost-0 (enc n-0 cost-0 account-0 bank-conf ncb (hash n-0 merc-conf-decommit) (pubk "enc" b-0))) (privk "sig" c-0)) (enc n-0 cost-0 account-0 bank-conf ncb (hash n-0 merc-conf-decommit) (pubk "enc" b-0)))) (pubk "enc" b-0))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c-0 m-0 b-0 n-0 cost-0 (hash n-0 merc-conf-decommit)) btr-0 mtr-1) (privk "sig" b-0)) (pubk "enc" m-0))))) (label 356) (parent 339) (realized) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (vars (merc-conf-decommit mesg) (account account-0 acct) (cost cost-0 amount) (n ncb ncm n-0 data) (item merchandise) (bank-conf btr mtr mtr-0 merc-conf btr-0 mtr-1 mtr-2 text) (c m b c-0 m-0 b-0 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 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 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 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 bank 2 (merc-conf-decommit merc-conf-decommit) (account account-0) (cost cost-0) (n n-0) (ncb ncb) (bank-conf bank-conf) (btr btr-0) (mtr mtr-1) (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-2) (c c) (m m) (b b)) (precedes ((0 1) (3 2)) ((1 0) (2 0)) ((1 0) (5 0)) ((2 1) (3 0)) ((3 1) (0 0)) ((3 3) (1 1)) ((3 4) (1 2)) ((4 1) (3 0)) ((5 1) (4 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr mtr-0 btr-0 mtr-2) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation generalization deleted (4 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 (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 (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc 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 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 (payreq c-0 m-0 b-0 (hash cost-0 n-0) merc-conf-decommit mtr-1 (cat (sign (order c-0 m-0 b-0 cost-0 (enc n-0 cost-0 account-0 bank-conf ncb (hash n-0 merc-conf-decommit) (pubk "enc" b-0))) (privk "sig" c-0)) (enc n-0 cost-0 account-0 bank-conf ncb (hash n-0 merc-conf-decommit) (pubk "enc" b-0)))) (pubk "enc" b-0))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c-0 m-0 b-0 n-0 cost-0 (hash n-0 merc-conf-decommit)) btr-0 mtr-1) (privk "sig" b-0)) (pubk "enc" m-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-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 357) (parent 340) (realized) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (vars (merc-conf-decommit mesg) (account account-0 acct) (cost cost-0 amount) (n ncb ncm n-0 data) (item merchandise) (bank-conf btr mtr mtr-0 merc-conf btr-0 mtr-1 mtr-2 text) (c m b c-0 m-0 b-0 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 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 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 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 bank 2 (merc-conf-decommit merc-conf-decommit) (account account-0) (cost cost-0) (n n-0) (ncb ncb) (bank-conf bank-conf) (btr btr-0) (mtr mtr-1) (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-2) (c c) (m m) (b b)) (precedes ((0 1) (3 2)) ((1 0) (2 0)) ((1 0) (5 0)) ((2 1) (0 0)) ((3 1) (0 0)) ((3 3) (1 1)) ((3 4) (1 2)) ((4 1) (3 0)) ((5 1) (4 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr mtr-0 btr-0 mtr-2) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation generalization deleted (4 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 (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 (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc 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 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 (payreq c-0 m-0 b-0 (hash cost-0 n-0) merc-conf-decommit mtr-1 (cat (sign (order c-0 m-0 b-0 cost-0 (enc n-0 cost-0 account-0 bank-conf ncb (hash n-0 merc-conf-decommit) (pubk "enc" b-0))) (privk "sig" c-0)) (enc n-0 cost-0 account-0 bank-conf ncb (hash n-0 merc-conf-decommit) (pubk "enc" b-0)))) (pubk "enc" b-0))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c-0 m-0 b-0 n-0 cost-0 (hash n-0 merc-conf-decommit)) btr-0 mtr-1) (privk "sig" b-0)) (pubk "enc" m-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-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 358) (parent 341) (realized) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (vars (merc-conf-decommit mesg) (account account-0 acct) (cost cost-0 amount) (n ncb ncm n-0 data) (item merchandise) (bank-conf btr mtr mtr-0 merc-conf btr-0 mtr-1 mtr-2 mtr-3 text) (c m b c-0 m-0 b-0 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 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 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 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 bank 2 (merc-conf-decommit merc-conf-decommit) (account account-0) (cost cost-0) (n n-0) (ncb ncb) (bank-conf bank-conf) (btr btr-0) (mtr mtr-1) (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-2) (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-3) (c c) (m m) (b b)) (precedes ((0 1) (3 2)) ((1 0) (2 0)) ((1 0) (5 0)) ((1 0) (6 0)) ((2 1) (0 0)) ((3 1) (0 0)) ((3 3) (1 1)) ((3 4) (1 2)) ((4 1) (3 0)) ((5 1) (3 0)) ((6 1) (4 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr mtr-0 btr-0 mtr-2 mtr-3) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation generalization deleted (4 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 (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 (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc 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 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 (payreq c-0 m-0 b-0 (hash cost-0 n-0) merc-conf-decommit mtr-1 (cat (sign (order c-0 m-0 b-0 cost-0 (enc n-0 cost-0 account-0 bank-conf ncb (hash n-0 merc-conf-decommit) (pubk "enc" b-0))) (privk "sig" c-0)) (enc n-0 cost-0 account-0 bank-conf ncb (hash n-0 merc-conf-decommit) (pubk "enc" b-0)))) (pubk "enc" b-0))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c-0 m-0 b-0 n-0 cost-0 (hash n-0 merc-conf-decommit)) btr-0 mtr-1) (privk "sig" b-0)) (pubk "enc" m-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-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)))) ((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-3 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 359) (parent 342) (realized) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr mtr-0 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 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 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 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 ncb bank-conf)) (precedes ((0 1) (3 2)) ((1 0) (2 0)) ((2 1) (4 0)) ((3 1) (0 0)) ((3 3) (1 1)) ((3 4) (1 2)) ((4 1) (3 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation generalization deleted (4 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 (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 (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc 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 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 ncb bank-conf)) (send (cat ncb bank-conf)))) (label 360) (parent 343) (seen 376) (realized) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr mtr-0 merc-conf mtr-1 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 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 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 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 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-1) (c c) (m m) (b b)) (precedes ((0 1) (3 2)) ((1 0) (2 0)) ((1 0) (5 0)) ((2 1) (3 0)) ((3 1) (0 0)) ((3 3) (1 1)) ((3 4) (1 2)) ((4 1) (3 0)) ((5 1) (4 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr mtr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation generalization deleted (4 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 (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 (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc 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 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 ncb bank-conf)) (send (cat 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-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 361) (parent 344) (seen 377) (realized) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr mtr-0 merc-conf mtr-1 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 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 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 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 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-1) (c c) (m m) (b b)) (precedes ((0 1) (3 2)) ((1 0) (2 0)) ((1 0) (5 0)) ((2 1) (0 0)) ((3 1) (0 0)) ((3 3) (1 1)) ((3 4) (1 2)) ((4 1) (3 0)) ((5 1) (4 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr mtr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation generalization deleted (4 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 (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 (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc 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 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 ncb bank-conf)) (send (cat 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-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 362) (parent 345) (seen 378) (realized) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr mtr-0 merc-conf mtr-1 mtr-2 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 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 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 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 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-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 1) (3 2)) ((1 0) (2 0)) ((1 0) (5 0)) ((1 0) (6 0)) ((2 1) (0 0)) ((3 1) (0 0)) ((3 3) (1 1)) ((3 4) (1 2)) ((4 1) (3 0)) ((5 1) (3 0)) ((6 1) (4 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr mtr-0 mtr-1 mtr-2) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation generalization deleted (4 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 (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 (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc 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 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 ncb bank-conf)) (send (cat 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-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 363) (parent 346) (seen 379) (realized) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr mtr-0 btr-0 mtr-1 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 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr-0) (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-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-1) (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-0) (mtr mtr-1) (c c) (m m) (b b)) (precedes ((1 0) (2 0)) ((1 0) (4 0)) ((2 1) (0 0)) ((2 1) (1 2)) ((3 1) (4 2)) ((4 1) (3 0)) ((4 3) (1 1)) ((4 4) (1 2))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr-0 btr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation generalization weakened ((2 1) (1 1))) (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 (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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 (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-0 mtr-1) (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-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 (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (privk "sig" m))))) (label 364) (parent 347) (seen 321) (realized) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr mtr-0 btr-0 mtr-1 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 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr-0) (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-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-1) (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-0) (mtr mtr-1) (c c) (m m) (b b)) (precedes ((0 1) (4 0)) ((1 0) (2 0)) ((2 1) (0 0)) ((3 1) (4 2)) ((4 1) (3 0)) ((4 3) (1 1)) ((4 4) (1 2))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr-0 btr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation generalization deleted (5 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 (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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 (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-0 mtr-1) (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-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 (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (privk "sig" m))))) (label 365) (parent 348) (realized) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (vars (merc-conf-decommit mesg) (account account-0 acct) (cost cost-0 amount) (n ncb ncm n-0 data) (item merchandise) (bank-conf btr mtr mtr-0 btr-0 mtr-1 merc-conf btr-1 mtr-2 text) (c m b c-0 m-0 b-0 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 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr-0) (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-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-1) (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-0) (mtr mtr-1) (c c) (m m) (b b)) (deflistener (cat n (hash ncb bank-conf))) (defstrand bank 2 (merc-conf-decommit merc-conf-decommit) (account account-0) (cost cost-0) (n n-0) (ncb ncb) (bank-conf bank-conf) (btr btr-1) (mtr mtr-2) (c c-0) (m m-0) (b b-0)) (precedes ((1 0) (2 0)) ((1 0) (6 0)) ((2 1) (0 0)) ((2 1) (5 0)) ((3 1) (4 2)) ((4 1) (3 0)) ((4 3) (1 1)) ((4 4) (1 2)) ((5 1) (4 0)) ((6 1) (5 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr-0 btr-0 mtr-1 btr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation nonce-test (displaced 7 2 merc 2) n (5 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 (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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 (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-0 mtr-1) (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-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 (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (privk "sig" m)))) ((recv (cat n (hash ncb bank-conf))) (send (cat n (hash ncb bank-conf)))) ((recv (enc (payreq c-0 m-0 b-0 (hash cost-0 n-0) merc-conf-decommit mtr-2 (cat (sign (order c-0 m-0 b-0 cost-0 (enc n-0 cost-0 account-0 bank-conf ncb (hash n-0 merc-conf-decommit) (pubk "enc" b-0))) (privk "sig" c-0)) (enc n-0 cost-0 account-0 bank-conf ncb (hash n-0 merc-conf-decommit) (pubk "enc" b-0)))) (pubk "enc" b-0))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c-0 m-0 b-0 n-0 cost-0 (hash n-0 merc-conf-decommit)) btr-1 mtr-2) (privk "sig" b-0)) (pubk "enc" m-0))))) (label 366) (parent 349) (unrealized (6 0)) (comment "2 in cohort - 2 not yet seen")) (defskeleton minipay (vars (merc-conf-decommit mesg) (account account-0 acct) (cost cost-0 amount) (n ncb ncm n-0 data) (item merchandise) (bank-conf btr mtr mtr-0 btr-0 mtr-1 merc-conf btr-1 mtr-2 mtr-3 text) (c m b c-0 m-0 b-0 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 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr-0) (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-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-1) (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-0) (mtr mtr-1) (c c) (m m) (b b)) (deflistener (cat n (hash ncb bank-conf))) (defstrand bank 2 (merc-conf-decommit merc-conf-decommit) (account account-0) (cost cost-0) (n n-0) (ncb ncb) (bank-conf bank-conf) (btr btr-1) (mtr mtr-2) (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-3) (c c) (m m) (b b)) (precedes ((1 0) (2 0)) ((1 0) (6 0)) ((1 0) (7 0)) ((2 1) (0 0)) ((2 1) (3 0)) ((3 1) (4 2)) ((4 1) (3 0)) ((4 3) (1 1)) ((4 4) (1 2)) ((5 1) (4 0)) ((6 1) (5 0)) ((7 1) (5 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr-0 btr-0 mtr-1 btr-1 mtr-3) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation nonce-test (added-strand merc 2) n (5 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 (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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 (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-0 mtr-1) (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-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 (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (privk "sig" m)))) ((recv (cat n (hash ncb bank-conf))) (send (cat n (hash ncb bank-conf)))) ((recv (enc (payreq c-0 m-0 b-0 (hash cost-0 n-0) merc-conf-decommit mtr-2 (cat (sign (order c-0 m-0 b-0 cost-0 (enc n-0 cost-0 account-0 bank-conf ncb (hash n-0 merc-conf-decommit) (pubk "enc" b-0))) (privk "sig" c-0)) (enc n-0 cost-0 account-0 bank-conf ncb (hash n-0 merc-conf-decommit) (pubk "enc" b-0)))) (pubk "enc" b-0))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c-0 m-0 b-0 n-0 cost-0 (hash n-0 merc-conf-decommit)) btr-1 mtr-2) (privk "sig" b-0)) (pubk "enc" m-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-3 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 367) (parent 349) (unrealized (6 0)) (comment "3 in cohort - 3 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr mtr-0 btr-0 mtr-1 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 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr-0) (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-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-1) (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-0) (mtr mtr-1) (c c) (m m) (b b)) (deflistener (cat n (hash ncb bank-conf))) (deflistener (cat ncb bank-conf)) (precedes ((1 0) (2 0)) ((1 0) (6 0)) ((2 1) (0 0)) ((2 1) (5 0)) ((3 1) (4 2)) ((4 1) (3 0)) ((4 3) (1 1)) ((4 4) (1 2)) ((5 1) (4 0)) ((6 1) (5 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr-0 btr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation nonce-test (displaced 7 2 merc 2) n (5 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 (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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 (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-0 mtr-1) (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-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 (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (privk "sig" m)))) ((recv (cat n (hash ncb bank-conf))) (send (cat n (hash ncb bank-conf)))) ((recv (cat ncb bank-conf)) (send (cat ncb bank-conf)))) (label 368) (parent 350) (unrealized (6 0)) (comment "2 in cohort - 2 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr mtr-0 btr-0 mtr-1 merc-conf mtr-2 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 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr-0) (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-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-1) (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-0) (mtr mtr-1) (c c) (m m) (b b)) (deflistener (cat n (hash ncb bank-conf))) (deflistener (cat 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-2) (c c) (m m) (b b)) (precedes ((1 0) (2 0)) ((1 0) (6 0)) ((1 0) (7 0)) ((2 1) (0 0)) ((2 1) (3 0)) ((3 1) (4 2)) ((4 1) (3 0)) ((4 3) (1 1)) ((4 4) (1 2)) ((5 1) (4 0)) ((6 1) (5 0)) ((7 1) (5 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr-0 btr-0 mtr-1 mtr-2) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation nonce-test (added-strand merc 2) n (5 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 (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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 (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-0 mtr-1) (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-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 (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (privk "sig" m)))) ((recv (cat n (hash ncb bank-conf))) (send (cat n (hash ncb bank-conf)))) ((recv (cat ncb bank-conf)) (send (cat 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-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 369) (parent 350) (unrealized (6 0)) (comment "3 in cohort - 3 not yet seen")) (defskeleton minipay (vars (merc-conf-decommit mesg) (account account-0 acct) (cost cost-0 amount) (n ncb ncm n-0 data) (item merchandise) (bank-conf btr mtr mtr-0 btr-0 mtr-1 merc-conf mtr-2 btr-1 mtr-3 text) (c m b c-0 m-0 b-0 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 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr-0) (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-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-1) (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-0) (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)) (deflistener (cat n (hash ncb bank-conf))) (defstrand bank 2 (merc-conf-decommit merc-conf-decommit) (account account-0) (cost cost-0) (n n-0) (ncb ncb) (bank-conf bank-conf) (btr btr-1) (mtr mtr-3) (c c-0) (m m-0) (b b-0)) (precedes ((1 0) (2 0)) ((1 0) (5 0)) ((1 0) (7 0)) ((2 1) (0 0)) ((2 1) (6 0)) ((3 1) (4 2)) ((4 1) (3 0)) ((4 3) (1 1)) ((4 4) (1 2)) ((5 1) (3 0)) ((6 1) (4 0)) ((7 1) (6 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr-0 btr-0 mtr-1 mtr-2 btr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation nonce-test (displaced 8 2 merc 2) n (6 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 (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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 (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-0 mtr-1) (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-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 (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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-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)))) ((recv (cat n (hash ncb bank-conf))) (send (cat n (hash ncb bank-conf)))) ((recv (enc (payreq c-0 m-0 b-0 (hash cost-0 n-0) merc-conf-decommit mtr-3 (cat (sign (order c-0 m-0 b-0 cost-0 (enc n-0 cost-0 account-0 bank-conf ncb (hash n-0 merc-conf-decommit) (pubk "enc" b-0))) (privk "sig" c-0)) (enc n-0 cost-0 account-0 bank-conf ncb (hash n-0 merc-conf-decommit) (pubk "enc" b-0)))) (pubk "enc" b-0))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c-0 m-0 b-0 n-0 cost-0 (hash n-0 merc-conf-decommit)) btr-1 mtr-3) (privk "sig" b-0)) (pubk "enc" m-0))))) (label 370) (parent 353) (seen 382) (unrealized (7 0)) (comment "3 in cohort - 2 not yet seen")) (defskeleton minipay (vars (merc-conf-decommit mesg) (account account-0 acct) (cost cost-0 amount) (n ncb ncm n-0 data) (item merchandise) (bank-conf btr mtr mtr-0 btr-0 mtr-1 merc-conf mtr-2 btr-1 mtr-3 text) (c m b c-0 m-0 b-0 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 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr-0) (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-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-1) (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-0) (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)) (deflistener (cat n (hash ncb bank-conf))) (defstrand bank 2 (merc-conf-decommit merc-conf-decommit) (account account-0) (cost cost-0) (n n-0) (ncb ncb) (bank-conf bank-conf) (btr btr-1) (mtr mtr-3) (c c-0) (m m-0) (b b-0)) (precedes ((1 0) (2 0)) ((1 0) (5 0)) ((1 0) (7 0)) ((2 1) (0 0)) ((3 1) (4 2)) ((4 1) (3 0)) ((4 3) (1 1)) ((4 4) (1 2)) ((5 1) (6 0)) ((6 1) (4 0)) ((7 1) (6 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr-0 btr-0 mtr-1 mtr-2 btr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation nonce-test (displaced 8 5 merc 2) n (6 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 (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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 (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-0 mtr-1) (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-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 (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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-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)))) ((recv (cat n (hash ncb bank-conf))) (send (cat n (hash ncb bank-conf)))) ((recv (enc (payreq c-0 m-0 b-0 (hash cost-0 n-0) merc-conf-decommit mtr-3 (cat (sign (order c-0 m-0 b-0 cost-0 (enc n-0 cost-0 account-0 bank-conf ncb (hash n-0 merc-conf-decommit) (pubk "enc" b-0))) (privk "sig" c-0)) (enc n-0 cost-0 account-0 bank-conf ncb (hash n-0 merc-conf-decommit) (pubk "enc" b-0)))) (pubk "enc" b-0))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c-0 m-0 b-0 n-0 cost-0 (hash n-0 merc-conf-decommit)) btr-1 mtr-3) (privk "sig" b-0)) (pubk "enc" m-0))))) (label 371) (parent 353) (seen 383) (unrealized (7 0)) (comment "3 in cohort - 2 not yet seen")) (defskeleton minipay (vars (merc-conf-decommit mesg) (account account-0 acct) (cost cost-0 amount) (n ncb ncm n-0 data) (item merchandise) (bank-conf btr mtr mtr-0 btr-0 mtr-1 merc-conf mtr-2 btr-1 mtr-3 mtr-4 text) (c m b c-0 m-0 b-0 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 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr-0) (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-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-1) (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-0) (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)) (deflistener (cat n (hash ncb bank-conf))) (defstrand bank 2 (merc-conf-decommit merc-conf-decommit) (account account-0) (cost cost-0) (n n-0) (ncb ncb) (bank-conf bank-conf) (btr btr-1) (mtr mtr-3) (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-4) (c c) (m m) (b b)) (precedes ((1 0) (2 0)) ((1 0) (5 0)) ((1 0) (7 0)) ((1 0) (8 0)) ((2 1) (0 0)) ((3 1) (4 2)) ((4 1) (3 0)) ((4 3) (1 1)) ((4 4) (1 2)) ((5 1) (3 0)) ((6 1) (4 0)) ((7 1) (6 0)) ((8 1) (6 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr-0 btr-0 mtr-1 mtr-2 btr-1 mtr-4) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation nonce-test (added-strand merc 2) n (6 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 (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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 (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-0 mtr-1) (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-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 (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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-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)))) ((recv (cat n (hash ncb bank-conf))) (send (cat n (hash ncb bank-conf)))) ((recv (enc (payreq c-0 m-0 b-0 (hash cost-0 n-0) merc-conf-decommit mtr-3 (cat (sign (order c-0 m-0 b-0 cost-0 (enc n-0 cost-0 account-0 bank-conf ncb (hash n-0 merc-conf-decommit) (pubk "enc" b-0))) (privk "sig" c-0)) (enc n-0 cost-0 account-0 bank-conf ncb (hash n-0 merc-conf-decommit) (pubk "enc" b-0)))) (pubk "enc" b-0))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c-0 m-0 b-0 n-0 cost-0 (hash n-0 merc-conf-decommit)) btr-1 mtr-3) (privk "sig" b-0)) (pubk "enc" m-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-4 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 372) (parent 353) (seen 394) (unrealized (7 0)) (comment "4 in cohort - 3 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr mtr-0 btr-0 mtr-1 merc-conf mtr-2 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 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr-0) (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-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-1) (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-0) (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)) (deflistener (cat n (hash ncb bank-conf))) (deflistener (cat ncb bank-conf)) (precedes ((1 0) (2 0)) ((1 0) (5 0)) ((1 0) (7 0)) ((2 1) (0 0)) ((2 1) (6 0)) ((3 1) (4 2)) ((4 1) (3 0)) ((4 3) (1 1)) ((4 4) (1 2)) ((5 1) (3 0)) ((6 1) (4 0)) ((7 1) (6 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr-0 btr-0 mtr-1 mtr-2) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation nonce-test (displaced 8 2 merc 2) n (6 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 (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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 (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-0 mtr-1) (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-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 (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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-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)))) ((recv (cat n (hash ncb bank-conf))) (send (cat n (hash ncb bank-conf)))) ((recv (cat ncb bank-conf)) (send (cat ncb bank-conf)))) (label 373) (parent 354) (seen 387) (unrealized (7 0)) (comment "3 in cohort - 2 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr mtr-0 btr-0 mtr-1 merc-conf mtr-2 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 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr-0) (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-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-1) (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-0) (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)) (deflistener (cat n (hash ncb bank-conf))) (deflistener (cat ncb bank-conf)) (precedes ((1 0) (2 0)) ((1 0) (5 0)) ((1 0) (7 0)) ((2 1) (0 0)) ((3 1) (4 2)) ((4 1) (3 0)) ((4 3) (1 1)) ((4 4) (1 2)) ((5 1) (6 0)) ((6 1) (4 0)) ((7 1) (6 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr-0 btr-0 mtr-1 mtr-2) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation nonce-test (displaced 8 5 merc 2) n (6 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 (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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 (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-0 mtr-1) (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-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 (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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-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)))) ((recv (cat n (hash ncb bank-conf))) (send (cat n (hash ncb bank-conf)))) ((recv (cat ncb bank-conf)) (send (cat ncb bank-conf)))) (label 374) (parent 354) (seen 388) (unrealized (7 0)) (comment "3 in cohort - 2 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr mtr-0 btr-0 mtr-1 merc-conf mtr-2 mtr-3 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 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr-0) (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-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-1) (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-0) (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)) (deflistener (cat n (hash ncb bank-conf))) (deflistener (cat 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-3) (c c) (m m) (b b)) (precedes ((1 0) (2 0)) ((1 0) (5 0)) ((1 0) (7 0)) ((1 0) (8 0)) ((2 1) (0 0)) ((3 1) (4 2)) ((4 1) (3 0)) ((4 3) (1 1)) ((4 4) (1 2)) ((5 1) (3 0)) ((6 1) (4 0)) ((7 1) (6 0)) ((8 1) (6 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr-0 btr-0 mtr-1 mtr-2 mtr-3) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation nonce-test (added-strand merc 2) n (6 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 (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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 (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-0 mtr-1) (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-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 (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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-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)))) ((recv (cat n (hash ncb bank-conf))) (send (cat n (hash ncb bank-conf)))) ((recv (cat ncb bank-conf)) (send (cat 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-3 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 375) (parent 354) (seen 401) (unrealized (7 0)) (comment "4 in cohort - 3 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr mtr-0 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 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 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 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 1) (3 2)) ((1 0) (2 0)) ((2 1) (3 0)) ((3 1) (0 0)) ((3 3) (1 1)) ((3 4) (1 2))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr mtr-0) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation generalization deleted (4 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 (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 (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc 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 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 376) (parent 356) (seen 314) (realized) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr mtr-0 merc-conf mtr-1 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 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 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 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-1) (c c) (m m) (b b)) (precedes ((0 1) (3 2)) ((1 0) (2 0)) ((1 0) (4 0)) ((2 1) (3 0)) ((3 1) (0 0)) ((3 3) (1 1)) ((3 4) (1 2)) ((4 1) (3 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr mtr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation generalization deleted (4 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 (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 (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc 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 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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-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 377) (parent 357) (seen 376) (realized) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr mtr-0 merc-conf mtr-1 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 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 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 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-1) (c c) (m m) (b b)) (precedes ((0 1) (3 2)) ((1 0) (2 0)) ((1 0) (4 0)) ((2 1) (0 0)) ((3 1) (0 0)) ((3 3) (1 1)) ((3 4) (1 2)) ((4 1) (3 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr mtr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation generalization deleted (4 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 (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 (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc 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 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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-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 378) (parent 358) (seen 314) (realized) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr mtr-0 merc-conf mtr-1 mtr-2 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 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 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 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-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 1) (3 2)) ((1 0) (2 0)) ((1 0) (4 0)) ((1 0) (5 0)) ((2 1) (0 0)) ((3 1) (0 0)) ((3 3) (1 1)) ((3 4) (1 2)) ((4 1) (3 0)) ((5 1) (3 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr mtr-0 mtr-1 mtr-2) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation generalization deleted (4 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 (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 (hash n (hash ncb bank-conf)) (sign (order c m b cost (enc 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 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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-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 379) (parent 359) (seen 378) (realized) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr mtr-0 btr-0 mtr-1 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 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr-0) (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-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-1) (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-0) (mtr mtr-1) (c c) (m m) (b b)) (precedes ((0 1) (3 0)) ((1 0) (2 0)) ((2 1) (0 0)) ((2 1) (4 0)) ((3 1) (4 2)) ((4 1) (3 0)) ((4 3) (1 1)) ((4 4) (1 2))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr-0 btr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation generalization weakened ((0 1) (4 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 (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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 (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-0 mtr-1) (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-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 (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (privk "sig" m))))) (label 380) (parent 365) (realized) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (vars (merc-conf-decommit mesg) (account account-0 acct) (cost cost-0 amount) (n ncb ncm n-0 data) (item merchandise) (bank-conf btr mtr mtr-0 btr-0 mtr-1 merc-conf btr-1 mtr-2 text) (c m b c-0 m-0 b-0 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 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr-0) (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-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-1) (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-0) (mtr mtr-1) (c c) (m m) (b b)) (deflistener (cat n (hash ncb bank-conf))) (defstrand bank 2 (merc-conf-decommit merc-conf-decommit) (account account-0) (cost cost-0) (n n-0) (ncb ncb) (bank-conf bank-conf) (btr btr-1) (mtr mtr-2) (c c-0) (m m-0) (b b-0)) (precedes ((1 0) (2 0)) ((2 1) (0 0)) ((2 1) (6 0)) ((3 1) (4 2)) ((4 1) (3 0)) ((4 3) (1 1)) ((4 4) (1 2)) ((5 1) (4 0)) ((6 1) (5 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr-0 btr-0 mtr-1 btr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation nonce-test (displaced 7 2 merc 2) ncb (6 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 (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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 (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-0 mtr-1) (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-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 (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (privk "sig" m)))) ((recv (cat n (hash ncb bank-conf))) (send (cat n (hash ncb bank-conf)))) ((recv (enc (payreq c-0 m-0 b-0 (hash cost-0 n-0) merc-conf-decommit mtr-2 (cat (sign (order c-0 m-0 b-0 cost-0 (enc n-0 cost-0 account-0 bank-conf ncb (hash n-0 merc-conf-decommit) (pubk "enc" b-0))) (privk "sig" c-0)) (enc n-0 cost-0 account-0 bank-conf ncb (hash n-0 merc-conf-decommit) (pubk "enc" b-0)))) (pubk "enc" b-0))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c-0 m-0 b-0 n-0 cost-0 (hash n-0 merc-conf-decommit)) btr-1 mtr-2) (privk "sig" b-0)) (pubk "enc" m-0))))) (label 381) (parent 366) (realized) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (vars (merc-conf-decommit mesg) (account account-0 acct) (cost cost-0 amount) (n ncb ncm n-0 data) (item merchandise) (bank-conf btr mtr mtr-0 btr-0 mtr-1 merc-conf btr-1 mtr-2 mtr-3 text) (c m b c-0 m-0 b-0 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 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr-0) (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-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-1) (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-0) (mtr mtr-1) (c c) (m m) (b b)) (deflistener (cat n (hash ncb bank-conf))) (defstrand bank 2 (merc-conf-decommit merc-conf-decommit) (account account-0) (cost cost-0) (n n-0) (ncb ncb) (bank-conf bank-conf) (btr btr-1) (mtr mtr-2) (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-3) (c c) (m m) (b b)) (precedes ((1 0) (2 0)) ((1 0) (7 0)) ((2 1) (0 0)) ((2 1) (5 0)) ((3 1) (4 2)) ((4 1) (3 0)) ((4 3) (1 1)) ((4 4) (1 2)) ((5 1) (4 0)) ((6 1) (5 0)) ((7 1) (6 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr-0 btr-0 mtr-1 btr-1 mtr-3) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation nonce-test (added-strand merc 2) ncb (6 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 (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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 (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-0 mtr-1) (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-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 (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (privk "sig" m)))) ((recv (cat n (hash ncb bank-conf))) (send (cat n (hash ncb bank-conf)))) ((recv (enc (payreq c-0 m-0 b-0 (hash cost-0 n-0) merc-conf-decommit mtr-2 (cat (sign (order c-0 m-0 b-0 cost-0 (enc n-0 cost-0 account-0 bank-conf ncb (hash n-0 merc-conf-decommit) (pubk "enc" b-0))) (privk "sig" c-0)) (enc n-0 cost-0 account-0 bank-conf ncb (hash n-0 merc-conf-decommit) (pubk "enc" b-0)))) (pubk "enc" b-0))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c-0 m-0 b-0 n-0 cost-0 (hash n-0 merc-conf-decommit)) btr-1 mtr-2) (privk "sig" b-0)) (pubk "enc" m-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-3 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 382) (parent 366) (realized) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (vars (merc-conf-decommit mesg) (account account-0 acct) (cost cost-0 amount) (n ncb ncm n-0 data) (item merchandise) (bank-conf btr mtr mtr-0 btr-0 mtr-1 merc-conf btr-1 mtr-2 mtr-3 text) (c m b c-0 m-0 b-0 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 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr-0) (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-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-1) (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-0) (mtr mtr-1) (c c) (m m) (b b)) (deflistener (cat n (hash ncb bank-conf))) (defstrand bank 2 (merc-conf-decommit merc-conf-decommit) (account account-0) (cost cost-0) (n n-0) (ncb ncb) (bank-conf bank-conf) (btr btr-1) (mtr mtr-2) (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-3) (c c) (m m) (b b)) (precedes ((1 0) (2 0)) ((1 0) (7 0)) ((2 1) (0 0)) ((2 1) (6 0)) ((3 1) (4 2)) ((4 1) (3 0)) ((4 3) (1 1)) ((4 4) (1 2)) ((5 1) (4 0)) ((6 1) (5 0)) ((7 1) (5 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr-0 btr-0 mtr-1 btr-1 mtr-3) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation nonce-test (displaced 8 2 merc 2) ncb (6 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 (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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 (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-0 mtr-1) (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-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 (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (privk "sig" m)))) ((recv (cat n (hash ncb bank-conf))) (send (cat n (hash ncb bank-conf)))) ((recv (enc (payreq c-0 m-0 b-0 (hash cost-0 n-0) merc-conf-decommit mtr-2 (cat (sign (order c-0 m-0 b-0 cost-0 (enc n-0 cost-0 account-0 bank-conf ncb (hash n-0 merc-conf-decommit) (pubk "enc" b-0))) (privk "sig" c-0)) (enc n-0 cost-0 account-0 bank-conf ncb (hash n-0 merc-conf-decommit) (pubk "enc" b-0)))) (pubk "enc" b-0))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c-0 m-0 b-0 n-0 cost-0 (hash n-0 merc-conf-decommit)) btr-1 mtr-2) (privk "sig" b-0)) (pubk "enc" m-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-3 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 383) (parent 367) (realized) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (vars (merc-conf-decommit mesg) (account account-0 acct) (cost cost-0 amount) (n ncb ncm n-0 data) (item merchandise) (bank-conf btr mtr mtr-0 btr-0 mtr-1 merc-conf btr-1 mtr-2 mtr-3 text) (c m b c-0 m-0 b-0 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 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr-0) (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-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-1) (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-0) (mtr mtr-1) (c c) (m m) (b b)) (deflistener (cat n (hash ncb bank-conf))) (defstrand bank 2 (merc-conf-decommit merc-conf-decommit) (account account-0) (cost cost-0) (n n-0) (ncb ncb) (bank-conf bank-conf) (btr btr-1) (mtr mtr-2) (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-3) (c c) (m m) (b b)) (precedes ((1 0) (2 0)) ((1 0) (7 0)) ((2 1) (0 0)) ((2 1) (3 0)) ((3 1) (4 2)) ((4 1) (3 0)) ((4 3) (1 1)) ((4 4) (1 2)) ((5 1) (4 0)) ((6 1) (5 0)) ((7 1) (6 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr-0 btr-0 mtr-1 btr-1 mtr-3) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation nonce-test (displaced 8 7 merc 2) ncb (6 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 (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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 (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-0 mtr-1) (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-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 (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (privk "sig" m)))) ((recv (cat n (hash ncb bank-conf))) (send (cat n (hash ncb bank-conf)))) ((recv (enc (payreq c-0 m-0 b-0 (hash cost-0 n-0) merc-conf-decommit mtr-2 (cat (sign (order c-0 m-0 b-0 cost-0 (enc n-0 cost-0 account-0 bank-conf ncb (hash n-0 merc-conf-decommit) (pubk "enc" b-0))) (privk "sig" c-0)) (enc n-0 cost-0 account-0 bank-conf ncb (hash n-0 merc-conf-decommit) (pubk "enc" b-0)))) (pubk "enc" b-0))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c-0 m-0 b-0 n-0 cost-0 (hash n-0 merc-conf-decommit)) btr-1 mtr-2) (privk "sig" b-0)) (pubk "enc" m-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-3 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 384) (parent 367) (realized) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (vars (merc-conf-decommit mesg) (account account-0 acct) (cost cost-0 amount) (n ncb ncm n-0 data) (item merchandise) (bank-conf btr mtr mtr-0 btr-0 mtr-1 merc-conf btr-1 mtr-2 mtr-3 mtr-4 text) (c m b c-0 m-0 b-0 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 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr-0) (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-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-1) (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-0) (mtr mtr-1) (c c) (m m) (b b)) (deflistener (cat n (hash ncb bank-conf))) (defstrand bank 2 (merc-conf-decommit merc-conf-decommit) (account account-0) (cost cost-0) (n n-0) (ncb ncb) (bank-conf bank-conf) (btr btr-1) (mtr mtr-2) (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-3) (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-4) (c c) (m m) (b b)) (precedes ((1 0) (2 0)) ((1 0) (7 0)) ((1 0) (8 0)) ((2 1) (0 0)) ((2 1) (3 0)) ((3 1) (4 2)) ((4 1) (3 0)) ((4 3) (1 1)) ((4 4) (1 2)) ((5 1) (4 0)) ((6 1) (5 0)) ((7 1) (5 0)) ((8 1) (6 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr-0 btr-0 mtr-1 btr-1 mtr-3 mtr-4) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation nonce-test (added-strand merc 2) ncb (6 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 (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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 (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-0 mtr-1) (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-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 (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (privk "sig" m)))) ((recv (cat n (hash ncb bank-conf))) (send (cat n (hash ncb bank-conf)))) ((recv (enc (payreq c-0 m-0 b-0 (hash cost-0 n-0) merc-conf-decommit mtr-2 (cat (sign (order c-0 m-0 b-0 cost-0 (enc n-0 cost-0 account-0 bank-conf ncb (hash n-0 merc-conf-decommit) (pubk "enc" b-0))) (privk "sig" c-0)) (enc n-0 cost-0 account-0 bank-conf ncb (hash n-0 merc-conf-decommit) (pubk "enc" b-0)))) (pubk "enc" b-0))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c-0 m-0 b-0 n-0 cost-0 (hash n-0 merc-conf-decommit)) btr-1 mtr-2) (privk "sig" b-0)) (pubk "enc" m-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-3 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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-4 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 385) (parent 367) (realized) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr mtr-0 btr-0 mtr-1 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 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr-0) (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-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-1) (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-0) (mtr mtr-1) (c c) (m m) (b b)) (deflistener (cat n (hash ncb bank-conf))) (deflistener (cat ncb bank-conf)) (precedes ((1 0) (2 0)) ((2 1) (0 0)) ((2 1) (6 0)) ((3 1) (4 2)) ((4 1) (3 0)) ((4 3) (1 1)) ((4 4) (1 2)) ((5 1) (4 0)) ((6 1) (5 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr-0 btr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation nonce-test (displaced 7 2 merc 2) ncb (6 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 (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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 (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-0 mtr-1) (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-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 (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (privk "sig" m)))) ((recv (cat n (hash ncb bank-conf))) (send (cat n (hash ncb bank-conf)))) ((recv (cat ncb bank-conf)) (send (cat ncb bank-conf)))) (label 386) (parent 368) (realized) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr mtr-0 btr-0 mtr-1 merc-conf mtr-2 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 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr-0) (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-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-1) (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-0) (mtr mtr-1) (c c) (m m) (b b)) (deflistener (cat n (hash ncb bank-conf))) (deflistener (cat 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-2) (c c) (m m) (b b)) (precedes ((1 0) (2 0)) ((1 0) (7 0)) ((2 1) (0 0)) ((2 1) (5 0)) ((3 1) (4 2)) ((4 1) (3 0)) ((4 3) (1 1)) ((4 4) (1 2)) ((5 1) (4 0)) ((6 1) (5 0)) ((7 1) (6 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr-0 btr-0 mtr-1 mtr-2) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation nonce-test (added-strand merc 2) ncb (6 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 (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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 (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-0 mtr-1) (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-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 (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (privk "sig" m)))) ((recv (cat n (hash ncb bank-conf))) (send (cat n (hash ncb bank-conf)))) ((recv (cat ncb bank-conf)) (send (cat 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-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 387) (parent 368) (realized) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr mtr-0 btr-0 mtr-1 merc-conf mtr-2 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 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr-0) (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-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-1) (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-0) (mtr mtr-1) (c c) (m m) (b b)) (deflistener (cat n (hash ncb bank-conf))) (deflistener (cat 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-2) (c c) (m m) (b b)) (precedes ((1 0) (2 0)) ((1 0) (7 0)) ((2 1) (0 0)) ((2 1) (6 0)) ((3 1) (4 2)) ((4 1) (3 0)) ((4 3) (1 1)) ((4 4) (1 2)) ((5 1) (4 0)) ((6 1) (5 0)) ((7 1) (5 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr-0 btr-0 mtr-1 mtr-2) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation nonce-test (displaced 8 2 merc 2) ncb (6 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 (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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 (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-0 mtr-1) (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-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 (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (privk "sig" m)))) ((recv (cat n (hash ncb bank-conf))) (send (cat n (hash ncb bank-conf)))) ((recv (cat ncb bank-conf)) (send (cat 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-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 388) (parent 369) (realized) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr mtr-0 btr-0 mtr-1 merc-conf mtr-2 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 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr-0) (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-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-1) (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-0) (mtr mtr-1) (c c) (m m) (b b)) (deflistener (cat n (hash ncb bank-conf))) (deflistener (cat 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-2) (c c) (m m) (b b)) (precedes ((1 0) (2 0)) ((1 0) (7 0)) ((2 1) (0 0)) ((2 1) (3 0)) ((3 1) (4 2)) ((4 1) (3 0)) ((4 3) (1 1)) ((4 4) (1 2)) ((5 1) (4 0)) ((6 1) (5 0)) ((7 1) (6 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr-0 btr-0 mtr-1 mtr-2) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation nonce-test (displaced 8 7 merc 2) ncb (6 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 (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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 (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-0 mtr-1) (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-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 (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (privk "sig" m)))) ((recv (cat n (hash ncb bank-conf))) (send (cat n (hash ncb bank-conf)))) ((recv (cat ncb bank-conf)) (send (cat 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-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 389) (parent 369) (realized) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr mtr-0 btr-0 mtr-1 merc-conf mtr-2 mtr-3 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 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr-0) (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-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-1) (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-0) (mtr mtr-1) (c c) (m m) (b b)) (deflistener (cat n (hash ncb bank-conf))) (deflistener (cat 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-2) (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-3) (c c) (m m) (b b)) (precedes ((1 0) (2 0)) ((1 0) (7 0)) ((1 0) (8 0)) ((2 1) (0 0)) ((2 1) (3 0)) ((3 1) (4 2)) ((4 1) (3 0)) ((4 3) (1 1)) ((4 4) (1 2)) ((5 1) (4 0)) ((6 1) (5 0)) ((7 1) (5 0)) ((8 1) (6 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr-0 btr-0 mtr-1 mtr-2 mtr-3) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation nonce-test (added-strand merc 2) ncb (6 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 (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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 (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-0 mtr-1) (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-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 (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (privk "sig" m)))) ((recv (cat n (hash ncb bank-conf))) (send (cat n (hash ncb bank-conf)))) ((recv (cat ncb bank-conf)) (send (cat 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-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)))) ((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-3 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 390) (parent 369) (realized) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (vars (merc-conf-decommit mesg) (account account-0 acct) (cost cost-0 amount) (n ncb ncm n-0 data) (item merchandise) (bank-conf btr mtr mtr-0 btr-0 mtr-1 merc-conf mtr-2 btr-1 mtr-3 text) (c m b c-0 m-0 b-0 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 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr-0) (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-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-1) (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-0) (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)) (deflistener (cat n (hash ncb bank-conf))) (defstrand bank 2 (merc-conf-decommit merc-conf-decommit) (account account-0) (cost cost-0) (n n-0) (ncb ncb) (bank-conf bank-conf) (btr btr-1) (mtr mtr-3) (c c-0) (m m-0) (b b-0)) (precedes ((1 0) (2 0)) ((1 0) (5 0)) ((2 1) (0 0)) ((2 1) (7 0)) ((3 1) (4 2)) ((4 1) (3 0)) ((4 3) (1 1)) ((4 4) (1 2)) ((5 1) (3 0)) ((6 1) (4 0)) ((7 1) (6 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr-0 btr-0 mtr-1 mtr-2 btr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation nonce-test (displaced 8 2 merc 2) ncb (7 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 (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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 (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-0 mtr-1) (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-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 (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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-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)))) ((recv (cat n (hash ncb bank-conf))) (send (cat n (hash ncb bank-conf)))) ((recv (enc (payreq c-0 m-0 b-0 (hash cost-0 n-0) merc-conf-decommit mtr-3 (cat (sign (order c-0 m-0 b-0 cost-0 (enc n-0 cost-0 account-0 bank-conf ncb (hash n-0 merc-conf-decommit) (pubk "enc" b-0))) (privk "sig" c-0)) (enc n-0 cost-0 account-0 bank-conf ncb (hash n-0 merc-conf-decommit) (pubk "enc" b-0)))) (pubk "enc" b-0))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c-0 m-0 b-0 n-0 cost-0 (hash n-0 merc-conf-decommit)) btr-1 mtr-3) (privk "sig" b-0)) (pubk "enc" m-0))))) (label 391) (parent 370) (seen 381) (realized) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay (vars (merc-conf-decommit mesg) (account account-0 acct) (cost cost-0 amount) (n ncb ncm n-0 data) (item merchandise) (bank-conf btr mtr mtr-0 btr-0 mtr-1 merc-conf mtr-2 btr-1 mtr-3 mtr-4 text) (c m b c-0 m-0 b-0 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 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr-0) (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-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-1) (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-0) (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)) (deflistener (cat n (hash ncb bank-conf))) (defstrand bank 2 (merc-conf-decommit merc-conf-decommit) (account account-0) (cost cost-0) (n n-0) (ncb ncb) (bank-conf bank-conf) (btr btr-1) (mtr mtr-3) (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-4) (c c) (m m) (b b)) (precedes ((1 0) (2 0)) ((1 0) (5 0)) ((1 0) (8 0)) ((2 1) (0 0)) ((2 1) (6 0)) ((3 1) (4 2)) ((4 1) (3 0)) ((4 3) (1 1)) ((4 4) (1 2)) ((5 1) (3 0)) ((6 1) (4 0)) ((7 1) (6 0)) ((8 1) (7 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr-0 btr-0 mtr-1 mtr-2 btr-1 mtr-4) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation nonce-test (added-strand merc 2) ncb (7 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 (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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 (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-0 mtr-1) (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-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 (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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-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)))) ((recv (cat n (hash ncb bank-conf))) (send (cat n (hash ncb bank-conf)))) ((recv (enc (payreq c-0 m-0 b-0 (hash cost-0 n-0) merc-conf-decommit mtr-3 (cat (sign (order c-0 m-0 b-0 cost-0 (enc n-0 cost-0 account-0 bank-conf ncb (hash n-0 merc-conf-decommit) (pubk "enc" b-0))) (privk "sig" c-0)) (enc n-0 cost-0 account-0 bank-conf ncb (hash n-0 merc-conf-decommit) (pubk "enc" b-0)))) (pubk "enc" b-0))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c-0 m-0 b-0 n-0 cost-0 (hash n-0 merc-conf-decommit)) btr-1 mtr-3) (privk "sig" b-0)) (pubk "enc" m-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-4 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 392) (parent 370) (seen 382) (realized) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay (vars (merc-conf-decommit mesg) (account account-0 acct) (cost cost-0 amount) (n ncb ncm n-0 data) (item merchandise) (bank-conf btr mtr mtr-0 btr-0 mtr-1 merc-conf mtr-2 btr-1 mtr-3 text) (c m b c-0 m-0 b-0 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 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr-0) (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-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-1) (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-0) (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)) (deflistener (cat n (hash ncb bank-conf))) (defstrand bank 2 (merc-conf-decommit merc-conf-decommit) (account account-0) (cost cost-0) (n n-0) (ncb ncb) (bank-conf bank-conf) (btr btr-1) (mtr mtr-3) (c c-0) (m m-0) (b b-0)) (precedes ((1 0) (2 0)) ((1 0) (5 0)) ((2 1) (0 0)) ((3 1) (4 2)) ((4 1) (3 0)) ((4 3) (1 1)) ((4 4) (1 2)) ((5 1) (7 0)) ((6 1) (4 0)) ((7 1) (6 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr-0 btr-0 mtr-1 mtr-2 btr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation nonce-test (displaced 8 5 merc 2) ncb (7 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 (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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 (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-0 mtr-1) (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-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 (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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-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)))) ((recv (cat n (hash ncb bank-conf))) (send (cat n (hash ncb bank-conf)))) ((recv (enc (payreq c-0 m-0 b-0 (hash cost-0 n-0) merc-conf-decommit mtr-3 (cat (sign (order c-0 m-0 b-0 cost-0 (enc n-0 cost-0 account-0 bank-conf ncb (hash n-0 merc-conf-decommit) (pubk "enc" b-0))) (privk "sig" c-0)) (enc n-0 cost-0 account-0 bank-conf ncb (hash n-0 merc-conf-decommit) (pubk "enc" b-0)))) (pubk "enc" b-0))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c-0 m-0 b-0 n-0 cost-0 (hash n-0 merc-conf-decommit)) btr-1 mtr-3) (privk "sig" b-0)) (pubk "enc" m-0))))) (label 393) (parent 371) (realized) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (vars (merc-conf-decommit mesg) (account account-0 acct) (cost cost-0 amount) (n ncb ncm n-0 data) (item merchandise) (bank-conf btr mtr mtr-0 btr-0 mtr-1 merc-conf mtr-2 btr-1 mtr-3 mtr-4 text) (c m b c-0 m-0 b-0 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 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr-0) (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-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-1) (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-0) (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)) (deflistener (cat n (hash ncb bank-conf))) (defstrand bank 2 (merc-conf-decommit merc-conf-decommit) (account account-0) (cost cost-0) (n n-0) (ncb ncb) (bank-conf bank-conf) (btr btr-1) (mtr mtr-3) (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-4) (c c) (m m) (b b)) (precedes ((1 0) (2 0)) ((1 0) (5 0)) ((1 0) (8 0)) ((2 1) (0 0)) ((3 1) (4 2)) ((4 1) (3 0)) ((4 3) (1 1)) ((4 4) (1 2)) ((5 1) (6 0)) ((6 1) (4 0)) ((7 1) (6 0)) ((8 1) (7 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr-0 btr-0 mtr-1 mtr-2 btr-1 mtr-4) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation nonce-test (added-strand merc 2) ncb (7 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 (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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 (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-0 mtr-1) (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-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 (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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-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)))) ((recv (cat n (hash ncb bank-conf))) (send (cat n (hash ncb bank-conf)))) ((recv (enc (payreq c-0 m-0 b-0 (hash cost-0 n-0) merc-conf-decommit mtr-3 (cat (sign (order c-0 m-0 b-0 cost-0 (enc n-0 cost-0 account-0 bank-conf ncb (hash n-0 merc-conf-decommit) (pubk "enc" b-0))) (privk "sig" c-0)) (enc n-0 cost-0 account-0 bank-conf ncb (hash n-0 merc-conf-decommit) (pubk "enc" b-0)))) (pubk "enc" b-0))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c-0 m-0 b-0 n-0 cost-0 (hash n-0 merc-conf-decommit)) btr-1 mtr-3) (privk "sig" b-0)) (pubk "enc" m-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-4 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 394) (parent 371) (seen 393) (realized) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay (vars (merc-conf-decommit mesg) (account account-0 acct) (cost cost-0 amount) (n ncb ncm n-0 data) (item merchandise) (bank-conf btr mtr mtr-0 btr-0 mtr-1 merc-conf mtr-2 btr-1 mtr-3 mtr-4 text) (c m b c-0 m-0 b-0 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 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr-0) (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-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-1) (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-0) (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)) (deflistener (cat n (hash ncb bank-conf))) (defstrand bank 2 (merc-conf-decommit merc-conf-decommit) (account account-0) (cost cost-0) (n n-0) (ncb ncb) (bank-conf bank-conf) (btr btr-1) (mtr mtr-3) (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-4) (c c) (m m) (b b)) (precedes ((1 0) (2 0)) ((1 0) (5 0)) ((1 0) (8 0)) ((2 1) (0 0)) ((2 1) (7 0)) ((3 1) (4 2)) ((4 1) (3 0)) ((4 3) (1 1)) ((4 4) (1 2)) ((5 1) (3 0)) ((6 1) (4 0)) ((7 1) (6 0)) ((8 1) (6 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr-0 btr-0 mtr-1 mtr-2 btr-1 mtr-4) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation nonce-test (displaced 9 2 merc 2) ncb (7 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 (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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 (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-0 mtr-1) (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-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 (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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-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)))) ((recv (cat n (hash ncb bank-conf))) (send (cat n (hash ncb bank-conf)))) ((recv (enc (payreq c-0 m-0 b-0 (hash cost-0 n-0) merc-conf-decommit mtr-3 (cat (sign (order c-0 m-0 b-0 cost-0 (enc n-0 cost-0 account-0 bank-conf ncb (hash n-0 merc-conf-decommit) (pubk "enc" b-0))) (privk "sig" c-0)) (enc n-0 cost-0 account-0 bank-conf ncb (hash n-0 merc-conf-decommit) (pubk "enc" b-0)))) (pubk "enc" b-0))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c-0 m-0 b-0 n-0 cost-0 (hash n-0 merc-conf-decommit)) btr-1 mtr-3) (privk "sig" b-0)) (pubk "enc" m-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-4 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 395) (parent 372) (seen 383) (realized) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay (vars (merc-conf-decommit mesg) (account account-0 acct) (cost cost-0 amount) (n ncb ncm n-0 data) (item merchandise) (bank-conf btr mtr mtr-0 btr-0 mtr-1 merc-conf mtr-2 btr-1 mtr-3 mtr-4 text) (c m b c-0 m-0 b-0 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 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr-0) (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-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-1) (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-0) (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)) (deflistener (cat n (hash ncb bank-conf))) (defstrand bank 2 (merc-conf-decommit merc-conf-decommit) (account account-0) (cost cost-0) (n n-0) (ncb ncb) (bank-conf bank-conf) (btr btr-1) (mtr mtr-3) (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-4) (c c) (m m) (b b)) (precedes ((1 0) (2 0)) ((1 0) (5 0)) ((1 0) (8 0)) ((2 1) (0 0)) ((3 1) (4 2)) ((4 1) (3 0)) ((4 3) (1 1)) ((4 4) (1 2)) ((5 1) (3 0)) ((6 1) (4 0)) ((7 1) (6 0)) ((8 1) (7 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr-0 btr-0 mtr-1 mtr-2 btr-1 mtr-4) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation nonce-test (displaced 9 8 merc 2) ncb (7 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 (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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 (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-0 mtr-1) (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-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 (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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-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)))) ((recv (cat n (hash ncb bank-conf))) (send (cat n (hash ncb bank-conf)))) ((recv (enc (payreq c-0 m-0 b-0 (hash cost-0 n-0) merc-conf-decommit mtr-3 (cat (sign (order c-0 m-0 b-0 cost-0 (enc n-0 cost-0 account-0 bank-conf ncb (hash n-0 merc-conf-decommit) (pubk "enc" b-0))) (privk "sig" c-0)) (enc n-0 cost-0 account-0 bank-conf ncb (hash n-0 merc-conf-decommit) (pubk "enc" b-0)))) (pubk "enc" b-0))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c-0 m-0 b-0 n-0 cost-0 (hash n-0 merc-conf-decommit)) btr-1 mtr-3) (privk "sig" b-0)) (pubk "enc" m-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-4 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 396) (parent 372) (seen 393) (realized) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay (vars (merc-conf-decommit mesg) (account account-0 acct) (cost cost-0 amount) (n ncb ncm n-0 data) (item merchandise) (bank-conf btr mtr mtr-0 btr-0 mtr-1 merc-conf mtr-2 btr-1 mtr-3 mtr-4 mtr-5 text) (c m b c-0 m-0 b-0 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 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr-0) (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-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-1) (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-0) (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)) (deflistener (cat n (hash ncb bank-conf))) (defstrand bank 2 (merc-conf-decommit merc-conf-decommit) (account account-0) (cost cost-0) (n n-0) (ncb ncb) (bank-conf bank-conf) (btr btr-1) (mtr mtr-3) (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-4) (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-5) (c c) (m m) (b b)) (precedes ((1 0) (2 0)) ((1 0) (5 0)) ((1 0) (8 0)) ((1 0) (9 0)) ((2 1) (0 0)) ((3 1) (4 2)) ((4 1) (3 0)) ((4 3) (1 1)) ((4 4) (1 2)) ((5 1) (3 0)) ((6 1) (4 0)) ((7 1) (6 0)) ((8 1) (6 0)) ((9 1) (7 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr-0 btr-0 mtr-1 mtr-2 btr-1 mtr-4 mtr-5) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation nonce-test (added-strand merc 2) ncb (7 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 (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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 (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-0 mtr-1) (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-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 (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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-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)))) ((recv (cat n (hash ncb bank-conf))) (send (cat n (hash ncb bank-conf)))) ((recv (enc (payreq c-0 m-0 b-0 (hash cost-0 n-0) merc-conf-decommit mtr-3 (cat (sign (order c-0 m-0 b-0 cost-0 (enc n-0 cost-0 account-0 bank-conf ncb (hash n-0 merc-conf-decommit) (pubk "enc" b-0))) (privk "sig" c-0)) (enc n-0 cost-0 account-0 bank-conf ncb (hash n-0 merc-conf-decommit) (pubk "enc" b-0)))) (pubk "enc" b-0))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c-0 m-0 b-0 n-0 cost-0 (hash n-0 merc-conf-decommit)) btr-1 mtr-3) (privk "sig" b-0)) (pubk "enc" m-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-4 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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-5 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 397) (parent 372) (seen 394) (realized) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr mtr-0 btr-0 mtr-1 merc-conf mtr-2 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 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr-0) (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-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-1) (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-0) (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)) (deflistener (cat n (hash ncb bank-conf))) (deflistener (cat ncb bank-conf)) (precedes ((1 0) (2 0)) ((1 0) (5 0)) ((2 1) (0 0)) ((2 1) (7 0)) ((3 1) (4 2)) ((4 1) (3 0)) ((4 3) (1 1)) ((4 4) (1 2)) ((5 1) (3 0)) ((6 1) (4 0)) ((7 1) (6 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr-0 btr-0 mtr-1 mtr-2) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation nonce-test (displaced 8 2 merc 2) ncb (7 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 (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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 (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-0 mtr-1) (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-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 (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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-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)))) ((recv (cat n (hash ncb bank-conf))) (send (cat n (hash ncb bank-conf)))) ((recv (cat ncb bank-conf)) (send (cat ncb bank-conf)))) (label 398) (parent 373) (seen 386) (realized) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr mtr-0 btr-0 mtr-1 merc-conf mtr-2 mtr-3 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 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr-0) (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-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-1) (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-0) (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)) (deflistener (cat n (hash ncb bank-conf))) (deflistener (cat 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-3) (c c) (m m) (b b)) (precedes ((1 0) (2 0)) ((1 0) (5 0)) ((1 0) (8 0)) ((2 1) (0 0)) ((2 1) (6 0)) ((3 1) (4 2)) ((4 1) (3 0)) ((4 3) (1 1)) ((4 4) (1 2)) ((5 1) (3 0)) ((6 1) (4 0)) ((7 1) (6 0)) ((8 1) (7 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr-0 btr-0 mtr-1 mtr-2 mtr-3) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation nonce-test (added-strand merc 2) ncb (7 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 (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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 (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-0 mtr-1) (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-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 (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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-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)))) ((recv (cat n (hash ncb bank-conf))) (send (cat n (hash ncb bank-conf)))) ((recv (cat ncb bank-conf)) (send (cat 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-3 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 399) (parent 373) (seen 387) (realized) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr mtr-0 btr-0 mtr-1 merc-conf mtr-2 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 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr-0) (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-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-1) (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-0) (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)) (deflistener (cat n (hash ncb bank-conf))) (deflistener (cat ncb bank-conf)) (precedes ((1 0) (2 0)) ((1 0) (5 0)) ((2 1) (0 0)) ((3 1) (4 2)) ((4 1) (3 0)) ((4 3) (1 1)) ((4 4) (1 2)) ((5 1) (7 0)) ((6 1) (4 0)) ((7 1) (6 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr-0 btr-0 mtr-1 mtr-2) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation nonce-test (displaced 8 5 merc 2) ncb (7 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 (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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 (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-0 mtr-1) (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-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 (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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-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)))) ((recv (cat n (hash ncb bank-conf))) (send (cat n (hash ncb bank-conf)))) ((recv (cat ncb bank-conf)) (send (cat ncb bank-conf)))) (label 400) (parent 374) (realized) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr mtr-0 btr-0 mtr-1 merc-conf mtr-2 mtr-3 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 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr-0) (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-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-1) (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-0) (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)) (deflistener (cat n (hash ncb bank-conf))) (deflistener (cat 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-3) (c c) (m m) (b b)) (precedes ((1 0) (2 0)) ((1 0) (5 0)) ((1 0) (8 0)) ((2 1) (0 0)) ((3 1) (4 2)) ((4 1) (3 0)) ((4 3) (1 1)) ((4 4) (1 2)) ((5 1) (6 0)) ((6 1) (4 0)) ((7 1) (6 0)) ((8 1) (7 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr-0 btr-0 mtr-1 mtr-2 mtr-3) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation nonce-test (added-strand merc 2) ncb (7 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 (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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 (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-0 mtr-1) (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-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 (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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-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)))) ((recv (cat n (hash ncb bank-conf))) (send (cat n (hash ncb bank-conf)))) ((recv (cat ncb bank-conf)) (send (cat 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-3 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 401) (parent 374) (seen 400) (realized) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr mtr-0 btr-0 mtr-1 merc-conf mtr-2 mtr-3 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 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr-0) (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-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-1) (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-0) (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)) (deflistener (cat n (hash ncb bank-conf))) (deflistener (cat 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-3) (c c) (m m) (b b)) (precedes ((1 0) (2 0)) ((1 0) (5 0)) ((1 0) (8 0)) ((2 1) (0 0)) ((2 1) (7 0)) ((3 1) (4 2)) ((4 1) (3 0)) ((4 3) (1 1)) ((4 4) (1 2)) ((5 1) (3 0)) ((6 1) (4 0)) ((7 1) (6 0)) ((8 1) (6 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr-0 btr-0 mtr-1 mtr-2 mtr-3) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation nonce-test (displaced 9 2 merc 2) ncb (7 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 (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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 (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-0 mtr-1) (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-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 (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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-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)))) ((recv (cat n (hash ncb bank-conf))) (send (cat n (hash ncb bank-conf)))) ((recv (cat ncb bank-conf)) (send (cat 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-3 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 402) (parent 375) (seen 388) (realized) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr mtr-0 btr-0 mtr-1 merc-conf mtr-2 mtr-3 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 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr-0) (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-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-1) (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-0) (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)) (deflistener (cat n (hash ncb bank-conf))) (deflistener (cat 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-3) (c c) (m m) (b b)) (precedes ((1 0) (2 0)) ((1 0) (5 0)) ((1 0) (8 0)) ((2 1) (0 0)) ((3 1) (4 2)) ((4 1) (3 0)) ((4 3) (1 1)) ((4 4) (1 2)) ((5 1) (3 0)) ((6 1) (4 0)) ((7 1) (6 0)) ((8 1) (7 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr-0 btr-0 mtr-1 mtr-2 mtr-3) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation nonce-test (displaced 9 8 merc 2) ncb (7 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 (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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 (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-0 mtr-1) (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-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 (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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-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)))) ((recv (cat n (hash ncb bank-conf))) (send (cat n (hash ncb bank-conf)))) ((recv (cat ncb bank-conf)) (send (cat 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-3 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 403) (parent 375) (seen 400) (realized) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr mtr-0 btr-0 mtr-1 merc-conf mtr-2 mtr-3 mtr-4 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 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr-0) (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-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-1) (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-0) (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)) (deflistener (cat n (hash ncb bank-conf))) (deflistener (cat 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-3) (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-4) (c c) (m m) (b b)) (precedes ((1 0) (2 0)) ((1 0) (5 0)) ((1 0) (8 0)) ((1 0) (9 0)) ((2 1) (0 0)) ((3 1) (4 2)) ((4 1) (3 0)) ((4 3) (1 1)) ((4 4) (1 2)) ((5 1) (3 0)) ((6 1) (4 0)) ((7 1) (6 0)) ((8 1) (6 0)) ((9 1) (7 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr-0 btr-0 mtr-1 mtr-2 mtr-3 mtr-4) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation nonce-test (added-strand merc 2) ncb (7 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 (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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 (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-0 mtr-1) (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-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 (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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-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)))) ((recv (cat n (hash ncb bank-conf))) (send (cat n (hash ncb bank-conf)))) ((recv (cat ncb bank-conf)) (send (cat 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-3 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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-4 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 404) (parent 375) (seen 401) (realized) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr mtr-0 btr-0 mtr-1 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 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr-0) (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-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-1) (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-0) (mtr mtr-1) (c c) (m m) (b b)) (precedes ((0 1) (4 2)) ((1 0) (2 0)) ((2 1) (0 0)) ((2 1) (4 0)) ((3 1) (4 2)) ((4 1) (3 0)) ((4 3) (1 1)) ((4 4) (1 2))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr-0 btr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation generalization weakened ((0 1) (3 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 (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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 (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-0 mtr-1) (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-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 (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (privk "sig" m))))) (label 405) (parent 380) (realized) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (vars (merc-conf-decommit mesg) (account account-0 acct) (cost cost-0 amount) (n ncb ncm n-0 data) (item merchandise) (bank-conf btr mtr mtr-0 btr-0 mtr-1 merc-conf btr-1 mtr-2 text) (c m b c-0 m-0 b-0 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 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr-0) (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-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-1) (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-0) (mtr mtr-1) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit merc-conf-decommit) (account account-0) (cost cost-0) (n n-0) (ncb ncb) (bank-conf bank-conf) (btr btr-1) (mtr mtr-2) (c c-0) (m m-0) (b b-0)) (precedes ((1 0) (2 0)) ((2 1) (0 0)) ((2 1) (5 0)) ((3 1) (4 2)) ((4 1) (3 0)) ((4 3) (1 1)) ((4 4) (1 2)) ((5 1) (4 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr-0 btr-0 mtr-1 btr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation generalization deleted (5 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 (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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 (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-0 mtr-1) (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-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 (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (privk "sig" m)))) ((recv (enc (payreq c-0 m-0 b-0 (hash cost-0 n-0) merc-conf-decommit mtr-2 (cat (sign (order c-0 m-0 b-0 cost-0 (enc n-0 cost-0 account-0 bank-conf ncb (hash n-0 merc-conf-decommit) (pubk "enc" b-0))) (privk "sig" c-0)) (enc n-0 cost-0 account-0 bank-conf ncb (hash n-0 merc-conf-decommit) (pubk "enc" b-0)))) (pubk "enc" b-0))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c-0 m-0 b-0 n-0 cost-0 (hash n-0 merc-conf-decommit)) btr-1 mtr-2) (privk "sig" b-0)) (pubk "enc" m-0))))) (label 406) (parent 381) (realized) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (vars (merc-conf-decommit mesg) (account account-0 acct) (cost cost-0 amount) (n ncb ncm n-0 data) (item merchandise) (bank-conf btr mtr mtr-0 btr-0 mtr-1 merc-conf btr-1 mtr-2 mtr-3 text) (c m b c-0 m-0 b-0 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 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr-0) (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-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-1) (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-0) (mtr mtr-1) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit merc-conf-decommit) (account account-0) (cost cost-0) (n n-0) (ncb ncb) (bank-conf bank-conf) (btr btr-1) (mtr mtr-2) (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-3) (c c) (m m) (b b)) (precedes ((1 0) (2 0)) ((1 0) (6 0)) ((2 1) (0 0)) ((2 1) (4 0)) ((3 1) (4 2)) ((4 1) (3 0)) ((4 3) (1 1)) ((4 4) (1 2)) ((5 1) (4 0)) ((6 1) (5 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr-0 btr-0 mtr-1 btr-1 mtr-3) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation generalization deleted (5 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 (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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 (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-0 mtr-1) (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-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 (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (privk "sig" m)))) ((recv (enc (payreq c-0 m-0 b-0 (hash cost-0 n-0) merc-conf-decommit mtr-2 (cat (sign (order c-0 m-0 b-0 cost-0 (enc n-0 cost-0 account-0 bank-conf ncb (hash n-0 merc-conf-decommit) (pubk "enc" b-0))) (privk "sig" c-0)) (enc n-0 cost-0 account-0 bank-conf ncb (hash n-0 merc-conf-decommit) (pubk "enc" b-0)))) (pubk "enc" b-0))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c-0 m-0 b-0 n-0 cost-0 (hash n-0 merc-conf-decommit)) btr-1 mtr-2) (privk "sig" b-0)) (pubk "enc" m-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-3 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 407) (parent 382) (realized) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (vars (merc-conf-decommit mesg) (account account-0 acct) (cost cost-0 amount) (n ncb ncm n-0 data) (item merchandise) (bank-conf btr mtr mtr-0 btr-0 mtr-1 merc-conf btr-1 mtr-2 mtr-3 text) (c m b c-0 m-0 b-0 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 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr-0) (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-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-1) (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-0) (mtr mtr-1) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit merc-conf-decommit) (account account-0) (cost cost-0) (n n-0) (ncb ncb) (bank-conf bank-conf) (btr btr-1) (mtr mtr-2) (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-3) (c c) (m m) (b b)) (precedes ((1 0) (2 0)) ((1 0) (6 0)) ((2 1) (0 0)) ((2 1) (5 0)) ((3 1) (4 2)) ((4 1) (3 0)) ((4 3) (1 1)) ((4 4) (1 2)) ((5 1) (4 0)) ((6 1) (4 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr-0 btr-0 mtr-1 btr-1 mtr-3) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation generalization deleted (5 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 (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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 (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-0 mtr-1) (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-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 (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (privk "sig" m)))) ((recv (enc (payreq c-0 m-0 b-0 (hash cost-0 n-0) merc-conf-decommit mtr-2 (cat (sign (order c-0 m-0 b-0 cost-0 (enc n-0 cost-0 account-0 bank-conf ncb (hash n-0 merc-conf-decommit) (pubk "enc" b-0))) (privk "sig" c-0)) (enc n-0 cost-0 account-0 bank-conf ncb (hash n-0 merc-conf-decommit) (pubk "enc" b-0)))) (pubk "enc" b-0))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c-0 m-0 b-0 n-0 cost-0 (hash n-0 merc-conf-decommit)) btr-1 mtr-2) (privk "sig" b-0)) (pubk "enc" m-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-3 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 408) (parent 383) (seen 420) (realized) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay (vars (merc-conf-decommit mesg) (account account-0 acct) (cost cost-0 amount) (n ncb ncm n-0 data) (item merchandise) (bank-conf btr mtr mtr-0 btr-0 mtr-1 merc-conf btr-1 mtr-2 mtr-3 text) (c m b c-0 m-0 b-0 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 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr-0) (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-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-1) (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-0) (mtr mtr-1) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit merc-conf-decommit) (account account-0) (cost cost-0) (n n-0) (ncb ncb) (bank-conf bank-conf) (btr btr-1) (mtr mtr-2) (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-3) (c c) (m m) (b b)) (precedes ((1 0) (2 0)) ((1 0) (6 0)) ((2 1) (0 0)) ((2 1) (3 0)) ((3 1) (4 2)) ((4 1) (3 0)) ((4 3) (1 1)) ((4 4) (1 2)) ((5 1) (4 0)) ((6 1) (5 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr-0 btr-0 mtr-1 btr-1 mtr-3) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation generalization deleted (5 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 (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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 (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-0 mtr-1) (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-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 (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (privk "sig" m)))) ((recv (enc (payreq c-0 m-0 b-0 (hash cost-0 n-0) merc-conf-decommit mtr-2 (cat (sign (order c-0 m-0 b-0 cost-0 (enc n-0 cost-0 account-0 bank-conf ncb (hash n-0 merc-conf-decommit) (pubk "enc" b-0))) (privk "sig" c-0)) (enc n-0 cost-0 account-0 bank-conf ncb (hash n-0 merc-conf-decommit) (pubk "enc" b-0)))) (pubk "enc" b-0))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c-0 m-0 b-0 n-0 cost-0 (hash n-0 merc-conf-decommit)) btr-1 mtr-2) (privk "sig" b-0)) (pubk "enc" m-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-3 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 409) (parent 384) (realized) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (vars (merc-conf-decommit mesg) (account account-0 acct) (cost cost-0 amount) (n ncb ncm n-0 data) (item merchandise) (bank-conf btr mtr mtr-0 btr-0 mtr-1 merc-conf btr-1 mtr-2 mtr-3 mtr-4 text) (c m b c-0 m-0 b-0 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 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr-0) (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-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-1) (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-0) (mtr mtr-1) (c c) (m m) (b b)) (defstrand bank 2 (merc-conf-decommit merc-conf-decommit) (account account-0) (cost cost-0) (n n-0) (ncb ncb) (bank-conf bank-conf) (btr btr-1) (mtr mtr-2) (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-3) (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-4) (c c) (m m) (b b)) (precedes ((1 0) (2 0)) ((1 0) (6 0)) ((1 0) (7 0)) ((2 1) (0 0)) ((2 1) (3 0)) ((3 1) (4 2)) ((4 1) (3 0)) ((4 3) (1 1)) ((4 4) (1 2)) ((5 1) (4 0)) ((6 1) (4 0)) ((7 1) (5 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr-0 btr-0 mtr-1 btr-1 mtr-3 mtr-4) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation generalization deleted (5 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 (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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 (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-0 mtr-1) (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-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 (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (privk "sig" m)))) ((recv (enc (payreq c-0 m-0 b-0 (hash cost-0 n-0) merc-conf-decommit mtr-2 (cat (sign (order c-0 m-0 b-0 cost-0 (enc n-0 cost-0 account-0 bank-conf ncb (hash n-0 merc-conf-decommit) (pubk "enc" b-0))) (privk "sig" c-0)) (enc n-0 cost-0 account-0 bank-conf ncb (hash n-0 merc-conf-decommit) (pubk "enc" b-0)))) (pubk "enc" b-0))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c-0 m-0 b-0 n-0 cost-0 (hash n-0 merc-conf-decommit)) btr-1 mtr-2) (privk "sig" b-0)) (pubk "enc" m-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-3 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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-4 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 410) (parent 385) (realized) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr mtr-0 btr-0 mtr-1 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 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr-0) (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-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-1) (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-0) (mtr mtr-1) (c c) (m m) (b b)) (deflistener (cat ncb bank-conf)) (precedes ((1 0) (2 0)) ((2 1) (0 0)) ((2 1) (5 0)) ((3 1) (4 2)) ((4 1) (3 0)) ((4 3) (1 1)) ((4 4) (1 2)) ((5 1) (4 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr-0 btr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation generalization deleted (5 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 (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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 (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-0 mtr-1) (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-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 (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (privk "sig" m)))) ((recv (cat ncb bank-conf)) (send (cat ncb bank-conf)))) (label 411) (parent 386) (seen 419) (realized) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr mtr-0 btr-0 mtr-1 merc-conf mtr-2 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 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr-0) (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-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-1) (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-0) (mtr mtr-1) (c c) (m m) (b b)) (deflistener (cat 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-2) (c c) (m m) (b b)) (precedes ((1 0) (2 0)) ((1 0) (6 0)) ((2 1) (0 0)) ((2 1) (4 0)) ((3 1) (4 2)) ((4 1) (3 0)) ((4 3) (1 1)) ((4 4) (1 2)) ((5 1) (4 0)) ((6 1) (5 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr-0 btr-0 mtr-1 mtr-2) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation generalization deleted (5 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 (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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 (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-0 mtr-1) (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-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 (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (privk "sig" m)))) ((recv (cat ncb bank-conf)) (send (cat 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-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 412) (parent 387) (seen 420) (realized) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr mtr-0 btr-0 mtr-1 merc-conf mtr-2 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 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr-0) (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-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-1) (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-0) (mtr mtr-1) (c c) (m m) (b b)) (deflistener (cat 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-2) (c c) (m m) (b b)) (precedes ((1 0) (2 0)) ((1 0) (6 0)) ((2 1) (0 0)) ((2 1) (5 0)) ((3 1) (4 2)) ((4 1) (3 0)) ((4 3) (1 1)) ((4 4) (1 2)) ((5 1) (4 0)) ((6 1) (4 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr-0 btr-0 mtr-1 mtr-2) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation generalization deleted (5 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 (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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 (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-0 mtr-1) (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-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 (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (privk "sig" m)))) ((recv (cat ncb bank-conf)) (send (cat 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-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 413) (parent 388) (seen 420) (realized) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr mtr-0 btr-0 mtr-1 merc-conf mtr-2 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 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr-0) (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-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-1) (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-0) (mtr mtr-1) (c c) (m m) (b b)) (deflistener (cat 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-2) (c c) (m m) (b b)) (precedes ((1 0) (2 0)) ((1 0) (6 0)) ((2 1) (0 0)) ((2 1) (3 0)) ((3 1) (4 2)) ((4 1) (3 0)) ((4 3) (1 1)) ((4 4) (1 2)) ((5 1) (4 0)) ((6 1) (5 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr-0 btr-0 mtr-1 mtr-2) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation generalization deleted (5 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 (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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 (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-0 mtr-1) (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-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 (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (privk "sig" m)))) ((recv (cat ncb bank-conf)) (send (cat 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-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 414) (parent 389) (seen 421) (realized) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr mtr-0 btr-0 mtr-1 merc-conf mtr-2 mtr-3 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 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr-0) (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-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-1) (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-0) (mtr mtr-1) (c c) (m m) (b b)) (deflistener (cat 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-2) (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-3) (c c) (m m) (b b)) (precedes ((1 0) (2 0)) ((1 0) (6 0)) ((1 0) (7 0)) ((2 1) (0 0)) ((2 1) (3 0)) ((3 1) (4 2)) ((4 1) (3 0)) ((4 3) (1 1)) ((4 4) (1 2)) ((5 1) (4 0)) ((6 1) (4 0)) ((7 1) (5 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr-0 btr-0 mtr-1 mtr-2 mtr-3) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation generalization deleted (5 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 (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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 (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-0 mtr-1) (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-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 (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (privk "sig" m)))) ((recv (cat ncb bank-conf)) (send (cat 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-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)))) ((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-3 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 415) (parent 390) (seen 422) (realized) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay (vars (merc-conf-decommit mesg) (account account-0 acct) (cost cost-0 amount) (n ncb ncm n-0 data) (item merchandise) (bank-conf btr mtr mtr-0 btr-0 mtr-1 merc-conf mtr-2 btr-1 mtr-3 text) (c m b c-0 m-0 b-0 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 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr-0) (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-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-1) (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-0) (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)) (defstrand bank 2 (merc-conf-decommit merc-conf-decommit) (account account-0) (cost cost-0) (n n-0) (ncb ncb) (bank-conf bank-conf) (btr btr-1) (mtr mtr-3) (c c-0) (m m-0) (b b-0)) (precedes ((1 0) (2 0)) ((1 0) (5 0)) ((2 1) (0 0)) ((3 1) (4 2)) ((4 1) (3 0)) ((4 3) (1 1)) ((4 4) (1 2)) ((5 1) (6 0)) ((6 1) (4 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr-0 btr-0 mtr-1 mtr-2 btr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation generalization deleted (6 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 (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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 (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-0 mtr-1) (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-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 (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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-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)))) ((recv (enc (payreq c-0 m-0 b-0 (hash cost-0 n-0) merc-conf-decommit mtr-3 (cat (sign (order c-0 m-0 b-0 cost-0 (enc n-0 cost-0 account-0 bank-conf ncb (hash n-0 merc-conf-decommit) (pubk "enc" b-0))) (privk "sig" c-0)) (enc n-0 cost-0 account-0 bank-conf ncb (hash n-0 merc-conf-decommit) (pubk "enc" b-0)))) (pubk "enc" b-0))) (send (enc (hash ncb bank-conf) (sign (bconf (hash c-0 m-0 b-0 n-0 cost-0 (hash n-0 merc-conf-decommit)) btr-1 mtr-3) (privk "sig" b-0)) (pubk "enc" m-0))))) (label 416) (parent 393) (realized) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr mtr-0 btr-0 mtr-1 merc-conf mtr-2 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 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr-0) (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-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-1) (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-0) (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)) (deflistener (cat ncb bank-conf)) (precedes ((1 0) (2 0)) ((1 0) (5 0)) ((2 1) (0 0)) ((3 1) (4 2)) ((4 1) (3 0)) ((4 3) (1 1)) ((4 4) (1 2)) ((5 1) (6 0)) ((6 1) (4 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr-0 btr-0 mtr-1 mtr-2) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation generalization deleted (6 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 (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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 (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-0 mtr-1) (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-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 (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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-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)))) ((recv (cat ncb bank-conf)) (send (cat ncb bank-conf)))) (label 417) (parent 400) (seen 423) (realized) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr mtr-0 btr-0 mtr-1 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 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr-0) (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-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-1) (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-0) (mtr mtr-1) (c c) (m m) (b b)) (precedes ((0 1) (1 1)) ((1 0) (2 0)) ((2 1) (0 0)) ((2 1) (4 0)) ((3 1) (4 2)) ((4 1) (3 0)) ((4 3) (1 1)) ((4 4) (1 2))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr-0 btr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation generalization weakened ((0 1) (4 2))) (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 (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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 (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-0 mtr-1) (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-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 (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (privk "sig" m))))) (label 418) (parent 405) (realized) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr mtr-0 btr-0 mtr-1 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 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr-0) (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-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-1) (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-0) (mtr mtr-1) (c c) (m m) (b b)) (precedes ((1 0) (2 0)) ((2 1) (0 0)) ((2 1) (4 0)) ((3 1) (4 2)) ((4 1) (3 0)) ((4 3) (1 1)) ((4 4) (1 2))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr-0 btr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation generalization deleted (5 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 (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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 (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-0 mtr-1) (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-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 (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (privk "sig" m))))) (label 419) (parent 406) (seen 326) (realized) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr mtr-0 btr-0 mtr-1 merc-conf mtr-2 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 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr-0) (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-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-1) (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-0) (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 ((1 0) (2 0)) ((1 0) (5 0)) ((2 1) (0 0)) ((2 1) (4 0)) ((3 1) (4 2)) ((4 1) (3 0)) ((4 3) (1 1)) ((4 4) (1 2)) ((5 1) (4 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr-0 btr-0 mtr-1 mtr-2) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation generalization deleted (5 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 (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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 (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-0 mtr-1) (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-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 (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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-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 420) (parent 407) (seen 419) (realized) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr mtr-0 btr-0 mtr-1 merc-conf mtr-2 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 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr-0) (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-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-1) (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-0) (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 ((1 0) (2 0)) ((1 0) (5 0)) ((2 1) (0 0)) ((2 1) (3 0)) ((3 1) (4 2)) ((4 1) (3 0)) ((4 3) (1 1)) ((4 4) (1 2)) ((5 1) (4 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr-0 btr-0 mtr-1 mtr-2) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation generalization deleted (5 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 (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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 (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-0 mtr-1) (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-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 (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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-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 421) (parent 409) (seen 326) (realized) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr mtr-0 btr-0 mtr-1 merc-conf mtr-2 mtr-3 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 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr-0) (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-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-1) (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-0) (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)) (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-3) (c c) (m m) (b b)) (precedes ((1 0) (2 0)) ((1 0) (5 0)) ((1 0) (6 0)) ((2 1) (0 0)) ((2 1) (3 0)) ((3 1) (4 2)) ((4 1) (3 0)) ((4 3) (1 1)) ((4 4) (1 2)) ((5 1) (4 0)) ((6 1) (4 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr-0 btr-0 mtr-1 mtr-2 mtr-3) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation generalization deleted (5 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 (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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 (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-0 mtr-1) (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-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 (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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-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)))) ((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-3 (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 422) (parent 410) (seen 421) (realized) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr mtr-0 btr-0 mtr-1 merc-conf mtr-2 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 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr-0) (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-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-1) (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-0) (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 ((1 0) (2 0)) ((1 0) (5 0)) ((2 1) (0 0)) ((3 1) (4 2)) ((4 1) (3 0)) ((4 3) (1 1)) ((4 4) (1 2)) ((5 1) (4 0))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr-0 btr-0 mtr-1 mtr-2) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation generalization deleted (6 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 (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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 (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-0 mtr-1) (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-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 (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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-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 423) (parent 416) (seen 321) (realized) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncb ncm data) (item merchandise) (bank-conf btr mtr mtr-0 btr-0 mtr-1 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 3 (account account) (cost cost) (n n) (ncb ncb) (ncm ncm) (item item) (merc-conf merc-conf) (bank-conf bank-conf) (btr btr-0) (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-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-1) (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-0) (mtr mtr-1) (c c) (m m) (b b)) (precedes ((0 1) (1 2)) ((1 0) (2 0)) ((2 1) (0 0)) ((2 1) (4 0)) ((3 1) (4 2)) ((4 1) (3 0)) ((4 3) (1 1)) ((4 4) (1 2))) (non-orig (privk "enc" m) (privk "sig" c) (privk "sig" m) (privk "sig" b)) (uniq-orig n ncb ncm btr mtr-0 btr-0 mtr-1) (facts (neq n ncb) (neq n ncm) (neq ncm ncb)) (operation generalization weakened ((0 1) (1 1))) (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 (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (recv (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (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 (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-0 mtr-1) (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-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 (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b)) (pubk "enc" m))) (send (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr-1) (privk "sig" b))) (send (sign (mconf (hash c m b n item cost (hash n (hash ncb bank-conf))) btr-0 mtr-1) (privk "sig" m))))) (label 424) (parent 418) (seen 419) (realized) (comment "1 in cohort - 0 not yet seen")) (comment "Nothing left to do") (defprotocol minipay 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 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 (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 425) (unrealized (0 2)) (origs (mtr (0 1))) (comment "Not closed under rules")) (defskeleton minipay (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) (rule cheq-merc-4) (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 426) (parent 425) (unrealized (0 2)) (origs (mtr (0 1))) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (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" m) (privk "sig" b)) (uniq-orig btr mtr) (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 427) (parent 426) (unrealized (0 2) (1 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (vars (for-bank 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 (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)) (precedes ((0 1) (1 0)) ((1 1) (0 2))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig btr mtr) (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 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)))) ((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 428) (parent 427) (unrealized (1 0)) (comment "2 in cohort - 2 not yet seen")) (defskeleton minipay (vars (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 (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)) (precedes ((0 1) (1 0)) ((1 1) (0 2))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig btr mtr) (operation nonce-test (contracted (for-bank (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" b)))) mtr (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 bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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))))) (label 429) (parent 428) (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 (vars (account account-0 acct) (cost amount) (n ncm ncb ncb-0 data) (item merchandise) (merc-conf btr mtr bank-conf bank-conf-0 btr-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 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 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-0) (mtr mtr) (c c) (m m) (b b)) (precedes ((0 1) (2 0)) ((1 1) (0 2)) ((2 1) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig btr mtr btr-0) (operation nonce-test (added-strand bank 2) mtr (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-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-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))) (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 (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-0 mtr) (privk "sig" b)) (pubk "enc" m))))) (label 430) (parent 428) (unrealized (1 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (vars (account acct) (cost amount) (n ncm ncb data) (item merchandise) (merc-conf btr mtr bank-conf btr-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 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) (c c) (m m) (b b)) (precedes ((0 1) (2 0)) ((1 1) (0 2)) ((2 1) (1 0))) (non-orig (privk "enc" m) (privk "enc" b) (privk "sig" m) (privk "sig" b)) (uniq-orig btr mtr btr-0) (operation nonce-test (contracted (bank-conf-0 bank-conf) (account-0 account) (ncb-0 ncb)) mtr (1 0) (enc (hash ncb bank-conf) (sign (bconf (hash c m b n cost (hash n (hash ncm item merc-conf))) btr-0 mtr) (privk "sig" b)) (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 (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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 (payreq c m b (hash cost n) (hash ncm item merc-conf) mtr (cat (sign (order c m b cost (enc n cost account bank-conf ncb (hash n (hash ncm item merc-conf)) (pubk "enc" 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) (privk "sig" b)) (pubk "enc" m))))) (label 431) (parent 430) (seen 429) (realized) (comment "1 in cohort - 0 not yet seen")) (comment "Nothing left to do") (defprotocol minipay 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 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 (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 432) (unrealized (0 2)) (origs (mtr (0 1))) (comment "Not closed under rules")) (defskeleton minipay (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) (rule cheq-merc-4) (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 433) (parent 432) (unrealized (0 2)) (origs (mtr (0 1))) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (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" b)) (uniq-orig btr mtr) (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 434) (parent 433) (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 for-bank) (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 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 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 (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 435) (unrealized (0 0)) (origs) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (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)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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 436) (parent 435) (unrealized (0 0)) (comment "2 in cohort - 2 not yet seen")) (defskeleton minipay (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)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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 437) (parent 436) (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 (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)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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 438) (parent 436) (unrealized (2 0)) (comment "2 in cohort - 2 not yet seen")) (defskeleton minipay (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)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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 439) (parent 438) (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 (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)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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 440) (parent 438) (seen 439) (realized) (comment "1 in cohort - 0 not yet seen")) (comment "Nothing left to do") (defprotocol minipay 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 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 (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 441) (unrealized (0 0)) (origs) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (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)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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 442) (parent 441) (unrealized (0 0)) (comment "2 in cohort - 2 not yet seen")) (defskeleton minipay (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)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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 443) (parent 442) (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 (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)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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 444) (parent 442) (unrealized (0 0) (2 0)) (comment "1 in cohort - 1 not yet seen")) (defskeleton minipay (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)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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 445) (parent 444) (unrealized (2 0)) (comment "2 in cohort - 2 not yet seen")) (defskeleton minipay (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)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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 446) (parent 445) (seen 443) (realized) (comment "1 in cohort - 0 not yet seen")) (defskeleton minipay (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)) (rule fact-cust-neq0 fact-cust-neq1 fact-cust-neq2) (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 447) (parent 445) (seen 446) (realized) (comment "1 in cohort - 0 not yet seen")) (comment "Nothing left to do")