Alpha: replace the faucet by preallocated-contract activation.

This commit is contained in:
Vincent Botbol 2018-03-08 11:50:51 -05:00 committed by Grégoire Henry
parent f98ed35583
commit c2990b4f14
28 changed files with 414 additions and 80 deletions

View File

@ -65,12 +65,6 @@ $client transfer 10 from bootstrap1 to hardlimit -arg "Unit"
$client transfer 10 from bootstrap1 to hardlimit -arg "Unit"
# $client transfer 10 from bootstrap1 to hardlimit -arg "unit" # should fail
$client originate free account free_account for $key1
$client get delegate for free_account
$client register key $key2 as delegate
$client set delegate for free_account to $key2
$client get delegate for free_account
$client get balance for bootstrap5 | assert "4,000,000 ꜩ"
$client transfer 400,000 from bootstrap5 to bootstrap1 -fee 0
$client transfer 400,000 from bootstrap1 to bootstrap5 -fee 0

View File

@ -51,7 +51,7 @@ let commands () =
@@ seq_of_param Block_hash.param)
(fun () block_hashes cctxt ->
reveal_block_nonces cctxt block_hashes) ;
command ~group ~desc: "Forge and inject redemption operations."
command ~group ~desc: "Forge and inject all the possible seed-nonce revelation operations."
no_options
(prefixes [ "reveal"; "nonces" ]
@@ stop)

View File

@ -133,13 +133,6 @@ let originate_account ?branch
Client_keys.sign cctxt src_sk bytes >>=? fun signature ->
originate cctxt ~block ~chain_id ~signature bytes
let faucet ?branch ~manager_pkh block rpc_config () =
get_branch rpc_config block branch >>=? fun (chain_id, branch) ->
let nonce = Rand.generate Constants_repr.nonce_length in
Alpha_services.Forge.Anonymous.faucet
rpc_config block ~branch ~id:manager_pkh ~nonce () >>=? fun bytes ->
originate rpc_config ~chain_id ~block bytes
let delegate_contract cctxt
block ?branch
~source ?src_pk ~manager_sk

View File

@ -104,13 +104,6 @@ val originate_contract:
#Proto_alpha.full ->
(Operation_hash.t * Contract.t) tzresult Lwt.t
val faucet :
?branch:int ->
manager_pkh:public_key_hash ->
Block_services.block ->
#Proto_alpha.rpc_context ->
unit -> (Operation_list_hash.elt * Contract.t) tzresult Lwt.t
val transfer :
#Proto_alpha.full ->
Block_services.block ->

View File

