Skip to content

Commit 079b426

Browse files
authored
Merge pull request #167 from goblint/fix-locations
Location fixes for Goblint YAML witness generation/validation
2 parents 833378d + ae3a494 commit 079b426

File tree

15 files changed

+125
-69
lines changed

15 files changed

+125
-69
lines changed

src/check.ml

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -760,8 +760,9 @@ and checkStmt (s: stmt) =
760760
currentLoc := l;
761761
let te = checkExp false e in
762762
typeMatch te voidPtrType
763-
| Return (re,l) -> begin
763+
| Return (re, l, el) -> begin
764764
currentLoc := l;
765+
currentExpLoc := el;
765766
match re, !currentReturnType with
766767
None, TVoid _ -> ()
767768
| _, TVoid _ -> ignore (warn "Invalid return value")

src/cil.ml

Lines changed: 9 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -767,8 +767,9 @@ and stmtkind =
767767
| Instr of instr list (** A group of instructions that do not
768768
contain control flow. Control
769769
implicitly falls through. *)
770-
| Return of exp option * location (** The return statement. This is a
771-
leaf in the CFG. *)
770+
| Return of exp option * location * location (** The return statement. This is a
771+
leaf in the CFG.
772+
Second location is just for expression. *)
772773

773774
| Goto of stmt ref * location (** A goto statement. Appears from
774775
actual goto's in the code. *)
@@ -1145,7 +1146,7 @@ let rec get_stmtLoc (statement : stmtkind) =
11451146
match statement with
11461147
Instr([]) -> lu
11471148
| Instr(hd::tl) -> get_instrLoc(hd)
1148-
| Return(_, loc) -> loc
1149+
| Return(_, loc, _) -> loc
11491150
| Goto(_, loc) -> loc
11501151
| ComputedGoto(_, loc) -> loc
11511152
| Break(loc) -> loc
@@ -3861,11 +3862,11 @@ class defaultCilPrinterClass : cilPrinter = object (self)
38613862
++ self#pBlock () thenBlock)
38623863

38633864
method private pStmtKind (next: stmt) () = function
3864-
Return(None, l) ->
3865+
Return(None, l, el) ->
38653866
self#pLineDirective l
38663867
++ text "return;"
38673868

3868-
| Return(Some e, l) ->
3869+
| Return(Some e, l, el) ->
38693870
self#pLineDirective l
38703871
++ text "return ("
38713872
++ self#pExp () e
@@ -5363,13 +5364,13 @@ and childrenStmt (toPrepend: instr list ref) : cilVisitor -> stmt -> stmt =
53635364
(* Just change the statement kind *)
53645365
let skind' =
53655366
match s.skind with
5366-
Break _ | Continue _ | Goto _ | Return (None, _) -> s.skind
5367+
Break _ | Continue _ | Goto _ | Return (None, _, _) -> s.skind
53675368
| ComputedGoto (e, l) ->
53685369
let e' = fExp e in
53695370
if e' != e then ComputedGoto (e', l) else s.skind
5370-
| Return (Some e, l) ->
5371+
| Return (Some e, l, el) ->
53715372
let e' = fExp e in
5372-
if e' != e then Return (Some e', l) else s.skind
5373+
if e' != e then Return (Some e', l, el) else s.skind
53735374
| Loop (b, l, el, s1, s2) ->
53745375
let b' = fBlock b in
53755376
if b' != b then Loop (b', l, el, s1, s2) else s.skind

src/cil.mli

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -964,8 +964,9 @@ and stmtkind =
964964
(** A group of instructions that do not contain control flow. Control
965965
implicitly falls through. *)
966966

967-
| Return of exp option * location
968-
(** The return statement. This is a leaf in the CFG. *)
967+
| Return of exp option * location * location
968+
(** The return statement. This is a leaf in the CFG.
969+
Second location is just for expression. *)
969970

