aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorLKedward <laurence.kedward@bristol.ac.uk>2020-09-07 08:56:39 +0100
committerLKedward <laurence.kedward@bristol.ac.uk>2020-09-07 09:19:41 +0100
commitfdcf6b8be7cce30ac50794ce1e8169aa4aa2ef8c (patch)
treea4ee3ee919042c35d8c70098f161ec36491fdcf4
parenta734a825f6477e712a37064dd89a326992d67e69 (diff)
downloadfpm-fdcf6b8be7cce30ac50794ce1e8169aa4aa2ef8c.tar.gz
fpm-fdcf6b8be7cce30ac50794ce1e8169aa4aa2ef8c.zip
Refactor: add basename filesystem fcn
Function to extract filename from path with or without suffix.
-rw-r--r--fpm/src/fpm_backend.f9022
-rw-r--r--fpm/src/fpm_filesystem.f9032
-rw-r--r--fpm/src/fpm_sources.f9019
3 files changed, 43 insertions, 30 deletions
diff --git a/fpm/src/fpm_backend.f90 b/fpm/src/fpm_backend.f90
index 5a16193..6d9f86b 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: exists, mkdir
+use fpm_filesystem, only: basename, 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,8 +21,7 @@ subroutine build_package(model)
type(fpm_model_t), intent(inout) :: model
integer :: i
- character(:), allocatable :: basename, linking
- character(:), allocatable :: file_parts(:)
+ character(:), allocatable :: base, linking
if(.not.exists(model%output_directory)) then
call mkdir(model%output_directory)
@@ -46,13 +45,12 @@ subroutine build_package(model)
if (model%sources(i)%unit_type == FPM_UNIT_PROGRAM) then
- call split(model%sources(i)%file_name,file_parts,delimiters='\/.')
- basename = file_parts(size(file_parts)-1)
+ base = basename(model%sources(i)%file_name,suffix=.false.)
call run("gfortran -c " // model%sources(i)%file_name // ' '//model%fortran_compile_flags &
- // " -o " // model%output_directory // '/' // basename // ".o")
+ // " -o " // model%output_directory // '/' // base // ".o")
- call run("gfortran " // model%output_directory // '/' // basename // ".o "// &
+ call run("gfortran " // model%output_directory // '/' // base // ".o "// &
linking //" " //model%link_flags // " -o " // model%output_directory &
// '/' // model%sources(i)%exe_name)
@@ -72,8 +70,7 @@ recursive subroutine build_source(model,source_file,linking)
character(:), allocatable, intent(inout) :: linking
integer :: i
- character(:), allocatable :: file_parts(:)
- character(:), allocatable :: basename
+ character(:), allocatable :: base
if (source_file%built) then
return
@@ -94,12 +91,11 @@ recursive subroutine build_source(model,source_file,linking)
end do
- call split(source_file%file_name,file_parts,delimiters='\/.')
- basename = file_parts(size(file_parts)-1)
+ base = basename(source_file%file_name,suffix=.false.)
call run("gfortran -c " // source_file%file_name // model%fortran_compile_flags &
- // " -o " // model%output_directory//'/'//basename // ".o")
- linking = linking // " " // model%output_directory//'/'// basename // ".o"
+ // " -o " // model%output_directory//'/'//base // ".o")
+ linking = linking // " " // model%output_directory//'/'// base // ".o"
source_file%built = .true.
diff --git a/fpm/src/fpm_filesystem.f90 b/fpm/src/fpm_filesystem.f90
index a86e813..f69d0fd 100644
--- a/fpm/src/fpm_filesystem.f90
+++ b/fpm/src/fpm_filesystem.f90
@@ -1,16 +1,44 @@
module fpm_filesystem
use fpm_environment, only: get_os_type, OS_LINUX, OS_MACOS, OS_WINDOWS
-use fpm_strings, only: f_string, string_t
+use fpm_strings, only: f_string, string_t, split
implicit none
private
-public :: number_of_rows, read_lines, list_files, mkdir, exists, &
+public :: basename, number_of_rows, read_lines, list_files, mkdir, exists, &
get_temp_filename
integer, parameter :: LINE_BUFFER_LEN = 1000
contains
+
+function basename(path,suffix) result (base)
+ ! Extract filename from path with/without suffix
+ !
+ character(*), intent(In) :: path
+ logical, intent(in), optional :: suffix
+ character(:), allocatable :: base
+
+ character(:), allocatable :: file_parts(:)
+ logical :: with_suffix
+
+ if (.not.present(suffix)) then
+ with_suffix = .true.
+ else
+ with_suffix = suffix
+ end if
+
+ if (with_suffix) then
+ call split(path,file_parts,delimiters='\/')
+ base = file_parts(size(file_parts))
+ else
+ call split(path,file_parts,delimiters='\/.')
+ base = file_parts(size(file_parts)-1)
+ end if
+
+end function basename
+
+
integer function number_of_rows(s) result(nrows)
! determine number or rows
integer,intent(in)::s
diff --git a/fpm/src/fpm_sources.f90 b/fpm/src/fpm_sources.f90
index bf6124a..d044051 100644
--- a/fpm/src/fpm_sources.f90
+++ b/fpm/src/fpm_sources.f90
@@ -1,5 +1,5 @@
module fpm_sources
-use fpm_filesystem, only: read_lines, list_files
+use fpm_filesystem, only: basename, read_lines, list_files
use fpm_strings, only: lower, split, str_ends_with, string_t
use fpm_manifest_executable, only: executable_t
implicit none
@@ -66,9 +66,6 @@ subroutine add_sources_from_dir(sources,directory,with_executables)
type(string_t), allocatable :: src_file_names(:)
type(srcfile_t), allocatable :: dir_sources(:)
- character(:), allocatable :: basename
- character(:), allocatable :: file_parts(:)
-
! Scan directory for sources
call list_files(directory, file_names)
file_names = [(string_t(directory//'/'//file_names(j)%s),j=1,size(file_names))]
@@ -99,10 +96,7 @@ subroutine add_sources_from_dir(sources,directory,with_executables)
if (with_executables) then
exclude_source(i) = .false.
- call split(src_file_names(i)%s,file_parts,delimiters='\/.')
- basename = file_parts(size(file_parts)-1)
-
- dir_sources(i)%exe_name = basename
+ dir_sources(i)%exe_name = basename(src_file_names(i)%s,suffix=.false.)
end if
end if
@@ -131,9 +125,6 @@ subroutine add_executable_sources(sources,executables)
logical, allocatable :: exclude_source(:)
type(srcfile_t), allocatable :: dir_sources(:)
- character(:), allocatable :: basename
- character(:), allocatable :: file_parts(:)
-
call get_executable_source_dirs(exe_dirs,executables)
do i=1,size(exe_dirs)
@@ -147,12 +138,10 @@ subroutine add_executable_sources(sources,executables)
! Only allow executables in 'executables' list
exclude_source(i) = (dir_sources(i)%unit_type == FPM_UNIT_PROGRAM)
-
- call split(dir_sources(i)%file_name,file_parts,delimiters='\/')
- basename = file_parts(size(file_parts))
do j=1,size(executables)
- if (executables(j)%main == basename) then
+ if (basename(dir_sources(i)%file_name,suffix=.true.) == &
+ executables(j)%main) then
exclude_source(i) = .false.
dir_sources(i)%exe_name = executables(j)%name
exit