diff options
-rw-r--r-- | fpm/src/fpm.f90 | 36 | ||||
-rw-r--r-- | fpm/src/fpm_sources.f90 | 27 |
2 files changed, 54 insertions, 9 deletions
diff --git a/fpm/src/fpm.f90 b/fpm/src/fpm.f90 index 29d663c..b57a713 100644 --- a/fpm/src/fpm.f90 +++ b/fpm/src/fpm.f90 @@ -18,12 +18,13 @@ public :: cmd_build, cmd_install, cmd_new, cmd_run, cmd_test 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 @@ -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) @@ -79,7 +101,11 @@ if (.not.(allocated(package%library) .or. allocated(package%executable))) then 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) diff --git a/fpm/src/fpm_sources.f90 b/fpm/src/fpm_sources.f90 index ac483f2..3c8a3cf 100644 --- a/fpm/src/fpm_sources.f90 +++ b/fpm/src/fpm_sources.f90 @@ -22,13 +22,13 @@ character(15), parameter :: INTRINSIC_MODULE_NAMES(*) = & contains -subroutine add_sources_from_dir(sources,directory,with_executables) +subroutine add_sources_from_dir(sources,directory,with_executables,error) ! Enumerate sources in a directory ! type(srcfile_t), allocatable, intent(inout), target :: sources(:) character(*), intent(in) :: directory logical, intent(in), optional :: with_executables - type(error_t), allocatable :: error + type(error_t), allocatable, intent(out) :: error integer :: i, j logical, allocatable :: is_source(:), exclude_source(:) @@ -51,12 +51,24 @@ subroutine add_sources_from_dir(sources,directory,with_executables) do i = 1, size(src_file_names) if (str_ends_with(lower(src_file_names(i)%s), ".f90")) then + dir_sources(i) = parse_f_source(src_file_names(i)%s, error) + + if (allocated(error)) then + return + end if + end if if (str_ends_with(lower(src_file_names(i)%s), ".c") .or. & str_ends_with(lower(src_file_names(i)%s), ".h")) then + dir_sources(i) = parse_c_source(src_file_names(i)%s,error) + + if (allocated(error)) then + return + end if + end if ! Exclude executables unless specified otherwise @@ -82,13 +94,14 @@ subroutine add_sources_from_dir(sources,directory,with_executables) end subroutine add_sources_from_dir -subroutine add_executable_sources(sources,executables,is_test) +subroutine add_executable_sources(sources,executables,is_test,error) ! Add sources from executable directories specified in manifest ! Only allow executables that are explicitly specified in manifest ! type(srcfile_t), allocatable, intent(inout), target :: sources(:) class(executable_t), intent(in) :: executables(:) logical, intent(in) :: is_test + type(error_t), allocatable, intent(out) :: error integer :: i, j @@ -99,8 +112,14 @@ subroutine add_executable_sources(sources,executables,is_test) call get_executable_source_dirs(exe_dirs,executables) do i=1,size(exe_dirs) + call add_sources_from_dir(dir_sources,exe_dirs(i)%s, & - with_executables=.true.) + with_executables=.true.,error=error) + + if (allocated(error)) then + return + end if + end do allocate(exclude_source(size(dir_sources))) |