@ -260,23 +260,6 @@ let commands () =
operation_submitted_message cctxt oph
end;
command ~group:alphanet ~desc: "Open a new FREE account (Alphanet only)."
(args1 force_switch)
(prefixes [ "originate" ; "free" ; "account" ]
@@ RawContractAlias.fresh_alias_param
~name: "new" ~desc: "name of the new contract"
@@ prefix "for"
@@ Public_key_hash.alias_param
~name: "mgr" ~desc: "manager of the new contract"
@@ stop)
begin fun force alias_name (_, manager_pkh) (cctxt: Proto_alpha.full) ->
RawContractAlias.of_fresh cctxt force alias_name >>=? fun alias_name ->
faucet ~manager_pkh cctxt#block cctxt () >>=? fun (oph, contract) ->
operation_submitted_message cctxt
~contracts:[contract] oph >>=? fun () ->
save_contract ~force cctxt alias_name contract
end;
command ~group:alphanet ~desc: "Activate a protocol (Alphanet dictator only)."
no_options
(prefixes [ "activate" ; "protocol" ]

View File

@ -6,6 +6,8 @@
"Nonce_hash",
"Script_expr_hash",
"Contract_hash",
"Blinded_public_key_hash",
"Unclaimed_public_key_hash",
"Qty_repr",
"Tez_repr",
@ -28,6 +30,7 @@
"Block_header_repr",
"Operation_repr",
"Manager_repr",
"Commitment_repr",
"Raw_context",
"Storage_sigs",
@ -44,6 +47,7 @@
"Bootstrap_storage",
"Fitness_storage",
"Vote_storage",
"Commitment_storage",
"Init_storage",
"Alpha_context",

View File

@ -90,6 +90,11 @@ module Fitness = struct
end
module Commitment = struct
include Commitment_repr
include Commitment_storage
end
let init = Init_storage.may_initialize
let finalize ?commit_message:message c =

View File

@ -262,7 +262,6 @@ module Constants : sig
val origination_burn: Tez.t
val block_security_deposit: Tez.t
val endorsement_security_deposit: Tez.t
val faucet_credit: Tez.t
val max_revelations_per_block: int
val preserved_cycles: context -> int
@ -642,9 +641,9 @@ and anonymous_operation =
bh1: Block_header.t ;
bh2: Block_header.t ;
}
| Faucet of {
| Activation of {
id: Ed25519.Public_key_hash.t ;
nonce: MBytes.t ;
secret: Blinded_public_key_hash.secret ;
}
and sourced_operations =
@ -753,6 +752,19 @@ module Roll : sig
end
module Commitment : sig
type t =
{ blinded_public_key_hash : Blinded_public_key_hash.t ;
amount : Tez.tez }
val get_opt:
context -> Unclaimed_public_key_hash.t -> t option tzresult Lwt.t
val delete:
context -> Unclaimed_public_key_hash.t -> context tzresult Lwt.t
end
val init:
Context.t ->
level:Int32.t ->

View File

@ -36,7 +36,8 @@ type error += Too_early_double_baking_evidence
of { level: Raw_level.t ; current: Raw_level.t } (* `Temporary *)
type error += Outdated_double_baking_evidence
of { level: Raw_level.t ; last: Raw_level.t } (* `Permanent *)
type error += Invalid_activation
type error += Wrong_activation_secret
let () =
register_error_kind
@ -287,7 +288,29 @@ let () =
Some (level, last)
| _ -> None)
(fun (level, last) ->
Outdated_double_baking_evidence { level ; last })
Outdated_double_baking_evidence { level ; last }) ;
register_error_kind
`Permanent
~id:"operation.invalid_activation"
~title:"Invalid activation"
~description:"The given key has already been activated or the given \
key does not correspond to any preallocated contract"
~pp:(fun ppf () ->
Format.fprintf ppf "Invalid activation.")
Data_encoding.unit
(function Invalid_activation -> Some () | _ -> None)
(fun () -> Invalid_activation) ;
register_error_kind
`Permanent
~id:"operation.wrong_activation_secret"
~title:"Wrong activation secret"
~description:"The submitted activation key does not match the \
registered key."
~pp:(fun ppf () ->
Format.fprintf ppf "Wrong activation secret.")
Data_encoding.unit
(function Wrong_activation_secret -> Some () | _ -> None)
(fun () -> Wrong_activation_secret)
let apply_consensus_operation_content ctxt
pred_block block_priority operation = function
@ -465,7 +488,7 @@ let apply_sourced_operation
fork_test_chain ctxt hash expiration >>= fun ctxt ->
return (ctxt, origination_nonce, None, Tez.zero, Tez.zero)
let apply_anonymous_operation ctxt delegate origination_nonce kind =
let apply_anonymous_operation ctxt _delegate origination_nonce kind =
match kind with
| Seed_nonce_revelation { level ; nonce } ->
let level = Level.from_raw ctxt level in
@ -548,12 +571,18 @@ let apply_anonymous_operation ctxt delegate origination_nonce kind =
| Ok v -> v
| Error _ -> Tez.zero in
return (ctxt, origination_nonce, Tez.zero, reward)
| Faucet { id = manager ; _ } ->
Contract.originate ctxt
origination_nonce
~manager ~delegate ~balance:Constants.faucet_credit ?script:None
~spendable:true ~delegatable:true >>=? fun (ctxt, _, origination_nonce) ->
return (ctxt, origination_nonce, Tez.zero, Tez.zero)
| Activation { id = pkh ; secret } ->
let h_pkh = Unclaimed_public_key_hash.of_ed25519_pkh pkh in
Commitment.get_opt ctxt h_pkh >>=? function
| None -> fail Invalid_activation
| Some { blinded_public_key_hash = submitted_bpkh ; amount } ->
let blinded_pkh = Blinded_public_key_hash.of_ed25519_pkh secret pkh in
fail_unless
Blinded_public_key_hash.(blinded_pkh = submitted_bpkh)
Wrong_activation_secret >>=? fun () ->
Commitment.delete ctxt h_pkh >>=? fun ctxt ->
Contract.(credit ctxt (implicit_contract pkh) amount) >>=? fun ctxt ->
return (ctxt, origination_nonce, Tez.zero, Tez.zero)
let apply_operation
ctxt delegate pred_block block_prio hash operation =

