aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorJohn S. Urban <urbanjost@comcast.net>2021-01-31 15:57:21 -0500
committerJohn S. Urban <urbanjost@comcast.net>2021-01-31 15:57:21 -0500
commit712d5edc3903921633829b984326de61310aea39 (patch)
tree6e1f27a6d67f98dbaa1f8546b8c4196f30f3e613
parentbc9fa943c5f954bbdbbdda9280fc558948ce9bbd (diff)
downloadfpm-712d5edc3903921633829b984326de61310aea39.tar.gz
fpm-712d5edc3903921633829b984326de61310aea39.zip
space
-rw-r--r--fpm/src/fpm/cmd/new.f902
-rw-r--r--fpm/src/fpm_source_parsing.f9024
2 files changed, 13 insertions, 13 deletions
diff --git a/fpm/src/fpm/cmd/new.f90 b/fpm/src/fpm/cmd/new.f90
index d0cf60c..5149bea 100644
--- a/fpm/src/fpm/cmd/new.f90
+++ b/fpm/src/fpm/cmd/new.f90
@@ -71,7 +71,7 @@ integer,parameter :: tfc = selected_char_kind('DEFAULT')
character(len=:,kind=tfc),allocatable :: bname ! baeename of NAME
character(len=:,kind=tfc),allocatable :: tomlfile(:)
character(len=:,kind=tfc),allocatable :: littlefile(:)
-
+
!> TOP DIRECTORY NAME PROCESSING
!> see if requested new directory already exists and process appropriately
if(exists(settings%name) .and. .not.settings%backfill )then
diff --git a/fpm/src/fpm_source_parsing.f90 b/fpm/src/fpm_source_parsing.f90
index 33b8400..fc0b629 100644
--- a/fpm/src/fpm_source_parsing.f90
+++ b/fpm/src/fpm_source_parsing.f90
@@ -6,8 +6,8 @@
!>
!> 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.
+!>
+!> Both functions return an instance of the [[srcfile_t]] type.
!>
!> For more information, please read the documentation for each function:
!>
@@ -38,7 +38,7 @@ character(15), parameter :: INTRINSIC_MODULE_NAMES(*) = &
contains
!> Parsing of free-form fortran source files
-!>
+!>
!> The following statements are recognised and parsed:
!>
!> - `Module`/`submodule`/`program` declaration
@@ -171,7 +171,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
@@ -264,7 +264,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
@@ -288,7 +288,7 @@ function parse_f_source(f_filename,error) result(f_source)
temp_string = lower(split_n(file_lines(i)%s,n=2,delims=' ',stat=stat))
if (stat == 0) then
-
+
if (scan(temp_string,'=(')>0 ) then
! Ignore:
! program =*
@@ -343,7 +343,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
@@ -359,7 +359,7 @@ end function parse_f_source
!> Parsing of c source files
-!>
+!>
!> The following statements are recognised and parsed:
!>
!> - `#include` preprocessor statement
@@ -396,9 +396,9 @@ function parse_c_source(c_filename,error) result(c_source)
c_source%unit_type = FPM_UNIT_UNKNOWN
return
end if
-
+
c_source%digest = fnv_1a(file_lines)
-
+
do pass = 1,2
n_include = 0
file_loop: do i=1,size(file_lines)
@@ -406,7 +406,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
@@ -440,7 +440,7 @@ end function parse_c_source
!> 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
!>
function split_n(string,delims,n,stat) result(substring)