Skip to content

Commit 72b960b

Browse files
authored
Hacky fix for the help/new test (#352)
1 parent 8f27d57 commit 72b960b

File tree

2 files changed

+61
-74
lines changed

2 files changed

+61
-74
lines changed

fpm/test/help_test/help_test.f90

Lines changed: 38 additions & 63 deletions
Original file line numberDiff line numberDiff line change
@@ -2,6 +2,8 @@ program help_test
22
! note hardcoded len=k1 instead of len=: in this test is a work-around a gfortran bug in old
33
! pre-v8.3 versions
44
use,intrinsic :: iso_fortran_env, only : stdin=>input_unit, stdout=>output_unit, stderr=>error_unit
5+
use fpm_filesystem, only : dirname, join_path, exists
6+
use fpm_environment, only : get_os_type, OS_WINDOWS
57
implicit none
68
integer :: i, j
79
integer :: be, af
@@ -11,7 +13,7 @@ program help_test
1113
character(len=k1) :: message
1214
logical,allocatable :: tally(:)
1315
!intel-bug!character(len=:),allocatable :: book1(:), book2(:)
14-
character(len=k1),allocatable :: book1(:), book2(:), book3(:)
16+
character(len=k1),allocatable :: book1(:), book2(:)
1517
!intel-bug!character(len=:),allocatable :: page1(:)
1618
character(len=k1),allocatable :: page1(:)
1719
integer :: lines
@@ -20,58 +22,57 @@ program help_test
2022
character(len=*),parameter :: cmds(*) = [character(len=80) :: &
2123
! build manual as pieces using various help commands
2224
! debug version
23-
'fpm run -- --version ',& ! verify fpm version being used
24-
'fpm run -- --help > fpm_scratch_help.txt',&
25-
'fpm run -- help new >> fpm_scratch_help.txt',&
26-
'fpm run -- help update >> fpm_scratch_help.txt',&
27-
'fpm run -- build --help >> fpm_scratch_help.txt',&
28-
'fpm run -- help run >> fpm_scratch_help.txt',&
29-
'fpm run -- help test >> fpm_scratch_help.txt',&
30-
'fpm run -- help runner >> fpm_scratch_help.txt',&
31-
'fpm run -- help install >> fpm_scratch_help.txt',&
32-
'fpm run -- help list >> fpm_scratch_help.txt',&
33-
'fpm run -- help help >> fpm_scratch_help.txt',&
34-
'fpm run -- --version >> fpm_scratch_help.txt',&
35-
! release version
36-
'fpm run --release -- --version ',& ! verify fpm version being used
37-
'fpm run --release -- --help > fpm_scratch_help3.txt',&
38-
'fpm run --release -- help new >> fpm_scratch_help3.txt',&
39-
'fpm run --release -- help update >> fpm_scratch_help3.txt',&
40-
'fpm run --release -- build --help >> fpm_scratch_help3.txt',&
41-
'fpm run --release -- help run >> fpm_scratch_help3.txt',&
42-
'fpm run --release -- help test >> fpm_scratch_help3.txt',&
43-
'fpm run --release -- help runner >> fpm_scratch_help3.txt',&
44-
'fpm run --release -- help install >> fpm_scratch_help3.txt',&
45-
'fpm run --release -- help list >> fpm_scratch_help3.txt',&
46-
'fpm run --release -- help help >> fpm_scratch_help3.txt',&
47-
'fpm run --release -- --version >> fpm_scratch_help3.txt',&
25+
' --version ',& ! verify fpm version being used
26+
' --help > fpm_scratch_help.txt',&
27+
' help new >> fpm_scratch_help.txt',&
28+
' help update >> fpm_scratch_help.txt',&
29+
' build --help >> fpm_scratch_help.txt',&
30+
' help run >> fpm_scratch_help.txt',&
31+
' help test >> fpm_scratch_help.txt',&
32+
' help runner >> fpm_scratch_help.txt',&
33+
' help install >> fpm_scratch_help.txt',&
34+
' help list >> fpm_scratch_help.txt',&
35+
' help help >> fpm_scratch_help.txt',&
36+
' --version >> fpm_scratch_help.txt',&
4837
! generate manual
49-
'fpm run -- help manual > fpm_scratch_manual.txt']
38+
' help manual > fpm_scratch_manual.txt']
5039