970971
| Goto of stmt ref * location
971972
(** A goto statement. Appears from actual goto's in the code or from

src/ext/dataslicing/dataslicing.ml

Lines changed: 5 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -336,16 +336,16 @@ let sliceInstr (inst : instr) : instr list =
336336
instrs @ (Call (ret', sliceExp 1 fn, args', l, el) :: set)
337337
| _ -> E.s (unimp "inst %a" d_instr inst)
338338

339-
let sliceReturnExp (eo : exp option) (l : location) : stmtkind =
339+
let sliceReturnExp (eo : exp option) (l : location) (el : location) : stmtkind =
340340
match eo with
341341
| Some e ->
342342
begin
343343
match sliceExpAll e l with
344-
| [], e' -> Return (Some e', l)
344+
| [], e' -> Return (Some e', l, el)
345345
| instrs, e' -> Block (mkBlock [mkStmt (Instr instrs);
346-
mkStmt (Return (Some e', l))])
346+
mkStmt (Return (Some e', l, el))])
347347
end
348-
| None -> Return (None, l)
348+
| None -> Return (None, l, el)
349349

350350
let rec sliceStmtKind (sk : stmtkind) : stmtkind =
351351
match sk with
@@ -354,7 +354,7 @@ let rec sliceStmtKind (sk : stmtkind) : stmtkind =
354354
| If (e, b1, b2, l, el) -> If (sliceExp 1 e, sliceBlock b1, sliceBlock b2, l, el)
355355
| Break l -> Break l
356356
| Continue l -> Continue l
357-
| Return (eo, l) -> sliceReturnExp eo l
357+
| Return (eo, l, el) -> sliceReturnExp eo l el
358358
| Switch (e, b, sl, l, el) -> Switch (sliceExp 1 e, sliceBlock b,
359359
Util.list_map sliceStmt sl, l, el)
360360
| Loop (b, l, el, so1, so2) -> Loop (sliceBlock b, l, el,

src/ext/liveness/usedef.ml

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -190,8 +190,8 @@ let computeUseDefStmtKind ?(acc_used=VS.empty)
190190
let ve e = ignore (visitCilExpr useDefVisitor e) in
191191
let _ =
192192
match sk with
193-
Return (None, _) -> ()
194-
| Return (Some e, _) -> ve e
193+
Return (None, _, _) -> ()
194+
| Return (Some e, _, _) -> ve e
195195
| If (e, _, _, _, _) -> ve e
196196
| Break _ | Goto _ | Continue _ -> ()
197197
| ComputedGoto (e, _) -> ve e
@@ -218,8 +218,8 @@ let rec computeDeepUseDefStmtKind ?(acc_used=VS.empty)
218218
varDefs := acc_defs;
219219
let ve e = ignore (visitCilExpr useDefVisitor e) in
220220
match sk with
221-
Return (None, _) -> !varUsed, !varDefs
222-
| Return (Some e, _) ->
221+
Return (None, _, _) -> !varUsed, !varDefs
222+
| Return (Some e, _, _) ->
223223
let _ = ve e in
224224
!varUsed, !varDefs
225225
| If (e, tb, fb, _, _) ->

src/ext/pta/ptranal.ml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -304,7 +304,7 @@ let analyze_instr (i : instr ) : unit =
304304
let rec analyze_stmt (s : stmt ) : unit =
305305
match s.skind with
306306
Instr il -> List.iter analyze_instr il
307-
| Return (eo, l) ->
307+
| Return (eo, l, el) ->
308308
begin
309309
match eo with
310310
Some e ->

src/ext/syntacticsearch/funcFunction.ml

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -32,7 +32,7 @@ class fun_find_returns funname funid result : nopCilVisitor =
3232

3333
method! vstmt stmt =
3434
match stmt.skind with
35-
| Return (Some exp, loc) ->
35+
| Return (Some exp, loc, eloc) ->
3636
result :=
3737
!result
3838
@ [
@@ -42,7 +42,7 @@ class fun_find_returns funname funid result : nopCilVisitor =
4242
-1 );
4343
];
4444
DoChildren
45-
| Return (None, loc) ->
45+
| Return (None, loc, eloc) ->
4646
result := !result @ [ ("", loc, "void", -1) ];
4747
DoChildren
4848
| _ -> DoChildren
@@ -72,7 +72,7 @@ class fun_find_sig funname funid result : nopCilVisitor =
7272

7373
method! vstmt stmt =
7474
match stmt.skind with
75-
| Return (Some exp, loc) ->
75+
| Return (Some exp, loc, eloc) ->
7676
result :=
7777
!result
7878
@ [
@@ -82,7 +82,7 @@ class fun_find_sig funname funid result : nopCilVisitor =
8282
-1 );
8383
];
8484
SkipChildren
85-
| Return (None, loc) ->
85+
| Return (None, loc, eloc) ->
8686
result := !result @ [ ("", loc, "void", -1) ];
8787
SkipChildren
8888
| _ -> DoChildren

src/ext/syntacticsearch/funcVar.ml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -170,7 +170,7 @@ let rec search_stmt_list_for_var list name varid includeCallTmp =
170170
( match x.skind with
171171
| Instr ins_list ->
172172
search_instr_list_for_var ins_list name varid includeCallTmp
173-
| Return (Some exp, loc) ->
173+
| Return (Some exp, loc, eloc) ->
174174
search_expression exp name loc varid includeCallTmp
175175
| ComputedGoto (exp, loc) ->
176176
search_expression exp name loc varid includeCallTmp

src/formatparse.mly

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1334,7 +1334,7 @@ stmt:
13341334
}
13351335
| RETURN exp_opt SEMICOLON
13361336
{ (fun mkTemp loc args ->
1337-
mkStmt (Return((fst $2) args, loc)))
1337+
mkStmt (Return((fst $2) args, loc, locUnknown))) (* TODO: better eloc *)
13381338
}
13391339
| BREAK SEMICOLON
13401340
{ (fun mkTemp loc args ->

src/frontc/cabs.ml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -223,7 +223,7 @@ and statement =
223223
| FOR of for_clause * expression * expression * statement * cabsloc * cabsloc (* second cabsloc is just for expression *)
224224
| BREAK of cabsloc
225225
| CONTINUE of cabsloc
226-
| RETURN of expression * cabsloc
226+
| RETURN of expression * cabsloc * cabsloc (* second cabsloc is just for expression *)
227227
| SWITCH of expression * statement * cabsloc * cabsloc (* second cabsloc is just for expression *)
228228
| CASE of expression * statement * cabsloc * cabsloc (* second cabsloc is just for expression *)
229229
| CASERANGE of expression * expression * statement * cabsloc * cabsloc (* second cabsloc is just for expression *)

0 commit comments

Comments
 (0)