Proto: the number of validation is now a protocol constant

This commit is contained in:
Grégoire Henry 2018-01-31 10:04:35 +01:00 committed by Benjamin Canou
parent 42023753a2
commit ae3ff0503b
24 changed files with 88 additions and 88 deletions

View File

@ -392,7 +392,6 @@ go_alpha_go() {
activate \ activate \
protocol ProtoALphaALphaALphaALphaALphaALphaALphaALphaDdp3zK \ protocol ProtoALphaALphaALphaALphaALphaALphaALphaALphaDdp3zK \
with fitness 1 \ with fitness 1 \
and passes 1 \
and key dictator and key dictator
} }

View File

@ -199,7 +199,6 @@ activate_alpha() {
-block genesis \ -block genesis \
activate protocol ProtoALphaALphaALphaALphaALphaALphaALphaALphaDdp3zK \ activate protocol ProtoALphaALphaALphaALphaALphaALphaALphaALphaDdp3zK \
with fitness 1 \ with fitness 1 \
and passes 1 \
and key dictator and key dictator
} }
@ -232,7 +231,7 @@ main () {
cat <<EOF cat <<EOF
if type tezos-client-reset >/dev/null 2>&1 ; then tezos-client-reset; fi ; if type tezos-client-reset >/dev/null 2>&1 ; then tezos-client-reset; fi ;
alias tezos-client="$client" ; alias tezos-client="$client" ;
alias tezos-activate-alpha="$client -block genesis activate protocol ProtoALphaALphaALphaALphaALphaALphaALphaALphaDdp3zK with fitness 1 and passes 1 and key dictator" ; alias tezos-activate-alpha="$client -block genesis activate protocol ProtoALphaALphaALphaALphaALphaALphaALphaALphaDdp3zK with fitness 1 and key dictator" ;
alias tezos-client-reset="rm -rf \"$client_dir\"; unalias tezos-client tezos-activate-alpha tezos-client-reset" ; alias tezos-client-reset="rm -rf \"$client_dir\"; unalias tezos-client tezos-activate-alpha tezos-client-reset" ;
alias tezos-autocomplete="source \"$bin_dir/bash-completion.sh\"" ; alias tezos-autocomplete="source \"$bin_dir/bash-completion.sh\"" ;
trap tezos-client-reset EXIT ; trap tezos-client-reset EXIT ;

View File

@ -14,10 +14,14 @@ module Make(Context : sig type t end) = struct
fitness: Fitness.t ; fitness: Fitness.t ;
message: string option ; message: string option ;
max_operation_data_length: int ; max_operation_data_length: int ;
max_number_of_operations: int list ;
max_operations_ttl: int ; max_operations_ttl: int ;
} }
type quota = {
max_size: int ;
max_op: int option ;
}
type rpc_context = { type rpc_context = {
block_hash: Block_hash.t ; block_hash: Block_hash.t ;
block_header: Block_header.t ; block_header: Block_header.t ;
@ -30,6 +34,7 @@ module Make(Context : sig type t end) = struct
type error = .. type error = ..
type 'a tzresult = ('a, error list) result type 'a tzresult = ('a, error list) result
val max_block_length: int val max_block_length: int
val validation_passes: quota list
type operation type operation
val parse_operation: val parse_operation:
Operation_hash.t -> Operation.t -> operation tzresult Operation_hash.t -> Operation.t -> operation tzresult

View File