5140
!'fpm run >> fpm_scratch_help.txt',&
5241
!'fpm run -- --list >> fpm_scratch_help.txt',&
5342
!'fpm run -- list --list >> fpm_scratch_help.txt',&
5443
character(len=*),parameter :: names(*)=[character(len=10) ::&
5544
'fpm','new','update','build','run','test','runner','install','list','help']
56-
character(len=:),allocatable :: add
45+
character(len=:), allocatable :: prog
46+
integer :: length
47+
48+
! FIXME: Super hacky way to get the name of the fpm executable,
49+
! it works better than invoking fpm again but should be replaced ASAP.
50+
call get_command_argument(0, length=length)
51+
allocate(character(len=length) :: prog)
52+
call get_command_argument(0, prog)
53+
path = dirname(prog)
54+
if (get_os_type() == OS_WINDOWS) then
55+
prog = join_path(path, "..", "app", "fpm.exe")
56+
if (.not.exists(prog)) then
57+
prog = join_path(path, "..", "..", "app", "fpm.exe")
58+
end if
59+
else
60+
prog = join_path(path, "..", "app", "fpm")
61+
if (.not.exists(prog)) then
62+
prog = join_path(path, "..", "..", "app", "fpm")
63+
end if
64+
end if
5765

5866
write(*,'(g0:,1x)')'<INFO>TEST help SUBCOMMAND STARTED'
5967
if(allocated(tally))deallocate(tally)
6068
allocate(tally(0))
6169
call wipe('fpm_scratch_help.txt')
62-
call wipe('fpm_scratch_help3.txt')
6370
call wipe('fpm_scratch_manual.txt')
6471

6572
! check that output has NAME SYNOPSIS DESCRIPTION
66-
do j=1,2
67-
if(j.eq.1)then
68-
ADD=' '
69-
else
70-
ADD=' --release '
71-
endif
7273
do i=1,size(names)
7374
write(*,*)'<INFO>check '//names(i)//' for NAME SYNOPSIS DESCRIPTION'
74-
path= 'fpm run '//add//' -- help '//names(i)//' >fpm_scratch_help.txt'
75+
path= prog // ' help '//names(i)//' >fpm_scratch_help.txt'
7576
message=''
7677
call execute_command_line(path,exitstat=estat,cmdstat=cstat,cmdmsg=message)
7778
write(*,'(*(g0))')'<INFO>CMD=',path,' EXITSTAT=',estat,' CMDSTAT=',cstat,' MESSAGE=',trim(message)
@@ -99,13 +100,12 @@ program help_test
99100
write(*,*)'<INFO>have completed ',count(tally),' tests'
100101
call wipe('fpm_scratch_help.txt')
101102
enddo
102-
enddo
103103

104104

105105
! execute the fpm(1) commands
106106
do i=1,size(cmds)
107107
message=''
108-
path= cmds(i)
108+
path= prog // cmds(i)
109109
call execute_command_line(path,exitstat=estat,cmdstat=cstat,cmdmsg=message)
110110
write(*,'(*(g0))')'<INFO>CMD=',path,' EXITSTAT=',estat,' CMDSTAT=',cstat,' MESSAGE=',trim(message)
111111
tally=[tally,all([estat.eq.0,cstat.eq.0])]
@@ -114,14 +114,11 @@ program help_test
114114
! compare book written in fragments with manual
115115
call swallow('fpm_scratch_help.txt',book1)
116116
call swallow('fpm_scratch_manual.txt',book2)
117-
call swallow('fpm_scratch_help3.txt',book3)
118117
! get rid of lines from run() which is not on stderr at the moment
119118
book1=pack(book1,index(book1,' + build/').eq.0)
120119
book2=pack(book1,index(book2,' + build/').eq.0)
121-
book3=pack(book3,index(book3,' + build/').eq.0)
122120
write(*,*)'<INFO>book1 ',size(book1), len(book1)
123121
write(*,*)'<INFO>book2 ',size(book2), len(book2)
124-
write(*,*)'<INFO>book2 ',size(book3), len(book3)
125122
if(size(book1).ne.size(book2))then
126123
write(*,*)'<ERROR>manual and "debug" appended pages are not the same size'
127124
tally=[tally,.false.]
@@ -134,18 +131,6 @@ program help_test
134131
tally=[tally,.true.]
135132
endif
136133
endif
137-
if(size(book3).ne.size(book2))then
138-
write(*,*)'<ERROR>manual and "release" appended pages are not the same size'
139-
tally=[tally,.false.]
140-
else
141-
if(all(book3.ne.book2))then
142-
tally=[tally,.false.]
143-
write(*,*)'<ERROR>manual and "release" appended pages are not the same'
144-
else
145-
write(*,*)'<INFO>manual and "release" appended pages are the same'
146-
tally=[tally,.true.]
147-
endif
148-
endif
149134