View File

@ -0,0 +1,37 @@
(**************************************************************************)
(* *)
(* Copyright (c) 2014 - 2018. *)
(* Dynamic Ledger Solutions, Inc. <contact@tezos.com> *)
(* *)
(* All rights reserved. No warranty, explicit or implicit, provided. *)
(* *)
(**************************************************************************)
type t = MBytes.t
type secret = MBytes.t
let size = Ed25519.Public_key_hash.size
let secret_size = Ed25519.Public_key_hash.size
let encoding = Data_encoding.Fixed.bytes size
let secret_encoding = Data_encoding.Fixed.bytes secret_size
let of_ed25519_pkh secret pkh =
Ed25519.Public_key_hash.to_bytes @@
Ed25519.Public_key_hash.hash_bytes
~key:secret
[ Ed25519.Public_key_hash.to_bytes pkh ]
let compare = MBytes.compare
let (=) = MBytes.(=)
let of_hex h =
if Compare.Int.(String.length h <> size * 2) then
invalid_arg "Blinded_public_key_hash.of_hex" ;
MBytes.of_hex (`Hex h)
let secret_of_hex h =
if Compare.Int.(String.length h <> secret_size * 2) then
invalid_arg "Blinded_public_key_hash.secret_of_hex" ;
MBytes.of_hex (`Hex h)

View File

@ -0,0 +1,22 @@
(**************************************************************************)
(* *)
(* Copyright (c) 2014 - 2018. *)
(* Dynamic Ledger Solutions, Inc. <contact@tezos.com> *)
(* *)
(* All rights reserved. No warranty, explicit or implicit, provided. *)
(* *)
(**************************************************************************)
type t
val encoding : t Data_encoding.t
type secret
val secret_encoding : secret Data_encoding.t
val of_ed25519_pkh : secret -> Ed25519.Public_key_hash.t -> t
val of_hex : string -> t
val secret_of_hex : string -> secret
val compare : t -> t -> int
val (=) : t -> t -> bool

View File

@ -0,0 +1,25 @@
(**************************************************************************)
(* *)
(* Copyright (c) 2014 - 2018. *)
(* Dynamic Ledger Solutions, Inc. <contact@tezos.com> *)
(* *)
(* All rights reserved. No warranty, explicit or implicit, provided. *)
(* *)
(**************************************************************************)
type t = {
blinded_public_key_hash : Blinded_public_key_hash.t ;
amount : Tez_repr.t
}
let encoding =
let open Data_encoding in
conv
(fun { blinded_public_key_hash ; amount } ->
( blinded_public_key_hash, amount ))
(fun ( blinded_public_key_hash, amount) ->
{ blinded_public_key_hash ; amount })
(obj2
(req "blinded_public_key_hash" Blinded_public_key_hash.encoding)
(req "amount" Tez_repr.encoding)
)

View File

@ -0,0 +1,15 @@
(**************************************************************************)
(* *)
(* Copyright (c) 2014 - 2018. *)
(* Dynamic Ledger Solutions, Inc. <contact@tezos.com> *)
(* *)
(* All rights reserved. No warranty, explicit or implicit, provided. *)
(* *)
(**************************************************************************)
type t = {
blinded_public_key_hash : Blinded_public_key_hash.t ;
amount : Tez_repr.t ;
}
val encoding : t Data_encoding.t

View File

