Skip to content

Commit 0a5953e

Browse files
committed
add test with --release switch on run
1 parent be8f4d2 commit 0a5953e

File tree

2 files changed

+89
-40
lines changed

2 files changed

+89
-40
lines changed

fpm/src/fpm_command_line.f90

Lines changed: 1 addition & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -489,9 +489,6 @@ subroutine set_help()
489489
' part of your default programming environment, as well as letting ', &
490490
' you share your projects with others in a similar manner. ', &
491491
' ', &
492-
' See the fpm(1) repository at https://fortran-lang.org/packages/fpm ', &
493-
' for a listing of registered projects. ', &
494-
' ', &
495492
' All output goes into the directory "build/" which can generally be ', &
496493
' removed and rebuilt if required. Note that if external packages are ', &
497494
' being used you need network connectivity to rebuild from scratch. ', &
@@ -545,6 +542,7 @@ subroutine set_help()
545542
' fpm run myprogram --release -- -x 10 -y 20 --title "my title" ', &
546543
' ', &
547544
'SEE ALSO ', &
545+
' ', &
548546
' + The fpm(1) home page is at https://github.com/fortran-lang/fpm ', &
549547
' + Registered fpm(1) packages are at https://fortran-lang.org/packages ', &
550548
' + The fpm(1) TOML file format is described at ', &

fpm/test/help_test/help_test.f90

Lines changed: 88 additions & 37 deletions
Original file line numberDiff line numberDiff line change
@@ -1,21 +1,22 @@
11
program help_test
22
use,intrinsic :: iso_fortran_env, only : stdin=>input_unit, stdout=>output_unit, stderr=>error_unit
33
implicit none
4-
integer :: i
4+
integer :: i, j
55
integer :: be, af
66
character(len=:),allocatable :: path
77
integer :: estat, cstat
88
character(len=256) :: message
99
logical,allocatable :: tally(:)
1010
!intel-bug!character(len=:),allocatable :: book1(:), book2(:)
11-
character(len=132),allocatable :: book1(:), book2(:)
11+
character(len=132),allocatable :: book1(:), book2(:), book3(:)
1212
!intel-bug!character(len=:),allocatable :: page1(:)
1313
character(len=132),allocatable :: page1(:)
1414
integer :: lines
1515
integer :: chars
1616
! run a variety of "fpm help" variations and verify expected files are generated
1717
character(len=*),parameter :: cmds(*) = [character(len=80) :: &
1818
! build manual as pieces using various help commands
19+
! debug version
1920
'fpm run -- --version ',& ! verify fpm version being used
2021
'fpm run -- --help > fpm_scratch_help.txt',&
2122
'fpm run -- help new >> fpm_scratch_help.txt',&
@@ -26,51 +27,70 @@ program help_test
2627
'fpm run -- help list >> fpm_scratch_help.txt',&
2728
'fpm run -- help help >> fpm_scratch_help.txt',&
2829
'fpm run -- --version >> fpm_scratch_help.txt',&
30+
! release version
31+
'fpm run --release -- --version ',& ! verify fpm version being used
32+
'fpm run --release -- --help > fpm_scratch_help3.txt',&
33+
'fpm run --release -- help new >> fpm_scratch_help3.txt',&
34+
'fpm run --release -- build --help >> fpm_scratch_help3.txt',&
35+
'fpm run --release -- help run >> fpm_scratch_help3.txt',&
36+
'fpm run --release -- help test >> fpm_scratch_help3.txt',&
37+
'fpm run --release -- help runner >> fpm_scratch_help3.txt',&
38+
'fpm run --release -- help list >> fpm_scratch_help3.txt',&
39+
'fpm run --release -- help help >> fpm_scratch_help3.txt',&
40+
'fpm run --release -- --version >> fpm_scratch_help3.txt',&
2941
! generate manual
3042
'fpm run -- help manual > fpm_scratch_manual.txt']
3143

3244
!'fpm run >> fpm_scratch_help.txt',&
3345
!'fpm run -- --list >> fpm_scratch_help.txt',&
3446
!'fpm run -- list --list >> fpm_scratch_help.txt',&
3547
character(len=*),parameter :: names(*)=[character(len=10) :: 'fpm','new','build','run','test','runner','list','help']
48+
character(len=:),allocatable :: add
3649

