diff options
-rw-r--r-- | fpm/src/fpm_compiler.f90 | 57 | ||||
-rw-r--r-- | fpm/test/help_test/help_test.f90 | 30 |
2 files changed, 45 insertions, 42 deletions
diff --git a/fpm/src/fpm_compiler.f90 b/fpm/src/fpm_compiler.f90 index 76a91ad..6336e4e 100644 --- a/fpm/src/fpm_compiler.f90 +++ b/fpm/src/fpm_compiler.f90 @@ -14,7 +14,8 @@ type(fpm_model_t), intent(inout) :: model character(len=:),allocatable :: fflags ! optional flags that might be overridden by user character(len=:),allocatable :: modpath -character(len=:),allocatable :: mandatory ! flags required for fpm to function properly +character(len=:),allocatable :: mandatory ! flags required for fpm to function properly; + ! ie. add module path and module include directory as appropriate ! special reserved names "debug" and "release" are for supported compilers with no user-specified compile or load flags @@ -56,7 +57,7 @@ character(len=:),allocatable :: mandatory ! flags required for fpm to function p & -ffast-math& & -funroll-loops& &' - mandatory=' -J '//modpath//' -I '//modpath ! add module path as apprpriate + mandatory=' -J '//modpath//' -I '//modpath case('debug_caf') fflags = '& & -Wall& @@ -68,7 +69,7 @@ character(len=:),allocatable :: mandatory ! flags required for fpm to function p & -fcheck-array-temporaries& & -fbacktrace& &' - mandatory=' -J '//modpath//' -I '//modpath ! add module path as apprpriate + mandatory=' -J '//modpath//' -I '//modpath case('release_gfortran') fflags='& & -O3& @@ -79,7 +80,7 @@ character(len=:),allocatable :: mandatory ! flags required for fpm to function p & -funroll-loops& & -fcoarray=single& &' - mandatory=' -J '//modpath//' -I '//modpath ! add module path as apprpriate + mandatory=' -J '//modpath//' -I '//modpath case('debug_gfortran') fflags = '& & -Wall& @@ -92,7 +93,7 @@ character(len=:),allocatable :: mandatory ! flags required for fpm to function p & -fbacktrace& & -fcoarray=single& &' - mandatory=' -J '//modpath//' -I '//modpath ! add module path as apprpriate + mandatory=' -J '//modpath//' -I '//modpath case('release_f95') fflags='& @@ -103,7 +104,7 @@ character(len=:),allocatable :: mandatory ! flags required for fpm to function p & -ffast-math& & -funroll-loops& &' - mandatory=' -J '//modpath//' -I '//modpath ! add module path as apprpriate + mandatory=' -J '//modpath//' -I '//modpath case('debug_f95') fflags = '& & -Wall& @@ -116,13 +117,13 @@ character(len=:),allocatable :: mandatory ! flags required for fpm to function p & -Wno-maybe-uninitialized -Wno-uninitialized& & -fbacktrace& &' - mandatory=' -J '//modpath//' -I '//modpath ! add module path as apprpriate + mandatory=' -J '//modpath//' -I '//modpath case('release_nvfortran') fflags = '& & -Mbackslash& &' - mandatory=' -module '//modpath//' -I '//modpath ! add module path as apprpriate + mandatory=' -module '//modpath//' -I '//modpath case('debug_nvfortran') fflags = '& & -Minform=inform& @@ -133,7 +134,7 @@ character(len=:),allocatable :: mandatory ! flags required for fpm to function p & -Mchkstk& & -traceback& &' - mandatory=' -module '//modpath//' -I '//modpath ! add module path as apprpriate + mandatory=' -module '//modpath//' -I '//modpath case('release_ifort') fflags = '& @@ -147,7 +148,7 @@ character(len=:),allocatable :: mandatory ! flags required for fpm to function p & -assume byterecl& & -assume nounderscore& &' - mandatory=' -module '//modpath//' -I '//modpath ! add module path as apprpriate + mandatory=' -module '//modpath//' -I '//modpath case('debug_ifort') fflags = '& & -warn all& @@ -159,42 +160,42 @@ character(len=:),allocatable :: mandatory ! flags required for fpm to function p & -assume byterecl& & -traceback& &' - mandatory=' -module '//modpath//' -I '//modpath ! add module path as apprpriate + mandatory=' -module '//modpath//' -I '//modpath case('release_ifx') fflags = ' ' - mandatory=' -module '//modpath//' -I '//modpath ! add module path as apprpriate + mandatory=' -module '//modpath//' -I '//modpath case('debug_ifx') fflags = ' ' - mandatory=' -module '//modpath//' -I '//modpath ! add module path as apprpriate + mandatory=' -module '//modpath//' -I '//modpath case('release_pgfortran','release_pgf90','release_pgf95') ! Portland Group F90/F95 compilers fflags = ' ' - mandatory=' -module '//modpath//' -I '//modpath ! add module path as apprpriate + mandatory=' -module '//modpath//' -I '//modpath case('debug_pgfortran','debug_pgf90','debug_pgf95') ! Portland Group F90/F95 compilers fflags = ' ' - mandatory=' -module '//modpath//' -I '//modpath ! add module path as apprpriate + mandatory=' -module '//modpath//' -I '//modpath case('release_flang') fflags = ' ' - mandatory=' -module '//modpath//' -I '//modpath ! add module path as apprpriate + mandatory=' -module '//modpath//' -I '//modpath case('debug_flang') fflags = ' ' - mandatory=' -module '//modpath//' -I '//modpath ! add module path as apprpriate + mandatory=' -module '//modpath//' -I '//modpath case('release_lfc') fflags = ' ' - mandatory=' -M '//modpath//' -I '//modpath ! add module path as apprpriate + mandatory=' -M '//modpath//' -I '//modpath case('debug_lfc') fflags = ' ' - mandatory=' -M '//modpath//' -I '//modpath ! add module path as apprpriate + mandatory=' -M '//modpath//' -I '//modpath case('release_nagfor') fflags = ' & & -O4& & -coarray=single& & -PIC& - ' - mandatory=' -mdir '//modpath//' -I '//modpath !! add module path as apprpriate + &' + mandatory=' -mdir '//modpath//' -I '//modpath ! case('debug_nagfor') fflags = '& & -g& @@ -203,25 +204,25 @@ character(len=:),allocatable :: mandatory ! flags required for fpm to function p & -gline& & -coarray=single& & -PIC& - ' - mandatory=' -mdir '//modpath//' -I '//modpath !! add module path as apprpriate + &' + mandatory=' -mdir '//modpath//' -I '//modpath ! case('release_crayftn') fflags = ' ' - mandatory=' -J '//modpath//' -I '//modpath ! add module path as apprpriate + mandatory=' -J '//modpath//' -I '//modpath case('debug_crayftn') fflags = ' ' - mandatory=' -J '//modpath//' -I '//modpath ! add module path as apprpriate + mandatory=' -J '//modpath//' -I '//modpath case('release_xlf90') fflags = ' ' - mandatory=' -qmoddir '//modpath//' -I '//modpath ! add module path as apprpriate + mandatory=' -qmoddir '//modpath//' -I '//modpath case('debug_xlf90') fflags = ' ' - mandatory=' -qmoddir '//modpath//' -I '//modpath ! add module path as apprpriate + mandatory=' -qmoddir '//modpath//' -I '//modpath case default fflags = ' ' - mandatory=' -module '//modpath//' -I '//modpath ! add module path as apprpriate + mandatory=' -module '//modpath//' -I '//modpath write(*,*)'<WARNING> unknown compiler (',compiler,')' write(*,*)' and build name (',build_name,')' write(*,*)' combination.' diff --git a/fpm/test/help_test/help_test.f90 b/fpm/test/help_test/help_test.f90 index 78b9c81..390b274 100644 --- a/fpm/test/help_test/help_test.f90 +++ b/fpm/test/help_test/help_test.f90 @@ -1,16 +1,18 @@ program help_test +! note hardcoded len=512 instead of len=: in this test is a work-around a gfortran bug in old +! pre-v8.3 versions use,intrinsic :: iso_fortran_env, only : stdin=>input_unit, stdout=>output_unit, stderr=>error_unit implicit none integer :: i, j integer :: be, af character(len=:),allocatable :: path integer :: estat, cstat -character(len=256) :: message +character(len=512) :: message logical,allocatable :: tally(:) !intel-bug!character(len=:),allocatable :: book1(:), book2(:) -character(len=132),allocatable :: book1(:), book2(:), book3(:) +character(len=512),allocatable :: book1(:), book2(:), book3(:) !intel-bug!character(len=:),allocatable :: page1(:) -character(len=132),allocatable :: page1(:) +character(len=512),allocatable :: page1(:) integer :: lines integer :: chars ! run a variety of "fpm help" variations and verify expected files are generated @@ -142,22 +144,22 @@ character(len=:),allocatable :: add ! overall size of manual !chars=size(book2) !lines=max(count(char(10).eq.book2),count(char(13).eq.book2)) - chars=size(book2)*len(book2) + chars=sum(len_trim(book2)) ! SUM TRIMMED LENGTH lines=size(book2) - if( (chars.lt.13000) .or. (lines.lt.350) )then + if( (chars.lt.12000) .or. (lines.lt.350) )then write(*,*)'<ERROR>"debug" manual is suspiciously small, bytes=',chars,' lines=',lines tally=[tally,.false.] else - write(*,*)'<INFO>"debug" manual size is bytes=',chars,' lines=',lines + write(*,*)'<INFO>"debug" manual size in bytes=',chars,' lines=',lines tally=[tally,.true.] endif - chars=size(book3)*len(book3) + chars=sum(len_trim(book3)) ! SUM TRIMMED LENGTH lines=size(book3) - if( (chars.lt.13000) .or. (lines.lt.350) )then + if( (chars.lt.12000) .or. (lines.lt.350) )then write(*,*)'<ERROR>"release" manual is suspiciously small, bytes=',chars,' lines=',lines tally=[tally,.false.] else - write(*,*)'<INFO>"release" manual size is bytes=',chars,' lines=',lines + write(*,*)'<INFO>"release" manual size in bytes=',chars,' lines=',lines tally=[tally,.true.] endif @@ -178,7 +180,7 @@ subroutine wipe(filename) character(len=*),intent(in) :: filename integer :: ios integer :: lun -character(len=256) :: message +character(len=512) :: message open(file=filename,newunit=lun,iostat=ios,iomsg=message) if(ios.eq.0)then close(unit=lun,iostat=ios,status='delete',iomsg=message) @@ -196,7 +198,7 @@ implicit none character(*),intent(in) :: filename ! filename to shlep character(len=1),allocatable,intent(out) :: text(:) ! array to hold file integer :: nchars, igetunit, ios -character(len=256) :: message +character(len=512) :: message character(len=4096) :: local_filename ios=0 nchars=0 @@ -233,7 +235,7 @@ subroutine swallow(FILENAME,pageout) implicit none character(len=*),intent(in) :: FILENAME ! file to read !intel-bug!character(len=:),allocatable,intent(out) :: pageout(:) ! page to hold file in memory -character(len=132),allocatable,intent(out) :: pageout(:) ! page to hold file in memory +character(len=512),allocatable,intent(out) :: pageout(:) ! page to hold file in memory character(len=1),allocatable :: text(:) ! array to hold file in memory call slurp(FILENAME,text) ! allocate character array and copy file into it @@ -252,7 +254,7 @@ function page(array) result (table) character(len=1),intent(in) :: array(:) !intel-bug!character(len=:),allocatable :: table(:) -character(len=132),allocatable :: table(:) +character(len=512),allocatable :: table(:) integer :: i integer :: linelength integer :: length @@ -284,7 +286,7 @@ character(len=1),parameter :: cr=char(13) if(allocated(table))deallocate(table) !intel-bug!allocate(character(len=linelength) :: table(lines)) - allocate(character(len=132) :: table(lines)) + allocate(character(len=512) :: table(lines)) table=' ' linecount=1 position=1 |