@ -0,0 +1,38 @@
(**************************************************************************)
(* *)
(* Copyright (c) 2014 - 2018. *)
(* Dynamic Ledger Solutions, Inc. <contact@tezos.com> *)
(* *)
(* All rights reserved. No warranty, explicit or implicit, provided. *)
(* *)
(**************************************************************************)
open Commitment_repr
let test_commitments = [
"dca88243fece75e9c22e", "4a6af2f5c466bf0a7a1001a1e9468cbfca82cef6", 1868898542104130027;
"c736bfb7074f69bee133", "32d7b02afc218623b4e2fd85b84b06f0a1d202d2", 517697389496079974;
"e07bb6ba71082141eae0", "17a0241048b13857abe19db7fa11ac63de3eda5e", 962290491831710023;
"17efe5e32c28126c4e94", "7484c711d0cbd8ba6e7f9965311a4903ea17b80a", 1233665184704419921;
"5c742b7e335b265cfa82", "3ca39ae8ddd026030af633561382d4e16c8c2cae", 131959324067470008;
"40196c01a502608d7f22", "ebb81e0f79c568c0181e9db9cdafde7a8db65f82", 112378240876120002;
"d7abb1cd59a66ce3fc42", "f8e91e7adba8cc32ce848a43e440de7c3e4f0866", 1060667014046690017;
"f7a1e97970689cce7291", "4f964fbe29971a85c7152541519b1dbb8e436184", 71300478465380003;
"f59ee7283f7eda5b3c03", "591e167977f9c4739ab17cc9d40a672737b45fa1", 283380756728119992;
"076b7feedde492164ca3", "8a5bb1da65cbbc7f3acdc3a3dae22b43364d80a6", 1357762577679880028
]
let init_commitment ctxt (hpkh, blind, amount) =
let half_public_key_hash = Unclaimed_public_key_hash.of_hex hpkh in
let blinded_public_key_hash = Blinded_public_key_hash.of_hex blind in
let amount = Tez_repr.of_mutez_exn (Int64.of_int amount) in
Storage.Commitments.init
ctxt half_public_key_hash
{ blinded_public_key_hash ; amount }
let init ctxt =
fold_left_s init_commitment ctxt test_commitments >>=? fun ctxt ->
return ctxt
let get_opt = Storage.Commitments.get_option
let delete = Storage.Commitments.delete

View File

@ -0,0 +1,19 @@
(**************************************************************************)
(* *)
(* Copyright (c) 2014 - 2018. *)
(* Dynamic Ledger Solutions, Inc. <contact@tezos.com> *)
(* *)
(* All rights reserved. No warranty, explicit or implicit, provided. *)
(* *)
(**************************************************************************)
val init:
Raw_context.t -> Raw_context.t tzresult Lwt.t
val get_opt:
Raw_context.t -> Unclaimed_public_key_hash.t ->
Commitment_repr.t option tzresult Lwt.t
val delete:
Raw_context.t -> Unclaimed_public_key_hash.t ->
Raw_context.t tzresult Lwt.t

View File

@ -38,10 +38,6 @@ let block_reward =
let endorsement_reward =
Tez_repr.(mul_exn one 2)
(* 100,000 tez *)
let faucet_credit =
Tez_repr.(mul_exn one 100_000)
(* 4,000,000 tez *)
let bootstrap_wealth =
Tez_repr.(mul_exn one 4_000_000)

View File

@ -412,10 +412,6 @@ module Forge = struct
block ~branch ~level ~nonce () =
operations ctxt block ~branch [Seed_nonce_revelation { level ; nonce }]
let faucet ctxt
block ~branch ~id ~nonce () =
operations ctxt block ~branch [Faucet { id ; nonce }]
end
let empty_proof_of_work_nonce =
@ -521,4 +517,3 @@ module Parse = struct
S.block ctxt block () ({ shell ; protocol_data } : Block_header.raw)
end

View File

@ -183,13 +183,6 @@ module Forge : sig
nonce:Nonce.t ->
unit -> MBytes.t shell_tzresult Lwt.t
val faucet:
'a #RPC_context.simple -> 'a ->
branch:Block_hash.t ->
id:public_key_hash ->
nonce:MBytes.t ->
unit -> MBytes.t shell_tzresult Lwt.t
end
val protocol_data:

View File

@ -15,6 +15,7 @@ let initialize ctxt =
Bootstrap_storage.init ctxt >>=? fun ctxt ->
Roll_storage.init_first_cycles ctxt >>=? fun ctxt ->
Vote_storage.init ctxt >>=? fun ctxt ->
Commitment_storage.init ctxt >>=? fun ctxt ->
return ctxt
let may_initialize ctxt ~level ~timestamp ~fitness =

View File

