Skip to content

Commit e6f8785

Browse files
authored
Merge pull request #170 from LKedward/parsing-tests
Source parsing tests
2 parents e6c5e6a + 3eb42ba commit e6f8785

File tree

5 files changed

+886
-39
lines changed

5 files changed

+886
-39
lines changed

fpm/src/fpm.f90

Lines changed: 31 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -18,12 +18,13 @@ module fpm
1818

1919
contains
2020

21-
subroutine build_model(model, settings, package)
21+
subroutine build_model(model, settings, package, error)
2222
! Constructs a valid fpm model from command line settings and toml manifest
2323
!
2424
type(fpm_model_t), intent(out) :: model
2525
type(fpm_build_settings), intent(in) :: settings
2626
type(package_t), intent(in) :: package
27+
type(error_t), allocatable, intent(out) :: error
2728

2829
model%package_name = package%name
2930

@@ -37,14 +38,35 @@ subroutine build_model(model, settings, package)
3738

3839
! Add sources from executable directories
3940
if (allocated(package%executable)) then
40-
call add_executable_sources(model%sources, package%executable,is_test=.false.)
41+
42+
call add_executable_sources(model%sources, package%executable, &
43+
is_test=.false., error=error)
44+
45+
if (allocated(error)) then
46+
return
47+
end if
48+
4149
end if
4250
if (allocated(package%test)) then
43-
call add_executable_sources(model%sources, package%test,is_test=.true.)
51+
52+
call add_executable_sources(model%sources, package%test, &
53+
is_test=.true., error=error)
54+
55+
if (allocated(error)) then
56+
return
57+
end if
58+
4459
end if
4560

4661
if (allocated(package%library)) then
47-
call add_sources_from_dir(model%sources,package%library%source_dir)
62+
63+
call add_sources_from_dir(model%sources,package%library%source_dir, &
64+
error=error)
65+
66+
if (allocated(error)) then
67+
return
68+
end if
69+
4870
end if
4971

5072
call resolve_module_dependencies(model%sources)
@@ -79,7 +101,11 @@ subroutine cmd_build(settings)
79101
error stop 1
80102
end if
81103

82-
call build_model(model, settings, package)
104+
call build_model(model, settings, package, error)
105+
if (allocated(error)) then
106+
print '(a)', error%message
107+
error stop 1
108+
end if
83109

84110
call build_package(model)
85111

fpm/src/fpm/error.f90

Lines changed: 70 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -5,6 +5,7 @@ module fpm_error
55

66
public :: error_t
77
public :: fatal_error, syntax_error, file_not_found_error
8+
public :: file_parse_error
89

910

1011
!> Data type defining an error
@@ -55,4 +56,73 @@ subroutine file_not_found_error(error, file_name)
5556
end subroutine file_not_found_error
5657

5758

59+
!> Error created when file parsing fails
60+
subroutine file_parse_error(error, file_name, message, line_num, &
61+
line_string, line_col)
62+
63+
!> Instance of the error data
64+
type(error_t), allocatable, intent(out) :: error
65+
66+
!> Name of file
67+
character(len=*), intent(in) :: file_name
68+
69+
!> Parse error message
70+
character(len=*), intent(in) :: message
71+
72+
!> Line number of parse error
73+
integer, intent(in), optional :: line_num
74+
75+
!> Line context string
76+
character(len=*), intent(in), optional :: line_string
77+
78+
!> Line context column
79+
integer, intent(in), optional :: line_col
80+
81+
character(50) :: temp_string
82+
83+
allocate(error)
84+
error%message = 'Parse error: '//message//new_line('a')
85+
86+
error%message = error%message//file_name
87+
88+
if (present(line_num)) then
89+
90+
write(temp_string,'(I0)') line_num
91+
92+
error%message = error%message//':'//trim(temp_string)
93+
94+
end if
95+
96+
if (present(line_col)) then
97+
98+
if (line_col > 0) then
99+
100+
write(temp_string,'(I0)') line_col
101+
error%message = error%message//':'//trim(temp_string)
102+
103+
end if
104+
105+
end if
106+
107+
if (present(line_string)) then
108+
109+
error%message = error%message//new_line('a')
110+
error%message = error%message//' | '//line_string
111+
112+
if (present(line_col)) then
113+
114+
if (line_col > 0) then
115+
116+
error%message = error%message//new_line('a')
117+
error%message = error%message//' | '//repeat(' ',line_col-1)//'^'
118+
119+
end if
120+
121+
end if
122+
123+
end if
124+
125+
end subroutine file_parse_error
126+
127+
58128
end module fpm_error

0 commit comments

Comments
 (0)