Skip to content

Commit 67103ac

Browse files
committed
Merge branch 'main' into fix-issue-35-line-length-rule
2 parents 8a6510f + 1073162 commit 67103ac

9 files changed

+609
-153
lines changed

src/fluff_ast/fluff_ast.f90

Lines changed: 16 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -7,7 +7,14 @@ module fluff_ast
77
NODE_IDENTIFIER, NODE_LITERAL, NODE_ARRAY_LITERAL, &
88
NODE_CALL_OR_SUBSCRIPT, NODE_SUBROUTINE_DEF, NODE_SUBROUTINE_CALL, &
99
NODE_DECLARATION, NODE_PARAMETER_DECLARATION, NODE_IF, NODE_DO_LOOP, &
10-
NODE_DO_WHILE, NODE_SELECT_CASE, NODE_CASE_BLOCK, NODE_MODULE
10+
NODE_DO_WHILE, NODE_SELECT_CASE, NODE_CASE_BLOCK, NODE_MODULE, &
11+
NODE_USE_STATEMENT, NODE_PRINT_STATEMENT, NODE_WRITE_STATEMENT, &
12+
NODE_READ_STATEMENT, NODE_ALLOCATE_STATEMENT, NODE_DEALLOCATE_STATEMENT, &
13+
NODE_STOP, NODE_RETURN, NODE_GOTO, NODE_ERROR_STOP, NODE_CYCLE, NODE_EXIT, &
14+
NODE_WHERE, NODE_INTERFACE_BLOCK, NODE_DERIVED_TYPE, NODE_POINTER_ASSIGNMENT, &
15+
NODE_FORALL, NODE_CASE_RANGE, NODE_CASE_DEFAULT, NODE_COMPLEX_LITERAL, &
16+
NODE_INCLUDE_STATEMENT, NODE_CONTAINS, NODE_FORMAT_DESCRIPTOR, &
17+
NODE_COMMENT, NODE_IMPLICIT_STATEMENT, NODE_UNKNOWN
1118
implicit none
1219
private
1320

@@ -25,9 +32,7 @@ module fluff_ast
2532
procedure :: get_node_location => ast_get_node_location
2633
end type fluff_ast_context_t
2734

28-
! Node type constants - now imported from fortfront
29-
integer, parameter :: NODE_UNKNOWN = 0
30-
! All other constants imported from fortfront
35+
! Node type constants - all imported from fortfront
3136

3237
! Public procedures
3338
public :: create_ast_context
@@ -38,6 +43,13 @@ module fluff_ast
3843
public :: NODE_CALL_OR_SUBSCRIPT, NODE_SUBROUTINE_DEF, NODE_SUBROUTINE_CALL
3944
public :: NODE_DECLARATION, NODE_PARAMETER_DECLARATION, NODE_IF, NODE_DO_LOOP
4045
public :: NODE_DO_WHILE, NODE_SELECT_CASE, NODE_CASE_BLOCK, NODE_MODULE
46+
public :: NODE_USE_STATEMENT, NODE_PRINT_STATEMENT, NODE_WRITE_STATEMENT
47+
public :: NODE_READ_STATEMENT, NODE_ALLOCATE_STATEMENT, NODE_DEALLOCATE_STATEMENT
48+
public :: NODE_STOP, NODE_RETURN, NODE_GOTO, NODE_ERROR_STOP, NODE_CYCLE, NODE_EXIT
49+
public :: NODE_WHERE, NODE_INTERFACE_BLOCK, NODE_DERIVED_TYPE, NODE_POINTER_ASSIGNMENT
50+
public :: NODE_FORALL, NODE_CASE_RANGE, NODE_CASE_DEFAULT, NODE_COMPLEX_LITERAL
51+
public :: NODE_INCLUDE_STATEMENT, NODE_CONTAINS, NODE_FORMAT_DESCRIPTOR
52+
public :: NODE_COMMENT, NODE_IMPLICIT_STATEMENT
4153

4254
contains
4355

src/fluff_linter/fluff_linter.f90

Lines changed: 11 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -97,31 +97,29 @@ subroutine linter_lint_file(this, filename, diagnostics, error_msg)
9797
character(len=1000) :: line
9898
integer :: unit, iostat
9999

