From 7b8d1dcf1ba8ad2ae7a0090bd07ebaf366145c82 Mon Sep 17 00:00:00 2001 From: "init current directory[i]" Date: Fri, 4 Dec 2020 08:46:36 -0500 Subject: remove compare of built manual and manual --- fpm/test/help_test/help_test.f90 | 64 ++++++++++++++++++++++++---------------- 1 file changed, 38 insertions(+), 26 deletions(-) diff --git a/fpm/test/help_test/help_test.f90 b/fpm/test/help_test/help_test.f90 index 8d5437e..ad5d3a9 100644 --- a/fpm/test/help_test/help_test.f90 +++ b/fpm/test/help_test/help_test.f90 @@ -1,14 +1,15 @@ program help_test use,intrinsic :: iso_fortran_env, only : stdin=>input_unit, stdout=>output_unit, stderr=>error_unit implicit none -integer :: i, j +integer :: i integer :: be, af character(len=:),allocatable :: path integer :: estat, cstat character(len=256) :: message logical,allocatable :: tally(:) character(len=1),allocatable :: book1(:), book2(:) -character(len=:),allocatable :: page1(:) +!intel_bug!character(len=:),allocatable :: page1(:) +character(len=132),allocatable :: page1(:) integer :: lines integer :: chars ! run a variety of "fpm help" variations and verify expected files are generated @@ -31,7 +32,7 @@ character(len=*),parameter :: cmds(*) = [character(len=80) :: & !'fpm run -- list --list >> fpm_scratch_help.txt',& character(len=*),parameter :: names(*)=[character(len=10) :: 'fpm','new','build','run','test','runner','list','help'] - write(*,'(g0:,1x)')'TEST help SUBCOMMAND STARTED' + write(*,'(g0:,1x)')'TEST help SUBCOMMAND STARTED' if(allocated(tally))deallocate(tally) allocate(tally(0)) call wipe('fpm_scratch_help.txt') @@ -39,11 +40,11 @@ character(len=*),parameter :: names(*)=[character(len=10) :: 'fpm','new','build' ! check that output has NAME SYNOPSIS DESCRIPTION do i=1,size(names) - write(*,*)'check '//names(i)//' for NAME SYNOPSIS DESCRIPTION' + write(*,*)'check '//names(i)//' for NAME SYNOPSIS DESCRIPTION' path= 'fpm run -- help '//names(i)//' >fpm_scratch_help.txt' message='' call execute_command_line(path,exitstat=estat,cmdstat=cstat,cmdmsg=message) - write(*,'(*(g0))')'CMD=',path,' EXITSTAT=',estat,' CMDSTAT=',cstat,' MESSAGE=',trim(message) + write(*,'(*(g0))')'CMD=',path,' EXITSTAT=',estat,' CMDSTAT=',cstat,' MESSAGE=',trim(message) tally=[tally,all([estat.eq.0,cstat.eq.0])] call swallow('fpm_scratch_help.txt',page1) if(size(page1).lt.3)then @@ -61,7 +62,7 @@ character(len=*),parameter :: names(*)=[character(len=10) :: 'fpm','new','build' write(*,*)'missing expected sections in ',names(i) write(*,'(a)')page1 endif - write(*,*)'have completed ',count(tally),' tests' + write(*,*)'have completed ',count(tally),' tests' call wipe('fpm_scratch_help.txt') call wipe('fpm_scratch_manual.txt') enddo @@ -72,42 +73,49 @@ character(len=*),parameter :: names(*)=[character(len=10) :: 'fpm','new','build' message='' path= cmds(i) call execute_command_line(path,exitstat=estat,cmdstat=cstat,cmdmsg=message) - write(*,'(*(g0))')'CMD=',path,' EXITSTAT=',estat,' CMDSTAT=',cstat,' MESSAGE=',trim(message) + write(*,'(*(g0))')'CMD=',path,' EXITSTAT=',estat,' CMDSTAT=',cstat,' MESSAGE=',trim(message) tally=[tally,all([estat.eq.0,cstat.eq.0])] enddo ! compare book written in fragments with manual call slurp('fpm_scratch_help.txt',book1) call slurp('fpm_scratch_manual.txt',book2) - if(all(book1.ne.book2))then - tally=[tally,.false.] - write(*,*)'manual and appended pages are not the same' - else - write(*,*)'manual and appended pages are the same' - tally=[tally,.true.] - endif + write(*,*)'book1 ',size(book1), len(book1) + write(*,*)'book2 ',size(book2), len(book2) + !if(size(book1).ne.size(book2))then + ! write(*,*)'manual and appended pages are not the same size' + ! tally=[tally,.false.] + !else + ! if(all(book1.ne.book2))then + ! tally=[tally,.false.] + ! write(*,*)'manual and appended pages are not the same' + ! else + ! write(*,*)'manual and appended pages are the same' + ! tally=[tally,.true.] + ! endif + !endif ! overall size of manual chars=size(book2) lines=max(count(char(10).eq.book2),count(char(13).eq.book2)) if( (chars.lt.13000) .or. (lines.lt.350) )then - write(*,*)'manual is suspiciously small, bytes=',chars,' lines=',lines + write(*,*)'manual is suspiciously small, bytes=',chars,' lines=',lines tally=[tally,.false.] else - write(*,*)'manual size is bytes=',chars,' lines=',lines + write(*,*)'manual size is bytes=',chars,' lines=',lines tally=[tally,.true.] endif - write(*,'("HELP TEST TALLY=",*(g0))')tally + write(*,'("HELP TEST TALLY=",*(g0))')tally + call wipe('fpm_scratch_help.txt') + call wipe('fpm_scratch_manual.txt') if(all(tally))then - write(*,'(*(g0))')'PASSED: all ',count(tally),' tests passed ' + write(*,'(*(g0))')'PASSED: all ',count(tally),' tests passed ' else - write(*,*)'FAILED: PASSED=',count(tally),' FAILED=',count(.not.tally) + write(*,*)'FAILED: PASSED=',count(tally),' FAILED=',count(.not.tally) stop 5 endif - call wipe('fpm_scratch_help.txt') - call wipe('fpm_scratch_manual.txt') - write(*,'(g0:,1x)')'TEST help SUBCOMMAND COMPLETE' + write(*,'(g0:,1x)')'TEST help SUBCOMMAND COMPLETE' contains subroutine wipe(filename) @@ -168,13 +176,14 @@ end subroutine stderr_local subroutine swallow(FILENAME,pageout) implicit none character(len=*),intent(in) :: FILENAME ! file to read -character(len=:),allocatable,intent(out) :: pageout(:) ! page to hold file in memory +!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=1),allocatable :: text(:) ! array to hold file in memory call slurp(FILENAME,text) ! allocate character array and copy file into it if(.not.allocated(text))then - write(*,*)'*swallow* failed to load file '//FILENAME + write(*,*)'*swallow* failed to load file '//FILENAME else ! convert array of characters to array of lines pageout=page(text) deallocate(text) ! release memory @@ -186,7 +195,8 @@ function page(array) result (table) !$@(#) M_strings::page(3fp): function to copy char array to page of text character(len=1),intent(in) :: array(:) -character(len=:),allocatable :: table(:) +!intel-bug!character(len=:),allocatable :: table(:) +character(len=132),allocatable :: table(:) integer :: i integer :: linelength integer :: length @@ -216,7 +226,8 @@ character(len=1),parameter :: nl=char(10) endif if(allocated(table))deallocate(table) - allocate(character(len=linelength) :: table(lines)) + !intel-bug!allocate(character(len=linelength) :: table(lines)) + allocate(character(len=132) :: table(lines)) table=' ' linecount=1 @@ -226,6 +237,7 @@ character(len=1),parameter :: nl=char(10) linecount=linecount+1 position=1 elseif(linelength.ne.0)then + write(*,*)'',linecount,position,array(i) table(linecount)(position:position)=array(i) position=position+1 endif -- cgit v1.2.3