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
40 changes: 16 additions & 24 deletions src/fpm.f90
Original file line number Diff line number Diff line change
Expand Up @@ -18,7 +18,7 @@ module fpm
resolve_target_linking, build_target_t, build_target_ptr, &
FPM_TARGET_EXECUTABLE, FPM_TARGET_ARCHIVE
use fpm_manifest, only : get_package_data, package_config_t
use fpm_error, only : error_t, fatal_error
use fpm_error, only : error_t, fatal_error, fpm_stop
use fpm_manifest_test, only : test_config_t
use,intrinsic :: iso_fortran_env, only : stdin=>input_unit, &
& stdout=>output_unit, &
Expand Down Expand Up @@ -196,7 +196,7 @@ subroutine build_model(model, settings, package, error)
! Check for duplicate modules
call check_modules_for_duplicates(model, duplicates_found)
if (duplicates_found) then
error stop 'Error: One or more duplicate module names found.'
call fpm_stop(1,'*build_model*:Error: One or more duplicate module names found.')
end if
end subroutine build_model

Expand Down Expand Up @@ -255,20 +255,17 @@ subroutine cmd_build(settings)

call get_package_data(package, "fpm.toml", error, apply_defaults=.true.)
if (allocated(error)) then
print '(a)', error%message
error stop 1
call fpm_stop(1,'*cmd_build*:package error:'//error%message)
end if

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

call targets_from_sources(targets,model,error)
if (allocated(error)) then
print '(a)', error%message
error stop 1
call fpm_stop(1,'*cmd_build*:target error:'//error%message)
end if

if(settings%list)then
Expand Down Expand Up @@ -304,20 +301,17 @@ subroutine cmd_run(settings,test)

call get_package_data(package, "fpm.toml", error, apply_defaults=.true.)
if (allocated(error)) then
print '(a)', error%message
error stop 1
call fpm_stop(1, '*cmd_run*:package error:'//error%message)
end if

call build_model(model, settings%fpm_build_settings, package, error)
if (allocated(error)) then
print '(a)', error%message
error stop 1
call fpm_stop(1, '*cmd_run*:model error:'//error%message)
end if

call targets_from_sources(targets,model,error)
if (allocated(error)) then
print '(a)', error%message
error stop 1
call fpm_stop(1, '*cmd_run*:targets error:'//error%message)
end if

if (test) then
Expand Down Expand Up @@ -373,11 +367,10 @@ subroutine cmd_run(settings,test)
! Check if any apps/tests were found
if (col_width < 0) then
if (test) then
write(stderr,*) 'No tests to run'
call fpm_stop(0,'No tests to run')
else
write(stderr,*) 'No executables to run'
call fpm_stop(0,'No executables to run')
end if
stop
end if

! Check all names are valid
Expand All @@ -391,7 +384,7 @@ subroutine cmd_run(settings,test)
line=join(settings%name)
if(line.ne.'.')then ! do not report these special strings
if(any(.not.found))then
write(stderr,'(A)',advance="no")'fpm::run<ERROR> specified names '
write(stderr,'(A)',advance="no")'<ERROR>*cmd_run*:specified names '
do j=1,size(settings%name)
if (.not.found(j)) write(stderr,'(A)',advance="no") '"'//trim(settings%name(j))//'" '
end do
Expand All @@ -406,9 +399,9 @@ subroutine cmd_run(settings,test)
call compact_list_all()

if(line.eq.'.' .or. line.eq.' ')then ! do not report these special strings
stop
call fpm_stop(0,'')
else
stop 1
call fpm_stop(1,'')
endif

end if
Expand All @@ -430,18 +423,17 @@ subroutine cmd_run(settings,test)
exitstat=stat(i))
endif
else
write(stderr,*)'fpm::run<ERROR>',executables(i)%s,' not found'
stop 1
call fpm_stop(1,'*cmd_run*:'//executables(i)%s//' not found')
end if
end do

if (any(stat /= 0)) then
do i=1,size(stat)
if (stat(i) /= 0) then
write(*,*) '<ERROR> Execution failed for "',basename(executables(i)%s),'"'
write(stderr,'(*(g0:,1x))') '<ERROR> Execution failed for object "',basename(executables(i)%s),'"'
end if
end do
stop 1
call fpm_stop(1,'*cmd_run*:stopping due to failed executions')
end if

endif
Expand Down
5 changes: 2 additions & 3 deletions src/fpm/cmd/install.f90
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,7 @@ module fpm_cmd_install
use fpm, only : build_model
use fpm_backend, only : build_package
use fpm_command_line, only : fpm_install_settings
use fpm_error, only : error_t, fatal_error
use fpm_error, only : error_t, fatal_error, fpm_stop
use fpm_filesystem, only : join_path, list_files
use fpm_installer, only : installer_t, new_installer
use fpm_manifest, only : package_config_t, get_package_data
Expand Down Expand Up @@ -168,8 +168,7 @@ end function is_module_file
subroutine handle_error(error)
type(error_t), intent(in), optional :: error
if (present(error)) then
print '("[Error]", 1x, a)', error%message
error stop 1
call fpm_stop(1,error%message)
end if
end subroutine handle_error

Expand Down
7 changes: 4 additions & 3 deletions src/fpm/cmd/new.f90
Original file line number Diff line number Diff line change
Expand Up @@ -55,9 +55,10 @@ module fpm_cmd_new

use fpm_command_line, only : fpm_new_settings
use fpm_environment, only : run, OS_LINUX, OS_MACOS, OS_WINDOWS
use fpm_filesystem, only : join_path, exists, basename, mkdir, is_dir, to_fortran_name
use fpm_filesystem, only : join_path, exists, basename, mkdir, is_dir
use fpm_filesystem, only : fileopen, fileclose, filewrite, warnwrite
use fpm_strings, only : join
use fpm_strings, only : join, to_fortran_name
use fpm_error, only : fpm_stop
use,intrinsic :: iso_fortran_env, only : stderr=>error_unit
implicit none
private
Expand Down Expand Up @@ -606,7 +607,7 @@ subroutine create_verified_basic_manifest(filename)
! continue building of manifest
! ...
call new_package(package, table, error=error)
if (allocated(error)) stop 3
if (allocated(error)) call fpm_stop( 3,'')
if(settings%verbose)then
call table%accept(ser)
endif
Expand Down
5 changes: 2 additions & 3 deletions src/fpm/cmd/update.f90
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
module fpm_cmd_update
use fpm_command_line, only : fpm_update_settings
use fpm_dependency, only : dependency_tree_t, new_dependency_tree
use fpm_error, only : error_t
use fpm_error, only : error_t, fpm_stop
use fpm_filesystem, only : exists, mkdir, join_path, delete_file
use fpm_manifest, only : package_config_t, get_package_data
implicit none
Expand Down Expand Up @@ -60,8 +60,7 @@ subroutine handle_error(error)
!> Potential error
type(error_t), intent(in), optional :: error
if (present(error)) then
print '(a)', error%message
error stop 1
call fpm_stop(1, error%message)
end if
end subroutine handle_error

Expand Down
75 changes: 63 additions & 12 deletions src/fpm/error.f90
Original file line number Diff line number Diff line change
@@ -1,11 +1,15 @@
!> Implementation of basic error handling.
module fpm_error
use,intrinsic :: iso_fortran_env, only : stdin=>input_unit, stdout=>output_unit, stderr=>error_unit
use fpm_strings, only : is_fortran_name, to_fortran_name
implicit none
private

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


!> Data type defining an error
Expand All @@ -16,16 +20,8 @@ module fpm_error

end type error_t


!> Alias syntax errors to fatal errors for now
interface syntax_error
module procedure :: fatal_error
end interface syntax_error


contains


!> Generic fatal runtime error
subroutine fatal_error(error, message)

Expand All @@ -40,6 +36,43 @@ subroutine fatal_error(error, message)

end subroutine fatal_error

subroutine syntax_error(error, message)

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

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

allocate(error)
error%message = message

end subroutine syntax_error

function bad_name_error(error, label,name)

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

!> Error message label to add to message
character(len=*), intent(in) :: label

!> name value to check
character(len=*), intent(in) :: name

logical :: bad_name_error

if(.not.is_fortran_name(to_fortran_name(name)))then
bad_name_error=.true.
allocate(error)
error%message = 'manifest file syntax error: '//label//' name must be composed only of &
&alphanumerics, "-" and "_" and start with a letter ::'//name
else
bad_name_error=.false.
endif

end function bad_name_error


!> Error created when a file is missing or not found
subroutine file_not_found_error(error, file_name)
Expand Down Expand Up @@ -82,9 +115,9 @@ subroutine file_parse_error(error, file_name, message, line_num, &

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
Expand Down Expand Up @@ -115,14 +148,32 @@ subroutine file_parse_error(error, file_name, message, line_num, &

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

subroutine fpm_stop(value,message)
! TODO: if verbose mode, call ERROR STOP instead of STOP
! TODO: if M_escape is used, add color
! to work with older compilers might need a case statement for values

!> value to use on STOP
integer, intent(in) :: value
!> Error message
character(len=*), intent(in) :: message
if(message.ne.'')then
if(value.gt.0)then
write(stderr,'("<ERROR>",a)')trim(message)
else
write(stderr,'("<INFO> ",a)')trim(message)
endif
endif
stop value
end subroutine fpm_stop

end module fpm_error
5 changes: 4 additions & 1 deletion src/fpm/manifest/example.f90
Original file line number Diff line number Diff line change
Expand Up @@ -17,7 +17,7 @@
module fpm_manifest_example
use fpm_manifest_dependency, only : dependency_config_t, new_dependencies
use fpm_manifest_executable, only : executable_config_t
use fpm_error, only : error_t, syntax_error
use fpm_error, only : error_t, syntax_error, bad_name_error
use fpm_toml, only : toml_table, toml_key, toml_stat, get_value
implicit none
private
Expand Down Expand Up @@ -61,6 +61,9 @@ subroutine new_example(self, table, error)
call syntax_error(error, "Could not retrieve example name")
return
end if
if (bad_name_error(error,'example',self%name))then
return
endif
call get_value(table, "source-dir", self%source_dir, "example")
call get_value(table, "main", self%main, "main.f90")

Expand Down
7 changes: 5 additions & 2 deletions src/fpm/manifest/executable.f90
Original file line number Diff line number Diff line change
Expand Up @@ -12,8 +12,8 @@
!>```
module fpm_manifest_executable
use fpm_manifest_dependency, only : dependency_config_t, new_dependencies
use fpm_error, only : error_t, syntax_error
use fpm_strings, only : string_t
use fpm_error, only : error_t, syntax_error, bad_name_error
use fpm_strings, only : string_t
use fpm_toml, only : toml_table, toml_key, toml_stat, get_value
implicit none
private
Expand Down Expand Up @@ -72,6 +72,9 @@ subroutine new_executable(self, table, error)
call syntax_error(error, "Could not retrieve executable name")
return
end if
if (bad_name_error(error,'executable',self%name))then
return
endif
call get_value(table, "source-dir", self%source_dir, "app")
call get_value(table, "main", self%main, "main.f90")

Expand Down
5 changes: 4 additions & 1 deletion src/fpm/manifest/package.f90
Original file line number Diff line number Diff line change
Expand Up @@ -39,7 +39,7 @@ module fpm_manifest_package
use fpm_manifest_install, only: install_config_t, new_install_config
use fpm_manifest_test, only : test_config_t, new_test
use fpm_filesystem, only : exists, getline, join_path
use fpm_error, only : error_t, fatal_error, syntax_error
use fpm_error, only : error_t, fatal_error, syntax_error, bad_name_error
use fpm_toml, only : toml_table, toml_array, toml_key, toml_stat, get_value, &
& len
use fpm_versioning, only : version_t, new_version
Expand Down Expand Up @@ -131,6 +131,9 @@ subroutine new_package(self, table, root, error)
call syntax_error(error, "Could not retrieve package name")
return
end if
if (bad_name_error(error,'package',self%name))then
return
endif

if (len(self%name) <= 0) then
call syntax_error(error, "Package name must be a non-empty string")
Expand Down
5 changes: 4 additions & 1 deletion src/fpm/manifest/test.f90
Original file line number Diff line number Diff line change
Expand Up @@ -17,7 +17,7 @@
module fpm_manifest_test
use fpm_manifest_dependency, only : dependency_config_t, new_dependencies
use fpm_manifest_executable, only : executable_config_t
use fpm_error, only : error_t, syntax_error
use fpm_error, only : error_t, syntax_error, bad_name_error
use fpm_toml, only : toml_table, toml_key, toml_stat, get_value
implicit none
private
Expand Down Expand Up @@ -61,6 +61,9 @@ subroutine new_test(self, table, error)
call syntax_error(error, "Could not retrieve test name")
return
end if
if (bad_name_error(error,'test',self%name))then
return
endif
call get_value(table, "source-dir", self%source_dir, "test")
call get_value(table, "main", self%main, "main.f90")

Expand Down
Loading