@ -27,10 +27,6 @@ type validation_result = {
max_operation_data_length: int ; max_operation_data_length: int ;
(** The maximum size of operations in bytes. *) (** The maximum size of operations in bytes. *)
max_number_of_operations: int list ;
(** The maximum number of operations allowed in one block
(per validation pass). *)
max_operations_ttl: int ; max_operations_ttl: int ;
(** The "time-to-live" of operation for the next block: any (** The "time-to-live" of operation for the next block: any
operations whose 'branch' is older than 'ttl' blocks in the operations whose 'branch' is older than 'ttl' blocks in the
@ -38,6 +34,15 @@ type validation_result = {
} }
type quota = {
max_size: int ;
(** The maximum size (in bytes) of the serialized list of
operations. *)
max_op: int option ;
(** The maximum number of operation.
[None] means no limit. *)
}
type rpc_context = { type rpc_context = {
block_hash: Block_hash.t ; block_hash: Block_hash.t ;
block_header: Block_header.t ; block_header: Block_header.t ;
@ -53,6 +58,10 @@ module type PROTOCOL = sig
(** The maximum size of block headers in bytes. *) (** The maximum size of block headers in bytes. *)
val max_block_length: int val max_block_length: int
(** The number of validation passes (length of the list) and the
operation's quota for each pass. *)
val validation_passes: quota list
(** The version specific type of operations. *) (** The version specific type of operations. *)
type operation type operation

View File

@ -16,10 +16,14 @@ type validation_result = {
fitness: Fitness.t ; fitness: Fitness.t ;
message: string option ; message: string option ;
max_operation_data_length: int ; max_operation_data_length: int ;
max_number_of_operations: int list ;
max_operations_ttl: int ; max_operations_ttl: int ;
} }
type quota = {
max_size: int ;
max_op: int option ;
}
type rpc_context = { type rpc_context = {
block_hash: Block_hash.t ; block_hash: Block_hash.t ;
block_header: Block_header.t ; block_header: Block_header.t ;
@ -112,6 +116,7 @@ module Node_protocol_environment_sigs = struct
and type Block_header.t = Block_header.t and type Block_header.t = Block_header.t
and type 'a RPC_directory.t = 'a RPC_directory.t and type 'a RPC_directory.t = 'a RPC_directory.t
and type Updater.validation_result = validation_result and type Updater.validation_result = validation_result
and type Updater.quota = quota
and type Updater.rpc_context = rpc_context and type Updater.rpc_context = rpc_context
type error += Ecoproto_error of Error_monad.error list type error += Ecoproto_error of Error_monad.error list
@ -125,6 +130,7 @@ module type RAW_PROTOCOL = sig
type error = .. type error = ..
type 'a tzresult = ('a, error list) result type 'a tzresult = ('a, error list) result
val max_block_length: int val max_block_length: int
val validation_passes: quota list
type operation type operation
val parse_operation: val parse_operation:
Operation_hash.t -> Operation.t -> operation tzresult Operation_hash.t -> Operation.t -> operation tzresult

View File

@ -21,10 +21,14 @@ type validation_result = {
fitness: Fitness.t ; fitness: Fitness.t ;
message: string option ; message: string option ;
max_operation_data_length: int ; max_operation_data_length: int ;
max_number_of_operations: int list ;
max_operations_ttl: int ; max_operations_ttl: int ;
} }
type quota = {
max_size: int ;
max_op: int option ;
}
type rpc_context = { type rpc_context = {
block_hash: Block_hash.t ; block_hash: Block_hash.t ;
block_header: Block_header.t ; block_header: Block_header.t ;
@ -37,6 +41,7 @@ module type RAW_PROTOCOL = sig
type error = .. type error = ..
type 'a tzresult = ('a, error list) result type 'a tzresult = ('a, error list) result
val max_block_length: int val max_block_length: int
val validation_passes: quota list
type operation type operation
val parse_operation: val parse_operation:
Operation_hash.t -> Operation.t -> operation tzresult Operation_hash.t -> Operation.t -> operation tzresult
@ -102,6 +107,7 @@ module Node_protocol_environment_sigs : sig
and type Block_header.t = Block_header.t and type Block_header.t = Block_header.t
and type 'a RPC_directory.t = 'a RPC_directory.t and type 'a RPC_directory.t = 'a RPC_directory.t
and type Updater.validation_result = validation_result and type Updater.validation_result = validation_result
and type Updater.quota = quota
and type Updater.rpc_context = rpc_context and type Updater.rpc_context = rpc_context
type error += Ecoproto_error of Error_monad.error list type error += Ecoproto_error of Error_monad.error list

View File

@ -61,7 +61,7 @@ let debug w =
Format.kasprintf (fun msg -> Worker.record_event w (Debug msg)) Format.kasprintf (fun msg -> Worker.record_event w (Debug msg))
let check_header let check_header
(pred: State.Block.t) hash (header: Block_header.t) = (pred: State.Block.t) validation_passes hash (header: Block_header.t) =
let pred_header = State.Block.header pred in let pred_header = State.Block.header pred in
fail_unless fail_unless
(Int32.succ pred_header.shell.level = header.shell.level) (Int32.succ pred_header.shell.level = header.shell.level)
@ -75,8 +75,7 @@ let check_header
Fitness.(pred_header.shell.fitness < header.shell.fitness) Fitness.(pred_header.shell.fitness < header.shell.fitness)
(invalid_block hash Non_increasing_fitness) >>=? fun () -> (invalid_block hash Non_increasing_fitness) >>=? fun () ->
fail_unless fail_unless
(header.shell.validation_passes = (header.shell.validation_passes = validation_passes)
List.length (State.Block.max_number_of_operations pred))
(invalid_block hash (invalid_block hash
(Unexpected_number_of_validation_passes header.shell.validation_passes) (Unexpected_number_of_validation_passes header.shell.validation_passes)
) >>=? fun () -> ) >>=? fun () ->
@ -120,12 +119,14 @@ let apply_block
operations = operations =
let pred_header = State.Block.header pred let pred_header = State.Block.header pred
and pred_hash = State.Block.hash pred in and pred_hash = State.Block.hash pred in
check_header pred hash header >>=? fun () -> check_header pred (List.length Proto.validation_passes) hash header >>=? fun () ->
iteri2_p iteri2_p
(fun i ops max -> (fun i ops quota ->
fail_unless fail_unless
(List.length ops <= max) (Option.unopt_map ~default:true
(invalid_block hash @@ ~f:(fun max -> List.length ops <= max) quota.Updater.max_op)
(let max = Option.unopt ~default:~-1 quota.Updater.max_op in
invalid_block hash @@
Too_many_operations Too_many_operations
{ pass = i + 1 ; found = List.length ops ; max }) >>=? fun () -> { pass = i + 1 ; found = List.length ops ; max }) >>=? fun () ->
let max_size = State.Block.max_operation_data_length pred in let max_size = State.Block.max_operation_data_length pred in
@ -138,7 +139,7 @@ let apply_block
{ operation = Operation.hash op ; { operation = Operation.hash op ;
size ; max = max_size })) ops >>=? fun () -> size ; max = max_size })) ops >>=? fun () ->
return ()) return ())
operations (State.Block.max_number_of_operations pred) >>=? fun () -> operations Proto.validation_passes >>=? fun () ->
let operation_hashes = List.map (List.map Operation.hash) operations in let operation_hashes = List.map (List.map Operation.hash) operations in
check_liveness net_state pred hash operation_hashes operations >>=? fun () -> check_liveness net_state pred hash operation_hashes operations >>=? fun () ->
map2_s (map2_s begin fun op_hash raw -> map2_s (map2_s begin fun op_hash raw ->

View File

@ -57,19 +57,12 @@ and 'a proto =
let start_prevalidation let start_prevalidation
?proto_header ?proto_header
?max_number_of_operations
~predecessor ~timestamp () = ~predecessor ~timestamp () =
let { Block_header.shell = let { Block_header.shell =
{ fitness = predecessor_fitness ; { fitness = predecessor_fitness ;
timestamp = predecessor_timestamp ; timestamp = predecessor_timestamp ;
level = predecessor_level } } = level = predecessor_level } } =
State.Block.header predecessor in State.Block.header predecessor in
let max_number_of_operations =
match max_number_of_operations with
| Some max -> max
| None ->
try List.hd (State.Block.max_number_of_operations predecessor)
with _ -> 0 in
let max_operation_data_length = let max_operation_data_length =
State.Block.max_operation_data_length predecessor in State.Block.max_operation_data_length predecessor in
State.Block.context predecessor >>= fun predecessor_context -> State.Block.context predecessor >>= fun predecessor_context ->
@ -98,6 +91,8 @@ let start_prevalidation
?proto_header ?proto_header
() ()
>>=? fun state -> >>=? fun state ->
(* FIXME arbitrary value, to be customisable *)
let max_number_of_operations = 1000 in
return (State { proto = (module Proto) ; state ; return (State { proto = (module Proto) ; state ;
max_number_of_operations ; max_operation_data_length }) max_number_of_operations ; max_operation_data_length })

View File

@ -11,7 +11,6 @@ type prevalidation_state
val start_prevalidation : val start_prevalidation :
?proto_header: MBytes.t -> ?proto_header: MBytes.t ->
?max_number_of_operations: int ->
predecessor: State.Block.t -> predecessor: State.Block.t ->
timestamp: Time.t -> timestamp: Time.t ->
unit -> prevalidation_state tzresult Lwt.t unit -> prevalidation_state tzresult Lwt.t

View File

@ -172,7 +172,6 @@ module Locked_block = struct
Store.Block.Contents.store (store, genesis.block) Store.Block.Contents.store (store, genesis.block)
{ Store.Block.header ; message = Some "Genesis" ; { Store.Block.header ; message = Some "Genesis" ;
max_operations_ttl = 0 ; context ; max_operations_ttl = 0 ; context ;
max_number_of_operations = [];
max_operation_data_length = 0; max_operation_data_length = 0;
} >>= fun () -> } >>= fun () ->
Lwt.return header Lwt.return header
@ -379,8 +378,6 @@ module Block = struct
let message { contents = { message } } = message let message { contents = { message } } = message
let max_operations_ttl { contents = { max_operations_ttl } } = let max_operations_ttl { contents = { max_operations_ttl } } =
max_operations_ttl max_operations_ttl
let max_number_of_operations { contents = { max_number_of_operations } } =
max_number_of_operations
let max_operation_data_length { contents = { max_operation_data_length } } = let max_operation_data_length { contents = { max_operation_data_length } } =
max_operation_data_length max_operation_data_length
@ -474,7 +471,7 @@ module Block = struct
let store let store
net_state block_header operations net_state block_header operations
{ Updater.context ; message ; max_operations_ttl ; { Updater.context ; message ; max_operations_ttl ;
max_number_of_operations ; max_operation_data_length } = max_operation_data_length } =
let bytes = Block_header.to_bytes block_header in let bytes = Block_header.to_bytes block_header in
let hash = Block_header.hash_raw bytes in let hash = Block_header.hash_raw bytes in
(* let's the validator check the consistency... of fitness, level, ... *) (* let's the validator check the consistency... of fitness, level, ... *)
@ -494,7 +491,6 @@ module Block = struct
Store.Block.header = block_header ; Store.Block.header = block_header ;
message ; message ;
max_operations_ttl ; max_operations_ttl ;
max_number_of_operations ;
max_operation_data_length ; max_operation_data_length ;
context = commit ; context = commit ;
} in } in

