aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--fpm/src/fpm_command_line.f904
-rw-r--r--fpm/test/help_test/help_test.f90125
2 files changed, 89 insertions, 40 deletions
diff --git a/fpm/src/fpm_command_line.f90 b/fpm/src/fpm_command_line.f90
index da885f9..2a44a4f 100644
--- a/fpm/src/fpm_command_line.f90
+++ b/fpm/src/fpm_command_line.f90
@@ -489,9 +489,6 @@ contains
' part of your default programming environment, as well as letting ', &
' you share your projects with others in a similar manner. ', &
' ', &
- ' See the fpm(1) repository at https://fortran-lang.org/packages/fpm ', &
- ' for a listing of registered projects. ', &
- ' ', &
' All output goes into the directory "build/" which can generally be ', &
' removed and rebuilt if required. Note that if external packages are ', &
' being used you need network connectivity to rebuild from scratch. ', &
@@ -545,6 +542,7 @@ contains
' fpm run myprogram --release -- -x 10 -y 20 --title "my title" ', &
' ', &
'SEE ALSO ', &
+ ' ', &
' + The fpm(1) home page is at https://github.com/fortran-lang/fpm ', &
' + Registered fpm(1) packages are at https://fortran-lang.org/packages ', &
' + The fpm(1) TOML file format is described at ', &
diff --git a/fpm/test/help_test/help_test.f90 b/fpm/test/help_test/help_test.f90
index 03daa97..78b9c81 100644
--- a/fpm/test/help_test/help_test.f90
+++ b/fpm/test/help_test/help_test.f90
@@ -1,14 +1,14 @@
program help_test
use,intrinsic :: iso_fortran_env, only : stdin=>input_unit, stdout=>output_unit, stderr=>error_unit
implicit none
-integer :: i
+integer :: i, j
integer :: be, af
character(len=:),allocatable :: path
integer :: estat, cstat
character(len=256) :: message
logical,allocatable :: tally(:)
!intel-bug!character(len=:),allocatable :: book1(:), book2(:)
-character(len=132),allocatable :: book1(:), book2(:)
+character(len=132),allocatable :: book1(:), book2(:), book3(:)
!intel-bug!character(len=:),allocatable :: page1(:)
character(len=132),allocatable :: page1(:)
integer :: lines
@@ -16,6 +16,7 @@ integer :: chars
! run a variety of "fpm help" variations and verify expected files are generated
character(len=*),parameter :: cmds(*) = [character(len=80) :: &
! build manual as pieces using various help commands
+! debug version
'fpm run -- --version ',& ! verify fpm version being used
'fpm run -- --help > fpm_scratch_help.txt',&
'fpm run -- help new >> fpm_scratch_help.txt',&
@@ -26,6 +27,17 @@ character(len=*),parameter :: cmds(*) = [character(len=80) :: &
'fpm run -- help list >> fpm_scratch_help.txt',&
'fpm run -- help help >> fpm_scratch_help.txt',&
'fpm run -- --version >> fpm_scratch_help.txt',&
+! release version
+'fpm run --release -- --version ',& ! verify fpm version being used
+'fpm run --release -- --help > fpm_scratch_help3.txt',&
+'fpm run --release -- help new >> fpm_scratch_help3.txt',&
+'fpm run --release -- build --help >> fpm_scratch_help3.txt',&
+'fpm run --release -- help run >> fpm_scratch_help3.txt',&
+'fpm run --release -- help test >> fpm_scratch_help3.txt',&
+'fpm run --release -- help runner >> fpm_scratch_help3.txt',&
+'fpm run --release -- help list >> fpm_scratch_help3.txt',&
+'fpm run --release -- help help >> fpm_scratch_help3.txt',&
+'fpm run --release -- --version >> fpm_scratch_help3.txt',&
! generate manual
'fpm run -- help manual > fpm_scratch_manual.txt']
@@ -33,44 +45,52 @@ character(len=*),parameter :: cmds(*) = [character(len=80) :: &
!'fpm run -- --list >> fpm_scratch_help.txt',&
!'fpm run -- list --list >> fpm_scratch_help.txt',&
character(len=*),parameter :: names(*)=[character(len=10) :: 'fpm','new','build','run','test','runner','list','help']
+character(len=:),allocatable :: add
write(*,'(g0:,1x)')'<INFO>TEST help SUBCOMMAND STARTED'
if(allocated(tally))deallocate(tally)
allocate(tally(0))
call wipe('fpm_scratch_help.txt')
+ call wipe('fpm_scratch_help3.txt')
call wipe('fpm_scratch_manual.txt')
! check that output has NAME SYNOPSIS DESCRIPTION
- do i=1,size(names)
- write(*,*)'<INFO>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))')'<INFO>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
- write(*,*)'<ERROR>help for '//names(i)//' ridiculiously small'
- tally=[tally,.false.]
- exit
- endif
- !!write(*,*)findloc(page1,'NAME').eq.1
- be=count(.not.tally)
- tally=[tally,count(page1.eq.'NAME').eq.1]
- tally=[tally,count(page1.eq.'SYNOPSIS').eq.1]
- tally=[tally,count(page1.eq.'DESCRIPTION').eq.1]
- af=count(.not.tally)
- if(be.ne.af)then
- write(*,*)'<ERROR>missing expected sections in ',names(i)
- write(*,*)page1(1) ! assuming at least size 1 for debugging mingw
- write(*,*)count(page1.eq.'NAME')
- write(*,*)count(page1.eq.'SYNOPSIS')
- write(*,*)count(page1.eq.'DESCRIPTION')
- write(*,'(a)')page1
+ do j=1,2
+ if(j.eq.1)then
+ ADD=' '
+ else
+ ADD=' --release '
endif
- write(*,*)'<INFO>have completed ',count(tally),' tests'
- call wipe('fpm_scratch_help.txt')
- call wipe('fpm_scratch_manual.txt')
+ do i=1,size(names)
+ write(*,*)'<INFO>check '//names(i)//' for NAME SYNOPSIS DESCRIPTION'
+ path= 'fpm run '//add//' -- help '//names(i)//' >fpm_scratch_help.txt'
+ message=''
+ call execute_command_line(path,exitstat=estat,cmdstat=cstat,cmdmsg=message)
+ write(*,'(*(g0))')'<INFO>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
+ write(*,*)'<ERROR>help for '//names(i)//' ridiculiously small'
+ tally=[tally,.false.]
+ exit
+ endif
+ !!write(*,*)findloc(page1,'NAME').eq.1
+ be=count(.not.tally)
+ tally=[tally,count(page1.eq.'NAME').eq.1]
+ tally=[tally,count(page1.eq.'SYNOPSIS').eq.1]
+ tally=[tally,count(page1.eq.'DESCRIPTION').eq.1]
+ af=count(.not.tally)
+ if(be.ne.af)then
+ write(*,*)'<ERROR>missing expected sections in ',names(i)
+ write(*,*)page1(1) ! assuming at least size 1 for debugging mingw
+ write(*,*)count(page1.eq.'NAME')
+ write(*,*)count(page1.eq.'SYNOPSIS')
+ write(*,*)count(page1.eq.'DESCRIPTION')
+ write(*,'(a)')page1
+ endif
+ write(*,*)'<INFO>have completed ',count(tally),' tests'
+ call wipe('fpm_scratch_help.txt')
+ enddo
enddo
@@ -86,20 +106,35 @@ character(len=*),parameter :: names(*)=[character(len=10) :: 'fpm','new','build'
! compare book written in fragments with manual
call swallow('fpm_scratch_help.txt',book1)
call swallow('fpm_scratch_manual.txt',book2)
+ call swallow('fpm_scratch_help3.txt',book3)
! get rid of lines from run() which is not on stderr at the moment
book1=pack(book1,index(book1,' + build/').eq.0)
book2=pack(book1,index(book2,' + build/').eq.0)
+ book3=pack(book3,index(book3,' + build/').eq.0)
write(*,*)'<INFO>book1 ',size(book1), len(book1)
write(*,*)'<INFO>book2 ',size(book2), len(book2)
+ write(*,*)'<INFO>book2 ',size(book3), len(book3)
if(size(book1).ne.size(book2))then
- write(*,*)'<ERROR>manual and appended pages are not the same size'
+ write(*,*)'<ERROR>manual and "debug" appended pages are not the same size'
tally=[tally,.false.]
else
if(all(book1.ne.book2))then
tally=[tally,.false.]
- write(*,*)'<ERROR>manual and appended pages are not the same'
+ write(*,*)'<ERROR>manual and "debug" appended pages are not the same'
else
- write(*,*)'<INFO>manual and appended pages are the same'
+ write(*,*)'<INFO>manual and "debug" appended pages are the same'
+ tally=[tally,.true.]
+ endif
+ endif
+ if(size(book3).ne.size(book2))then
+ write(*,*)'<ERROR>manual and "release" appended pages are not the same size'
+ tally=[tally,.false.]
+ else
+ if(all(book3.ne.book2))then
+ tally=[tally,.false.]
+ write(*,*)'<ERROR>manual and "release" appended pages are not the same'
+ else
+ write(*,*)'<INFO>manual and "release" appended pages are the same'
tally=[tally,.true.]
endif
endif
@@ -110,15 +145,25 @@ character(len=*),parameter :: names(*)=[character(len=10) :: 'fpm','new','build'
chars=size(book2)*len(book2)
lines=size(book2)
if( (chars.lt.13000) .or. (lines.lt.350) )then
- write(*,*)'<ERROR>manual is suspiciously small, bytes=',chars,' lines=',lines
+ 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
+ tally=[tally,.true.]
+ endif
+ chars=size(book3)*len(book3)
+ lines=size(book3)
+ if( (chars.lt.13000) .or. (lines.lt.350) )then
+ write(*,*)'<ERROR>"release" manual is suspiciously small, bytes=',chars,' lines=',lines
tally=[tally,.false.]
else
- write(*,*)'<INFO>manual size is bytes=',chars,' lines=',lines
+ write(*,*)'<INFO>"release" manual size is bytes=',chars,' lines=',lines
tally=[tally,.true.]
endif
write(*,'("<INFO>HELP TEST TALLY=",*(g0))')tally
call wipe('fpm_scratch_help.txt')
+ call wipe('fpm_scratch_help3.txt')
call wipe('fpm_scratch_manual.txt')
if(all(tally))then
write(*,'(*(g0))')'<INFO>PASSED: all ',count(tally),' tests passed '
@@ -249,7 +294,13 @@ character(len=1),parameter :: cr=char(13)
position=1
elseif(array(i).eq.cr)then
elseif(linelength.ne.0)then
- table(linecount)(position:position)=array(i)
+ if(position.gt.len(table))then
+ write(*,*)'<ERROR> adding character past edge of text',table(linecount),array(i)
+ elseif(linecount.gt.size(table))then
+ write(*,*)'<ERROR> adding line past end of text',linecount,size(table)
+ else
+ table(linecount)(position:position)=array(i)
+ endif
position=position+1
endif
enddo