Skip to content

Commit 0d37e2e

Browse files
committed
Updates CHANGELOG and adds Fortran sample code
1 parent ae5bb0c commit 0d37e2e

File tree

5 files changed

+233
-0
lines changed

5 files changed

+233
-0
lines changed

CHANGELOG.md

Lines changed: 6 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -7,6 +7,12 @@ and this project adheres to [Semantic Versioning](http://semver.org/).
77

88
## [Unreleased]
99

10+
### Changed
11+
12+
- Fixes syntax highlighting for nested case-select constructs
13+
([#181](https://github.com/krvajal/vscode-fortran-support/issues/181)) via
14+
([#201](https://github.com/krvajal/vscode-fortran-support/pull/201))
15+
1016
## [2.2.0] - 2020-04-11
1117

1218
### Changed

test/resources/class.f90

Lines changed: 41 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,41 @@
1+
module main
2+
3+
use iso_fortran_env, only: real64
4+
implicit none
5+
private
6+
7+
type, public :: test_t
8+
real(real64) :: a, b
9+
contains
10+
procedure, private :: init_sub
11+
generic :: init => init_sub
12+
end type test_t
13+
14+
type :: node
15+
private
16+
type(node), pointer :: next => null()
17+
class(*), allocatable :: item
18+
19+
contains
20+
final :: node_finalizer
21+
22+
end type node
23+
24+
contains
25+
26+
subroutine init_sub(this, a, b)
27+
28+
class( test_t ) :: this
29+
real(real64),intent(in) :: a, b
30+
31+
this%a = a
32+
this%b = b
33+
34+
end subroutine init_sub
35+
36+
subroutine node_finalizer(a)
37+
type(node) :: a
38+
39+
end subroutine node_finalizer
40+
41+
end module main

test/resources/select_case.f90

Lines changed: 38 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,38 @@
1+
2+
! ------------------------------------------------------------------------------
3+
!
4+
! Tests the syntax highlighting of nested case select constructs is correct
5+
!-------------------------------------------------------------------------------
6+
7+
program select_case_test
8+
implicit none
9+
10+
integer :: i, j, k
11+
12+
13+
select case(i)
14+
case(1)
15+
select case(j)
16+
case(1)
17+
print*, i, j
18+
case(2)
19+
print*, i, j
20+
case default
21+
print*, i, j
22+
end select
23+
24+
case(2)
25+
select case(k)
26+
case(1)
27+
print*, i, j
28+
case(2)
29+
print*, i, j
30+
case default
31+
print*, i, j
32+
end select
33+
34+
case default
35+
print*, i, j
36+
end select
37+
38+
end program select_case_test

test/resources/select_rank.f90

Lines changed: 85 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,85 @@
1+
2+
3+
! ------------------------------------------------------------------------------
4+
!
5+
! Tests the syntax highlighting of nested rank select constructs is correct
6+
! @note requires GCC 10.0+ to compile or ifort 2019.1+
7+
!-------------------------------------------------------------------------------
8+
9+
program select_rank_test
10+
implicit none
11+
12+
real, dimension(2, 2) :: a, b
13+
14+
a = -666.0; b = -666.0
15+
call initialize(a)
16+
call nested_initialise(a, b)
17+
18+
print*, a
19+
print*, b
20+
21+
contains
22+
23+
subroutine initialize (arg)
24+
real :: arg(..)
25+
select rank (arg)
26+
rank (0) ! scalar
27+
arg = 0.0
28+
rank (1)
29+
arg(:) = 0.0
30+
rank (2)
31+
arg(:, :) = 0.0
32+
rank default
33+
print *, "Subroutine initialize called with unexpected rank argument"
34+
end select
35+
return
36+
end subroutine
37+
38+
subroutine nested_initialise(arg1, arg2)
39+
!< @note this is meant to test the syntax highlighting, nothing else!
40+
real :: arg1(..), arg2(..)
41+
select rank (arg1)
42+
rank (0) ! scalar
43+
arg1 = 0.0
44+
select rank (arg2)
45+
rank (0) ! scalar
46+
arg2 = 0.0
47+
rank (1)
48+
arg2(:) = 0.0
49+
rank (2)
50+
arg2(:, :) = 0.0
51+
rank default
52+
print *, "Subroutine initialize called with unexpected rank argument"
53+
end select
54+
rank (1)
55+
arg1(:) = 0.0
56+
select rank (arg2)
57+
rank (0) ! scalar
58+
arg2 = 0.0
59+
rank (1)
60+
arg2(:) = 0.0
61+
rank (2)
62+
arg2(:, :) = 0.0
63+
rank default
64+
print *, "Subroutine initialize called with unexpected rank argument"
65+
end select
66+
rank (2)
67+
arg1(:, :) = 0.0
68+
select rank (arg2)
69+
rank (0) ! scalar
70+
arg2 = 0.0
71+
rank (1)
72+
arg2(:) = 0.0
73+
rank (2)
74+
arg2(:, :) = 0.0
75+
rank default
76+
print *, "Subroutine initialize called with unexpected rank argument"
77+
end select
78+
rank default
79+
print *, "Subroutine initialize called with unexpected rank argument"
80+
end select
81+
return
82+
83+
end subroutine nested_initialise
84+
85+
end program select_rank_test

test/resources/select_type.f90

Lines changed: 63 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,63 @@
1+
2+
! ------------------------------------------------------------------------------
3+
!
4+
! Tests the syntax highlighting of nested type select constructs is correct
5+
!-------------------------------------------------------------------------------
6+
7+
program select_type_test
8+
implicit none
9+
10+
11+
type :: point
12+
real :: x, y
13+
end type point
14+
15+
type, extends(point) :: point_3d
16+
real :: z
17+
end type point_3d
18+
19+
type, extends(point) :: color_point
20+
integer :: color
21+
end type color_point
22+
23+
type(point_3d), target :: p3
24+
type(color_point), target :: c
25+
class(point), pointer :: p_or_c
26+
class(point), pointer :: p
27+
28+
p_or_c => c
29+
p => p3
30+
select type ( a => p_or_c )
31+
class is ( point )
32+
! "class ( point ) :: a" implied here
33+
print *, a%x, a%y ! this block executes
34+
select type(a)
35+
type is (point_3d)
36+
print*, "type(point_3d)"
37+
type is (color_point)
38+
print*, "type(color_point)"
39+
class default
40+
print*, "no matching type"
41+
end select
42+
43+
class is (color_point) ! does not execute
44+
select type(p)
45+
class is (point_3d)
46+
print*, "class(point_3d)"
47+
class is (color_point)
48+
print*, "class(color_point)"
49+
class is (point)
50+
print*, "class(point)"
51+
class default
52+
print*, "no matching class"
53+
end select
54+
55+
type is ( point_3d ) ! does not execute
56+
! "type ( point_3d ) :: a" implied here
57+
print *, a%x, a%y, a%z
58+
class default
59+
print*, "no matching class"
60+
end select
61+
62+
63+
end program select_type_test

0 commit comments

Comments
 (0)