View File

@ -134,7 +134,6 @@ module Block : sig
val level: t -> Int32.t val level: t -> Int32.t
val message: t -> string option val message: t -> string option
val max_operations_ttl: t -> int val max_operations_ttl: t -> int
val max_number_of_operations: t -> int list
val max_operation_data_length: t -> int val max_operation_data_length: t -> int
val is_genesis: t -> bool val is_genesis: t -> bool

View File

@ -84,7 +84,6 @@ module Block = struct
header: Block_header.t ; header: Block_header.t ;
message: string option ; message: string option ;
max_operations_ttl: int ; max_operations_ttl: int ;
max_number_of_operations: int list;
max_operation_data_length: int; max_operation_data_length: int;
context: Context_hash.t ; context: Context_hash.t ;
} }
@ -99,21 +98,17 @@ module Block = struct
let open Data_encoding in let open Data_encoding in
conv conv
(fun { header ; message ; max_operations_ttl ; (fun { header ; message ; max_operations_ttl ;
max_number_of_operations ; max_operation_data_length ; max_operation_data_length ; context } ->
context } ->
(message, max_operations_ttl, (message, max_operations_ttl,
max_number_of_operations, max_operation_data_length, max_operation_data_length, context, header))
context, header))
(fun (message, max_operations_ttl, (fun (message, max_operations_ttl,
max_number_of_operations, max_operation_data_length, max_operation_data_length, context, header) ->
context, header) ->
{ header ; message ; max_operations_ttl ; { header ; message ; max_operations_ttl ;
max_number_of_operations ; max_operation_data_length ; max_operation_data_length ;
context }) context })
(obj6 (obj5
(opt "message" string) (opt "message" string)
(req "max_operations_ttl" uint16) (req "max_operations_ttl" uint16)
(req "max_number_of_operations" (list uint16))
(req "max_operation_data_length" uint16) (req "max_operation_data_length" uint16)
(req "context" Context_hash.encoding) (req "context" Context_hash.encoding)
(req "header" Block_header.encoding)) (req "header" Block_header.encoding))

