Skip to content

Commit 125e2e1

Browse files
committed
cleanup errata in fpm_compiler.f90
1 parent ad9aee9 commit 125e2e1

File tree

2 files changed

+45
-42
lines changed

2 files changed

+45
-42
lines changed

fpm/src/fpm_compiler.f90

Lines changed: 29 additions & 28 deletions
Original file line numberDiff line numberDiff line change
@@ -14,7 +14,8 @@ subroutine add_compile_flag_defaults(build_name,compiler,model)
1414

1515
character(len=:),allocatable :: fflags ! optional flags that might be overridden by user
1616
character(len=:),allocatable :: modpath
17-
character(len=:),allocatable :: mandatory ! flags required for fpm to function properly
17+
character(len=:),allocatable :: mandatory ! flags required for fpm to function properly;
18+
! ie. add module path and module include directory as appropriate
1819

1920
! special reserved names "debug" and "release" are for supported compilers with no user-specified compile or load flags
2021

@@ -56,7 +57,7 @@ subroutine add_compile_flag_defaults(build_name,compiler,model)
5657
& -ffast-math&
5758
& -funroll-loops&
5859
&'
59-
mandatory=' -J '//modpath//' -I '//modpath ! add module path as apprpriate
60+
mandatory=' -J '//modpath//' -I '//modpath
6061
case('debug_caf')
6162
fflags = '&
6263
& -Wall&
@@ -68,7 +69,7 @@ subroutine add_compile_flag_defaults(build_name,compiler,model)
6869
& -fcheck-array-temporaries&
6970
& -fbacktrace&
7071
&'
71-
mandatory=' -J '//modpath//' -I '//modpath ! add module path as apprpriate
72+
mandatory=' -J '//modpath//' -I '//modpath
7273
case('release_gfortran')
7374
fflags='&
7475
& -O3&
@@ -79,7 +80,7 @@ subroutine add_compile_flag_defaults(build_name,compiler,model)
7980
& -funroll-loops&
8081
& -fcoarray=single&
8182
&'
82-
mandatory=' -J '//modpath//' -I '//modpath ! add module path as apprpriate
83+
mandatory=' -J '//modpath//' -I '//modpath
8384
case('debug_gfortran')
8485
fflags = '&
8586
& -Wall&
@@ -92,7 +93,7 @@ subroutine add_compile_flag_defaults(build_name,compiler,model)
9293
& -fbacktrace&
9394
& -fcoarray=single&
9495
&'
95-
mandatory=' -J '//modpath//' -I '//modpath ! add module path as apprpriate
96+
mandatory=' -J '//modpath//' -I '//modpath
9697

9798
case('release_f95')
9899
fflags='&
@@ -103,7 +104,7 @@ subroutine add_compile_flag_defaults(build_name,compiler,model)
103104
& -ffast-math&
104105
& -funroll-loops&
105106
&'
106-
mandatory=' -J '//modpath//' -I '//modpath ! add module path as apprpriate
107+
mandatory=' -J '//modpath//' -I '//modpath
107108
case('debug_f95')
108109
fflags = '&
109110
& -Wall&
@@ -116,13 +117,13 @@ subroutine add_compile_flag_defaults(build_name,compiler,model)
116117
& -Wno-maybe-uninitialized -Wno-uninitialized&
117118
& -fbacktrace&
118119
&'
119-
mandatory=' -J '//modpath//' -I '//modpath ! add module path as apprpriate
120+
mandatory=' -J '//modpath//' -I '//modpath
120121

121122
case('release_nvfortran')
122123
fflags = '&
123124
& -Mbackslash&
124125
&'
125-
mandatory=' -module '//modpath//' -I '//modpath ! add module path as apprpriate
126+
mandatory=' -module '//modpath//' -I '//modpath
126127
case('debug_nvfortran')
127128
fflags = '&
128129
& -Minform=inform&
@@ -133,7 +134,7 @@ subroutine add_compile_flag_defaults(build_name,compiler,model)
133134
& -Mchkstk&
134135
& -traceback&
135136
&'
136-
mandatory=' -module '//modpath//' -I '//modpath ! add module path as apprpriate
137+
mandatory=' -module '//modpath//' -I '//modpath
137138