3750
write(*,'(g0:,1x)')'<INFO>TEST help SUBCOMMAND STARTED'
3851
if(allocated(tally))deallocate(tally)
3952
allocate(tally(0))
4053
call wipe('fpm_scratch_help.txt')
54+
call wipe('fpm_scratch_help3.txt')
4155
call wipe('fpm_scratch_manual.txt')
4256

4357
! check that output has NAME SYNOPSIS DESCRIPTION
44-
do i=1,size(names)
45-
write(*,*)'<INFO>check '//names(i)//' for NAME SYNOPSIS DESCRIPTION'
46-
path= 'fpm run -- help '//names(i)//' >fpm_scratch_help.txt'
47-
message=''
48-
call execute_command_line(path,exitstat=estat,cmdstat=cstat,cmdmsg=message)
49-
write(*,'(*(g0))')'<INFO>CMD=',path,' EXITSTAT=',estat,' CMDSTAT=',cstat,' MESSAGE=',trim(message)
50-
tally=[tally,all([estat.eq.0,cstat.eq.0])]
51-
call swallow('fpm_scratch_help.txt',page1)
52-
if(size(page1).lt.3)then
53-
write(*,*)'<ERROR>help for '//names(i)//' ridiculiously small'
54-
tally=[tally,.false.]
55-
exit
56-
endif
57-
!!write(*,*)findloc(page1,'NAME').eq.1
58-
be=count(.not.tally)
59-
tally=[tally,count(page1.eq.'NAME').eq.1]
60-
tally=[tally,count(page1.eq.'SYNOPSIS').eq.1]
61-
tally=[tally,count(page1.eq.'DESCRIPTION').eq.1]
62-
af=count(.not.tally)
63-
if(be.ne.af)then
64-
write(*,*)'<ERROR>missing expected sections in ',names(i)
65-
write(*,*)page1(1) ! assuming at least size 1 for debugging mingw
66-
write(*,*)count(page1.eq.'NAME')
67-
write(*,*)count(page1.eq.'SYNOPSIS')
68-
write(*,*)count(page1.eq.'DESCRIPTION')
69-
write(*,'(a)')page1
58+
do j=1,2
59+
if(j.eq.1)then
60+
ADD=' '
61+
else
62+
ADD=' --release '
7063
endif
71-
write(*,*)'<INFO>have completed ',count(tally),' tests'
72-
call wipe('fpm_scratch_help.txt')
73-
call wipe('fpm_scratch_manual.txt')
64+
do i=1,size(names)
65+
write(*,*)'<INFO>check '//names(i)//' for NAME SYNOPSIS DESCRIPTION'
66+
path= 'fpm run '//add//' -- help '//names(i)//' >fpm_scratch_help.txt'
67+
message=''
68+
call execute_command_line(path,exitstat=estat,cmdstat=cstat,cmdmsg=message)
69+
write(*,'(*(g0))')'<INFO>CMD=',path,' EXITSTAT=',estat,' CMDSTAT=',cstat,' MESSAGE=',trim(message)
70+
tally=[tally,all([estat.eq.0,cstat.eq.0])]
71+
call swallow('fpm_scratch_help.txt',page1)
72+
if(size(page1).lt.3)then
73+
write(*,*)'<ERROR>help for '//names(i)//' ridiculiously small'
74+
tally=[tally,.false.]
75+
exit
76+
endif
77+
!!write(*,*)findloc(page1,'NAME').eq.1
78+
be=count(.not.tally)
79+
tally=[tally,count(page1.eq.'NAME').eq.1]
80+
tally=[tally,count(page1.eq.'SYNOPSIS').eq.1]
81+
tally=[tally,count(page1.eq.'DESCRIPTION').eq.1]
82+
af=count(.not.tally)
83+
if(be.ne.af)then
84+
write(*,*)'<ERROR>missing expected sections in ',names(i)
85+
write(*,*)page1(1) ! assuming at least size 1 for debugging mingw
86+
write(*,*)count(page1.eq.'NAME')
87+
write(*,*)count(page1.eq.'SYNOPSIS')
88+
write(*,*)count(page1.eq.'DESCRIPTION')
89+
write(*,'(a)')page1
90+
endif
91+
write(*,*)'<INFO>have completed ',count(tally),' tests'
92+
call wipe('fpm_scratch_help.txt')
93+
enddo
7494
enddo
7595