View File

@ -88,7 +88,6 @@ module Block : sig
header: Block_header.t ; header: Block_header.t ;
message: string option ; message: string option ;
max_operations_ttl: int ; max_operations_ttl: int ;
max_number_of_operations: int list;
max_operation_data_length: int; max_operation_data_length: int;
context: Context_hash.t ; context: Context_hash.t ;
} }

View File

@ -16,6 +16,9 @@ let parse_operation = Tezos_context.Operation.parse
let max_block_length = let max_block_length =
Tezos_context.Block_header.max_header_length Tezos_context.Block_header.max_header_length
let validation_passes =
[ Updater.{ max_size = 1024 * 1024 ; max_op = None } ] (* 1MB *)
let rpc_services = Services_registration.rpc_services let rpc_services = Services_registration.rpc_services
type validation_mode = type validation_mode =

View File

@ -137,7 +137,6 @@ let finalize ?commit_message:message c =
let constants = Raw_context.constants c in let constants = Raw_context.constants c in
{ Updater.context ; fitness ; message ; max_operations_ttl = 60 ; { Updater.context ; fitness ; message ; max_operations_ttl = 60 ;
max_operation_data_length = constants.max_operation_data_length ; max_operation_data_length = constants.max_operation_data_length ;
max_number_of_operations = constants.max_number_of_operations ;
} }
let configure_sandbox = Raw_context.configure_sandbox let configure_sandbox = Raw_context.configure_sandbox

