diff options
-rw-r--r-- | fpm/src/fpm.f90 | 1 | ||||
-rw-r--r-- | fpm/src/fpm/error.f90 | 8 | ||||
-rw-r--r-- | fpm/src/fpm/git.f90 | 4 | ||||
-rw-r--r-- | fpm/src/fpm/manifest/package.f90 | 4 | ||||
-rw-r--r-- | fpm/src/fpm_backend.f90 | 14 | ||||
-rw-r--r-- | fpm/src/fpm_filesystem.f90 | 32 | ||||
-rw-r--r-- | fpm/src/fpm_model.f90 | 2 | ||||
-rw-r--r-- | fpm/src/fpm_sources.f90 | 24 | ||||
-rw-r--r-- | fpm/src/fpm_strings.f90 | 8 | ||||
-rw-r--r-- | fpm/src/fpm_targets.f90 | 32 |
10 files changed, 65 insertions, 64 deletions
diff --git a/fpm/src/fpm.f90 b/fpm/src/fpm.f90 index 07bf483..aa9a4e6 100644 --- a/fpm/src/fpm.f90 +++ b/fpm/src/fpm.f90 @@ -25,6 +25,7 @@ public :: cmd_build, cmd_install, cmd_run contains + recursive subroutine add_libsources_from_package(sources,link_libraries,package_list,package, & package_root,dev_depends,error) ! Discover library sources in a package, recursively including dependencies diff --git a/fpm/src/fpm/error.f90 b/fpm/src/fpm/error.f90 index 2cfd964..e69ff1e 100644 --- a/fpm/src/fpm/error.f90 +++ b/fpm/src/fpm/error.f90 @@ -82,9 +82,9 @@ contains allocate(error) error%message = 'Parse error: '//message//new_line('a') - + error%message = error%message//file_name - + if (present(line_num)) then write(temp_string,'(I0)') line_num @@ -115,9 +115,9 @@ contains error%message = error%message//new_line('a') error%message = error%message//' | '//repeat(' ',line_col-1)//'^' - + end if - + end if end if diff --git a/fpm/src/fpm/git.f90 b/fpm/src/fpm/git.f90 index af4ae22..187b551 100644 --- a/fpm/src/fpm/git.f90 +++ b/fpm/src/fpm/git.f90 @@ -138,7 +138,7 @@ contains !> Error type(error_t), allocatable, intent(out) :: error - + !> git object ref character(:), allocatable :: object @@ -173,7 +173,7 @@ contains return end if - end subroutine checkout + end subroutine checkout !> Show information on git target diff --git a/fpm/src/fpm/manifest/package.f90 b/fpm/src/fpm/manifest/package.f90 index 7f2f91e..64b0f82 100644 --- a/fpm/src/fpm/manifest/package.f90 +++ b/fpm/src/fpm/manifest/package.f90 @@ -115,10 +115,10 @@ contains call new_build_config(self%build, child, error) if (allocated(error)) return - + call get_value(table, "version", version, "0") call new_version(self%version, version, error) - + if (allocated(error)) return call get_value(table, "dependencies", child, requested=.false.) diff --git a/fpm/src/fpm_backend.f90 b/fpm/src/fpm_backend.f90 index 632da64..b455398 100644 --- a/fpm/src/fpm_backend.f90 +++ b/fpm/src/fpm_backend.f90 @@ -8,7 +8,7 @@ use fpm_model, only: fpm_model_t, srcfile_t, build_target_t, FPM_UNIT_MODULE, & FPM_UNIT_SUBMODULE, FPM_UNIT_SUBPROGRAM, & FPM_UNIT_CSOURCE, FPM_UNIT_PROGRAM, & FPM_SCOPE_TEST, FPM_TARGET_OBJECT, FPM_TARGET_ARCHIVE, FPM_TARGET_EXECUTABLE - + use fpm_strings, only: split implicit none @@ -41,9 +41,9 @@ subroutine build_package(model) linking = linking//" "//model%link_flags do i=1,size(model%targets) - + call build_target(model,model%targets(i)%ptr,linking) - + end do end subroutine build_package @@ -52,7 +52,7 @@ end subroutine build_package recursive subroutine build_target(model,target,linking) ! Compile Fortran source, called recursively on it dependents - ! + ! type(fpm_model_t), intent(in) :: model type(build_target_t), intent(inout) :: target character(:), allocatable, intent(in) :: linking @@ -89,10 +89,10 @@ recursive subroutine build_target(model,target,linking) target%dependencies(i)%ptr%target_type == FPM_TARGET_OBJECT) then exe_obj => target%dependencies(i)%ptr - + ! Construct object list for executable objs = " "//exe_obj%output_file - + ! Include non-library object dependencies do j=1,size(exe_obj%dependencies) @@ -107,7 +107,7 @@ recursive subroutine build_target(model,target,linking) end if end do - + if (.not.exists(dirname(target%output_file))) then call mkdir(dirname(target%output_file)) end if diff --git a/fpm/src/fpm_filesystem.f90 b/fpm/src/fpm_filesystem.f90 index 52c9b58..77b22d1 100644 --- a/fpm/src/fpm_filesystem.f90 +++ b/fpm/src/fpm_filesystem.f90 @@ -52,7 +52,7 @@ function canon_path(path) result(canon) ! Canonicalize path for comparison ! Handles path string redundancies ! Does not test existence of path - ! + ! ! To be replaced by realpath/_fullname in stdlib_os ! character(*), intent(in) :: path @@ -106,7 +106,7 @@ function canon_path(path) result(canon) end if end if - + temp(j:j) = nixpath(i:i) j = j + 1 @@ -131,23 +131,23 @@ function dirname(path) result (dir) end function dirname -logical function is_dir(dir) - character(*), intent(in) :: dir - integer :: stat +logical function is_dir(dir) + character(*), intent(in) :: dir + integer :: stat - select case (get_os_type()) + select case (get_os_type()) case (OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_CYGWIN, OS_SOLARIS, OS_FREEBSD) - call execute_command_line("test -d " // dir , exitstat=stat) + call execute_command_line("test -d " // dir , exitstat=stat) - case (OS_WINDOWS) - call execute_command_line('cmd /c "if not exist ' // windows_path(dir) // '\ exit /B 1"', exitstat=stat) + case (OS_WINDOWS) + call execute_command_line('cmd /c "if not exist ' // windows_path(dir) // '\ exit /B 1"', exitstat=stat) - end select + end select - is_dir = (stat == 0) + is_dir = (stat == 0) -end function is_dir +end function is_dir function join_path(a1,a2,a3,a4,a5) result(path) @@ -294,7 +294,7 @@ recursive subroutine list_files(dir, files, recurse) do i=1,size(files) if (is_dir(files(i)%s)) then - call list_files(files(i)%s, dir_files, recurse=.true.) + call list_files(files(i)%s, dir_files, recurse=.true.) sub_dir_files = [sub_dir_files, dir_files] end if @@ -326,7 +326,7 @@ function get_temp_filename() result(tempfile) type(c_ptr) :: c_tempfile_ptr character(len=1), pointer :: c_tempfile(:) - + interface function c_tempnam(dir,pfx) result(tmp) bind(c,name="tempnam") @@ -368,7 +368,7 @@ function windows_path(path) result(winpath) winpath(idx:idx) = '\' idx = index(winpath,'/') end do - + end function windows_path @@ -387,7 +387,7 @@ function unix_path(path) result(nixpath) nixpath(idx:idx) = '/' idx = index(nixpath,'\') end do - + end function unix_path end module fpm_filesystem diff --git a/fpm/src/fpm_model.f90 b/fpm/src/fpm_model.f90 index 3f14125..20f174b 100644 --- a/fpm/src/fpm_model.f90 +++ b/fpm/src/fpm_model.f90 @@ -33,7 +33,7 @@ integer, parameter :: FPM_TARGET_ARCHIVE = 2 integer, parameter :: FPM_TARGET_OBJECT = 3 type srcfile_t - ! Type for encapsulating a source file + ! Type for encapsulating a source file ! and it's metadata character(:), allocatable :: file_name ! File path relative to cwd diff --git a/fpm/src/fpm_sources.f90 b/fpm/src/fpm_sources.f90 index 46d439c..5e42430 100644 --- a/fpm/src/fpm_sources.f90 +++ b/fpm/src/fpm_sources.f90 @@ -5,7 +5,7 @@ use fpm_model, only: srcfile_t, fpm_model_t, & 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.) use fpm_manifest_executable, only: executable_config_t @@ -119,9 +119,9 @@ end subroutine add_sources_from_dir subroutine add_executable_sources(sources,executables,scope,auto_discover,error) - ! Include sources from any directories specified + ! Include sources from any directories specified ! in [[executable]] entries and apply any customisations - ! + ! type(srcfile_t), allocatable, intent(inout), target :: sources(:) class(executable_config_t), intent(in) :: executables(:) integer, intent(in) :: scope @@ -153,7 +153,7 @@ subroutine add_executable_sources(sources,executables,scope,auto_discover,error) if (basename(sources(j)%file_name,suffix=.true.) == executables(i)%main .and.& canon_path(dirname(sources(j)%file_name)) == & canon_path(executables(i)%source_dir) ) then - + sources(j)%exe_name = executables(i)%name if (allocated(executables(i)%link)) then exe_source%link_libraries = executables(i)%link @@ -171,7 +171,7 @@ subroutine add_executable_sources(sources,executables,scope,auto_discover,error) exe_source%link_libraries = executables(i)%link end if exe_source%unit_scope = scope - + if (allocated(error)) return if (.not.allocated(sources)) then @@ -215,7 +215,7 @@ end subroutine get_executable_source_dirs function parse_f_source(f_filename,error) result(f_source) - ! Rudimentary scan of Fortran source file and + ! Rudimentary scan of Fortran source file and ! extract program unit name and use/include dependencies ! character(*), intent(in) :: f_filename @@ -313,7 +313,7 @@ function parse_f_source(f_filename,error) result(f_source) 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 @@ -400,7 +400,7 @@ function parse_f_source(f_filename,error) result(f_source) if (index(temp_string,':') > 0) then temp_string = temp_string(index(temp_string,':')+1:) - + end if if (.not.validate_name(temp_string)) then @@ -467,7 +467,7 @@ function parse_f_source(f_filename,error) result(f_source) (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 @@ -483,7 +483,7 @@ end function parse_f_source function parse_c_source(c_filename,error) result(c_source) - ! Rudimentary scan of c source file and + ! Rudimentary scan of c source file and ! extract include dependencies ! character(*), intent(in) :: c_filename @@ -519,7 +519,7 @@ function parse_c_source(c_filename,error) result(c_source) ! 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 @@ -555,7 +555,7 @@ function split_n(string,delims,n,stat) result(substring) ! n=0 will return the last item ! n=-1 will return the penultimate item etc. ! - ! stat = 1 on return if the index + ! stat = 1 on return if the index ! is not found ! character(*), intent(in) :: string diff --git a/fpm/src/fpm_strings.f90 b/fpm/src/fpm_strings.f90 index b94e80b..a6511c9 100644 --- a/fpm/src/fpm_strings.f90 +++ b/fpm/src/fpm_strings.f90 @@ -44,7 +44,7 @@ function f_string(c_string) do i=1,n f_string(i:i) = c_string(i) end do - + end function f_string @@ -100,7 +100,7 @@ subroutine split(input_line,array,delimiters,order,nulls) ! Author: John S. Urban ! License: Public Domain - + ! given a line of structure " par1 par2 par3 ... parn " store each par(n) into a separate variable in array. ! o by default adjacent delimiters in the input string do not create an empty string in the output array ! o no quoting of delimiters is supported @@ -109,7 +109,7 @@ subroutine split(input_line,array,delimiters,order,nulls) character(len=*),optional,intent(in) :: order ! order of output array sequential|[reverse|right] character(len=*),optional,intent(in) :: nulls ! return strings composed of delimiters or not ignore|return|ignoreend character(len=:),allocatable,intent(out) :: array(:) ! output array of tokens - + integer :: n ! max number of strings INPUT_LINE could split into if all delimiter integer,allocatable :: ibegin(:) ! positions in input string where tokens start integer,allocatable :: iterm(:) ! positions in input string where tokens end @@ -126,7 +126,7 @@ subroutine split(input_line,array,delimiters,order,nulls) integer :: inotnull ! count strings not composed of delimiters integer :: ireturn ! number of tokens returned integer :: imax ! length of longest token - + ! decide on value for optional DELIMITERS parameter if (present(delimiters)) then ! optional delimiter list was present if(delimiters.ne.'')then ! if DELIMITERS was specified and not null use it diff --git a/fpm/src/fpm_targets.f90 b/fpm/src/fpm_targets.f90 index 9a29431..c3a59fd 100644 --- a/fpm/src/fpm_targets.f90 +++ b/fpm/src/fpm_targets.f90 @@ -23,14 +23,14 @@ subroutine targets_from_sources(model,sources) model%package_name,'lib'//model%package_name//'.a')) do i=1,size(sources) - + select case (sources(i)%unit_type) case (FPM_UNIT_MODULE,FPM_UNIT_SUBMODULE,FPM_UNIT_SUBPROGRAM,FPM_UNIT_CSOURCE) call add_target(model%targets,source = sources(i), & type = FPM_TARGET_OBJECT,& output_file = get_object_name(sources(i))) - + if (with_lib .and. sources(i)%unit_scope == FPM_SCOPE_LIB) then ! Archive depends on object call add_dependency(model%targets(1)%ptr, model%targets(size(model%targets))%ptr) @@ -42,7 +42,7 @@ subroutine targets_from_sources(model,sources) output_file = get_object_name(sources(i)), & source = sources(i) & ) - + if (sources(i)%unit_scope == FPM_SCOPE_APP) then call add_target(model%targets,type = FPM_TARGET_EXECUTABLE,& link_libraries = sources(i)%link_libraries, & @@ -51,7 +51,7 @@ subroutine targets_from_sources(model,sources) call add_target(model%targets,type = FPM_TARGET_EXECUTABLE,& link_libraries = sources(i)%link_libraries, & output_file = join_path(model%output_directory,'test',sources(i)%exe_name)) - + end if ! Executable depends on object @@ -61,7 +61,7 @@ subroutine targets_from_sources(model,sources) ! Executable depends on library call add_dependency(model%targets(size(model%targets))%ptr, model%targets(1)%ptr) end if - + end select end do @@ -70,20 +70,20 @@ subroutine targets_from_sources(model,sources) function get_object_name(source) result(object_file) ! Generate object target path from source name and model params - ! + ! ! type(srcfile_t), intent(in) :: source character(:), allocatable :: object_file - + integer :: i character(1), parameter :: filesep = '/' character(:), allocatable :: dir - + object_file = canon_path(source%file_name) ! Ignore first directory level object_file = object_file(index(object_file,filesep)+1:) - + ! Convert any remaining directory separators to underscores i = index(object_file,filesep) do while(i > 0) @@ -101,9 +101,9 @@ subroutine targets_from_sources(model,sources) case default object_file = join_path(model%output_directory,model%package_name,object_file)//'.o' - + end select - + end function get_object_name end subroutine targets_from_sources @@ -143,7 +143,7 @@ subroutine add_target(targets,type,output_file,source,link_libraries) if (present(source)) new_target%source = source if (present(link_libraries)) new_target%link_libraries = link_libraries allocate(new_target%dependencies(0)) - + targets = [targets, build_target_ptr(new_target)] end subroutine add_target @@ -171,7 +171,7 @@ subroutine resolve_module_dependencies(targets,error) integer :: i, j do i=1,size(targets) - + if (.not.allocated(targets(i)%ptr%source)) cycle do j=1,size(targets(i)%ptr%source%modules_used) @@ -180,7 +180,7 @@ subroutine resolve_module_dependencies(targets,error) ! Dependency satisfied in same file, skip cycle end if - + if (targets(i)%ptr%source%unit_scope == FPM_SCOPE_APP .OR. & targets(i)%ptr%source%unit_scope == FPM_SCOPE_TEST ) then dep%ptr => & @@ -203,7 +203,7 @@ subroutine resolve_module_dependencies(targets,error) end do - end do + end do end subroutine resolve_module_dependencies @@ -244,7 +244,7 @@ function find_module_dependency(targets,module_name,include_dir) result(target_p end if end do - + end do end function find_module_dependency |