@ -39,9 +39,9 @@ and anonymous_operation =
bh1: Block_header_repr.t ;
bh2: Block_header_repr.t ;
}
| Faucet of {
| Activation of {
id: Ed25519.Public_key_hash.t ;
nonce: MBytes.t ;
secret: Blinded_public_key_hash.secret ;
}
and sourced_operations =
@ -342,19 +342,19 @@ module Encoding = struct
)
(fun ((), bh1, bh2) -> Double_baking_evidence { bh1 ; bh2 })
let faucet_encoding =
let activation_encoding =
(obj3
(req "kind" (constant "faucet"))
(req "id" Ed25519.Public_key_hash.encoding)
(req "nonce" (Fixed.bytes 16)))
(req "kind" (constant "activation"))
(req "pkh" Ed25519.Public_key_hash.encoding)
(req "secret" Blinded_public_key_hash.secret_encoding))
let faucet_case tag =
case tag faucet_encoding
let activation_case tag =
case tag activation_encoding
(function
| Faucet { id ; nonce } -> Some ((), id, nonce)
| Activation { id ; secret } -> Some ((), id, secret)
| _ -> None
)
(fun ((), id, nonce) -> Faucet { id ; nonce })
(fun ((), id, secret) -> Activation { id ; secret })
let unsigned_operation_case tag op_encoding =
case tag
@ -365,7 +365,7 @@ module Encoding = struct
seed_nonce_revelation_case (Tag 0) ;
double_endorsement_evidence_case (Tag 1) op_encoding ;
double_baking_evidence_case (Tag 2) ;
faucet_case (Tag 3) ;
activation_case (Tag 3) ;
]))))
(function Anonymous_operations ops -> Some ops | _ -> None)
(fun ops -> Anonymous_operations ops)

View File

@ -39,9 +39,9 @@ and anonymous_operation =
bh1: Block_header_repr.t ;
bh2: Block_header_repr.t ;
}
| Faucet of {
| Activation of {
id: Ed25519.Public_key_hash.t ;
nonce: MBytes.t ;
secret: Blinded_public_key_hash.secret ;
}
and sourced_operations =

View File

@ -137,4 +137,3 @@ include T with type t := t and type context := context
val record_endorsement: context -> int -> context
val endorsement_already_recorded: context -> int -> bool

View File

@ -141,6 +141,7 @@ module Contract = struct
type t = Script_repr.expr
let encoding = Script_repr.expr_encoding
end))
type bigmap_key = Raw_context.t * Contract_repr.t
module Big_map =
@ -421,6 +422,14 @@ module Seed = struct
end
(** Commitments *)
module Commitments =
Make_indexed_data_storage
(Make_subcontext(Raw_context)(struct let name = ["commitments"] end))
(Unclaimed_public_key_hash.Index)
(Make_value(Commitment_repr))
(** Resolver *)
let () =

View File

@ -257,3 +257,10 @@ module Seed : sig
end
end
(** Commitments *)
module Commitments : Indexed_data_storage
with type key = Unclaimed_public_key_hash.t
and type value = Commitment_repr.t
and type t := Raw_context.t

View File

