Skip to content

Commit

Permalink
fix: remove codelens for inner element
Browse files Browse the repository at this point in the history
such as redefines and renames target
  • Loading branch information
NeoKaios committed Aug 8, 2024
1 parent 0442593 commit f31d2fc
Show file tree
Hide file tree
Showing 2 changed files with 11 additions and 29 deletions.
13 changes: 11 additions & 2 deletions src/lsp/cobol_lsp/lsp_request.ml
Original file line number Diff line number Diff line change
Expand Up @@ -599,6 +599,7 @@ let codelens_positions ~uri group =
let filename = Lsp.Uri.to_path uri in
let open struct
include Cobol_common.Visitor
include Cobol_data.Visitor
type context =
| ProcedureDiv
| DataDiv
Expand All @@ -615,13 +616,21 @@ let codelens_positions ~uri group =
skip (context, PosSet.add range.start acc)
in
Cobol_unit.Visitor.fold_unit_group
object
object (v)
inherit [_] Cobol_unit.Visitor.folder
method! fold_procedure _ = set_context ProcedureDiv
method! fold_paragraph' _ = skip
method! fold_data_definitions _ = set_context DataDiv
method! fold_paragraph' _ = skip
method! fold_procedure_name' = take_when_in ProcedureDiv
method! fold_qualname' = take_when_in DataDiv
method! fold_record_renaming { renaming_name; _ } =
take_when_in DataDiv renaming_name
method! fold_field_definition' { payload = field; _ } acc =
fold_field_definition v { field with field_redefines = None } acc
|> skip
method! fold_table_definition' { payload = table; _ } acc =
fold_table_definition v { table with table_redefines = None } acc
|> skip
end group (None, PosSet.empty)
|> snd

Expand Down
27 changes: 0 additions & 27 deletions test/lsp/lsp_codelens.ml
Original file line number Diff line number Diff line change
Expand Up @@ -79,15 +79,6 @@ let%expect_test "codelens" =
9 02 CC PIC X. 02 DD PIC X.
10 66 ABCD RENAMES BB THRU DD.
1 reference
__rootdir__/prog.cob:8.31:
5 WORKING-STORAGE SECTION.
6 01 AA.
7 02 BB PIC X.
8 > 02 BBprime REDEFINES BB PIC 9.
---- ^
9 02 CC PIC X. 02 DD PIC X.
10 66 ABCD RENAMES BB THRU DD.
3 references
__rootdir__/prog.cob:9.13:
6 01 AA.
7 02 BB PIC X.
Expand Down Expand Up @@ -115,24 +106,6 @@ let%expect_test "codelens" =
11 01 ZZ OCCURS 5 TIMES INDEXED BY INDEX1.
12 02 YY PIC X.
1 reference
__rootdir__/prog.cob:10.26:
7 02 BB PIC X.
8 02 BBprime REDEFINES BB PIC 9.
9 02 CC PIC X. 02 DD PIC X.
10 > 66 ABCD RENAMES BB THRU DD.
---- ^
11 01 ZZ OCCURS 5 TIMES INDEXED BY INDEX1.
12 02 YY PIC X.
3 references
__rootdir__/prog.cob:10.34:
7 02 BB PIC X.
8 02 BBprime REDEFINES BB PIC 9.
9 02 CC PIC X. 02 DD PIC X.
10 > 66 ABCD RENAMES BB THRU DD.
---- ^
11 01 ZZ OCCURS 5 TIMES INDEXED BY INDEX1.
12 02 YY PIC X.
2 references
__rootdir__/prog.cob:11.11:
8 02 BBprime REDEFINES BB PIC 9.
9 02 CC PIC X. 02 DD PIC X.
Expand Down

0 comments on commit f31d2fc

Please sign in to comment.