138139
case('release_ifort')
139140
fflags = '&
@@ -147,7 +148,7 @@ subroutine add_compile_flag_defaults(build_name,compiler,model)
147148
& -assume byterecl&
148149
& -assume nounderscore&
149150
&'
150-
mandatory=' -module '//modpath//' -I '//modpath ! add module path as apprpriate
151+
mandatory=' -module '//modpath//' -I '//modpath
151152
case('debug_ifort')
152153
fflags = '&
153154
& -warn all&
@@ -159,42 +160,42 @@ subroutine add_compile_flag_defaults(build_name,compiler,model)
159160
& -assume byterecl&
160161
& -traceback&
161162
&'
162-
mandatory=' -module '//modpath//' -I '//modpath ! add module path as apprpriate
163+
mandatory=' -module '//modpath//' -I '//modpath
163164
case('release_ifx')
164165
fflags = ' '
165-
mandatory=' -module '//modpath//' -I '//modpath ! add module path as apprpriate
166+
mandatory=' -module '//modpath//' -I '//modpath
166167
case('debug_ifx')
167168
fflags = ' '
168-
mandatory=' -module '//modpath//' -I '//modpath ! add module path as apprpriate
169+
mandatory=' -module '//modpath//' -I '//modpath
169170

170171
case('release_pgfortran','release_pgf90','release_pgf95') ! Portland Group F90/F95 compilers
171172
fflags = ' '
172-
mandatory=' -module '//modpath//' -I '//modpath ! add module path as apprpriate
173+
mandatory=' -module '//modpath//' -I '//modpath
173174
case('debug_pgfortran','debug_pgf90','debug_pgf95') ! Portland Group F90/F95 compilers
174175
fflags = ' '
175-
mandatory=' -module '//modpath//' -I '//modpath ! add module path as apprpriate
176+
mandatory=' -module '//modpath//' -I '//modpath
176177

177178
case('release_flang')
178179
fflags = ' '
179-
mandatory=' -module '//modpath//' -I '//modpath ! add module path as apprpriate
180+
mandatory=' -module '//modpath//' -I '//modpath
180181
case('debug_flang')
181182
fflags = ' '
182-
mandatory=' -module '//modpath//' -I '//modpath ! add module path as apprpriate
183+
mandatory=' -module '//modpath//' -I '//modpath
183184

184185
case('release_lfc')
185186
fflags = ' '
186-
mandatory=' -M '//modpath//' -I '//modpath ! add module path as apprpriate
187+
mandatory=' -M '//modpath//' -I '//modpath
187188
case('debug_lfc')
188189
fflags = ' '
189-
mandatory=' -M '//modpath//' -I '//modpath ! add module path as apprpriate
190+
mandatory=' -M '//modpath//' -I '//modpath
190191

191192
case('release_nagfor')
192193
fflags = ' &
193194
& -O4&
194195
& -coarray=single&
195196
& -PIC&
196-
'
197-
mandatory=' -mdir '//modpath//' -I '//modpath !! add module path as apprpriate
197+
&'
198+
mandatory=' -mdir '//modpath//' -I '//modpath !
198199
case('debug_nagfor')
199200
fflags = '&
200201
& -g&
@@ -203,25 +204,25 @@ subroutine add_compile_flag_defaults(build_name,compiler,model)
203204
& -gline&
204205
& -coarray=single&
205206
& -PIC&
206-
'
207-
mandatory=' -mdir '//modpath//' -I '//modpath !! add module path as apprpriate
207+
&'
208+
mandatory=' -mdir '//modpath//' -I '//modpath !
208209
case('release_crayftn')
209210
fflags = ' '
210-
mandatory=' -J '//modpath//' -I '//modpath ! add module path as apprpriate
211+
mandatory=' -J '//modpath//' -I '//modpath
211212
case('debug_crayftn')
212213
fflags = ' '
213-
mandatory=' -J '//modpath//' -I '//modpath ! add module path as apprpriate
214+
mandatory=' -J '//modpath//' -I '//modpath
214215

215216
case('release_xlf90')
216217
fflags = ' '
217-
mandatory=' -qmoddir '//modpath//' -I '//modpath ! add module path as apprpriate
218+
mandatory=' -qmoddir '//modpath//' -I '//modpath
218219
case('debug_xlf90')
219220
fflags = ' '
220-
mandatory=' -qmoddir '//modpath//' -I '//modpath ! add module path as apprpriate
221+
mandatory=' -qmoddir '//modpath//' -I '//modpath
221222

222223
case default
223224
fflags = ' '
224-
mandatory=' -module '//modpath//' -I '//modpath ! add module path as apprpriate
225+
mandatory=' -module '//modpath//' -I '//modpath
225226
write(*,*)'<WARNING> unknown compiler (',compiler,')'
226227
write(*,*)' and build name (',build_name,')'
227228
write(*,*)' combination.'

fpm/test/help_test/help_test.f90