View File

@ -11,7 +11,7 @@ type operation = Operation_hash.t
let max_operation_data_length = 42 let max_operation_data_length = 42
let max_block_length = 42 let max_block_length = 42
let max_number_of_operations = 42 let validation_passes = []
let parse_operation h _ = Ok h let parse_operation h _ = Ok h
@ -88,8 +88,7 @@ let finalize_block ctxt =
let message = Some (Format.asprintf "fitness <- %Ld" fitness) in let message = Some (Format.asprintf "fitness <- %Ld" fitness) in
let fitness = Fitness.from_int64 fitness in let fitness = Fitness.from_int64 fitness in
return { Updater.message ; context = ctxt.context ; fitness ; return { Updater.message ; context = ctxt.context ; fitness ;
max_operations_ttl = 0 ; max_operation_data_length = 0 ; max_operations_ttl = 0 ; max_operation_data_length = 0 }
max_number_of_operations = [] }
let rpc_services = Services.rpc_services let rpc_services = Services.rpc_services

View File

@ -66,19 +66,16 @@ let commands () =
@@ param ~name:"fitness" @@ param ~name:"fitness"
~desc:"Hardcoded fitness of the first block (integer)" ~desc:"Hardcoded fitness of the first block (integer)"
int64_parameter int64_parameter
@@ prefixes [ "and" ; "passes" ]
@@ param ~name:"passes"
~desc:"Hardcoded number of validation passes (integer)"
int_parameter
@@ prefixes [ "and" ; "key" ] @@ prefixes [ "and" ; "key" ]
@@ Client_keys.Secret_key.source_param @@ Client_keys.Secret_key.source_param
~name:"password" ~desc:"Dictator's key" ~name:"password" ~desc:"Dictator's key"
@@ stop) @@ stop)
begin fun timestamp hash fitness validation_passes sk (cctxt : Client_commands.full_context) -> begin fun timestamp hash fitness sk (cctxt : Client_commands.full_context) ->
let fitness = let fitness =
Tezos_client_alpha.Proto_alpha.Fitness_repr.from_int64 fitness in Tezos_client_alpha.Proto_alpha.Fitness_repr.from_int64 fitness in
bake cctxt ?timestamp cctxt#block bake cctxt ?timestamp cctxt#block
(Activate { protocol = hash ; validation_passes ; fitness }) sk >>=? fun hash -> (Activate { protocol = hash ; fitness })
sk >>=? fun hash ->
cctxt#answer "Injected %a" Block_hash.pp_short hash >>= fun () -> cctxt#answer "Injected %a" Block_hash.pp_short hash >>= fun () ->
return () return ()
end ; end ;
@ -87,18 +84,13 @@ let commands () =
args args
(prefixes [ "fork" ; "test" ; "protocol" ] (prefixes [ "fork" ; "test" ; "protocol" ]
@@ Protocol_hash.param ~name:"version" ~desc:"Protocol version (b58check)" @@ Protocol_hash.param ~name:"version" ~desc:"Protocol version (b58check)"
@@ prefixes [ "with" ; "passes" ] @@ prefixes [ "with" ; "key" ]
@@ param ~name:"passes"
~desc:"Hardcoded number of validation passes (integer)"
int_parameter
@@ prefixes [ "and" ; "key" ]
@@ Client_keys.Secret_key.source_param @@ Client_keys.Secret_key.source_param
~name:"password" ~desc:"Dictator's key" ~name:"password" ~desc:"Dictator's key"
@@ stop) @@ stop)
begin fun timestamp hash validation_passes sk cctxt -> begin fun timestamp hash sk cctxt ->
bake cctxt ?timestamp cctxt#block bake cctxt ?timestamp cctxt#block
(Activate_testnet { protocol = hash ; (Activate_testnet { protocol = hash ;
validation_passes ;
delay = Int64.mul 24L 3600L }) delay = Int64.mul 24L 3600L })
sk >>=? fun hash -> sk >>=? fun hash ->
cctxt#answer "Injected %a" Block_hash.pp_short hash >>= fun () -> cctxt#answer "Injected %a" Block_hash.pp_short hash >>= fun () ->