100-
! Read file contents
101-
open(newunit=unit, file=filename, status='old', action='read', iostat=iostat)
100+
! Read file contents preserving trailing whitespace
101+
open(newunit=unit, file=filename, status='old', action='read', &
102+
access='stream', form='unformatted', iostat=iostat)
102103
if (iostat /= 0) then
103104
error_msg = "Failed to open file: " // filename
104105
allocate(diagnostics(0))
105106
return
106107
end if
107108

108-
source_code = ""
109-
do
110-
read(unit, '(A)', iostat=iostat) line
111-
if (iostat == iostat_end) exit
109+
! Get file size and read entire content
110+
inquire(unit=unit, size=iostat)
111+
if (iostat > 0) then
112+
allocate(character(len=iostat) :: source_code)
113+
read(unit, iostat=iostat) source_code
112114
if (iostat /= 0) then
113115
close(unit)
114116
error_msg = "Failed to read file: " // filename
115117
allocate(diagnostics(0))
116118
return
117119
end if
118-
119-
if (len(source_code) > 0) then
120-
source_code = source_code // new_line('a') // trim(line)
121-
else
122-
source_code = trim(line)
123-
end if
124-
end do
120+
else
121+
source_code = ""
122+
end if
125123
close(unit)
126124

127125
! Parse AST fresh each time to avoid memory safety issues

src/fluff_rules/fluff_rules.f90

Lines changed: 220 additions & 71 deletions
Large diffs are not rendered by default.

test/test_rule_f004_trailing_whitespace.f90

Lines changed: 99 additions & 14 deletions
Original file line numberDiff line numberDiff line change
@@ -33,9 +33,7 @@ subroutine test_trailing_whitespace()
3333
integer :: i
3434
logical :: found_f004
3535

36-
! Skip test if fortfront not available
37-
print *, " ⚠ Trailing whitespace (skipped - fortfront not available)"
38-
return
36+
! Enable test - fortfront is available
3937

4038
! Note: The spaces after 'none' and 'x' are intentional
4139
test_code = "program test" // new_line('a') // &
@@ -46,10 +44,12 @@ subroutine test_trailing_whitespace()
4644

4745
linter = create_linter_engine()
4846

49-
! Create temporary file
50-
open(unit=99, file="test_f004.f90", status="replace")
51-
write(99, '(A)') test_code
52-
close(99)
47+
! Create temporary file using printf to preserve trailing whitespace
48+
call system('printf "program test\n" > test_f004.f90')
49+
call system('printf " implicit none \n" >> test_f004.f90')
50+
call system('printf " integer :: x \n" >> test_f004.f90')
51+
call system('printf " x = 42\n" >> test_f004.f90')
52+
call system('printf "end program test\n" >> test_f004.f90')
5353

5454
! Lint the file
5555
call linter%lint_file("test_f004.f90", diagnostics, error_msg)
@@ -85,9 +85,7 @@ subroutine test_no_trailing_whitespace()
8585
integer :: i
8686
logical :: found_f004
8787

88-
! Skip test if fortfront not available
89-
print *, " ⚠ No trailing whitespace (skipped - fortfront not available)"
90-
return
88+
! Enable test - fortfront is available
9189

9290
test_code = "program test" // new_line('a') // &
9391
" implicit none" // new_line('a') // &
@@ -129,13 +127,100 @@ subroutine test_no_trailing_whitespace()
129127
end subroutine test_no_trailing_whitespace
130128

