@@ -23,7 +23,7 @@ def test_hover_abstract_int_procedure():
23
23
string = write_rpc_request (1 , "initialize" , {"rootPath" : str (test_dir )})
24
24
file_path = test_dir / "subdir" / "test_abstract.f90"
25
25
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" ])
27
27
assert errcode == 0
28
28
ref_results = [
29
29
"""SUBROUTINE test(a, b)
@@ -348,3 +348,97 @@ def test_hover_submodule_procedure():
348
348
REAL(dp) :: fi""" ,
349
349
]
350
350
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 )
0 commit comments