@@ -60,9 +60,9 @@ let ctype_of_ty (env: env) (ty: ty) : ctype =
6060 raise (CircError " Failed to convert EC type to Circuit type" )
6161 end
6262 | Some ({size = (_ , None)} , _ ) ->
63- Format. eprintf " No concrete binding for array type@. " ; assert false
63+ raise ( CircError ( " No concrete binding for array type " ^ ( Format. asprintf " %a " EcPrinting. (pp_type PPEnv. (ofenv env)) ty)))
6464 | Some (_ , {size = (_ , None)} ) ->
65- Format. eprintf " No concrete binding for bitstring type@. " ; assert false
65+ raise ( CircError ( " No concrete binding for bitstring type " ^ ( Format. asprintf " %a " EcPrinting. (pp_type PPEnv. (ofenv env)) ty)))
6666 end
6767
6868
@@ -106,10 +106,10 @@ module BVOps = struct
106106 let circuit_of_parametric_bvop (env : env ) (op : [`Path of path | `BvBind of EcDecl.crb_bvoperator] ) (args : arg list ) : circuit =
107107 let op = match op with
108108 | `BvBind op -> op
109- | `Path p -> let op = match EcEnv.Circuit. lookup_bvoperator_path env p with
109+ | `Path p -> begin match EcEnv.Circuit. lookup_bvoperator_path env p with
110110 | Some op -> op
111- | None -> assert false
112- in op
111+ | None -> raise ( CircError ( " No binding matching operator at path " ^ ( EcPath. tostring p)) )
112+ end
113113 in
114114 circuit_of_parametric_bvop op args
115115
@@ -140,10 +140,10 @@ module BVOps = struct
140140 let circuit_of_bvop (env : env ) (op : [`Path of path | `BvBind of EcDecl.crb_bvoperator] ) : circuit =
141141 let op = match op with
142142 | `BvBind op -> op
143- | `Path p -> let op = match EcEnv.Circuit. lookup_bvoperator_path env p with
143+ | `Path p -> begin match EcEnv.Circuit. lookup_bvoperator_path env p with
144144 | Some op -> op
145- | None -> assert false
146- in op
145+ | None -> raise ( CircError ( " No binding matching operator at path " ^ ( EcPath. tostring p)) )
146+ end
147147 in
148148 circuit_of_bvop op
149149end
@@ -162,15 +162,16 @@ module BitstringOps = struct
162162 | `BSBinding bnd -> bnd
163163 | `Path p -> begin match EcEnv.Circuit. reverse_bitstring_operator env p with
164164 | Some bnd -> bnd
165- | None -> assert false
165+ | None -> raise ( CircError ( " No binding matching operator at path " ^ ( EcPath. tostring p)))
166166 end
167167 in
168+ (* assert false => should be guarded by a previous call to op_is_bsop *)
168169 match bnd with
169170 | bs , `From -> assert false (* doesn't translate to circuit *)
170171 | {size = (_ , Some size )} , `OfInt -> begin match args with
171172 | [ `Constant i ] ->
172173 circuit_of_zint ~size i
173- | _ -> assert false
174+ | args -> raise ( CircError ( Format. asprintf " Bad arguments for bitstring of_int: expected (int) got (%a) " EcPrinting. (pp_list " , " pp_arg) args))
174175 end
175176 | {size = (_ , None)} , `OfInt ->
176177 raise (CircError " No concrete binding for type of of_int@." ) (* FIXME: error messages *)
@@ -196,28 +197,35 @@ module ArrayOps = struct
196197 | `ABinding bnd -> bnd
197198 | `Path p -> begin match EcEnv.Circuit. reverse_array_operator env p with
198199 | Some bnd -> bnd
199- | None -> assert false
200- end
200+ | None -> raise ( CircError ( " No binding matching operator at path " ^ ( EcPath. tostring p)))
201+ end
201202 in
203+ (* assert false => should be guarded by a call to op_is_arrayop *)
202204 match op with
203205 | (arr , `ToList) -> assert false (* We do not translate this to circuit *)
204206 | (arr , `Get) -> begin match args with
205207 | [ `Circuit ((`CArray _, inps) as arr); `Constant i] ->
206208 array_get arr (BI. to_int i)
207- | _ -> assert false
209+ | args ->
210+ let err = Format. asprintf " Bad inputs to arr get: Expected (arr, idx) got (%a)" (EcPrinting. pp_list " ," pp_arg) args in
211+ raise (CircError err)
208212 end
209213 (* FIXME: Check argument order *)
210214 | ({size = (_ , Some size )} , `OfList) -> begin match args with
211215 | [ `Circuit dfl; `List cs ] -> array_oflist cs dfl size
212- | _ -> assert false
216+ | args ->
217+ let err = Format. asprintf " Bad inputs to arr of_list: Expected (default, list) got (%a)" (EcPrinting. pp_list " ," pp_arg) args in
218+ raise (CircError err)
213219 end
214220 | ({size = (_ , None)} , `OfList) -> raise (CircError " Array of list with non-concrete size" )
215221 | (_arr , `Set) -> begin match args with
216222 | [ `Circuit ((`CArray _, _) as arr);
217223 `Constant i;
218224 `Circuit ((`CBitstring _, _) as bs) ] ->
219225 array_set arr (BI. to_int i) bs
220- | _ -> assert false
226+ | args ->
227+ let err = Format. asprintf " Bad inputs to arr set: Expected (arr, idx, new_val) got (%a)" (EcPrinting. pp_list " ," pp_arg) args in
228+ raise (CircError err)
221229 end
222230end
223231open ArrayOps
@@ -229,8 +237,10 @@ let circuit_uninit (env:env) (t: ty) : circuit =
229237module CircuitSpec = struct
230238 let circuit_from_spec env (c : [`Path of path | `Bind of EcDecl.crb_circuit ] ) : circuit =
231239 let c = match c with
232- | `Path p -> let c = EcEnv.Circuit. reverse_circuit env p in
233- if (Option. is_some c) then Option. get c else assert false
240+ | `Path p -> begin match EcEnv.Circuit. reverse_circuit env p with
241+ | Some c -> c
242+ | None -> raise (CircError (" No spec binding for operator at path " ^ EcPath. (tostring p)))
243+ end
234244 | `Bind c -> c
235245 in
236246 let _, name = (EcPath. toqsymbol c.operator) in
@@ -266,7 +276,7 @@ let circuit_of_baseop (env: env) (p: path) : circuit =
266276 else if op_has_spec env p then
267277 circuit_from_spec env (`Path p)
268278 else
269- assert false
279+ assert false (* Should be guarded by call to op_is_base *)
270280
271281let op_is_parametric_base (env : env ) (p : path ) =
272282 op_is_parametric_bvop env p ||
@@ -281,7 +291,7 @@ let circuit_of_parametric_baseop (env: env) (p: path) (args: arg list) : circuit
281291 else if op_is_bsop env p then
282292 circuit_of_bsop env (`Path p) args
283293 else
284- assert false
294+ assert false (* Should be guarded by call to op_is_parametric_base *)
285295
286296let circuit_of_op (env : env ) (p : path ) : circuit =
287297 let op = try
@@ -290,8 +300,8 @@ let circuit_of_op (env: env) (p: path) : circuit =
290300 raise (CircError " Failed reverse operator" )
291301 in
292302 match op with
293- | `Bitstring (bs , op ) -> assert false
294- | `Array _ -> assert false
303+ | `Bitstring (bs , op ) -> assert false (* Should be guarded by a call to op_is_base *)
304+ | `Array _ -> assert false (* Should be guarded by a call to op_is_parametric_base *)
295305 | `BvOperator bvbnd -> circuit_of_bvop env (`BvBind bvbnd)
296306 | `Circuit c -> circuit_from_spec env (`Bind c)
297307
@@ -305,7 +315,7 @@ let circuit_of_op_with_args (env: env) (p: path) (args: arg list) : circuit =
305315 | `Bitstring bsbnd -> circuit_of_bsop env (`BSBinding bsbnd) args
306316 | `Array abnd -> circuit_of_arrayop env (`ABinding abnd) args
307317 | `BvOperator bvbnd -> circuit_of_parametric_bvop env (`BvBind bvbnd) args
308- | `Circuit c -> assert false (* TODO : Do we want to have parametric operators coming from the spec? Yes *)
318+ | `Circuit c -> assert false (* FIXME PR : Do we want to have parametric operators coming from the spec? *)
309319(* ------------------------------ *)
310320
311321
@@ -347,7 +357,7 @@ let rec form_list_of_form ?(ppenv: EcPrinting.PPEnv.t option) (f: form) : form l
347357 h::(form_list_of_form t)
348358 | _ ->
349359 if debug then Option. may (fun ppenv -> Format. eprintf " Failed to destructure claimed list: %a@." (EcPrinting. pp_form ppenv) f) ppenv;
350- assert false
360+ raise ( CircError " Failed to destruct list " )
351361
352362let form_is_iter (f : form ) : bool =
353363 match f.f_node with
@@ -360,6 +370,8 @@ let form_is_iter (f: form) : bool =
360370(* Expands iter, fold and iteri (for integer arguments) *)
361371let expand_iter_form (hyps : hyps ) (f : form ) : form =
362372 let redmode = circ_red hyps in
373+ let env = toenv hyps in
374+ let ppenv = EcPrinting.PPEnv. ofenv env in
363375 let (@!!) f fs =
364376 EcTypesafeFol. fapply_safe ~redmode hyps f fs
365377 in
@@ -386,9 +398,9 @@ let expand_iter_form (hyps: hyps) (f: form) : form =
386398 let is = List. init (BI. to_int rep) BI. of_int in
387399 let f = List. fold_left (fun f i -> fn @!! [f]) base is in
388400 f
389- | _ -> assert false
401+ | _ -> raise ( CircError ( Format. asprintf " Failed to destructure form for iter expansion %a " EcPrinting. (pp_form ppenv) f))
390402 in
391- if debug then Format. eprintf " Expanded iter form: @.%a@." ( EcPrinting. pp_form ( EcPrinting.PPEnv. ofenv (toenv hyps)) ) res;
403+ if debug then Format. eprintf " Expanded iter form: @.%a@." EcPrinting. ( pp_form ppenv ) res;
392404 res
393405
394406let circuit_of_form
@@ -471,7 +483,14 @@ let circuit_of_form
471483 p = EcCoreLib.CI_List. p_list &&
472484 type_is_registered (LDecl. toenv hyps) t ->
473485 let hyps, cs = List. fold_left_map (fun hyps f ->
474- doit cache hyps f) hyps (form_list_of_form ~ppenv: (EcPrinting.PPEnv. ofenv (LDecl. toenv hyps)) f)
486+ doit cache hyps f) hyps
487+ (try
488+ (form_list_of_form ~ppenv: (EcPrinting.PPEnv. ofenv (LDecl. toenv hyps)) f)
489+ with
490+ CircError _ ->
491+ raise (CircError
492+ (Format. asprintf " Failed to destructure %a as list when attempting to convert it to an argument"
493+ EcPrinting. (pp_form PPEnv. (ofenv env)) f)))
475494 in
476495 hyps, arg_of_circuits cs
477496 | _ -> Format. eprintf " Failed to convert form to arg: %a@." EcPrinting. (pp_form (PPEnv. ofenv env)) f;
@@ -515,7 +534,6 @@ let circuit_of_form
515534 | OB_oper (Some (OP_Plain f )) ->
516535(* if debug then Format.eprintf "[BDEP] Opening definition of function at path %s" (EcPath.tostring pth); *)
517536 doit cache hyps f
518- | _ when pth = EcCoreLib.CI_Witness. p_witness -> assert false
519537 | _ ->
520538 begin match EcFol. op_kind (destr_op f_ |> fst) with
521539 | Some `True ->
@@ -662,6 +680,8 @@ let circuit_of_form
662680 and trans_iter (cache : cache ) (hyps : hyps ) (f : form ) (fs : form list ) =
663681 (* FIXME: move auxiliary function out of the definitions *)
664682 let redmode = circ_red hyps in
683+ let env = toenv hyps in
684+ let ppenv = EcPrinting.PPEnv. ofenv env in
665685 let fapply_safe f fs =
666686 let res = EcTypesafeFol. fapply_safe ~redmode hyps f fs in
667687 res
@@ -677,9 +697,10 @@ let circuit_of_form
677697 let hyps, fn = doit cache hyps fn in
678698 hyps, circuit_compose fn [f]
679699 ) (doit cache hyps base) fs
680- | ({f_node = Fop (p , _ )} , [rep ; fn ; base ]) when p = EcCoreLib.CI_Int. p_iter -> assert false
700+ (* FIXME PR: this is currently being implemented directly on circuits, do we want this case as well? *)
701+ | ({f_node = Fop (p , _ )} , [rep ; fn ; base ]) when p = EcCoreLib.CI_Int. p_iter -> assert false
681702 | ({f_node = Fop (p , _ )} , [rep ; fn ; base ]) when p = EcCoreLib.CI_Int. p_fold -> assert false
682- | _ -> assert false
703+ | _ -> raise ( CircError ( Format. asprintf " Failed to destr form %a to translate iter " EcPrinting. (pp_form ppenv) f))
683704 in
684705(*
685706 let t0 = Unix.gettimeofday () in
@@ -737,7 +758,7 @@ let process_instr (hyps: hyps) (mem: memory) (pstate: pstate) (inst: instr) : hy
737758 (List. combine
738759 (List. map (function
739760 | (PVloc v , _ty ) -> v
740- | _ -> assert false ) vs)
761+ | _ -> raise ( CircError " Failed to parse tuple assignment " ) ) vs)
741762 es) in
742763 pstate
743764 | Sasgn (LvTuple (vs ), e ) ->
@@ -879,22 +900,22 @@ let circ_taut = circ_taut
879900let circuit_permute (bsz : int ) (perm : int -> int ) (c : circuit ) : circuit =
880901 let c = match c with
881902 | (`CBitstring r , inps ) as c -> c
882- | _ -> assert false
903+ | _ -> assert false (* FIXME PR: currently only implemented for bitstring, do we want to expand this ? *)
883904 in
884905 (permute bsz perm c :> circuit )
885906
886907let circuit_mapreduce ?(perm : (int -> int) option ) (c : circuit ) (w_in : width ) (w_out : width ) : circuit list =
887908 let c = match c, perm with
888909 | (`CBitstring _ , inps ) as c , None -> c
889910 | (`CBitstring _ , inps ) as c , Some perm -> permute w_out perm c
890- | _ -> assert false
911+ | _ -> assert false (* FIXME PR: currently only implemented for bitstring, do we want to expand this ? *)
891912 in
892913 (decompose w_in w_out c :> circuit list )
893914
894915let cache_get = cache_get
895916let cache_add = cache_add
896917let empty_cache = empty_cache
897- let circuit_to_string (c : circuit ) : string = assert false
918+ let circuit_to_string (( circ , inps ) : circuit ) : string = Format. asprintf " (%a => %a) " EcPrinting. (pp_list " , " pp_cinp) inps pp_circ circ
898919let pstate_get = pstate_get
899920let pstate_get_opt = pstate_get_opt
900921let pstate_get_all = fun pstate -> List. snd (pstate_get_all pstate)
0 commit comments