aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--fpm/src/fpm_backend.f9041
-rw-r--r--fpm/src/fpm_filesystem.f9043
-rw-r--r--fpm/src/fpm_model.f908
-rw-r--r--fpm/src/fpm_sources.f906
4 files changed, 80 insertions, 18 deletions
diff --git a/fpm/src/fpm_backend.f90 b/fpm/src/fpm_backend.f90
index 6d9f86b..d8bfd44 100644
--- a/fpm/src/fpm_backend.f90
+++ b/fpm/src/fpm_backend.f90
@@ -3,7 +3,7 @@ module fpm_backend
! Implements the native fpm build backend
use fpm_environment, only: run
-use fpm_filesystem, only: basename, exists, mkdir
+use fpm_filesystem, only: basename, join_path, exists, mkdir
use fpm_model, only: fpm_model_t
use fpm_sources, only: srcfile_t, FPM_UNIT_MODULE, FPM_UNIT_SUBMODULE, &
FPM_UNIT_SUBPROGRAM, FPM_UNIT_CSOURCE, FPM_UNIT_PROGRAM
@@ -21,11 +21,14 @@ subroutine build_package(model)
type(fpm_model_t), intent(inout) :: model
integer :: i
- character(:), allocatable :: base, linking
+ character(:), allocatable :: base, linking, subdir
- if(.not.exists(model%output_directory)) then
+ if (.not.exists(model%output_directory)) then
call mkdir(model%output_directory)
end if
+ if (.not.exists(join_path(model%output_directory,model%package_name))) then
+ call mkdir(join_path(model%output_directory,model%package_name))
+ end if
linking = ""
do i=1,size(model%sources)
@@ -41,18 +44,33 @@ subroutine build_package(model)
end do
+ if (any([(model%sources(i)%unit_type == FPM_UNIT_PROGRAM,i=1,size(model%sources))])) then
+ if (.not.exists(join_path(model%output_directory,'test'))) then
+ call mkdir(join_path(model%output_directory,'test'))
+ end if
+ if (.not.exists(join_path(model%output_directory,'app'))) then
+ call mkdir(join_path(model%output_directory,'app'))
+ end if
+ end if
+
do i=1,size(model%sources)
if (model%sources(i)%unit_type == FPM_UNIT_PROGRAM) then
base = basename(model%sources(i)%file_name,suffix=.false.)
+ if (model%sources(i)%is_test) then
+ subdir = 'test'
+ else
+ subdir = 'app'
+ end if
+
call run("gfortran -c " // model%sources(i)%file_name // ' '//model%fortran_compile_flags &
- // " -o " // model%output_directory // '/' // base // ".o")
+ // " -o " // join_path(model%output_directory,subdir,base) // ".o")
- call run("gfortran " // model%output_directory // '/' // base // ".o "// &
- linking //" " //model%link_flags // " -o " // model%output_directory &
- // '/' // model%sources(i)%exe_name)
+ call run("gfortran " // join_path(model%output_directory, subdir, base) // ".o "// &
+ linking //" " //model%link_flags // " -o " // &
+ join_path(model%output_directory,subdir,model%sources(i)%exe_name) )
end if
@@ -70,7 +88,7 @@ recursive subroutine build_source(model,source_file,linking)
character(:), allocatable, intent(inout) :: linking
integer :: i
- character(:), allocatable :: base
+ character(:), allocatable :: object_file
if (source_file%built) then
return
@@ -91,11 +109,12 @@ recursive subroutine build_source(model,source_file,linking)
end do
- base = basename(source_file%file_name,suffix=.false.)
+ object_file = join_path(model%output_directory, model%package_name, &
+ basename(source_file%file_name,suffix=.false.)//'.o')
call run("gfortran -c " // source_file%file_name // model%fortran_compile_flags &
- // " -o " // model%output_directory//'/'//base // ".o")
- linking = linking // " " // model%output_directory//'/'// base // ".o"
+ // " -o " // object_file)
+ linking = linking // " " // object_file
source_file%built = .true.
diff --git a/fpm/src/fpm_filesystem.f90 b/fpm/src/fpm_filesystem.f90
index f69d0fd..59be19a 100644
--- a/fpm/src/fpm_filesystem.f90
+++ b/fpm/src/fpm_filesystem.f90
@@ -4,8 +4,8 @@ use fpm_strings, only: f_string, string_t, split
implicit none
private
-public :: basename, number_of_rows, read_lines, list_files, mkdir, exists, &
- get_temp_filename
+public :: basename, join_path, number_of_rows, read_lines, list_files,&
+ mkdir, exists, get_temp_filename
integer, parameter :: LINE_BUFFER_LEN = 1000
@@ -39,6 +39,45 @@ function basename(path,suffix) result (base)
end function basename
+function join_path(a1,a2,a3,a4,a5) result(path)
+ ! Construct path by joining strings with os file separator
+ !
+ character(*), intent(in) :: a1, a2
+ character(*), intent(in), optional :: a3,a4,a5
+ character(:), allocatable :: path
+
+ character(1) :: filesep
+
+ select case (get_os_type())
+ case (OS_LINUX,OS_MACOS)
+ filesep = '/'
+ case (OS_WINDOWS)
+ filesep = '\'
+ end select
+
+ path = a1 // filesep // a2
+
+ if (present(a3)) then
+ path = path // filesep // a3
+ else
+ return
+ end if
+
+ if (present(a4)) then
+ path = path // filesep // a4
+ else
+ return
+ end if
+
+ if (present(a5)) then
+ path = path // filesep // a5
+ else
+ return
+ end if
+
+end function join_path
+
+
integer function number_of_rows(s) result(nrows)
! determine number or rows
integer,intent(in)::s
diff --git a/fpm/src/fpm_model.f90 b/fpm/src/fpm_model.f90
index 307033d..0387dfb 100644
--- a/fpm/src/fpm_model.f90
+++ b/fpm/src/fpm_model.f90
@@ -3,7 +3,7 @@ module fpm_model
! Definition and validation of the backend model
use fpm_command_line, only: fpm_build_settings
-use fpm_filesystem, only: exists
+use fpm_filesystem, only: exists, join_path
use fpm_manifest, only: package_t, default_library, default_executable
use fpm_manifest_executable, only: executable_t
use fpm_sources, only: resolve_module_dependencies, add_sources_from_dir, &
@@ -46,15 +46,15 @@ subroutine build_model(model, settings, package)
model%output_directory = 'build/gfortran_debug'
model%fortran_compile_flags = ' -Wall -Wextra -Wimplicit-interface -fPIC -fmax-errors=1 -g '// &
'-fbounds-check -fcheck-array-temporaries -fbacktrace '// &
- '-J'//model%output_directory
+ '-J'//join_path(model%output_directory,model%package_name)
model%link_flags = ''
! Add sources from executable directories
if (allocated(package%executable)) then
- call add_executable_sources(model%sources, package%executable)
+ call add_executable_sources(model%sources, package%executable,is_test=.false.)
end if
if (allocated(package%test)) then
- call add_executable_sources(model%sources, package%test)
+ call add_executable_sources(model%sources, package%test,is_test=.true.)
end if
if (allocated(package%library)) then
diff --git a/fpm/src/fpm_sources.f90 b/fpm/src/fpm_sources.f90
index d044051..fb6e57a 100644
--- a/fpm/src/fpm_sources.f90
+++ b/fpm/src/fpm_sources.f90
@@ -35,6 +35,8 @@ type srcfile_t
! File path relative to cwd
character(:), allocatable :: exe_name
! Name of executable for FPM_UNIT_PROGRAM
+ logical :: is_test = .false.
+ ! Is executable a test?
type(string_t), allocatable :: modules_provided(:)
! Modules provided by this source file (lowerstring)
integer :: unit_type = FPM_UNIT_UNKNOWN
@@ -112,12 +114,13 @@ subroutine add_sources_from_dir(sources,directory,with_executables)
end subroutine add_sources_from_dir
-subroutine add_executable_sources(sources,executables)
+subroutine add_executable_sources(sources,executables,is_test)
! 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), optional :: executables(:)
+ logical, intent(in) :: is_test
integer :: i, j
@@ -144,6 +147,7 @@ subroutine add_executable_sources(sources,executables)
executables(j)%main) then
exclude_source(i) = .false.
dir_sources(i)%exe_name = executables(j)%name
+ dir_sources(i)%is_test = is_test
exit
end if
end do