diff options
-rw-r--r-- | fpm/src/fpm.f90 | 2 | ||||
-rw-r--r-- | fpm/src/fpm_model.f90 | 148 | ||||
-rw-r--r-- | fpm/src/fpm_source_parsing.f90 | 452 | ||||
-rw-r--r-- | fpm/src/fpm_sources.f90 | 436 | ||||
-rw-r--r-- | fpm/src/fpm_targets.f90 | 76 | ||||
-rw-r--r-- | fpm/test/fpm_test/test_source_parsing.f90 | 2 |
6 files changed, 668 insertions, 448 deletions
diff --git a/fpm/src/fpm.f90 b/fpm/src/fpm.f90 index 67be1cc..33c566e 100644 --- a/fpm/src/fpm.f90 +++ b/fpm/src/fpm.f90 @@ -24,7 +24,7 @@ use,intrinsic :: iso_fortran_env, only : stdin=>input_unit, & use fpm_manifest_dependency, only: dependency_config_t implicit none private -public :: cmd_build, cmd_install, cmd_run +public :: build_model, cmd_build, cmd_install, cmd_run contains diff --git a/fpm/src/fpm_model.f90 b/fpm/src/fpm_model.f90 index 031af78..1b38d59 100644 --- a/fpm/src/fpm_model.f90 +++ b/fpm/src/fpm_model.f90 @@ -1,5 +1,30 @@ +!># The fpm package model +!> +!> Defines the fpm model data types which encapsulate all information +!> required to correctly build a package and its dependencies. +!> +!> The process (see `[[build_model(subroutine)]]`) for generating a valid `[[fpm_model]]` is as follows: +!> +!> 1. Source files are discovered ([[fpm_sources]]) and parsed ([[fpm_source_parsing]]) +!> 2. A list of build targets is generated (`[[targets_from_sources]]`) from the sources +!> 3. Inter-target dependencies are resolved (`[[resolve_module_dependencies]]`) based on modules used and provided +!> 4. Object link lists are generated for link targets (executables and libraries) (`[[resolve_target_linking]]`) +!> +!> Once a valid `[[fpm_model]]` has been constructed, it may be passed to `[[fpm_backend:build_package]]` to +!> build the package. +!> +!>### Enumerations +!> +!> __Source type:__ `FPM_UNIT_*` +!> Describes the type of source file — determines build target generation +!> +!> __Source scope:__ `FPM_SCOPE_*` +!> Describes the scoping rules for using modules — controls module dependency resolution +!> +!> __Target type:__ `FPM_TARGET_*` +!> Describes the type of build target — determines backend build rules +!> module fpm_model -! Definition and validation of the backend model use iso_fortran_env, only: int64 use fpm_strings, only: string_t implicit none @@ -14,101 +39,154 @@ public :: FPM_UNIT_UNKNOWN, FPM_UNIT_PROGRAM, FPM_UNIT_MODULE, & FPM_TARGET_UNKNOWN, FPM_TARGET_EXECUTABLE, FPM_TARGET_ARCHIVE, & FPM_TARGET_OBJECT +!> Source type unknown integer, parameter :: FPM_UNIT_UNKNOWN = -1 +!> Source type is fortran program integer, parameter :: FPM_UNIT_PROGRAM = 1 +!> Source type is fortran module integer, parameter :: FPM_UNIT_MODULE = 2 +!> Source type is fortran submodule integer, parameter :: FPM_UNIT_SUBMODULE = 3 +!> Source type is fortran subprogram integer, parameter :: FPM_UNIT_SUBPROGRAM = 4 +!> Source type is c source file integer, parameter :: FPM_UNIT_CSOURCE = 5 +!> Source type is c header file integer, parameter :: FPM_UNIT_CHEADER = 6 + +!> Source has no module-use scope integer, parameter :: FPM_SCOPE_UNKNOWN = -1 +!> Module-use scope is library/dependency modules only integer, parameter :: FPM_SCOPE_LIB = 1 +!> Module-use scope is library/dependency modules only integer, parameter :: FPM_SCOPE_DEP = 2 +!> Module-use scope is library/dependency and app modules integer, parameter :: FPM_SCOPE_APP = 3 +!> Module-use scope is library/dependency and test modules integer, parameter :: FPM_SCOPE_TEST = 4 + +!> Target type is unknown (ignored) integer, parameter :: FPM_TARGET_UNKNOWN = -1 +!> Target type is executable integer, parameter :: FPM_TARGET_EXECUTABLE = 1 +!> Target type is library archive integer, parameter :: FPM_TARGET_ARCHIVE = 2 +!> Target type is compiled object integer, parameter :: FPM_TARGET_OBJECT = 3 + +!> Type for describing a source file type srcfile_t - ! Type for encapsulating a source file - ! and it's metadata + !> File path relative to cwd character(:), allocatable :: file_name - ! File path relative to cwd + + !> Name of executable for FPM_UNIT_PROGRAM character(:), allocatable :: exe_name - ! Name of executable for FPM_UNIT_PROGRAM + + !> Target module-use scope integer :: unit_scope = FPM_SCOPE_UNKNOWN - ! app/test/lib/dependency - logical :: is_test = .false. - ! Is executable a test? + + !> Modules provided by this source file (lowerstring) type(string_t), allocatable :: modules_provided(:) - ! Modules provided by this source file (lowerstring) + + !> Type of source unit integer :: unit_type = FPM_UNIT_UNKNOWN - ! Type of program unit + + !> Modules USEd by this source file (lowerstring) type(string_t), allocatable :: modules_used(:) - ! Modules USEd by this source file (lowerstring) + + !> Files INCLUDEd by this source file type(string_t), allocatable :: include_dependencies(:) - ! Files INCLUDEd by this source file + + !> Native libraries to link against type(string_t), allocatable :: link_libraries(:) - ! Native libraries to link against + + !> Current hash integer(int64) :: digest - ! Current hash + end type srcfile_t + +!> Wrapper type for constructing arrays of `[[build_target_t]]` pointers type build_target_ptr - ! For constructing arrays of build_target_t pointers + type(build_target_t), pointer :: ptr => null() + end type build_target_ptr + +!> Type describing a generated build target type build_target_t + + !> File path of build target object relative to cwd character(:), allocatable :: output_file - ! File path of build target object relative to cwd + + !> Primary source for this build target type(srcfile_t), allocatable :: source - ! Primary source for this build target + + !> Resolved build dependencies type(build_target_ptr), allocatable :: dependencies(:) - ! Resolved build dependencies + + !> Target type integer :: target_type = FPM_TARGET_UNKNOWN + + !> Native libraries to link against type(string_t), allocatable :: link_libraries(:) - ! Native libraries to link against - type(string_t), allocatable :: link_objects(:) - ! Objects needed to link this target + !> Objects needed to link this target + type(string_t), allocatable :: link_objects(:) + + !> Flag set when first visited to check for circular dependencies logical :: touched = .false. - ! Flag set when first visited to check for circular dependencies + + !> Flag set if build target is sorted for building logical :: sorted = .false. - ! Flag set if build target is sorted for building + + !> Flag set if build target will be skipped (not built) logical :: skip = .false. - ! Flag set if build target will be skipped (not built) + !> Targets in the same schedule group are guaranteed to be independent integer :: schedule = -1 - ! Targets in the same schedule group are guaranteed to be independent + + !> Previous source file hash integer(int64), allocatable :: digest_cached - ! Previous hash end type build_target_t + +!> Type describing everything required to build a package +!> and its dependencies. type :: fpm_model_t + + !> Name of package character(:), allocatable :: package_name - ! Name of package + + !> Array of sources type(srcfile_t), allocatable :: sources(:) - ! Array of sources + + !> Array of targets with module-dependencies resolved type(build_target_ptr), allocatable :: targets(:) - ! Array of targets with module-dependencies resolved + + !> Command line name to invoke fortran compiler character(:), allocatable :: fortran_compiler - ! Command line name to invoke fortran compiler + + !> Command line flags passed to fortran for compilation character(:), allocatable :: fortran_compile_flags - ! Command line flags passed to fortran for compilation + + !> Command line flags pass for linking character(:), allocatable :: link_flags - ! Command line flags pass for linking + + !> Output file for library archive character(:), allocatable :: library_file - ! Output file for library archive + + !> Base directory for build character(:), allocatable :: output_directory - ! Base directory for build + + !> Native libraries to link against type(string_t), allocatable :: link_libraries(:) - ! Native libraries to link against + end type fpm_model_t end module fpm_model diff --git a/fpm/src/fpm_source_parsing.f90 b/fpm/src/fpm_source_parsing.f90 new file mode 100644 index 0000000..ea5b4f9 --- /dev/null +++ b/fpm/src/fpm_source_parsing.f90 @@ -0,0 +1,452 @@ +!># Parsing of package source files +!> +!> This module exposes two functions, `[[parse_f_source]]` and `[[parse_c_source]]`, +!> which perform a rudimentary parsing of fortran and c source files +!> in order to extract information required for module dependency tracking. +!> +!> Both functions additionally calculate and store a file digest (hash) which +!> is used by the backend ([[fpm_backend]]) to skip compilation of unmodified sources. +!> +!> Both functions return an instance of the [[srcfile_t]] type. +!> +!> For more information, please read the documentation for each function: +!> +!> - `[[parse_f_source]]` +!> - `[[parse_c_source]]` +!> +module fpm_source_parsing +use fpm_error, only: error_t, file_parse_error, fatal_error +use fpm_strings, only: string_t, split, lower, str_ends_with, fnv_1a +use fpm_model, only: srcfile_t, & + FPM_UNIT_UNKNOWN, FPM_UNIT_PROGRAM, FPM_UNIT_MODULE, & + FPM_UNIT_SUBMODULE, FPM_UNIT_SUBPROGRAM, & + FPM_UNIT_CSOURCE, FPM_UNIT_CHEADER, FPM_SCOPE_UNKNOWN, & + FPM_SCOPE_LIB, FPM_SCOPE_DEP, FPM_SCOPE_APP, FPM_SCOPE_TEST +use fpm_filesystem, only: read_lines +implicit none + +private +public :: parse_f_source, parse_c_source + +character(15), parameter :: INTRINSIC_MODULE_NAMES(*) = & + ['iso_c_binding ', & + 'iso_fortran_env', & + 'ieee_arithmetic', & + 'ieee_exceptions', & + 'ieee_features '] + +contains + +!> Parsing of free-form fortran source files +!> +!> The following statements are recognised and parsed: +!> +!> - `Module`/`submodule`/`program` declaration +!> - Module `use` statement +!> - `include` statement +!> +!> @note Intrinsic modules used by sources are not listed in +!> the `modules_used` field of source objects. +!> +!> @note Submodules are treated as normal modules which `use` their +!> corresponding parent modules. +!> +!>### Parsing limitations +!> +!> __Statements must not continued onto another line +!> except for an `only:` list in the `use` statement.__ +!> +!> This is supported: +!> +!>```fortran +!> use my_module, only: & +!> my_var, my_function, my_subroutine +!>``` +!> +!> This is __NOT supported:__ +!> +!>```fortran +!> use & +!> my_module +!>``` +!> +function parse_f_source(f_filename,error) result(f_source) + character(*), intent(in) :: f_filename + type(srcfile_t) :: f_source + type(error_t), allocatable, intent(out) :: error + + integer :: stat + integer :: fh, n_use, n_include, n_mod, i, j, ic, pass + type(string_t), allocatable :: file_lines(:) + character(:), allocatable :: temp_string, mod_name + + f_source%file_name = f_filename + + open(newunit=fh,file=f_filename,status='old') + file_lines = read_lines(fh) + close(fh) + + f_source%digest = fnv_1a(file_lines) + + do pass = 1,2 + n_use = 0 + n_include = 0 + n_mod = 0 + file_loop: do i=1,size(file_lines) + + ! Skip lines that are continued: not statements + if (i > 1) then + ic = index(file_lines(i-1)%s,'!') + if (ic < 1) then + ic = len(file_lines(i-1)%s) + end if + temp_string = trim(file_lines(i-1)%s(1:ic)) + if (len(temp_string) > 0 .and. index(temp_string,'&') == len(temp_string)) then + cycle + end if + end if + + ! Process 'USE' statements + if (index(adjustl(lower(file_lines(i)%s)),'use ') == 1 .or. & + index(adjustl(lower(file_lines(i)%s)),'use::') == 1) then + + if (index(file_lines(i)%s,'::') > 0) then + + temp_string = split_n(file_lines(i)%s,delims=':',n=2,stat=stat) + if (stat /= 0) then + call file_parse_error(error,f_filename, & + 'unable to find used module name',i, & + file_lines(i)%s,index(file_lines(i)%s,'::')) + return + end if + + mod_name = split_n(temp_string,delims=' ,',n=1,stat=stat) + if (stat /= 0) then + call file_parse_error(error,f_filename, & + 'unable to find used module name',i, & + file_lines(i)%s) + return + end if + mod_name = lower(mod_name) + + else + + mod_name = split_n(file_lines(i)%s,n=2,delims=' ,',stat=stat) + if (stat /= 0) then + call file_parse_error(error,f_filename, & + 'unable to find used module name',i, & + file_lines(i)%s) + return + end if + mod_name = lower(mod_name) + + end if + + if (.not.validate_name(mod_name)) then + cycle + end if + + if (any([(index(mod_name,trim(INTRINSIC_MODULE_NAMES(j)))>0, & + j=1,size(INTRINSIC_MODULE_NAMES))])) then + cycle + end if + + n_use = n_use + 1 + + if (pass == 2) then + + f_source%modules_used(n_use)%s = mod_name + + end if + + end if + + ! Process 'INCLUDE' statements + ic = index(adjustl(lower(file_lines(i)%s)),'include') + if ( ic == 1 ) then + ic = index(lower(file_lines(i)%s),'include') + if (index(adjustl(file_lines(i)%s(ic+7:)),'"') == 1 .or. & + index(adjustl(file_lines(i)%s(ic+7:)),"'") == 1 ) then + + + n_include = n_include + 1 + + if (pass == 2) then + f_source%include_dependencies(n_include)%s = & + & split_n(file_lines(i)%s,n=2,delims="'"//'"',stat=stat) + if (stat /= 0) then + call file_parse_error(error,f_filename, & + 'unable to find include file name',i, & + file_lines(i)%s) + return + end if + end if + end if + end if + + ! Extract name of module if is module + if (index(adjustl(lower(file_lines(i)%s)),'module ') == 1) then + + mod_name = lower(split_n(file_lines(i)%s,n=2,delims=' ',stat=stat)) + if (stat /= 0) then + call file_parse_error(error,f_filename, & + 'unable to find module name',i, & + file_lines(i)%s) + return + end if + + if (mod_name == 'procedure' .or. & + mod_name == 'subroutine' .or. & + mod_name == 'function') then + ! Ignore these cases + cycle + end if + + if (.not.validate_name(mod_name)) then + call file_parse_error(error,f_filename, & + 'empty or invalid name for module',i, & + file_lines(i)%s, index(file_lines(i)%s,mod_name)) + return + end if + + n_mod = n_mod + 1 + + if (pass == 2) then + f_source%modules_provided(n_mod) = string_t(mod_name) + end if + + f_source%unit_type = FPM_UNIT_MODULE + + end if + + ! Extract name of submodule if is submodule + if (index(adjustl(lower(file_lines(i)%s)),'submodule') == 1) then + + mod_name = split_n(file_lines(i)%s,n=3,delims='()',stat=stat) + if (stat /= 0) then + call file_parse_error(error,f_filename, & + 'unable to get submodule name',i, & + file_lines(i)%s) + return + end if + if (.not.validate_name(mod_name)) then + call file_parse_error(error,f_filename, & + 'empty or invalid name for submodule',i, & + file_lines(i)%s, index(file_lines(i)%s,mod_name)) + return + end if + + n_mod = n_mod + 1 + + temp_string = split_n(file_lines(i)%s,n=2,delims='()',stat=stat) + if (stat /= 0) then + call file_parse_error(error,f_filename, & + 'unable to get submodule ancestry',i, & + file_lines(i)%s) + return + end if + + f_source%unit_type = FPM_UNIT_SUBMODULE + + n_use = n_use + 1 + + if (pass == 2) then + + if (index(temp_string,':') > 0) then + + temp_string = temp_string(index(temp_string,':')+1:) + + end if + + if (.not.validate_name(temp_string)) then + call file_parse_error(error,f_filename, & + 'empty or invalid name for submodule parent',i, & + file_lines(i)%s, index(file_lines(i)%s,temp_string)) + return + end if + + f_source%modules_used(n_use)%s = lower(temp_string) + + f_source%modules_provided(n_mod)%s = lower(mod_name) + + end if + + end if + + ! Detect if contains a program + ! (no modules allowed after program def) + if (index(adjustl(lower(file_lines(i)%s)),'program') == 1) then + + f_source%unit_type = FPM_UNIT_PROGRAM + + end if + + end do file_loop + + ! Default to subprogram unit type + if (f_source%unit_type == FPM_UNIT_UNKNOWN) then + f_source%unit_type = FPM_UNIT_SUBPROGRAM + end if + + if (pass == 1) then + allocate(f_source%modules_used(n_use)) + allocate(f_source%include_dependencies(n_include)) + allocate(f_source%modules_provided(n_mod)) + end if + + end do + + contains + + function validate_name(name) result(valid) + character(*), intent(in) :: name + logical :: valid + + integer :: i + + if (len_trim(name) < 1) then + valid = .false. + return + end if + + if (lower(name(1:1)) < 'a' .or. & + lower(name(1:1)) > 'z') then + + valid = .false. + return + end if + + do i=1,len(name) + + if (.not.( & + (name(i:i) >= '0' .and. name(i:i) <= '9').or. & + (lower(name(i:i)) >= 'a' .and. lower(name(i:i)) <= 'z').or. & + name(i:i) == '_') ) then + + valid = .false. + return + end if + + end do + + valid = .true. + return + + end function validate_name + +end function parse_f_source + + +!> Parsing of c source files +!> +!> The following statements are recognised and parsed: +!> +!> - `#include` preprocessor statement +!> +function parse_c_source(c_filename,error) result(c_source) + character(*), intent(in) :: c_filename + type(srcfile_t) :: c_source + type(error_t), allocatable, intent(out) :: error + + integer :: fh, n_include, i, pass, stat + type(string_t), allocatable :: file_lines(:) + + c_source%file_name = c_filename + + if (str_ends_with(lower(c_filename), ".c")) then + + c_source%unit_type = FPM_UNIT_CSOURCE + + elseif (str_ends_with(lower(c_filename), ".h")) then + + c_source%unit_type = FPM_UNIT_CHEADER + + end if + + allocate(c_source%modules_used(0)) + allocate(c_source%modules_provided(0)) + + open(newunit=fh,file=c_filename,status='old') + file_lines = read_lines(fh) + close(fh) + + c_source%digest = fnv_1a(file_lines) + + do pass = 1,2 + n_include = 0 + file_loop: do i=1,size(file_lines) + + ! Process 'INCLUDE' statements + if (index(adjustl(lower(file_lines(i)%s)),'#include') == 1 .and. & + index(file_lines(i)%s,'"') > 0) then + + n_include = n_include + 1 + + if (pass == 2) then + + c_source%include_dependencies(n_include)%s = & + & split_n(file_lines(i)%s,n=2,delims='"',stat=stat) + if (stat /= 0) then + call file_parse_error(error,c_filename, & + 'unable to get c include file',i, & + file_lines(i)%s,index(file_lines(i)%s,'"')) + return + end if + + end if + + end if + + end do file_loop + + if (pass == 1) then + allocate(c_source%include_dependencies(n_include)) + end if + + end do + +end function parse_c_source + +!> Split a string on one or more delimeters +!> and return the nth substring if it exists +!> +!> n=0 will return the last item +!> n=-1 will return the penultimate item etc. +!> +!> stat = 1 on return if the index +!> is not found +!> +function split_n(string,delims,n,stat) result(substring) + + character(*), intent(in) :: string + character(*), intent(in) :: delims + integer, intent(in) :: n + integer, intent(out) :: stat + character(:), allocatable :: substring + + integer :: i + character(:), allocatable :: string_parts(:) + + call split(string,string_parts,delims) + + if (n<1) then + i = size(string_parts) + n + if (i < 1) then + stat = 1 + return + end if + else + i = n + end if + + if (i>size(string_parts)) then + stat = 1 + return + end if + + substring = trim(adjustl(string_parts(i))) + stat = 0 + +end function split_n + +end module fpm_source_parsing
\ No newline at end of file diff --git a/fpm/src/fpm_sources.f90 b/fpm/src/fpm_sources.f90 index 5e78d6e..de2df1c 100644 --- a/fpm/src/fpm_sources.f90 +++ b/fpm/src/fpm_sources.f90 @@ -1,29 +1,24 @@ +!># Discovery of sources +!> +!> This module implements subroutines for building a list of +!> `[[srcfile_t]]` objects by looking for source files in the filesystem. +!> module fpm_sources -use fpm_error, only: error_t, file_parse_error, fatal_error -use fpm_model, only: srcfile_t, fpm_model_t, & - FPM_UNIT_UNKNOWN, FPM_UNIT_PROGRAM, FPM_UNIT_MODULE, & - FPM_UNIT_SUBMODULE, FPM_UNIT_SUBPROGRAM, & - FPM_UNIT_CSOURCE, FPM_UNIT_CHEADER, FPM_SCOPE_UNKNOWN, & - FPM_SCOPE_LIB, FPM_SCOPE_DEP, FPM_SCOPE_APP, FPM_SCOPE_TEST - -use fpm_filesystem, only: basename, canon_path, dirname, join_path, read_lines, list_files -use fpm_strings, only: lower, split, str_ends_with, string_t, operator(.in.), fnv_1a +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_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 implicit none private public :: add_sources_from_dir, add_executable_sources -public :: parse_f_source, parse_c_source - -character(15), parameter :: INTRINSIC_MODULE_NAMES(*) = & - ['iso_c_binding ', & - 'iso_fortran_env', & - 'ieee_arithmetic', & - 'ieee_exceptions', & - 'ieee_features '] contains +!> Wrapper to source parsing routines. +!> Selects parsing routine based on source file name extension function parse_source(source_file_path,error) result(source) character(*), intent(in) :: source_file_path type(error_t), allocatable, intent(out) :: error @@ -50,15 +45,19 @@ function parse_source(source_file_path,error) result(source) end function parse_source - +!> Add to `sources` by looking for source files in `directory` subroutine add_sources_from_dir(sources,directory,scope,with_executables,recurse,error) - ! Enumerate sources in a directory - ! + !> 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 character(*), intent(in) :: directory + !> Scope to apply to the discovered sources, see [[fpm_model]] for enumeration integer, intent(in) :: scope + !> Executable sources (fortran `program`s) are ignored unless `with_executables=.true.` logical, intent(in), optional :: with_executables + !> Whether to recursively search subdirectories, default is `.true.` logical, intent(in), optional :: recurse + !> Error handling type(error_t), allocatable, intent(out) :: error integer :: i @@ -118,14 +117,19 @@ subroutine add_sources_from_dir(sources,directory,scope,with_executables,recurse 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) - ! Include sources from any directories specified - ! in [[executable]] entries and apply any customisations - ! + !> 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 class(executable_config_t), intent(in) :: executables(:) + !> Scope to apply to the discovered sources: either `FPM_SCOPE_APP` or `FPM_SCOPE_TEST`, see [[fpm_model]] integer, intent(in) :: scope + !> If `.false.` only executables and tests specified in the manifest are added to `sources` logical, intent(in) :: auto_discover + !> Error handling type(error_t), allocatable, intent(out) :: error integer :: i, j @@ -184,10 +188,9 @@ subroutine add_executable_sources(sources,executables,scope,auto_discover,error) end subroutine add_executable_sources - +!> Build a list of unique source directories +!> from executables specified in manifest subroutine get_executable_source_dirs(exe_dirs,executables) - ! Build a list of unique source directories - ! from executables specified in manifest type(string_t), allocatable, intent(inout) :: exe_dirs(:) class(executable_config_t), intent(in) :: executables(:) @@ -213,385 +216,4 @@ subroutine get_executable_source_dirs(exe_dirs,executables) end subroutine get_executable_source_dirs - -function parse_f_source(f_filename,error) result(f_source) - ! Rudimentary scan of Fortran source file and - ! extract program unit name and use/include dependencies - ! - character(*), intent(in) :: f_filename - type(srcfile_t) :: f_source - type(error_t), allocatable, intent(out) :: error - - integer :: stat - integer :: fh, n_use, n_include, n_mod, i, j, ic, pass - type(string_t), allocatable :: file_lines(:) - character(:), allocatable :: temp_string, mod_name - - f_source%file_name = f_filename - - open(newunit=fh,file=f_filename,status='old') - file_lines = read_lines(fh) - close(fh) - - f_source%digest = fnv_1a(file_lines) - - do pass = 1,2 - n_use = 0 - n_include = 0 - n_mod = 0 - file_loop: do i=1,size(file_lines) - - ! Skip lines that are continued: not statements - if (i > 1) then - ic = index(file_lines(i-1)%s,'!') - if (ic < 1) then - ic = len(file_lines(i-1)%s) - end if - temp_string = trim(file_lines(i-1)%s(1:ic)) - if (len(temp_string) > 0 .and. index(temp_string,'&') == len(temp_string)) then - cycle - end if - end if - - ! Process 'USE' statements - if (index(adjustl(lower(file_lines(i)%s)),'use ') == 1 .or. & - index(adjustl(lower(file_lines(i)%s)),'use::') == 1) then - - if (index(file_lines(i)%s,'::') > 0) then - - temp_string = split_n(file_lines(i)%s,delims=':',n=2,stat=stat) - if (stat /= 0) then - call file_parse_error(error,f_filename, & - 'unable to find used module name',i, & - file_lines(i)%s,index(file_lines(i)%s,'::')) - return - end if - - mod_name = split_n(temp_string,delims=' ,',n=1,stat=stat) - if (stat /= 0) then - call file_parse_error(error,f_filename, & - 'unable to find used module name',i, & - file_lines(i)%s) - return - end if - mod_name = lower(mod_name) - - else - - mod_name = split_n(file_lines(i)%s,n=2,delims=' ,',stat=stat) - if (stat /= 0) then - call file_parse_error(error,f_filename, & - 'unable to find used module name',i, & - file_lines(i)%s) - return - end if - mod_name = lower(mod_name) - - end if - - if (.not.validate_name(mod_name)) then - cycle - end if - - if (any([(index(mod_name,trim(INTRINSIC_MODULE_NAMES(j)))>0, & - j=1,size(INTRINSIC_MODULE_NAMES))])) then - cycle - end if - - n_use = n_use + 1 - - if (pass == 2) then - - f_source%modules_used(n_use)%s = mod_name - - end if - - end if - - ! Process 'INCLUDE' statements - ic = index(adjustl(lower(file_lines(i)%s)),'include') - if ( ic == 1 ) then - ic = index(lower(file_lines(i)%s),'include') - if (index(adjustl(file_lines(i)%s(ic+7:)),'"') == 1 .or. & - index(adjustl(file_lines(i)%s(ic+7:)),"'") == 1 ) then - - - n_include = n_include + 1 - - if (pass == 2) then - f_source%include_dependencies(n_include)%s = & - & split_n(file_lines(i)%s,n=2,delims="'"//'"',stat=stat) - if (stat /= 0) then - call file_parse_error(error,f_filename, & - 'unable to find include file name',i, & - file_lines(i)%s) - return - end if - end if - end if - end if - - ! Extract name of module if is module - if (index(adjustl(lower(file_lines(i)%s)),'module ') == 1) then - - mod_name = lower(split_n(file_lines(i)%s,n=2,delims=' ',stat=stat)) - if (stat /= 0) then - call file_parse_error(error,f_filename, & - 'unable to find module name',i, & - file_lines(i)%s) - return - end if - - if (mod_name == 'procedure' .or. & - mod_name == 'subroutine' .or. & - mod_name == 'function') then - ! Ignore these cases - cycle - end if - - if (.not.validate_name(mod_name)) then - call file_parse_error(error,f_filename, & - 'empty or invalid name for module',i, & - file_lines(i)%s, index(file_lines(i)%s,mod_name)) - return - end if - - n_mod = n_mod + 1 - - if (pass == 2) then - f_source%modules_provided(n_mod) = string_t(mod_name) - end if - - f_source%unit_type = FPM_UNIT_MODULE - - end if - - ! Extract name of submodule if is submodule - if (index(adjustl(lower(file_lines(i)%s)),'submodule') == 1) then - - mod_name = split_n(file_lines(i)%s,n=3,delims='()',stat=stat) - if (stat /= 0) then - call file_parse_error(error,f_filename, & - 'unable to get submodule name',i, & - file_lines(i)%s) - return - end if - if (.not.validate_name(mod_name)) then - call file_parse_error(error,f_filename, & - 'empty or invalid name for submodule',i, & - file_lines(i)%s, index(file_lines(i)%s,mod_name)) - return - end if - - n_mod = n_mod + 1 - - temp_string = split_n(file_lines(i)%s,n=2,delims='()',stat=stat) - if (stat /= 0) then - call file_parse_error(error,f_filename, & - 'unable to get submodule ancestry',i, & - file_lines(i)%s) - return - end if - - f_source%unit_type = FPM_UNIT_SUBMODULE - - n_use = n_use + 1 - - if (pass == 2) then - - if (index(temp_string,':') > 0) then - - temp_string = temp_string(index(temp_string,':')+1:) - - end if - - if (.not.validate_name(temp_string)) then - call file_parse_error(error,f_filename, & - 'empty or invalid name for submodule parent',i, & - file_lines(i)%s, index(file_lines(i)%s,temp_string)) - return - end if - - f_source%modules_used(n_use)%s = lower(temp_string) - - f_source%modules_provided(n_mod)%s = lower(mod_name) - - end if - - end if - - ! Detect if contains a program - ! (no modules allowed after program def) - if (index(adjustl(lower(file_lines(i)%s)),'program') == 1) then - - f_source%unit_type = FPM_UNIT_PROGRAM - - end if - - end do file_loop - - ! Default to subprogram unit type - if (f_source%unit_type == FPM_UNIT_UNKNOWN) then - f_source%unit_type = FPM_UNIT_SUBPROGRAM - end if - - if (pass == 1) then - allocate(f_source%modules_used(n_use)) - allocate(f_source%include_dependencies(n_include)) - allocate(f_source%modules_provided(n_mod)) - end if - - end do - - contains - - function validate_name(name) result(valid) - character(*), intent(in) :: name - logical :: valid - - integer :: i - - if (len_trim(name) < 1) then - valid = .false. - return - end if - - if (lower(name(1:1)) < 'a' .or. & - lower(name(1:1)) > 'z') then - - valid = .false. - return - end if - - do i=1,len(name) - - if (.not.( & - (name(i:i) >= '0' .and. name(i:i) <= '9').or. & - (lower(name(i:i)) >= 'a' .and. lower(name(i:i)) <= 'z').or. & - name(i:i) == '_') ) then - - valid = .false. - return - end if - - end do - - valid = .true. - return - - end function validate_name - -end function parse_f_source - - -function parse_c_source(c_filename,error) result(c_source) - ! Rudimentary scan of c source file and - ! extract include dependencies - ! - character(*), intent(in) :: c_filename - type(srcfile_t) :: c_source - type(error_t), allocatable, intent(out) :: error - - integer :: fh, n_include, i, pass, stat - type(string_t), allocatable :: file_lines(:) - - c_source%file_name = c_filename - - if (str_ends_with(lower(c_filename), ".c")) then - - c_source%unit_type = FPM_UNIT_CSOURCE - - elseif (str_ends_with(lower(c_filename), ".h")) then - - c_source%unit_type = FPM_UNIT_CHEADER - - end if - - allocate(c_source%modules_used(0)) - allocate(c_source%modules_provided(0)) - - open(newunit=fh,file=c_filename,status='old') - file_lines = read_lines(fh) - close(fh) - - c_source%digest = fnv_1a(file_lines) - - do pass = 1,2 - n_include = 0 - file_loop: do i=1,size(file_lines) - - ! Process 'INCLUDE' statements - if (index(adjustl(lower(file_lines(i)%s)),'#include') == 1 .and. & - index(file_lines(i)%s,'"') > 0) then - - n_include = n_include + 1 - - if (pass == 2) then - - c_source%include_dependencies(n_include)%s = & - & split_n(file_lines(i)%s,n=2,delims='"',stat=stat) - if (stat /= 0) then - call file_parse_error(error,c_filename, & - 'unable to get c include file',i, & - file_lines(i)%s,index(file_lines(i)%s,'"')) - return - end if - - end if - - end if - - end do file_loop - - if (pass == 1) then - allocate(c_source%include_dependencies(n_include)) - end if - - end do - -end function parse_c_source - - -function split_n(string,delims,n,stat) result(substring) - ! Split a string on one or more delimeters - ! and return the nth substring if it exists - ! - ! n=0 will return the last item - ! n=-1 will return the penultimate item etc. - ! - ! stat = 1 on return if the index - ! is not found - ! - character(*), intent(in) :: string - character(*), intent(in) :: delims - integer, intent(in) :: n - integer, intent(out) :: stat - character(:), allocatable :: substring - - integer :: i - character(:), allocatable :: string_parts(:) - - call split(string,string_parts,delims) - - if (n<1) then - i = size(string_parts) + n - if (i < 1) then - stat = 1 - return - end if - else - i = n - end if - - if (i>size(string_parts)) then - stat = 1 - return - end if - - substring = trim(adjustl(string_parts(i))) - stat = 0 - -end function split_n - - end module fpm_sources diff --git a/fpm/src/fpm_targets.f90 b/fpm/src/fpm_targets.f90 index 03996f7..fe11e9d 100644 --- a/fpm/src/fpm_targets.f90 +++ b/fpm/src/fpm_targets.f90 @@ -1,3 +1,23 @@ +!># Build target handling +!> +!> This module handles the construction of the build target list +!> from the sources list (`[[targets_from_sources]]`), the +!> resolution of module-dependencies between build targets +!> (`[[resolve_module_dependencies]]`), and the enumeration of +!> objects required for link targets (`[[resolve_target_linking]]`). +!> +!> A build target (`[[build_target_t]]`) is a file to be generated +!> by the backend (compilation and linking). +!> +!> @note The current implementation is ignorant to the existence of +!> module files (`.mod`,`.smod`). Dependencies arising from modules +!> are based on the corresponding object files (`.o`) only. +!> +!> For more information, please read the documentation for the procedures: +!> +!> - `[[targets_from_sources]]` +!> - `[[resolve_module_dependencies]]` +!> module fpm_targets use fpm_error, only: error_t, fatal_error use fpm_model @@ -6,10 +26,39 @@ use fpm_filesystem, only: dirname, join_path, canon_path use fpm_strings, only: string_t, operator(.in.) implicit none +private +public targets_from_sources, resolve_module_dependencies +public resolve_target_linking, add_target, add_dependency + contains +!> Constructs a list of build targets from a list of source files +!> +!>### Source-target mapping +!> +!> One compiled object target (`FPM_TARGET_OBJECT`) is generated for each +!> non-executable source file (`FPM_UNIT_MODULE`,`FPM_UNIT_SUBMODULE`, +!> `FPM_UNIT_SUBPROGRAM`,`FPM_UNIT_CSOURCE`). +!> +!> If any source file has scope `FPM_SCOPE_LIB` (*i.e.* there are library sources) +!> then the first target in the target list will be a library archive target +!> (`FPM_TARGET_ARCHIVE`). The archive target will have a dependency on every +!> compiled object target corresponding to a library source file. +!> +!> One compiled object target (`FPM_TARGET_OBJECT`) and one executable target (`FPM_TARGET_EXECUTABLE`) is +!> generated for each exectuable source file (`FPM_UNIT_PROGRAM`). The exectuble target +!> always has a dependency on the corresponding compiled object target. If there +!> is a library, then the executable target has an additional dependency on the library +!> archive target. +!> +!> @note Inter-object dependencies based on modules used and provided are generated separately +!> in `[[resolve_module_dependencies]]` after all targets have been enumerated. subroutine targets_from_sources(model,sources) + + !> The package model within which to construct the target list type(fpm_model_t), intent(inout), target :: model + + !> The list of sources from which to construct the target list type(srcfile_t), intent(in) :: sources(:) integer :: i @@ -118,7 +167,7 @@ subroutine targets_from_sources(model,sources) end subroutine targets_from_sources -!> Add new target to target list +!> Allocate a new target and append to target list subroutine add_target(targets,type,output_file,source,link_libraries) type(build_target_ptr), allocatable, intent(inout) :: targets(:) integer, intent(in) :: type @@ -168,10 +217,29 @@ subroutine add_dependency(target, dependency) end subroutine add_dependency +!> Add dependencies to source-based targets (`FPM_TARGET_OBJECT`) +!> based on any modules used by the corresponding source file. +!> +!>### Source file scoping +!> +!> Source files are assigned a scope of either `FPM_SCOPE_LIB`, +!> `FPM_SCOPE_APP` or `FPM_SCOPE_TEST`. The scope controls which +!> modules may be used by the source file: +!> +!> - Library sources (`FPM_SCOPE_LIB`) may only use modules +!> also with library scope. This includes library modules +!> from dependencies. +!> +!> - Executable sources (`FPM_SCOPE_APP`,`FPM_SCOPE_TEST`) may use +!> library modules (including dependencies) as well as any modules +!> corresponding to source files __in the same directory__ as the +!> executable source. +!> +!> @warning If a module used by a source file cannot be resolved to +!> a source file in the package of the correct scope, then a __fatal error__ +!> is returned by the procedure and model construction fails. +!> subroutine resolve_module_dependencies(targets,error) - ! After enumerating all source files: resolve file dependencies - ! by searching on module names - ! type(build_target_ptr), intent(inout), target :: targets(:) type(error_t), allocatable, intent(out) :: error diff --git a/fpm/test/fpm_test/test_source_parsing.f90 b/fpm/test/fpm_test/test_source_parsing.f90 index d1d3e12..4463c07 100644 --- a/fpm/test/fpm_test/test_source_parsing.f90 +++ b/fpm/test/fpm_test/test_source_parsing.f90 @@ -2,7 +2,7 @@ module test_source_parsing use testsuite, only : new_unittest, unittest_t, error_t, test_failed use fpm_filesystem, only: get_temp_filename - use fpm_sources, only: parse_f_source, parse_c_source + use fpm_source_parsing, only: parse_f_source, parse_c_source use fpm_model, only: srcfile_t, FPM_UNIT_PROGRAM, FPM_UNIT_MODULE, & FPM_UNIT_SUBMODULE, FPM_UNIT_SUBPROGRAM, FPM_UNIT_CSOURCE use fpm_strings, only: operator(.in.) |