View File

@ -13,14 +13,12 @@ module Command = struct
(* Activate a protocol *) (* Activate a protocol *)
| Activate of { | Activate of {
protocol: Protocol_hash.t ; protocol: Protocol_hash.t ;
validation_passes: int ;
fitness: Fitness.t ; fitness: Fitness.t ;
} }
(* Activate a protocol as a testnet *) (* Activate a protocol as a testnet *)
| Activate_testnet of { | Activate_testnet of {
protocol: Protocol_hash.t ; protocol: Protocol_hash.t ;
validation_passes: int ;
delay: Int64.t ; delay: Int64.t ;
} }
@ -38,29 +36,27 @@ module Command = struct
union ~tag_size:`Uint8 [ union ~tag_size:`Uint8 [
case (Tag 0) case (Tag 0)
(mk_case "activate" (mk_case "activate"
(obj3 (obj2
(req "hash" Protocol_hash.encoding) (req "hash" Protocol_hash.encoding)
(req "validation_passes" uint8)
(req "fitness" Fitness.encoding) (req "fitness" Fitness.encoding)
)) ))
(function (function
| Activate { protocol ; validation_passes ; fitness} -> | Activate { protocol ; fitness} ->
Some (protocol, validation_passes, fitness) Some (protocol, fitness)
| _ -> None) | _ -> None)
(fun (protocol, validation_passes, fitness) -> (fun (protocol, fitness) ->
Activate { protocol ; validation_passes ; fitness }) ; Activate { protocol ; fitness }) ;
case (Tag 1) case (Tag 1)
(mk_case "activate_testnet" (mk_case "activate_testnet"
(obj3 (obj2
(req "hash" Protocol_hash.encoding) (req "hash" Protocol_hash.encoding)
(req "validation_passes" uint8)
(req "validity_time" int64))) (req "validity_time" int64)))
(function (function
| Activate_testnet { protocol ; validation_passes ; delay } -> | Activate_testnet { protocol ; delay } ->
Some (protocol, validation_passes, delay) Some (protocol, delay)
| _ -> None) | _ -> None)
(fun (protocol, validation_passes, delay) -> (fun (protocol, delay) ->
Activate_testnet { protocol ; validation_passes ; delay }) ; Activate_testnet { protocol ; delay }) ;
] ]
let signed_encoding = let signed_encoding =