Lines changed: 16 additions & 14 deletions
Original file line numberDiff line numberDiff line change
@@ -1,16 +1,18 @@
11
program help_test
2+
! note hardcoded len=512 instead of len=: in this test is a work-around a gfortran bug in old
3+
! pre-v8.3 versions
24
use,intrinsic :: iso_fortran_env, only : stdin=>input_unit, stdout=>output_unit, stderr=>error_unit
35
implicit none
46
integer :: i, j
57
integer :: be, af
68
character(len=:),allocatable :: path
79
integer :: estat, cstat
8-
character(len=256) :: message
10+
character(len=512) :: message
911
logical,allocatable :: tally(:)
1012
!intel-bug!character(len=:),allocatable :: book1(:), book2(:)
11-
character(len=132),allocatable :: book1(:), book2(:), book3(:)
13+
character(len=512),allocatable :: book1(:), book2(:), book3(:)
1214
!intel-bug!character(len=:),allocatable :: page1(:)
13-
character(len=132),allocatable :: page1(:)
15+
character(len=512),allocatable :: page1(:)
1416
integer :: lines
1517
integer :: chars
1618
! run a variety of "fpm help" variations and verify expected files are generated
@@ -142,22 +144,22 @@ program help_test
142144
! overall size of manual
143145
!chars=size(book2)
144146
!lines=max(count(char(10).eq.book2),count(char(13).eq.book2))
145-
chars=size(book2)*len(book2)
147+
chars=sum(len_trim(book2)) ! SUM TRIMMED LENGTH
146148
lines=size(book2)
147-
if( (chars.lt.13000) .or. (lines.lt.350) )then
149+
if( (chars.lt.12000) .or. (lines.lt.350) )then
148150
write(*,*)'<ERROR>"debug" manual is suspiciously small, bytes=',chars,' lines=',lines
149151
tally=[tally,.false.]
150152
else
151-
write(*,*)'<INFO>"debug" manual size is bytes=',chars,' lines=',lines
153+
write(*,*)'<INFO>"debug" manual size in bytes=',chars,' lines=',lines
152154
tally=[tally,.true.]
153155
endif
154-
chars=size(book3)*len(book3)
156+
chars=sum(len_trim(book3)) ! SUM TRIMMED LENGTH
155157
lines=size(book3)
156-
if( (chars.lt.13000) .or. (lines.lt.350) )then
158+
if( (chars.lt.12000) .or. (lines.lt.350) )then
157159
write(*,*)'<ERROR>"release" manual is suspiciously small, bytes=',chars,' lines=',lines
158160
tally=[tally,.false.]
159161
else
160-
write(*,*)'<INFO>"release" manual size is bytes=',chars,' lines=',lines
162+
write(*,*)'<INFO>"release" manual size in bytes=',chars,' lines=',lines
161163
tally=[tally,.true.]
162164
endif
163165

@@ -178,7 +180,7 @@ subroutine wipe(filename)
178180
character(len=*),intent(in) :: filename
179181
integer :: ios
180182
integer :: lun
181-
character(len=256) :: message
183+
character(len=512) :: message
182184
open(file=filename,newunit=lun,iostat=ios,iomsg=message)
183185
if(ios.eq.0)then
184186
close(unit=lun,iostat=ios,status='delete',iomsg=message)
@@ -196,7 +198,7 @@ subroutine slurp(filename,text)
196198
character(*),intent(in) :: filename ! filename to shlep
197199
character(len=1),allocatable,intent(out) :: text(:) ! array to hold file
198200
integer :: nchars, igetunit, ios
199-
character(len=256) :: message
201+
character(len=512) :: message
200202
character(len=4096) :: local_filename
201203
ios=0
202204
nchars=0
@@ -233,7 +235,7 @@ subroutine swallow(FILENAME,pageout)
233235
implicit none
234236
character(len=*),intent(in) :: FILENAME ! file to read
235237
!intel-bug!character(len=:),allocatable,intent(out) :: pageout(:) ! page to hold file in memory
236-
character(len=132),allocatable,intent(out) :: pageout(:) ! page to hold file in memory
238+
character(len=512),allocatable,intent(out) :: pageout(:) ! page to hold file in memory
237239
character(len=1),allocatable :: text(:) ! array to hold file in memory
238240

239241
call slurp(FILENAME,text) ! allocate character array and copy file into it
@@ -252,7 +254,7 @@ function page(array) result (table)
252254

253255
character(len=1),intent(in) :: array(:)
254256
!intel-bug!character(len=:),allocatable :: table(:)
255-
character(len=132),allocatable :: table(:)
257+
character(len=512),allocatable :: table(:)
256258
integer :: i
257259
integer :: linelength
258260
integer :: length
@@ -284,7 +286,7 @@ function page(array) result (table)
284286

285287
if(allocated(table))deallocate(table)
286288
!intel-bug!allocate(character(len=linelength) :: table(lines))
287-
allocate(character(len=132) :: table(lines))
289+
allocate(character(len=512) :: table(lines))
288290
table=' '
289291
linecount=1
290292
position=1

0 commit comments

Comments
 (0)