From 99543aead461ed0a9bc6671eadb02ec30a327202 Mon Sep 17 00:00:00 2001 From: Federico Perini Date: Sat, 13 Jan 2024 16:04:08 +0100 Subject: [PATCH] add custom source extension capability to `preprocess` support preprocessor suffixes fix for allocatable string replace function wiht subroutine fix allocations check present use macros only if allocated --- ci/run_tests.sh | 4 + .../preprocess_cpp_suffix/.gitignore | 1 + .../preprocess_cpp_suffix/app/main.f90 | 8 ++ .../preprocess_cpp_suffix/fpm.toml | 7 ++ .../src/preprocess_cpp.fpp | 22 ++++++ src/fpm.f90 | 38 ++++------ src/fpm/manifest/preprocess.f90 | 74 +++++++++++++++++++ src/fpm_model.f90 | 3 +- src/fpm_sources.f90 | 56 +++++++++++--- src/fpm_strings.f90 | 18 +++++ src/fpm_targets.f90 | 15 ++-- 11 files changed, 206 insertions(+), 40 deletions(-) create mode 100644 example_packages/preprocess_cpp_suffix/.gitignore create mode 100644 example_packages/preprocess_cpp_suffix/app/main.f90 create mode 100644 example_packages/preprocess_cpp_suffix/fpm.toml create mode 100644 example_packages/preprocess_cpp_suffix/src/preprocess_cpp.fpp diff --git a/ci/run_tests.sh b/ci/run_tests.sh index d84a00f1c5..c31f134312 100755 --- a/ci/run_tests.sh +++ b/ci/run_tests.sh @@ -150,6 +150,10 @@ pushd preprocess_cpp_deps "$fpm" build popd +pushd preprocess_cpp_suffix +"$fpm" run +popd + pushd preprocess_per_dependency "$fpm" run popd diff --git a/example_packages/preprocess_cpp_suffix/.gitignore b/example_packages/preprocess_cpp_suffix/.gitignore new file mode 100644 index 0000000000..a007feab07 --- /dev/null +++ b/example_packages/preprocess_cpp_suffix/.gitignore @@ -0,0 +1 @@ +build/* diff --git a/example_packages/preprocess_cpp_suffix/app/main.f90 b/example_packages/preprocess_cpp_suffix/app/main.f90 new file mode 100644 index 0000000000..7d77b56a06 --- /dev/null +++ b/example_packages/preprocess_cpp_suffix/app/main.f90 @@ -0,0 +1,8 @@ +program test_preprocess_suffix + use preprocess_cpp +#ifndef TESTMACRO + stop -1 +#else + stop 0 +#endif +end program test_preprocess_suffix diff --git a/example_packages/preprocess_cpp_suffix/fpm.toml b/example_packages/preprocess_cpp_suffix/fpm.toml new file mode 100644 index 0000000000..6399f1a67d --- /dev/null +++ b/example_packages/preprocess_cpp_suffix/fpm.toml @@ -0,0 +1,7 @@ +name = "preprocess_cpp_suffix" +version = "1" + +[preprocess] +[preprocess.cpp] +macros = ["TESTMACRO", "TESTMACRO2=3", "TESTMACRO3={version}"] +suffixes = ["fpp"] diff --git a/example_packages/preprocess_cpp_suffix/src/preprocess_cpp.fpp b/example_packages/preprocess_cpp_suffix/src/preprocess_cpp.fpp new file mode 100644 index 0000000000..d7ab5d1485 --- /dev/null +++ b/example_packages/preprocess_cpp_suffix/src/preprocess_cpp.fpp @@ -0,0 +1,22 @@ +module preprocess_cpp + implicit none + private + + public :: say_hello +contains + subroutine say_hello + print *, "Hello, preprocess_cpp!" +#ifndef TESTMACRO + This breaks the build. +#endif + +#if TESTMACRO2 != 3 + This breaks the build. +#endif + +#if TESTMACRO3 != 1 + This breaks the build. +#endif + + end subroutine say_hello +end module preprocess_cpp diff --git a/src/fpm.f90 b/src/fpm.f90 index 0a2712e612..bb2972bd9e 100644 --- a/src/fpm.f90 +++ b/src/fpm.f90 @@ -110,37 +110,23 @@ subroutine build_model(model, settings, package, error) model%packages(i)%version = package%version%s() !> Add this dependency's manifest macros - allocate(model%packages(i)%macros(0)) + call model%packages(i)%preprocess%destroy() if (allocated(dependency%preprocess)) then do j = 1, size(dependency%preprocess) - if (dependency%preprocess(j)%name == "cpp") then - if (.not. has_cpp) has_cpp = .true. - if (allocated(dependency%preprocess(j)%macros)) then - model%packages(i)%macros = [model%packages(i)%macros, dependency%preprocess(j)%macros] - end if - else - write(stderr, '(a)') 'Warning: Preprocessor ' // package%preprocess(i)%name // & - ' is not supported; will ignore it' - end if + call model%packages(i)%preprocess%add_config(dependency%preprocess(j)) end do end if !> Add this dependency's package-level macros if (allocated(dep%preprocess)) then do j = 1, size(dep%preprocess) - if (dep%preprocess(j)%name == "cpp") then - if (.not. has_cpp) has_cpp = .true. - if (allocated(dep%preprocess(j)%macros)) then - model%packages(i)%macros = [model%packages(i)%macros, dep%preprocess(j)%macros] - end if - else - write(stderr, '(a)') 'Warning: Preprocessor ' // package%preprocess(i)%name // & - ' is not supported; will ignore it' - end if + call model%packages(i)%preprocess%add_config(dep%preprocess(j)) end do end if + if (model%packages(i)%preprocess%is_cpp()) has_cpp = .true. + if (.not.allocated(model%packages(i)%sources)) allocate(model%packages(i)%sources(0)) if (allocated(dependency%library)) then @@ -149,7 +135,7 @@ subroutine build_model(model, settings, package, error) lib_dir = join_path(dep%proj_dir, dependency%library%source_dir) if (is_dir(lib_dir)) then call add_sources_from_dir(model%packages(i)%sources, lib_dir, FPM_SCOPE_LIB, & - error=error) + with_f_ext=model%packages(i)%preprocess%suffixes, error=error) if (allocated(error)) exit end if end if @@ -187,7 +173,8 @@ subroutine build_model(model, settings, package, error) ! Add sources from executable directories if (is_dir('app') .and. package%build%auto_executables) then call add_sources_from_dir(model%packages(1)%sources,'app', FPM_SCOPE_APP, & - with_executables=.true., error=error) + with_executables=.true., with_f_ext=model%packages(1)%preprocess%suffixes,& + error=error) if (allocated(error)) then return @@ -196,7 +183,8 @@ subroutine build_model(model, settings, package, error) end if if (is_dir('example') .and. package%build%auto_examples) then call add_sources_from_dir(model%packages(1)%sources,'example', FPM_SCOPE_EXAMPLE, & - with_executables=.true., error=error) + with_executables=.true., & + with_f_ext=model%packages(1)%preprocess%suffixes,error=error) if (allocated(error)) then return @@ -205,7 +193,8 @@ subroutine build_model(model, settings, package, error) end if if (is_dir('test') .and. package%build%auto_tests) then call add_sources_from_dir(model%packages(1)%sources,'test', FPM_SCOPE_TEST, & - with_executables=.true., error=error) + with_executables=.true., & + with_f_ext=model%packages(1)%preprocess%suffixes,error=error) if (allocated(error)) then return @@ -215,6 +204,7 @@ subroutine build_model(model, settings, package, error) if (allocated(package%executable)) then call add_executable_sources(model%packages(1)%sources, package%executable, FPM_SCOPE_APP, & auto_discover=package%build%auto_executables, & + with_f_ext=model%packages(1)%preprocess%suffixes, & error=error) if (allocated(error)) then @@ -225,6 +215,7 @@ subroutine build_model(model, settings, package, error) if (allocated(package%example)) then call add_executable_sources(model%packages(1)%sources, package%example, FPM_SCOPE_EXAMPLE, & auto_discover=package%build%auto_examples, & + with_f_ext=model%packages(1)%preprocess%suffixes, & error=error) if (allocated(error)) then @@ -235,6 +226,7 @@ subroutine build_model(model, settings, package, error) if (allocated(package%test)) then call add_executable_sources(model%packages(1)%sources, package%test, FPM_SCOPE_TEST, & auto_discover=package%build%auto_tests, & + with_f_ext=model%packages(1)%preprocess%suffixes, & error=error) if (allocated(error)) then diff --git a/src/fpm/manifest/preprocess.f90 b/src/fpm/manifest/preprocess.f90 index 3f9754725a..f7faff2a9c 100644 --- a/src/fpm/manifest/preprocess.f90 +++ b/src/fpm/manifest/preprocess.f90 @@ -14,6 +14,7 @@ module fpm_manifest_preprocess use fpm_error, only : error_t, syntax_error use fpm_strings, only : string_t use fpm_toml, only : toml_table, toml_key, toml_stat, get_value, get_list + use,intrinsic :: iso_fortran_env, only : stderr=>error_unit implicit none private @@ -39,6 +40,14 @@ module fpm_manifest_preprocess !> Print information on this instance procedure :: info + !> Operations + procedure :: destroy + procedure :: add_config + + !> Properties + procedure :: is_cpp + procedure :: is_fypp + end type preprocess_config_t interface operator(==) @@ -228,4 +237,69 @@ logical function preprocess_is_same(this,that) end function preprocess_is_same + !> Clean preprocessor structure + elemental subroutine destroy(this) + class(preprocess_config_t), intent(inout) :: this + + if (allocated(this%name))deallocate(this%name) + if (allocated(this%suffixes))deallocate(this%suffixes) + if (allocated(this%directories))deallocate(this%directories) + if (allocated(this%macros))deallocate(this%macros) + + end subroutine destroy + + !> Add preprocessor settings + subroutine add_config(this,that) + class(preprocess_config_t), intent(inout) :: this + type(preprocess_config_t), intent(in) :: that + + if (.not.that%name=="cpp") then + write(stderr, '(a)') 'Warning: Preprocessor ' // that%name // & + ' is not supported; will ignore it' + return + end if + + if (.not.allocated(this%name)) this%name = that%name + + ! Add macros + if (allocated(that%macros)) then + if (allocated(this%macros)) then + this%macros = [this%macros, that%macros] + else + allocate(this%macros, source = that%macros) + end if + endif + + ! Add suffixes + if (allocated(that%suffixes)) then + if (allocated(this%suffixes)) then + this%suffixes = [this%suffixes, that%suffixes] + else + allocate(this%suffixes, source = that%suffixes) + end if + endif + + ! Add directories + if (allocated(that%directories)) then + if (allocated(this%directories)) then + this%directories = [this%directories, that%directories] + else + allocate(this%directories, source = that%directories) + end if + endif + + end subroutine add_config + + ! Check cpp + logical function is_cpp(this) + class(preprocess_config_t), intent(in) :: this + is_cpp = this%name == "cpp" + end function is_cpp + + ! Check cpp + logical function is_fypp(this) + class(preprocess_config_t), intent(in) :: this + is_fypp = this%name == "fypp" + end function is_fypp + end module fpm_manifest_preprocess diff --git a/src/fpm_model.f90 b/src/fpm_model.f90 index dba15a8161..910498c2a2 100644 --- a/src/fpm_model.f90 +++ b/src/fpm_model.f90 @@ -39,6 +39,7 @@ module fpm_model use fpm_compiler, only: compiler_t, archiver_t, debug use fpm_dependency, only: dependency_tree_t use fpm_strings, only: string_t, str, len_trim +use fpm_manifest_preprocess, only: preprocess_config_t implicit none private @@ -137,7 +138,7 @@ module fpm_model type(srcfile_t), allocatable :: sources(:) !> List of macros. - type(string_t), allocatable :: macros(:) + type(preprocess_config_t) :: preprocess !> Package version number. character(:), allocatable :: version diff --git a/src/fpm_sources.f90 b/src/fpm_sources.f90 index 0165249f50..97c2feeb45 100644 --- a/src/fpm_sources.f90 +++ b/src/fpm_sources.f90 @@ -25,12 +25,16 @@ module fpm_sources !> Wrapper to source parsing routines. !> Selects parsing routine based on source file name extension -function parse_source(source_file_path,error) result(source) +function parse_source(source_file_path,custom_f_ext,error) result(source) character(*), intent(in) :: source_file_path + type(string_t), optional, intent(in) :: custom_f_ext(:) type(error_t), allocatable, intent(out) :: error type(srcfile_t) :: source + type(string_t), allocatable :: f_ext(:) - if (str_ends_with(lower(source_file_path), fortran_suffixes)) then + call list_fortran_suffixes(f_ext,custom_f_ext) + + if (str_ends_with(lower(source_file_path), f_ext)) then source = parse_f_source(source_file_path, error) @@ -42,7 +46,7 @@ function parse_source(source_file_path,error) result(source) source = parse_c_source(source_file_path,error) - end if + endif if (allocated(error)) then return @@ -50,8 +54,31 @@ function parse_source(source_file_path,error) result(source) end function parse_source +!> List fortran suffixes, including optional ones +subroutine list_fortran_suffixes(suffixes,with_f_ext) + type(string_t), allocatable, intent(out) :: suffixes(:) + !> Additional user-defined (preprocessor) extensions that should be treated as Fortran sources + type(string_t), intent(in), optional :: with_f_ext(:) + + integer :: ndefault,nuser,i + + ndefault = size(fortran_suffixes) + nuser = 0; if (present(with_f_ext)) nuser = size(with_f_ext) + + allocate(suffixes(ndefault + nuser)) + do i=1,ndefault + suffixes(i) = string_t(fortran_suffixes(i)) + end do + if (present(with_f_ext)) then + do i=1,nuser + suffixes(ndefault+1) = string_t(with_f_ext(i)%s) + end do + endif + +end subroutine list_fortran_suffixes + !> Add to `sources` by looking for source files in `directory` -subroutine add_sources_from_dir(sources,directory,scope,with_executables,recurse,error) +subroutine add_sources_from_dir(sources,directory,scope,with_executables,with_f_ext,recurse,error) !> List of `[[srcfile_t]]` objects to append to. Allocated if not allocated type(srcfile_t), allocatable, intent(inout), target :: sources(:) !> Directory in which to search for source files @@ -60,6 +87,8 @@ subroutine add_sources_from_dir(sources,directory,scope,with_executables,recurse integer, intent(in) :: scope !> Executable sources (fortran `program`s) are ignored unless `with_executables=.true.` logical, intent(in), optional :: with_executables + !> Additional user-defined (preprocessor) extensions that should be treated as Fortran sources + type(string_t), intent(in), optional :: with_f_ext(:) !> Whether to recursively search subdirectories, default is `.true.` logical, intent(in), optional :: recurse !> Error handling @@ -69,7 +98,7 @@ subroutine add_sources_from_dir(sources,directory,scope,with_executables,recurse logical, allocatable :: is_source(:), exclude_source(:) logical :: recurse_ type(string_t), allocatable :: file_names(:) - type(string_t), allocatable :: src_file_names(:) + type(string_t), allocatable :: src_file_names(:),f_ext(:) type(string_t), allocatable :: existing_src_files(:) type(srcfile_t), allocatable :: dir_sources(:) @@ -87,10 +116,15 @@ subroutine add_sources_from_dir(sources,directory,scope,with_executables,recurse allocate(existing_src_files(0)) end if + ! Get legal fortran suffixes + call list_fortran_suffixes(f_ext,with_f_ext) + 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), f_ext) .or. & str_ends_with(lower(file_names(i)%s), c_suffixes) ),i=1,size(file_names))] + + src_file_names = pack(file_names,is_source) allocate(dir_sources(size(src_file_names))) @@ -98,7 +132,7 @@ subroutine add_sources_from_dir(sources,directory,scope,with_executables,recurse do i = 1, size(src_file_names) - dir_sources(i) = parse_source(src_file_names(i)%s,error) + dir_sources(i) = parse_source(src_file_names(i)%s,with_f_ext,error) if (allocated(error)) return dir_sources(i)%unit_scope = scope @@ -129,7 +163,7 @@ end subroutine add_sources_from_dir !> Add to `sources` using the executable and test entries in the manifest and !> applies any executable-specific overrides such as `executable%name`. !> Adds all sources (including modules) from each `executable%source_dir` -subroutine add_executable_sources(sources,executables,scope,auto_discover,error) +subroutine add_executable_sources(sources,executables,scope,auto_discover,with_f_ext,error) !> List of `[[srcfile_t]]` objects to append to. Allocated if not allocated type(srcfile_t), allocatable, intent(inout), target :: sources(:) !> List of `[[executable_config_t]]` entries from manifest @@ -138,6 +172,8 @@ subroutine add_executable_sources(sources,executables,scope,auto_discover,error) integer, intent(in) :: scope !> If `.false.` only executables and tests specified in the manifest are added to `sources` logical, intent(in) :: auto_discover + !> Additional user-defined (preprocessor) extensions that should be treated as Fortran sources + type(string_t), intent(in), optional :: with_f_ext(:) !> Error handling type(error_t), allocatable, intent(out) :: error @@ -150,7 +186,7 @@ subroutine add_executable_sources(sources,executables,scope,auto_discover,error) do i=1,size(exe_dirs) call add_sources_from_dir(sources,exe_dirs(i)%s, scope, & - with_executables=auto_discover, recurse=.false., error=error) + with_executables=auto_discover, with_f_ext=with_f_ext,recurse=.false., error=error) if (allocated(error)) then return @@ -180,7 +216,7 @@ subroutine add_executable_sources(sources,executables,scope,auto_discover,error) ! Add if not already discovered (auto_discovery off) associate(exe => executables(i)) - exe_source = parse_source(join_path(exe%source_dir,exe%main),error) + exe_source = parse_source(join_path(exe%source_dir,exe%main),with_f_ext,error) exe_source%exe_name = exe%name if (allocated(exe%link)) then exe_source%link_libraries = exe%link diff --git a/src/fpm_strings.f90 b/src/fpm_strings.f90 index 55f57537e5..c3187db786 100644 --- a/src/fpm_strings.f90 +++ b/src/fpm_strings.f90 @@ -76,6 +76,7 @@ module fpm_strings interface str_ends_with procedure :: str_ends_with_str procedure :: str_ends_with_any + procedure :: str_ends_with_any_string end interface str_ends_with interface str @@ -122,6 +123,23 @@ pure logical function str_ends_with_any(s, e) result(r) end function str_ends_with_any +!> Test if a CHARACTER string ends with any of an array of string suffixs +pure logical function str_ends_with_any_string(s, e) result(r) + character(*), intent(in) :: s + type(string_t), intent(in) :: e(:) + + integer :: i + + r = .true. + do i=1,size(e) + + if (str_ends_with(s,trim(e(i)%s))) return + + end do + r = .false. + +end function str_ends_with_any_string + !> test if a CHARACTER string begins with a specified prefix pure logical function str_begins_with_str(s, e, case_sensitive) result(r) character(*), intent(in) :: s, e diff --git a/src/fpm_targets.f90 b/src/fpm_targets.f90 index df0d58810f..7c8c97b775 100644 --- a/src/fpm_targets.f90 +++ b/src/fpm_targets.f90 @@ -33,6 +33,7 @@ module fpm_targets use fpm_strings, only: string_t, operator(.in.), string_cat, fnv_1a, resize, lower, str_ends_with use fpm_compiler, only: get_macros use fpm_sources, only: get_exe_name_with_suffix +use fpm_manifest_preprocess, only: preprocess_config_t implicit none private @@ -233,7 +234,7 @@ subroutine build_target_list(targets,model) sources(i)%unit_type==FPM_UNIT_CSOURCE), & output_name = get_object_name(sources(i)), & features = model%packages(j)%features, & - macros = model%packages(j)%macros, & + preprocess = model%packages(j)%preprocess, & version = model%packages(j)%version) @@ -247,7 +248,7 @@ subroutine build_target_list(targets,model) call add_target(targets,package=model%packages(j)%name,source = sources(i), & type = FPM_TARGET_CPP_OBJECT, & output_name = get_object_name(sources(i)), & - macros = model%packages(j)%macros, & + preprocess = model%packages(j)%preprocess, & version = model%packages(j)%version) if (with_lib .and. sources(i)%unit_scope == FPM_SCOPE_LIB) then @@ -280,7 +281,7 @@ subroutine build_target_list(targets,model) output_name = get_object_name(sources(i)), & source = sources(i), & features = model%packages(j)%features, & - macros = model%packages(j)%macros & + preprocess = model%packages(j)%preprocess & ) if (sources(i)%unit_scope == FPM_SCOPE_APP) then @@ -413,7 +414,7 @@ end subroutine collect_exe_link_dependencies !> Allocate a new target and append to target list subroutine add_target(targets, package, type, output_name, source, link_libraries, & - & features, macros, version) + & features, preprocess, version) type(build_target_ptr), allocatable, intent(inout) :: targets(:) character(*), intent(in) :: package integer, intent(in) :: type @@ -421,7 +422,7 @@ subroutine add_target(targets, package, type, output_name, source, link_librarie type(srcfile_t), intent(in), optional :: source type(string_t), intent(in), optional :: link_libraries(:) type(fortran_features_t), intent(in), optional :: features - type(string_t), intent(in), optional :: macros(:) + type(preprocess_config_t), intent(in), optional :: preprocess character(*), intent(in), optional :: version integer :: i @@ -450,7 +451,9 @@ subroutine add_target(targets, package, type, output_name, source, link_librarie if (present(source)) new_target%source = source if (present(link_libraries)) new_target%link_libraries = link_libraries if (present(features)) new_target%features = features - if (present(macros)) new_target%macros = macros + if (present(preprocess)) then + if (allocated(preprocess%macros)) new_target%macros = preprocess%macros + endif if (present(version)) new_target%version = version allocate(new_target%dependencies(0))