aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorJoel <5474278+noisegul@users.noreply.github.com>2022-02-12 13:33:36 +0100
committerGitHub <noreply@github.com>2022-02-12 13:33:36 +0100
commit57b5636f5f573f06326fdecd24057a6297a53501 (patch)
tree865413a2144d94507067309dd43e6134495f27b7
parent68061db6f86951e9b3f3d553c54da728a9982dbd (diff)
downloadfpm-57b5636f5f573f06326fdecd24057a6297a53501.tar.gz
fpm-57b5636f5f573f06326fdecd24057a6297a53501.zip
Ignore hidden source files (#654)
* Add str_begins_with_str function * Add function to test if a single file is hidden * Exclude hidden files when finding source files
-rw-r--r--src/fpm_filesystem.F9012
-rw-r--r--src/fpm_sources.f909
-rw-r--r--src/fpm_strings.f9015
3 files changed, 30 insertions, 6 deletions
diff --git a/src/fpm_filesystem.F90 b/src/fpm_filesystem.F90
index 83cffe7..6837fef 100644
--- a/src/fpm_filesystem.F90
+++ b/src/fpm_filesystem.F90
@@ -6,7 +6,7 @@ module fpm_filesystem
OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_WINDOWS, &
OS_CYGWIN, OS_SOLARIS, OS_FREEBSD, OS_OPENBSD
use fpm_environment, only: separator, get_env
- use fpm_strings, only: f_string, replace, string_t, split, notabs
+ use fpm_strings, only: f_string, replace, string_t, split, notabs, str_begins_with_str
use iso_c_binding, only: c_char, c_ptr, c_int, c_null_char, c_associated, c_f_pointer
use fpm_error, only : fpm_stop
implicit none
@@ -14,6 +14,7 @@ module fpm_filesystem
public :: basename, canon_path, dirname, is_dir, join_path, number_of_rows, list_files, env_variable, &
mkdir, exists, get_temp_filename, windows_path, unix_path, getline, delete_file
public :: fileopen, fileclose, filewrite, warnwrite, parent_dir
+ public :: is_hidden_file
public :: read_lines, read_lines_expanded
public :: which
@@ -250,6 +251,15 @@ logical function is_dir(dir)
end function is_dir
+!> test if a file is hidden
+logical function is_hidden_file(file_basename) result(r)
+ character(*), intent(in) :: file_basename
+ if (len(file_basename) <= 2) then
+ r = .false.
+ else
+ r = str_begins_with_str(file_basename, '.')
+ end if
+end function is_hidden_file
!> Construct path by joining strings with os file separator
function join_path(a1,a2,a3,a4,a5) result(path)
diff --git a/src/fpm_sources.f90 b/src/fpm_sources.f90
index af2870f..05b9bc1 100644
--- a/src/fpm_sources.f90
+++ b/src/fpm_sources.f90
@@ -6,7 +6,7 @@
module fpm_sources
use fpm_error, only: error_t
use fpm_model, only: srcfile_t, FPM_UNIT_PROGRAM
-use fpm_filesystem, only: basename, canon_path, dirname, join_path, list_files
+use fpm_filesystem, only: basename, canon_path, dirname, join_path, list_files, is_hidden_file
use fpm_strings, only: lower, str_ends_with, string_t, operator(.in.)
use fpm_source_parsing, only: parse_f_source, parse_c_source
use fpm_manifest_executable, only: executable_config_t
@@ -81,9 +81,10 @@ subroutine add_sources_from_dir(sources,directory,scope,with_executables,recurse
allocate(existing_src_files(0))
end if
- is_source = [(.not.(canon_path(file_names(i)%s) .in. existing_src_files) .and. &
- (str_ends_with(lower(file_names(i)%s), fortran_suffixes) .or. &
- str_ends_with(lower(file_names(i)%s),[".c",".h"]) ),i=1,size(file_names))]
+ is_source = [(.not.(is_hidden_file(basename(file_names(i)%s))) .and. &
+ .not.(canon_path(file_names(i)%s) .in. existing_src_files) .and. &
+ (str_ends_with(lower(file_names(i)%s), fortran_suffixes) .or. &
+ str_ends_with(lower(file_names(i)%s),[".c",".h"]) ),i=1,size(file_names))]
src_file_names = pack(file_names,is_source)
allocate(dir_sources(size(src_file_names)))
diff --git a/src/fpm_strings.f90 b/src/fpm_strings.f90
index 4650ebd..aceb01a 100644
--- a/src/fpm_strings.f90
+++ b/src/fpm_strings.f90
@@ -39,7 +39,7 @@ use iso_c_binding, only: c_char, c_ptr, c_int, c_null_char, c_associated, c_f_po
implicit none
private
-public :: f_string, lower, split, str_ends_with, string_t
+public :: f_string, lower, split, str_ends_with, string_t, str_begins_with_str
public :: to_fortran_name, is_fortran_name
public :: string_array_contains, string_cat, len_trim, operator(.in.), fnv_1a
public :: replace, resize, str, join, glob
@@ -115,6 +115,19 @@ pure logical function str_ends_with_any(s, e) result(r)
end function str_ends_with_any
+!> test if a CHARACTER string begins with a specified prefix
+pure logical function str_begins_with_str(s, e) result(r)
+ character(*), intent(in) :: s, e
+ integer :: n1, n2
+ n1 = 1
+ n2 = 1 + len(e)-1
+ if (n2 > len(s)) then
+ r = .false.
+ else
+ r = (s(n1:n2) == e)
+ end if
+end function str_begins_with_str
+
!> return Fortran character variable when given a C-like array of
!! single characters terminated with a C_NULL_CHAR character
function f_string(c_string)