131129
subroutine test_multiple_trailing_spaces()
132-
! Skip test if fortfront not available
133-
print *, " ⚠ Multiple trailing spaces (skipped - fortfront not available)"
130+
type(linter_engine_t) :: linter
131+
type(diagnostic_t), allocatable :: diagnostics(:)
132+
character(len=:), allocatable :: error_msg
133+
character(len=:), allocatable :: test_code
134+
integer :: i, j
135+
integer :: f004_count
136+
137+
! Enable test - fortfront is available
138+
139+
! Multiple lines with trailing spaces of different lengths
140+
test_code = "program test" // new_line('a') // &
141+
" implicit none " // new_line('a') // & ! 5 trailing spaces
142+
" integer :: x " // new_line('a') // & ! 2 trailing spaces
143+
" real :: y " // new_line('a') // & ! 3 trailing spaces
144+
" x = 42" // new_line('a') // & ! No trailing space
145+
" y = 3.14" // new_line('a') // & ! No trailing space
146+
"end program test"
147+
148+
linter = create_linter_engine()
149+
150+
! Create temporary file
151+
open(unit=99, file="test_f004_multi.f90", status="replace")
152+
write(99, '(A)') test_code
153+
close(99)
154+
155+
! Lint the file
156+
call linter%lint_file("test_f004_multi.f90", diagnostics, error_msg)
157+
158+
! Count F004 violations
159+
f004_count = 0
160+
if (allocated(diagnostics)) then
161+
do i = 1, size(diagnostics)
162+
if (diagnostics(i)%code == "F004") then
163+
f004_count = f004_count + 1
164+
end if
165+
end do
166+
end if
167+
168+
! Clean up
169+
open(unit=99, file="test_f004_multi.f90", status="old")
170+
close(99, status="delete")
171+
172+
if (f004_count /= 3) then
173+
print *, "Expected 3 F004 violations, found", f004_count
174+
error stop "Failed: F004 should be triggered for each line with trailing whitespace"
175+
end if
176+
177+
print *, " ✓ Multiple trailing spaces"
178+
134179
end subroutine test_multiple_trailing_spaces
135180

136181
subroutine test_trailing_tabs()
137-
! Skip test if fortfront not available
138-
print *, " ⚠ Trailing tabs (skipped - fortfront not available)"
182+
type(linter_engine_t) :: linter
183+
type(diagnostic_t), allocatable :: diagnostics(:)
184+
character(len=:), allocatable :: error_msg
185+
character(len=:), allocatable :: test_code
186+
integer :: i
187+
logical :: found_f004
188+
189+
! Enable test - fortfront is available
190+
191+
linter = create_linter_engine()
192+
193+
! Create temporary file with trailing tabs using printf
194+
call system('printf "program test\n" > test_f004_tabs.f90')
195+
call system('printf " implicit none\t\n" >> test_f004_tabs.f90') ! Trailing tab
196+
call system('printf " integer :: x\t\t\n" >> test_f004_tabs.f90') ! Two trailing tabs
197+
call system('printf " x = 42\n" >> test_f004_tabs.f90')
198+
call system('printf "end program test\n" >> test_f004_tabs.f90')
199+
200+
! Lint the file
201+
call linter%lint_file("test_f004_tabs.f90", diagnostics, error_msg)
202+
203+
! Check for F004 violation
204+
found_f004 = .false.
205+
if (allocated(diagnostics)) then
206+
do i = 1, size(diagnostics)
207+
if (diagnostics(i)%code == "F004") then
208+
found_f004 = .true.
209+
exit
210+
end if
211+
end do
212+
end if
213+
214+
! Clean up
215+
open(unit=99, file="test_f004_tabs.f90", status="old")
216+
close(99, status="delete")
217+
218+
if (.not. found_f004) then
219+
error stop "Failed: F004 should be triggered for trailing tabs"
220+
end if
221+
222+
print *, " ✓ Trailing tabs"
223+
139224
end subroutine test_trailing_tabs
140225

141226
end program test_rule_f004_trailing_whitespace

test/test_rule_f005_mixed_tabs_spaces.f90

Lines changed: 98 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -33,9 +33,7 @@ subroutine test_mixed_tabs_spaces()
3333
integer :: i
3434
logical :: found_f005
3535

36-
! Skip test if fortfront not available
37-
print *, " ⚠ Mixed tabs and spaces (skipped - fortfront not available)"
38-
return
36+
! Enable test - fortfront is available
3937

4038
! Note: Using char(9) for tab character
4139
test_code = "program test" // new_line('a') // &
@@ -85,9 +83,7 @@ subroutine test_only_spaces()
8583
integer :: i
8684
logical :: found_f005
8785

88-
! Skip test if fortfront not available
89-
print *, " ⚠ Only spaces (skipped - fortfront not available)"
90-
return
86+
! Enable test - fortfront is available
9187