View File

@ -33,10 +33,9 @@ let () =
(fun () -> Invalid_signature) (fun () -> Invalid_signature)
type operation = unit type operation = unit
let max_operation_data_length = 0
let parse_operation _h _op = Error [] let parse_operation _h _op = Error []
let compare_operations _ _ = 0 let compare_operations _ _ = 0
let max_number_of_operations = 0 let validation_passes = []
type block = { type block = {
shell: Block_header.shell_header ; shell: Block_header.shell_header ;
@ -48,7 +47,6 @@ let max_block_length =
Data_encoding.Binary.length Data_encoding.Binary.length
Data.Command.encoding Data.Command.encoding
(Activate_testnet { protocol = Protocol_hash.hash_bytes [] ; (Activate_testnet { protocol = Protocol_hash.hash_bytes [] ;
validation_passes = 0 ;
delay = 0L }) delay = 0L })
+ +
begin begin
@ -83,24 +81,20 @@ let precheck_block
let prepare_application ctxt command timestamp fitness = let prepare_application ctxt command timestamp fitness =
match command with match command with
| Data.Command.Activate { protocol = hash ; validation_passes ; fitness } -> | Data.Command.Activate { protocol = hash ; fitness } ->
let message = let message =
Some (Format.asprintf "activate %a" Protocol_hash.pp_short hash) in Some (Format.asprintf "activate %a" Protocol_hash.pp_short hash) in
Updater.activate ctxt hash >>= fun ctxt -> Updater.activate ctxt hash >>= fun ctxt ->
return { Updater.message ; context = ctxt ; return { Updater.message ; context = ctxt ;
fitness ; max_operations_ttl = 0 ; fitness ; max_operations_ttl = 0 ;
max_number_of_operations =
Array.to_list (Array.make validation_passes 0) ;
max_operation_data_length = 0 } max_operation_data_length = 0 }
| Activate_testnet { protocol = hash ; validation_passes ; delay } -> | Activate_testnet { protocol = hash ; delay } ->
let message = let message =
Some (Format.asprintf "activate testnet %a" Protocol_hash.pp_short hash) in Some (Format.asprintf "activate testnet %a" Protocol_hash.pp_short hash) in
let expiration = Time.add timestamp delay in let expiration = Time.add timestamp delay in
Updater.fork_test_network ctxt ~protocol:hash ~expiration >>= fun ctxt -> Updater.fork_test_network ctxt ~protocol:hash ~expiration >>= fun ctxt ->
return { Updater.message ; context = ctxt ; fitness ; return { Updater.message ; context = ctxt ; fitness ;
max_operations_ttl = 0 ; max_operations_ttl = 0 ;
max_number_of_operations =
Array.to_list (Array.make validation_passes 0) ;
max_operation_data_length = 0 } max_operation_data_length = 0 }
@ -129,7 +123,6 @@ let begin_construction
return { Updater.message = None ; context = ctxt ; return { Updater.message = None ; context = ctxt ;
fitness ; max_operations_ttl = 0 ; fitness ; max_operations_ttl = 0 ;
max_operation_data_length = 0 ; max_operation_data_length = 0 ;
max_number_of_operations = [] ;
} }
| Some command -> | Some command ->
match Data_encoding.Binary.of_bytes Data.Command.encoding command with match Data_encoding.Binary.of_bytes Data.Command.encoding command with

View File

@ -0,0 +1,12 @@
(**************************************************************************)
(* *)
(* Copyright (c) 2014 - 2017. *)
(* Dynamic Ledger Solutions, Inc. <contact@tezos.com> *)
(* *)
(* All rights reserved. No warranty, explicit or implicit, provided. *)
(* *)
(**************************************************************************)
(** Tezos Protocol Implementation - Protocol Signature Instance *)
include Updater.PROTOCOL

View File

@ -41,7 +41,7 @@ let activate_alpha () =
~location:"edsk31vznjHSSpGExDMHYASz45VZqXN4DPxvsa4hAyY8dHM28cZzp6" in ~location:"edsk31vznjHSSpGExDMHYASz45VZqXN4DPxvsa4hAyY8dHM28cZzp6" in
Tezos_client_genesis.Client_proto_main.bake Tezos_client_genesis.Client_proto_main.bake
(new Client_rpcs.http_ctxt !rpc_config) (`Head 0) (new Client_rpcs.http_ctxt !rpc_config) (`Head 0)
(Activate { protocol = Client_proto_main.protocol ; validation_passes = 1 ; (Activate { protocol = Client_proto_main.protocol ;
fitness }) fitness })
dictator_sk dictator_sk

View File

@ -56,7 +56,7 @@ let get_activation_block baker context_hash head =
let fitness = let fitness =
Tezos_embedded_raw_protocol_alpha.Fitness_repr.from_int64 100L in Tezos_embedded_raw_protocol_alpha.Fitness_repr.from_int64 100L in
let command: Data.Command.t = let command: Data.Command.t =
Data.Command.Activate({protocol = Helpers_constants.alpha_hash ; validation_passes = 0 ; fitness}) in Data.Command.Activate({protocol = Helpers_constants.alpha_hash ; fitness}) in
let content_bytes = Data.Command.forge shell_header command in let content_bytes = Data.Command.forge shell_header command in
let signature = Ed25519.sign baker.ppk content_bytes in let signature = Ed25519.sign baker.ppk content_bytes in
let proto = (command , signature) in let proto = (command , signature) in

View File

@ -90,7 +90,6 @@ let lolblock ?(operations = []) header =
max_operations_ttl = 0 ; max_operations_ttl = 0 ;
message = None ; message = None ;
context = Context_hash.zero ; context = Context_hash.zero ;
max_number_of_operations = [] ;
max_operation_data_length = 0 ; max_operation_data_length = 0 ;
} }

View File

@ -80,7 +80,6 @@ activate_alpha() {
activate \ activate \
protocol ProtoALphaALphaALphaALphaALphaALphaALphaALphaDdp3zK \ protocol ProtoALphaALphaALphaALphaALphaALphaALphaALphaDdp3zK \
with fitness 1 \ with fitness 1 \
and passes 1 \
and key edsk31vznjHSSpGExDMHYASz45VZqXN4DPxvsa4hAyY8dHM28cZzp6 \ and key edsk31vznjHSSpGExDMHYASz45VZqXN4DPxvsa4hAyY8dHM28cZzp6 \
> /dev/stderr > /dev/stderr
} }