diff options
author | LKedward <laurence.kedward@bristol.ac.uk> | 2020-09-08 11:58:16 +0100 |
---|---|---|
committer | LKedward <laurence.kedward@bristol.ac.uk> | 2020-09-08 11:58:16 +0100 |
commit | fd49a2e6ee374d06206bd0ae47fce92c6339ea5d (patch) | |
tree | d7a9195d68af6b52ec1d98f671b4123f28af3a00 | |
parent | 8c8e4e9ec834c4a08078eb82a685fc001baa89aa (diff) | |
download | fpm-fd49a2e6ee374d06206bd0ae47fce92c6339ea5d.tar.gz fpm-fd49a2e6ee374d06206bd0ae47fce92c6339ea5d.zip |
Updates: for improved readability
Adds string_array_contains helper function for determining if array of string_t contains a particular string.
-rw-r--r-- | fpm/src/fpm.f90 | 3 | ||||
-rw-r--r-- | fpm/src/fpm_filesystem.f90 | 10 | ||||
-rw-r--r-- | fpm/src/fpm_sources.f90 | 9 | ||||
-rw-r--r-- | fpm/src/fpm_strings.f90 | 19 |
4 files changed, 30 insertions, 11 deletions
diff --git a/fpm/src/fpm.f90 b/fpm/src/fpm.f90 index 1bd4c7f..69fe155 100644 --- a/fpm/src/fpm.f90 +++ b/fpm/src/fpm.f90 @@ -22,9 +22,6 @@ type(fpm_build_settings), intent(in) :: settings type(package_t) :: package type(fpm_model_t) :: model type(error_t), allocatable :: error -type(string_t), allocatable :: files(:) -character(:), allocatable :: basename, linking -integer :: i, n call get_package_data(package, "fpm.toml", error) if (allocated(error)) then print '(a)', error%message diff --git a/fpm/src/fpm_filesystem.f90 b/fpm/src/fpm_filesystem.f90 index 297278b..d5c8e67 100644 --- a/fpm/src/fpm_filesystem.f90 +++ b/fpm/src/fpm_filesystem.f90 @@ -218,11 +218,15 @@ function windows_path(path) result(winpath) ! character(*), intent(in) :: path character(:), allocatable :: winpath - + + integer :: idx + winpath = path - do while(index(winpath,'/') > 0) - winpath(index(winpath,'/'):index(winpath,'/')) = '\' + idx = index(winpath,'/') + do while(idx > 0) + winpath(idx:idx) = '\' + idx = index(winpath,'/') end do end function windows_path diff --git a/fpm/src/fpm_sources.f90 b/fpm/src/fpm_sources.f90 index 99652e7..b84e31d 100644 --- a/fpm/src/fpm_sources.f90 +++ b/fpm/src/fpm_sources.f90 @@ -1,6 +1,6 @@ module fpm_sources use fpm_filesystem, only: basename, read_lines, list_files -use fpm_strings, only: lower, split, str_ends_with, string_t +use fpm_strings, only: lower, split, str_ends_with, string_t, operator(.in.) use fpm_manifest_executable, only: executable_t implicit none @@ -97,7 +97,7 @@ subroutine add_sources_from_dir(sources,directory,with_executables) ! Exclude executables unless specified otherwise exclude_source(i) = (dir_sources(i)%unit_type == FPM_UNIT_PROGRAM) if (dir_sources(i)%unit_type == FPM_UNIT_PROGRAM .and. & - present(with_executables)) then + & present(with_executables)) then if (with_executables) then exclude_source(i) = .false. @@ -174,12 +174,11 @@ subroutine get_executable_source_dirs(exe_dirs,executables) type(string_t) :: dirs_temp(size(executables)) - integer :: i, j, n + integer :: i, n n = 0 do i=1,size(executables) - if (.not.any([(dirs_temp(j)%s==executables(i)%source_dir, & - j=1,n)])) then + if (.not.(executables(i)%source_dir .in. dirs_temp)) then n = n + 1 dirs_temp(n)%s = executables(i)%source_dir diff --git a/fpm/src/fpm_strings.f90 b/fpm/src/fpm_strings.f90 index dd18f09..a6511c9 100644 --- a/fpm/src/fpm_strings.f90 +++ b/fpm/src/fpm_strings.f90 @@ -3,11 +3,16 @@ implicit none private public :: f_string, lower, split, str_ends_with, string_t +public :: string_array_contains, operator(.in.) type string_t character(len=:), allocatable :: s end type +interface operator(.in.) + module procedure string_array_contains +end interface + contains logical function str_ends_with(s, e) result(r) @@ -76,6 +81,20 @@ elemental pure function lower(str,begin,end) result (string) end function lower +logical function string_array_contains(search_string,array) + ! Check if array of string_t contains a particular string + ! + character(*), intent(in) :: search_string + type(string_t), intent(in) :: array(:) + + integer :: i + + string_array_contains = any([(array(i)%s==search_string, & + i=1,size(array))]) + +end function string_array_contains + + subroutine split(input_line,array,delimiters,order,nulls) ! parse string on delimiter characters and store tokens into an allocatable array" ! Author: John S. Urban |