150135
! overall size of manual
151136
!chars=size(book2)
@@ -159,19 +144,9 @@ program help_test
159144
write(*,*)'<INFO>"debug" manual size in bytes=',chars,' lines=',lines
160145
tally=[tally,.true.]
161146
endif
162-
chars=sum(len_trim(book3)) ! SUM TRIMMED LENGTH
163-
lines=size(book3)
164-
if( (chars.lt.12000) .or. (lines.lt.350) )then
165-
write(*,*)'<ERROR>"release" manual is suspiciously small, bytes=',chars,' lines=',lines
166-
tally=[tally,.false.]
167-
else
168-
write(*,*)'<INFO>"release" manual size in bytes=',chars,' lines=',lines
169-
tally=[tally,.true.]
170-
endif
171147

172148
write(*,'("<INFO>HELP TEST TALLY=",*(g0))')tally
173149
call wipe('fpm_scratch_help.txt')
174-
call wipe('fpm_scratch_help3.txt')
175150
call wipe('fpm_scratch_manual.txt')
176151
if(all(tally))then
177152
write(*,'(*(g0))')'<INFO>PASSED: all ',count(tally),' tests passed '

fpm/test/new_test/new_test.f90

Lines changed: 23 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,7 @@
11
program new_test
22
use,intrinsic :: iso_fortran_env, only : stdin=>input_unit, stdout=>output_unit, stderr=>error_unit
3-
use fpm_filesystem, only : is_dir, list_files, exists, windows_path, join_path
3+
use fpm_filesystem, only : is_dir, list_files, exists, windows_path, join_path, &
4+
dirname
45
use fpm_strings, only : string_t, operator(.in.)
56
use fpm_environment, only : run, get_os_type
67
use fpm_environment, only : OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_CYGWIN, OS_SOLARIS, OS_FREEBSD, OS_WINDOWS
@@ -158,18 +159,29 @@ program new_test
158159
stop 5
159160
endif
160161
contains
161-
function get_command_path() result(command_path)
162-
character(len=:), allocatable :: command_path
162+
function get_command_path() result(prog)
163+
character(len=:), allocatable :: prog
163164

164-
type(string_t), allocatable :: files(:)
165-
integer :: i
165+
character(len=:), allocatable :: path
166+
integer :: length
166167

167-
call list_files("build", files)
168-
do i = 1, size(files)
169-
if (index(files(i)%s, "gfortran") > 0) then
170-
command_path = join_path(files(i)%s, "app", "fpm")
171-
return
168+
! FIXME: Super hacky way to get the name of the fpm executable,
169+
! it works better than invoking fpm again but should be replaced ASAP.
170+
call get_command_argument(0, length=length)
171+
allocate(character(len=length) :: prog)
172+
call get_command_argument(0, prog)
173+
path = dirname(prog)
174+
if (get_os_type() == OS_WINDOWS) then
175+
prog = join_path(path, "..", "app", "fpm.exe")
176+
if (.not.exists(prog)) then
177+
prog = join_path(path, "..", "..", "app", "fpm.exe")
172178
end if
173-
end do
179+
else
180+
prog = join_path(path, "..", "app", "fpm")
181+
if (.not.exists(prog)) then
182+
prog = join_path(path, "..", "..", "app", "fpm")
183+
end if
184+
end if
185+
174186
end function
175187
end program new_test

0 commit comments

Comments
 (0)