Skip to content
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
36 changes: 31 additions & 5 deletions fpm/src/fpm.f90
Original file line number Diff line number Diff line change
Expand Up @@ -18,12 +18,13 @@ module fpm

contains

subroutine build_model(model, settings, package)
subroutine build_model(model, settings, package, error)
! Constructs a valid fpm model from command line settings and toml manifest
!
type(fpm_model_t), intent(out) :: model
type(fpm_build_settings), intent(in) :: settings
type(package_t), intent(in) :: package
type(error_t), allocatable, intent(out) :: error

model%package_name = package%name

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

! Add sources from executable directories
if (allocated(package%executable)) then
call add_executable_sources(model%sources, package%executable,is_test=.false.)

call add_executable_sources(model%sources, package%executable, &
is_test=.false., error=error)

if (allocated(error)) then
return
end if

end if
if (allocated(package%test)) then
call add_executable_sources(model%sources, package%test,is_test=.true.)

call add_executable_sources(model%sources, package%test, &
is_test=.true., error=error)

if (allocated(error)) then
return
end if

end if

if (allocated(package%library)) then
call add_sources_from_dir(model%sources,package%library%source_dir)

call add_sources_from_dir(model%sources,package%library%source_dir, &
error=error)

if (allocated(error)) then
return
end if

end if

call resolve_module_dependencies(model%sources)
Expand Down Expand Up @@ -79,7 +101,11 @@ subroutine cmd_build(settings)
error stop 1
end if

call build_model(model, settings, package)
call build_model(model, settings, package, error)
if (allocated(error)) then
print '(a)', error%message
error stop 1
end if

call build_package(model)

Expand Down
70 changes: 70 additions & 0 deletions fpm/src/fpm/error.f90
Original file line number Diff line number Diff line change
Expand Up @@ -5,6 +5,7 @@ module fpm_error

public :: error_t
public :: fatal_error, syntax_error, file_not_found_error
public :: file_parse_error


!> Data type defining an error
Expand Down Expand Up @@ -55,4 +56,73 @@ subroutine file_not_found_error(error, file_name)
end subroutine file_not_found_error


!> Error created when file parsing fails
subroutine file_parse_error(error, file_name, message, line_num, &
line_string, line_col)

!> Instance of the error data
type(error_t), allocatable, intent(out) :: error

!> Name of file
character(len=*), intent(in) :: file_name

!> Parse error message
character(len=*), intent(in) :: message

!> Line number of parse error
integer, intent(in), optional :: line_num

!> Line context string
character(len=*), intent(in), optional :: line_string

!> Line context column
integer, intent(in), optional :: line_col

character(50) :: temp_string

allocate(error)
error%message = 'Parse error: '//message//new_line('a')

error%message = error%message//file_name

if (present(line_num)) then

write(temp_string,'(I0)') line_num

error%message = error%message//':'//trim(temp_string)

end if

if (present(line_col)) then

if (line_col > 0) then

write(temp_string,'(I0)') line_col
error%message = error%message//':'//trim(temp_string)

end if

end if

if (present(line_string)) then

error%message = error%message//new_line('a')
error%message = error%message//' | '//line_string

if (present(line_col)) then

if (line_col > 0) then

error%message = error%message//new_line('a')
error%message = error%message//' | '//repeat(' ',line_col-1)//'^'

end if

end if

end if

end subroutine file_parse_error


end module fpm_error
Loading