Skip to content

Commit 6d10f9e

Browse files
committed
Re-add the computational model without promise-free optimization
1 parent 53d1c39 commit 6d10f9e

File tree

5 files changed

+91
-8
lines changed

5 files changed

+91
-8
lines changed

ArchSem/GenPromising.v

Lines changed: 9 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -431,9 +431,17 @@ Module GenPromising (IWA : InterfaceWithArch) (TM : TermModelsT IWA).
431431
Arguments to_final_archState {_ _ _}.
432432
End CPState.
433433

434-
(** Create a computational model from an ISA model and promising model *)
434+
(** Create computational models from an ISA model and promising model *)
435435
Definition Promising_to_Modelc (isem : iMon ()) (prom : BasicExecutablePM)
436436
(fuel : nat) : archModel.c ∅ :=
437+
λ n term (initMs : archState n),
438+
PState.from_archState prom initMs |>
439+
archModel.Res.from_exec
440+
$ CPState.to_final_archState
441+
<$> CPState.run isem prom term fuel.
442+
443+
Definition Promising_to_Modelc_pf (isem : iMon ()) (prom : BasicExecutablePM)
444+
(fuel : nat) : archModel.c ∅ :=
437445
λ n term (initMs : archState n),
438446
PState.from_archState prom initMs |>
439447
archModel.Res.from_exec

ArchSemArm/UMPromising.v