7696

@@ -86,20 +106,35 @@ program help_test
86106
! compare book written in fragments with manual
87107
call swallow('fpm_scratch_help.txt',book1)
88108
call swallow('fpm_scratch_manual.txt',book2)
109+
call swallow('fpm_scratch_help3.txt',book3)
89110
! get rid of lines from run() which is not on stderr at the moment
90111
book1=pack(book1,index(book1,' + build/').eq.0)
91112
book2=pack(book1,index(book2,' + build/').eq.0)
113+
book3=pack(book3,index(book3,' + build/').eq.0)
92114
write(*,*)'<INFO>book1 ',size(book1), len(book1)
93115
write(*,*)'<INFO>book2 ',size(book2), len(book2)
116+
write(*,*)'<INFO>book2 ',size(book3), len(book3)
94117
if(size(book1).ne.size(book2))then
95-
write(*,*)'<ERROR>manual and appended pages are not the same size'
118+
write(*,*)'<ERROR>manual and "debug" appended pages are not the same size'
96119
tally=[tally,.false.]
97120
else
98121
if(all(book1.ne.book2))then
99122
tally=[tally,.false.]
100-
write(*,*)'<ERROR>manual and appended pages are not the same'
123+
write(*,*)'<ERROR>manual and "debug" appended pages are not the same'
101124
else
102-
write(*,*)'<INFO>manual and appended pages are the same'
125+
write(*,*)'<INFO>manual and "debug" appended pages are the same'
126+
tally=[tally,.true.]
127+
endif
128+
endif
129+
if(size(book3).ne.size(book2))then
130+
write(*,*)'<ERROR>manual and "release" appended pages are not the same size'
131+
tally=[tally,.false.]
132+
else
133+
if(all(book3.ne.book2))then
134+
tally=[tally,.false.]
135+
write(*,*)'<ERROR>manual and "release" appended pages are not the same'
136+
else
137+
write(*,*)'<INFO>manual and "release" appended pages are the same'
103138
tally=[tally,.true.]
104139
endif
105140
endif
@@ -110,15 +145,25 @@ program help_test
110145
chars=size(book2)*len(book2)
111146
lines=size(book2)
112147
if( (chars.lt.13000) .or. (lines.lt.350) )then
113-
write(*,*)'<ERROR>manual is suspiciously small, bytes=',chars,' lines=',lines
148+
write(*,*)'<ERROR>"debug" manual is suspiciously small, bytes=',chars,' lines=',lines
149+
tally=[tally,.false.]
150+
else
151+
write(*,*)'<INFO>"debug" manual size is bytes=',chars,' lines=',lines
152+
tally=[tally,.true.]
153+
endif
154+
chars=size(book3)*len(book3)
155+
lines=size(book3)
156+
if( (chars.lt.13000) .or. (lines.lt.350) )then
157+
write(*,*)'<ERROR>"release" manual is suspiciously small, bytes=',chars,' lines=',lines
114158
tally=[tally,.false.]
115159
else
116-
write(*,*)'<INFO>manual size is bytes=',chars,' lines=',lines
160+
write(*,*)'<INFO>"release" manual size is bytes=',chars,' lines=',lines
117161
tally=[tally,.true.]
118162
endif
119163

120164
write(*,'("<INFO>HELP TEST TALLY=",*(g0))')tally
121165
call wipe('fpm_scratch_help.txt')
166+
call wipe('fpm_scratch_help3.txt')
122167
call wipe('fpm_scratch_manual.txt')
123168
if(all(tally))then
124169
write(*,'(*(g0))')'<INFO>PASSED: all ',count(tally),' tests passed '
@@ -249,7 +294,13 @@ function page(array) result (table)
249294
position=1
250295
elseif(array(i).eq.cr)then
251296
elseif(linelength.ne.0)then
252-
table(linecount)(position:position)=array(i)
297+
if(position.gt.len(table))then
298+
write(*,*)'<ERROR> adding character past edge of text',table(linecount),array(i)
299+
elseif(linecount.gt.size(table))then
300+
write(*,*)'<ERROR> adding line past end of text',linecount,size(table)
301+
else
302+
table(linecount)(position:position)=array(i)
303+
endif
253304
position=position+1
254305
endif
255306
enddo

0 commit comments

Comments
 (0)