9288
test_code = "program test" // new_line('a') // &
9389
" implicit none" // new_line('a') // &
@@ -129,13 +125,105 @@ subroutine test_only_spaces()
129125
end subroutine test_only_spaces
130126

131127
subroutine test_only_tabs()
132-
! Skip test if fortfront not available
133-
print *, " ⚠ Only tabs (skipped - fortfront not available)"
128+
type(linter_engine_t) :: linter
129+
type(diagnostic_t), allocatable :: diagnostics(:)
130+
character(len=:), allocatable :: error_msg
131+
character(len=:), allocatable :: test_code
132+
integer :: i
133+
logical :: found_f005
134+
135+
! Enable test - fortfront is available
136+
137+
! Use only tabs for indentation
138+
test_code = "program test" // new_line('a') // &
139+
char(9) // "implicit none" // new_line('a') // &
140+
char(9) // "integer :: x" // new_line('a') // &
141+
char(9) // "x = 42" // new_line('a') // &
142+
"end program test"
143+
144+
linter = create_linter_engine()
145+
146+
! Create temporary file
147+
open(unit=99, file="test_f005_tabs.f90", status="replace")
148+
write(99, '(A)') test_code
149+
close(99)
150+
151+
! Lint the file
152+
call linter%lint_file("test_f005_tabs.f90", diagnostics, error_msg)
153+
154+
! Check for F005 violation
155+
found_f005 = .false.
156+
if (allocated(diagnostics)) then
157+
do i = 1, size(diagnostics)
158+
if (diagnostics(i)%code == "F005") then
159+
found_f005 = .true.
160+
exit
161+
end if
162+
end do
163+
end if
164+
165+
! Clean up
166+
open(unit=99, file="test_f005_tabs.f90", status="old")
167+
close(99, status="delete")
168+
169+
if (found_f005) then
170+
error stop "Failed: F005 should not be triggered for consistent tabs"
171+
end if
172+
173+
print *, " ✓ Only tabs"
174+
134175
end subroutine test_only_tabs
135176

136177
subroutine test_multiple_mixed()
137-
! Skip test if fortfront not available
138-
print *, " ⚠ Multiple mixed indentations (skipped - fortfront not available)"
178+
type(linter_engine_t) :: linter
179+
type(diagnostic_t), allocatable :: diagnostics(:)
180+
character(len=:), allocatable :: error_msg
181+
character(len=:), allocatable :: test_code
182+
integer :: i
183+
integer :: f005_count
184+
185+
! Enable test - fortfront is available
186+
187+
! Multiple lines with mixed indentation
188+
test_code = "program test" // new_line('a') // &
189+
" implicit none" // new_line('a') // & ! 4 spaces
190+
char(9) // "integer :: x" // new_line('a') // & ! 1 tab
191+
" " // char(9) // "real :: y" // new_line('a') // & ! 2 spaces + 1 tab (mixed)
192+
char(9) // " x = 42" // new_line('a') // & ! 1 tab + 2 spaces (mixed)
193+
" y = 3.14" // new_line('a') // & ! 4 spaces
194+
"end program test"
195+
196+
linter = create_linter_engine()
197+
198+
! Create temporary file
199+
open(unit=99, file="test_f005_multi.f90", status="replace")
200+
write(99, '(A)') test_code
201+
close(99)
202+
203+
! Lint the file
204+
call linter%lint_file("test_f005_multi.f90", diagnostics, error_msg)
205+
206+
! Count F005 violations
207+
f005_count = 0
208+
if (allocated(diagnostics)) then
209+
do i = 1, size(diagnostics)
210+
if (diagnostics(i)%code == "F005") then
211+
f005_count = f005_count + 1
212+
end if
213+
end do
214+
end if
215+
216+
! Clean up
217+
open(unit=99, file="test_f005_multi.f90", status="old")
218+
close(99, status="delete")
219+
220+
if (f005_count /= 2) then
221+
print *, "Expected 2 F005 violations, found", f005_count
222+
error stop "Failed: F005 should be triggered for lines with mixed tabs and spaces"
223+
end if
224+
225+
print *, " ✓ Multiple mixed indentations"
226+
139227
end subroutine test_multiple_mixed
140228

141229
end program test_rule_f005_mixed_tabs_spaces

0 commit comments

Comments
 (0)