Lines changed: 5 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -690,9 +690,9 @@ Section ComputeProm.
690690
let base := List.length mem in
691691
let res_proms := Exec.results $
692692
run_to_termination_promise isem fuel base (CProm.init, PPState.Make ts mem IIS.init) in
693-
guard_or ("Could not finish promises within the size of the fuel")%string
693+
guard_or ("Out of fuel when searching for new promises")%string
694694
(∀ r ∈ res_proms, r.2 = true);;
695-
let promises := res_proms.*1.*1 |> CProm.proms ∘ union_list in
695+
let promises := res_proms.*1.*1 |> union_list |> CProm.proms in
696696
let tstates :=
697697
res_proms
698698
|> omap (λ '((cp, st), _),
@@ -785,3 +785,6 @@ Next Obligation. Admitted.
785785

786786
Definition UMPromising_cert_c isem fuel :=
787787
Promising_to_Modelc isem (UMPromising_exe' isem) fuel.
788+
789+
Definition UMPromising_cert_c_pf isem fuel :=
790+
Promising_to_Modelc_pf isem (UMPromising_exe' isem) fuel.

ArchSemArm/VMPromising.v

Lines changed: 5 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1972,9 +1972,9 @@ Section ComputeProm.
19721972
let base := List.length mem in
19731973
let res_proms := Exec.results $
19741974
run_to_termination_promise isem fuel base (CProm.init, PPState.Make ts mem IIS.init) in
1975-
guard_or ("Could not finish promises within the size of the fuel")%string
1975+
guard_or ("Out of fuel when searching for new promises")%string
19761976
(∀ r ∈ res_proms, r.2 = true);;
1977-
let promises := res_proms.*1.*1 |> CProm.proms ∘ union_list in
1977+
let promises := res_proms.*1.*1 |> union_list |> CProm.proms in
19781978
let tstates :=
19791979
res_proms
19801980
|> omap (λ '((cp, st), _),
@@ -2061,3 +2061,6 @@ Next Obligation. Admitted.
20612061

20622062
Definition VMPromising_cert_c isem fuel :=
20632063
Promising_to_Modelc isem (VMPromising_exe' isem) fuel.
2064+
2065+
Definition VMPromising_cert_c_pf isem fuel :=
2066+
Promising_to_Modelc_pf isem (VMPromising_exe' isem) fuel.

ArchSemArm/tests/UMPromisingTest.v

Lines changed: 37 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -158,6 +158,14 @@ Module LDR. (* LDR X0, [X1, X0] at 0x500, loading from 0x1000 *)
158158
vm_compute (_ <$> _).
159159
reflexivity.
160160
Qed.
161+
162+
Definition test_results_pf :=
163+
UMPromising_cert_c_pf arm_sem fuel n_threads termCond initState.
164+
165+
Goal reg_extract R0 0%fin <$> test_results_pf = Listset [Ok 0x2a%Z].
166+
vm_compute (_ <$> _).
167+
reflexivity.
168+
Qed.
161169
End LDR.
162170

163171
Module STRLDR. (* STR X2, [X1, X0]; LDR X0, [X1, X0] at 0x500, using address 0x1100 *)
@@ -195,6 +203,14 @@ Module STRLDR. (* STR X2, [X1, X0]; LDR X0, [X1, X0] at 0x500, using address 0x1
195203
vm_compute (_ <$> _).
196204
set_solver.
197205
Qed.
206+
207+
Definition test_results_pf :=
208+
UMPromising_cert_c_pf arm_sem fuel n_threads termCond initState.
209+
210+
Goal reg_extract R0 0%fin <$> test_results_pf ≡ Listset [Ok 0x2a%Z].
211+
vm_compute (_ <$> _).
212+
set_solver.
213+
Qed.
198214
End STRLDR.
199215

200216
Module MP.
@@ -266,6 +282,16 @@ Module MP.
266282
vm_compute (elements _).
267283
apply NoDup_Permutation; try solve_NoDup; set_solver.
268284
Qed.
285+
286+
Definition test_results_pf :=
287+
UMPromising_cert_c_pf arm_sem fuel n_threads termCond initState.
288+
289+
Goal elements (regs_extract [(1%fin, R5); (1%fin, R2)] <$> test_results) ≡ₚ
290+
[Ok [0x0%Z;0x2a%Z]; Ok [0x0%Z;0x0%Z]; Ok [0x1%Z; 0x2a%Z]; Ok [0x1%Z; 0x0%Z]].
291+
Proof.
292+
vm_compute (elements _).
293+
apply NoDup_Permutation; try solve_NoDup; set_solver.
294+
Qed.
269295
End MP.
270296

271297
Module MPDMBS.
@@ -340,4 +366,15 @@ Module MPDMBS.
340366
vm_compute (elements _).
341367
apply NoDup_Permutation; try solve_NoDup; set_solver.
342368
Qed.
369+
370+
Definition test_results_pf :=
371+
UMPromising_cert_c_pf arm_sem fuel n_threads termCond initState.
372+
373+
(** The test is fenced enough, the 0x1;0x0 outcome is impossible*)
374+
Goal elements (regs_extract [(1%fin, R5); (1%fin, R2)] <$> test_results) ≡ₚ
375+
[Ok [0x0%Z;0x2a%Z]; Ok [0x0%Z;0x0%Z]; Ok [0x1%Z; 0x2a%Z]].
376+
Proof.
377+
vm_compute (elements _).
378+
apply NoDup_Permutation; try solve_NoDup; set_solver.
379+
Qed.
343380
End MPDMBS.

ArchSemArm/tests/VMPromisingTest.v

Lines changed: 35 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -133,6 +133,14 @@ Module EORMMUOFF.
133133
vm_compute (_ <$> _).
134134
reflexivity.
135135
Qed.
136+
137+
Definition test_results_pf :=
138+
VMPromising_cert_c_pf arm_sem fuel n_threads termCond initState.
139+
140+
Goal reg_extract R0 0%fin <$> test_results_pf = Listset [Ok 0x110%Z].
141+
vm_compute (_ <$> _).
142+
reflexivity.
143+
Qed.
136144
End EORMMUOFF.
137145

138146
(* Run EOR X0, X1, X2 at PC.
@@ -199,6 +207,14 @@ Module EOR.
199207
vm_compute (_ <$> _).
200208
reflexivity.
201209
Qed.
210+
211+
Definition test_results_pf :=
212+
VMPromising_cert_c_pf arm_sem fuel n_threads termCond initState.
213+
214+
Goal reg_extract R0 0%fin <$> test_results_pf = Listset [Ok 0x110%Z].
215+
vm_compute (_ <$> _).
216+
reflexivity.
217+
Qed.
202218
End EOR.
203219

204220
(* LDR X0, [X1, X0] at VA 0x8000000500, loading from VA 0x8000001000
@@ -252,6 +268,14 @@ Module LDR.
252268
vm_compute (_ <$> _).
253269
reflexivity.
254270
Qed.
271+
272+
Definition test_results_pf :=
273+
VMPromising_cert_c_pf arm_sem fuel n_threads termCond initState.
274+
275+
Goal reg_extract R0 0%fin <$> test_results_pf = Listset [Ok 0x2a%Z].
276+
vm_compute (_ <$> _).
277+
reflexivity.
278+
Qed.
255279
End LDR.
256280

257281
(* STR X2, [X1, X0]; LDR X0, [X1, X0] at VA 0x8000000500,
@@ -304,6 +328,14 @@ Module STRLDR.
304328
vm_compute (_ <$> _).
305329
set_solver.
306330
Qed.
331+
332+
Definition test_results_pf :=
333+
VMPromising_cert_c_pf arm_sem fuel n_threads termCond initState.
334+
335+
Goal reg_extract R0 0%fin <$> test_results_pf ≡ Listset [Ok 0x2a%Z].
336+
vm_compute (_ <$> _).
337+
set_solver.
338+
Qed.
307339
End STRLDR.
308340

309341
(* Sequential page table modification in single thread *)
@@ -367,7 +399,7 @@ Module LDRPT.
367399
Definition fuel := 5%nat.
368400

369401
Definition test_results :=
370-
VMPromising_cert_c arm_sem fuel n_threads termCond initState.
402+
VMPromising_cert_c_pf arm_sem fuel n_threads termCond initState.
371403

372404
(* R0 should be 0x2a (from old mapping), R4 should be 0x42 (from new mapping) *)
373405
Goal elements (regs_extract [(0%fin, R0); (0%fin, R4)] <$> test_results) ≡ₚ
@@ -460,7 +492,7 @@ Module MP.
460492
Definition fuel := 8%nat.
461493

462494
Definition test_results :=
463-
VMPromising_cert_c arm_sem fuel n_threads termCond initState.
495+
VMPromising_cert_c_pf arm_sem fuel n_threads termCond initState.
464496

465497
Goal elements (regs_extract [(1%fin, R5); (1%fin, R2)] <$> test_results) ≡ₚ
466498
[Ok [0x0%Z;0x2a%Z]; Ok [0x0%Z;0x0%Z]; Ok [0x1%Z; 0x2a%Z]; Ok [0x1%Z; 0x0%Z]].
@@ -552,7 +584,7 @@ Module MPDMBS.
552584
Definition fuel := 8%nat.
553585

554586
Definition test_results :=
555-
VMPromising_cert_c arm_sem fuel n_threads termCond initState.
587+
VMPromising_cert_c_pf arm_sem fuel n_threads termCond initState.
556588

557589
(** The test is fenced enough, the 0x1; 0x0 outcome is impossible*)
558590
Goal elements (regs_extract [(1%fin, R5); (1%fin, R2)] <$> test_results) ≡ₚ

0 commit comments

Comments
 (0)