Skip to content

Commit f1ba00f

Browse files
committed
Add hover unittests for all possible types of kind, len, etc.
1 parent 107a9a0 commit f1ba00f

File tree

2 files changed

+137
-1
lines changed

2 files changed

+137
-1
lines changed

test/test_server_hover.py

Lines changed: 95 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -23,7 +23,7 @@ def test_hover_abstract_int_procedure():
2323
string = write_rpc_request(1, "initialize", {"rootPath": str(test_dir)})
2424
file_path = test_dir / "subdir" / "test_abstract.f90"
2525
string += hover_req(file_path, 7, 30)
26-
errcode, results = run_request(string, fortls_args=["--sort_keywords"])
26+
errcode, results = run_request(string, fortls_args=["--sort_keywords", "-n1"])
2727
assert errcode == 0
2828
ref_results = [
2929
"""SUBROUTINE test(a, b)
@@ -348,3 +348,97 @@ def test_hover_submodule_procedure():
348348
REAL(dp) :: fi""",
349349
]
350350
validate_hover(results, ref_results)
351+
352+
353+
def test_var_type_kinds():
354+
string = write_rpc_request(1, "initialize", {"rootPath": str(test_dir / "parse")})
355+
file_path = test_dir / "parse" / "test_kinds_and_dims.f90"
356+
string += hover_req(file_path, 2, 24)
357+
string += hover_req(file_path, 2, 27)
358+
string += hover_req(file_path, 3, 15)
359+
string += hover_req(file_path, 3, 19)
360+
string += hover_req(file_path, 4, 20)
361+
string += hover_req(file_path, 4, 25)
362+
string += hover_req(file_path, 5, 23)
363+
string += hover_req(file_path, 6, 25)
364+
errcode, results = run_request(string, fortls_args=["-n", "1"])
365+
assert errcode == 0
366+
ref_results = [
367+
"INTEGER(kind=4)",
368+
"INTEGER(kind=4), DIMENSION(3,4)",
369+
"INTEGER*8",
370+
"INTEGER*8, DIMENSION(3,4)",
371+
"INTEGER(8)",
372+
"INTEGER(8), DIMENSION(3,4)",
373+
"REAL(kind=r15)",
374+
"REAL(kind(0.d0))",
375+
]
376+
validate_hover(results, ref_results)
377+
378+
379+
def test_kind_function_result():
380+
string = write_rpc_request(1, "initialize", {"rootPath": str(test_dir / "parse")})
381+
file_path = test_dir / "parse" / "test_kinds_and_dims.f90"
382+
string += hover_req(file_path, 9, 18)
383+
string += hover_req(file_path, 14, 25)
384+
errcode, results = run_request(string, fortls_args=["-n", "1"])
385+
assert errcode == 0
386+
ref_results = [
387+
"""FUNCTION foo(val) RESULT(r)
388+
REAL(8), INTENT(IN) :: val
389+
REAL*8 :: r""",
390+
"""FUNCTION phi(val) RESULT(r)
391+
REAL(8), INTENT(IN) :: val
392+
REAL(kind=8) :: r""",
393+
]
394+
validate_hover(results, ref_results)
395+
396+
397+
def test_var_type_asterisk():
398+
string = write_rpc_request(1, "initialize", {"rootPath": str(test_dir / "parse")})
399+
file_path = test_dir / "parse" / "test_kinds_and_dims.f90"
400+
string += hover_req(file_path, 2 + 19, 18)
401+
string += hover_req(file_path, 2 + 19, 21)
402+
string += hover_req(file_path, 2 + 19, 29)
403+
string += hover_req(file_path, 3 + 19, 21)
404+
string += hover_req(file_path, 4 + 19, 17)
405+
string += hover_req(file_path, 5 + 19, 23)
406+
errcode, results = run_request(string, fortls_args=["-n", "1"])
407+
assert errcode == 0
408+
ref_results = [
409+
"CHARACTER*17",
410+
"CHARACTER*17, DIMENSION(3,4)",
411+
"CHARACTER*17, DIMENSION(9)",
412+
"CHARACTER*(6+3)",
413+
"CHARACTER*10, DIMENSION(3,4)",
414+
"CHARACTER*(LEN(B)), DIMENSION(3,4)",
415+
]
416+
validate_hover(results, ref_results)
417+
418+
419+
def test_var_name_asterisk():
420+
string = write_rpc_request(1, "initialize", {"rootPath": str(test_dir / "parse")})
421+
file_path = test_dir / "parse" / "test_kinds_and_dims.f90"
422+
string += hover_req(file_path, 26, 15)
423+
string += hover_req(file_path, 26, 22)
424+
string += hover_req(file_path, 26, 34)
425+
string += hover_req(file_path, 27, 15)
426+
string += hover_req(file_path, 28, 15)
427+
string += hover_req(file_path, 29, 15)
428+
string += hover_req(file_path, 31, 24)
429+
string += hover_req(file_path, 32, 32)
430+
# string += hover_req(file_path, 33, 32) # FIXME: this is not displayed correctly
431+
errcode, results = run_request(string, fortls_args=["-n", "1"])
432+
assert errcode == 0
433+
ref_results = [
434+
"CHARACTER*17",
435+
"CHARACTER*17, DIMENSION(3,4)",
436+
"CHARACTER*17, DIMENSION(9)",
437+
"CHARACTER*(6+3)",
438+
"CHARACTER*(LEN(A))",
439+
"CHARACTER*10, DIMENSION(*)",
440+
"CHARACTER(LEN=200)",
441+
"CHARACTER(KIND=4, LEN=200), DIMENSION(3,4)",
442+
# "CHARACTER(KIND=4, LEN=100), DIMENSION(3,4)",
443+
]
444+
validate_hover(results, ref_results)
Lines changed: 42 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,42 @@
1+
subroutine normal_kinds()
2+
integer, parameter :: r15 = selected_real_kind(15)
3+
integer(kind=4) :: a, b(3,4)
4+
integer*8 aa, bb(3,4)
5+
integer(8) :: aaa, bbb(3,4)
6+
real(kind=r15) :: r
7+
real(kind(0.d0)) :: rr
8+
end subroutine normal_kinds
9+
10+
real*8 function foo(val) result(r)
11+
real(8), intent(in) :: val
12+
r = val
13+
end function foo
14+
15+
real(kind=8) function phi(val) result(r)
16+
real(8), intent(in) :: val
17+
r = val
18+
end function phi
19+
20+
subroutine character_len_parsing(input)
21+
! global variable_type * length variable_name1, variable_name2,...
22+
CHARACTER*17 A, B(3,4), V(9)
23+
CHARACTER*(6+3) C
24+
CHARACTER*10D(3,4)
25+
CHARACTER*(LEN(B))DD(3,4)
26+
! local variable_type variable_name1 * length, variable_name2 * length,...
27+
CHARACTER AA*17, BB(3,4)*17, VV(9)*17
28+
CHARACTER CC*(6+3)
29+
CHARACTER AAA*(LEN(A))
30+
CHARACTER INPUT(*)*10
31+
! explicit len and kind for characters
32+
CHARACTER(LEN=200) F
33+
CHARACTER(KIND=4, LEN=200) FF(3,4)
34+
CHARACTER(KIND=4, LEN=200) AAAA(3,4)*100
35+
36+
! override global length with local length
37+
CHARACTER*10 BBB(3,4)*(LEN(B)) ! has the length of len(b)
38+
CHARACTER*10CCC(3,4)*(LEN(B)) ! no-space
39+
CHARACTER(KIND=4) BBBB(3,4)*(LEN(B)) ! cannot have *10(kind=4) or vice versa
40+
41+
INTEGER((4)) INT_KIND_IMP ! FIXME: (()) trips up the regex
42+
end subroutine character_len_parsing

0 commit comments

Comments
 (0)