@ -0,0 +1,38 @@
(**************************************************************************)
(* *)
(* Copyright (c) 2014 - 2018. *)
(* Dynamic Ledger Solutions, Inc. <contact@tezos.com> *)
(* *)
(* All rights reserved. No warranty, explicit or implicit, provided. *)
(* *)
(**************************************************************************)
type t = MBytes.t
let size = Ed25519.Public_key_hash.size / 2
let of_ed25519_pkh pkh =
MBytes.sub (Ed25519.Public_key_hash.to_bytes pkh) 0 size
let encoding = Data_encoding.Fixed.bytes size
let of_hex h =
if Compare.Int.(String.length h <> size * 2) then
invalid_arg "Blinded_public_key_hash.of_hex" ;
MBytes.of_hex (`Hex h)
module Index = struct
type t = MBytes.t
let path_length = 2
let to_path half_public_key_hash l =
let `Hex h = MBytes.to_hex half_public_key_hash in
String.sub h 0 2 :: String.sub h 2 (size - 2) :: l
let of_path = function
| [ h1 ; h2 ] -> Some (MBytes.of_hex (`Hex (h1 ^ h2)))
| _ -> None
end

View File

@ -0,0 +1,22 @@
(**************************************************************************)
(* *)
(* Copyright (c) 2014 - 2018. *)
(* Dynamic Ledger Solutions, Inc. <contact@tezos.com> *)
(* *)
(* All rights reserved. No warranty, explicit or implicit, provided. *)
(* *)
(**************************************************************************)
type t
val encoding : t Data_encoding.t
val of_ed25519_pkh : Ed25519.Public_key_hash.t -> t
val of_hex : string -> t
module Index : sig
type nonrec t = t
val path_length : int
val to_path : t -> string list -> string list
val of_path : string list -> t option
end

View File

@ -23,4 +23,5 @@ let () =
"origination", List.map wrap Test_origination.tests ;
"bigmaps", List.map wrap Test_big_maps.tests ;
"michelson", List.map wrap Test_michelson.tests ;
"activation", List.map wrap Test_activation.tests ;
]

View File

@ -0,0 +1,104 @@
(**************************************************************************)
(* *)
(* Copyright (c) 2014 - 2016. *)
(* Dynamic Ledger Solutions, Inc. <contact@tezos.com> *)
(* *)
(* All rights reserved. No warranty, explicit or implicit, provided. *)
(* *)
(**************************************************************************)
open Proto_alpha
open Error_monad
let name = "Isolate Activation"
exception No_error
open Isolate_helpers
(* Generated commitment with secret included in commitment storage :
pk = 097291124abb881ccdeea4f9a6912f34e3379586853360fa8ced414c1a3dee11
pkh =dca88243fece75e9c22e63d162a8ada8f0cf4d94
pk_b58 =tz1fkmDXEQdua3u71vstaKwR4h8KY7oT1PDF
amount = 1868898542104
secret =c5422e3864b9e6c5260e2aac76ea0f3d28d4fff7
half_pkh = dca88243fece75e9c22e
blinded_pkh : 4a6af2f5c466bf0a7a1001a1e9468cbfca82cef6
amount :1868898542104130027 *)
let used_blind = MBytes.of_string "abc"
let hash_bytes pkh_bytes bytes =
let open Ed25519.Public_key_hash in
let hb = to_bytes (hash_bytes [ bytes ; pkh_bytes ]) in
hash_bytes [ bytes ; hb ]
let test_hash_correctness () =
let open Ed25519 in
let module PKH = Public_key_hash in
let pk = Public_key.of_hex_exn (`Hex "097291124abb881ccdeea4f9a6912f34e3379586853360fa8ced414c1a3dee11") in
let pkh = PKH.of_hex_exn "dca88243fece75e9c22e63d162a8ada8f0cf4d94" in
let pkh_b58c = "tz1fkmDXEQdua3u71vstaKwR4h8KY7oT1PDF" in
let given_secret = MBytes.of_hex (`Hex "c5422e3864b9e6c5260e2aac76ea0f3d28d4fff7") in
let expected_half_pkh = MBytes.of_hex (`Hex "dca88243fece75e9c22e") in
let expected_blinded_pkh = MBytes.of_hex (`Hex "4a6af2f5c466bf0a7a1001a1e9468cbfca82cef6") in
Assert.equal ~eq:(Public_key_hash.equal) (Public_key.hash pk) pkh;
let pkh_bytes = PKH.to_bytes pkh in
let pkh' = PKH.of_b58check_exn pkh_b58c in
Assert.equal ~eq:(PKH.equal) pkh pkh';
let half_pkh'_bytes = MBytes.sub (PKH.to_bytes pkh') 0 10 in
Assert.equal ~eq:(MBytes.equal) half_pkh'_bytes expected_half_pkh;
let blinded_pkh = PKH.to_bytes (PKH.hash_bytes ~key:given_secret [ pkh_bytes ]) in
Assert.equal ~eq:(MBytes.equal) blinded_pkh expected_blinded_pkh;
return ()
let test_simple_activation () =
let module PKH = Ed25519.Public_key_hash in
Init.main () >>=? fun starting_block ->
let id = Ed25519.Public_key_hash.of_b58check_exn "tz1fkmDXEQdua3u71vstaKwR4h8KY7oT1PDF" in
let secret =
Blinded_public_key_hash.secret_of_hex
"c5422e3864b9e6c5260e2aac76ea0f3d28d4fff7" in
let activation_operation = Alpha_context.(Activation { id ; secret }) in
Proto_alpha.Apply.apply_anonymous_operation
starting_block.tezos_context
None
starting_block.hash
activation_operation >>=? fun (ctxt, _, _, _) ->
let open Proto_alpha.Alpha_context in
Lwt.return @@ Contract.of_b58check "tz1fkmDXEQdua3u71vstaKwR4h8KY7oT1PDF" >>=? fun ctrt ->
Proto_alpha.Alpha_context.Contract.get_balance ctxt ctrt >>=? fun amount ->
let expected_amount =
match Tez.of_mutez 1868898542104130027L with
| Some s -> s
| _ -> Assert.fail_msg "Invalid conversion"
in
Assert.equal ~eq:(Tez.equal) amount expected_amount;
return ()
let tests =
List.map
(fun (n, f) -> (n, (fun () -> f () >>= Assert.wrap)))
[ "activation.hash_correctness", test_hash_correctness ;
"activation.simple_activation", test_simple_activation
]