Skip to content

Commit 5de92b8

Browse files
committed
mingw bug
1 parent 0631665 commit 5de92b8

File tree

1 file changed

+7
-6
lines changed

1 file changed

+7
-6
lines changed

fpm/test/help_test/help_test.f90

Lines changed: 7 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -7,9 +7,10 @@ program help_test
77
integer :: estat, cstat
88
character(len=256) :: message
99
logical,allocatable :: tally(:)
10-
character(len=:),allocatable :: book1(:), book2(:)
11-
!intel_bug!character(len=:),allocatable :: page1(:)
12-
character(len=:),allocatable :: page1(:)
10+
!intel-bug!character(len=:),allocatable :: book1(:), book2(:)
11+
character(len=132),allocatable :: book1(:), book2(:)
12+
!intel-bug!character(len=:),allocatable :: page1(:)
13+
character(len=132),allocatable :: page1(:)
1314
integer :: lines
1415
integer :: chars
1516
! run a variety of "fpm help" variations and verify expected files are generated
@@ -187,7 +188,7 @@ subroutine swallow(FILENAME,pageout)
187188
implicit none
188189
character(len=*),intent(in) :: FILENAME ! file to read
189190
!intel-bug!character(len=:),allocatable,intent(out) :: pageout(:) ! page to hold file in memory
190-
character(len=:),allocatable,intent(out) :: pageout(:) ! page to hold file in memory
191+
character(len=132),allocatable,intent(out) :: pageout(:) ! page to hold file in memory
191192
character(len=1),allocatable :: text(:) ! array to hold file in memory
192193

193194
call slurp(FILENAME,text) ! allocate character array and copy file into it
@@ -206,7 +207,7 @@ function page(array) result (table)
206207

207208
character(len=1),intent(in) :: array(:)
208209
!intel-bug!character(len=:),allocatable :: table(:)
209-
character(len=:),allocatable :: table(:)
210+
character(len=132),allocatable :: table(:)
210211
integer :: i
211212
integer :: linelength
212213
integer :: length
@@ -238,7 +239,7 @@ function page(array) result (table)
238239

239240
if(allocated(table))deallocate(table)
240241
!intel-bug!allocate(character(len=linelength) :: table(lines))
241-
allocate(character(len=linelength) :: table(lines))
242+
allocate(character(len=132) :: table(lines))
242243
table=' '
243244
linecount=1
244245
position=1

0 commit comments

Comments
 (0)