Skip to content

Commit fd49a2e

Browse files
committed
Updates: for improved readability
Adds string_array_contains helper function for determining if array of string_t contains a particular string.
1 parent 8c8e4e9 commit fd49a2e

File tree

4 files changed

+30
-11
lines changed

4 files changed

+30
-11
lines changed

fpm/src/fpm.f90

Lines changed: 0 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -22,9 +22,6 @@ subroutine cmd_build(settings)
2222
type(package_t) :: package
2323
type(fpm_model_t) :: model
2424
type(error_t), allocatable :: error
25-
type(string_t), allocatable :: files(:)
26-
character(:), allocatable :: basename, linking
27-
integer :: i, n
2825
call get_package_data(package, "fpm.toml", error)
2926
if (allocated(error)) then
3027
print '(a)', error%message

fpm/src/fpm_filesystem.f90

Lines changed: 7 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -218,11 +218,15 @@ function windows_path(path) result(winpath)
218218
!
219219
character(*), intent(in) :: path
220220
character(:), allocatable :: winpath
221-
221+
222+
integer :: idx
223+
222224
winpath = path
223225

224-
do while(index(winpath,'/') > 0)
225-
winpath(index(winpath,'/'):index(winpath,'/')) = '\'
226+
idx = index(winpath,'/')
227+
do while(idx > 0)
228+
winpath(idx:idx) = '\'
229+
idx = index(winpath,'/')
226230
end do
227231

228232
end function windows_path

fpm/src/fpm_sources.f90

Lines changed: 4 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,6 @@
11
module fpm_sources
22
use fpm_filesystem, only: basename, read_lines, list_files
3-
use fpm_strings, only: lower, split, str_ends_with, string_t
3+
use fpm_strings, only: lower, split, str_ends_with, string_t, operator(.in.)
44
use fpm_manifest_executable, only: executable_t
55
implicit none
66

@@ -97,7 +97,7 @@ subroutine add_sources_from_dir(sources,directory,with_executables)
9797
! Exclude executables unless specified otherwise
9898
exclude_source(i) = (dir_sources(i)%unit_type == FPM_UNIT_PROGRAM)
9999
if (dir_sources(i)%unit_type == FPM_UNIT_PROGRAM .and. &
100-
present(with_executables)) then
100+
& present(with_executables)) then
101101
if (with_executables) then
102102

103103
exclude_source(i) = .false.
@@ -174,12 +174,11 @@ subroutine get_executable_source_dirs(exe_dirs,executables)
174174

175175
type(string_t) :: dirs_temp(size(executables))
176176

177-
integer :: i, j, n
177+
integer :: i, n
178178

179179
n = 0
180180
do i=1,size(executables)
181-
if (.not.any([(dirs_temp(j)%s==executables(i)%source_dir, &
182-
j=1,n)])) then
181+
if (.not.(executables(i)%source_dir .in. dirs_temp)) then
183182

184183
n = n + 1
185184
dirs_temp(n)%s = executables(i)%source_dir

fpm/src/fpm_strings.f90

Lines changed: 19 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -3,11 +3,16 @@ module fpm_strings
33

44
private
55
public :: f_string, lower, split, str_ends_with, string_t
6+
public :: string_array_contains, operator(.in.)
67

78
type string_t
89
character(len=:), allocatable :: s
910
end type
1011

12+
interface operator(.in.)
13+
module procedure string_array_contains
14+
end interface
15+
1116
contains
1217

1318
logical function str_ends_with(s, e) result(r)
@@ -76,6 +81,20 @@ elemental pure function lower(str,begin,end) result (string)
7681
end function lower
7782

7883

84+
logical function string_array_contains(search_string,array)
85+
! Check if array of string_t contains a particular string
86+
!
87+
character(*), intent(in) :: search_string
88+
type(string_t), intent(in) :: array(:)
89+
90+
integer :: i
91+
92+
string_array_contains = any([(array(i)%s==search_string, &
93+
i=1,size(array))])
94+
95+
end function string_array_contains
96+
97+
7998
subroutine split(input_line,array,delimiters,order,nulls)
8099
! parse string on delimiter characters and store tokens into an allocatable array"
81100
! Author: John S. Urban

0 commit comments

Comments
 (0)