Here is the third (and last) PGI compiler bug that I have run across while working on a rather large project. Of the two that I reported this week, one bug has already been fixed in the 8.0-2 release, as I found after downloading the latest version.
module hdbl
implicit none
TYPE :: zdtyp
INTEGER :: m, n, ne
CHARACTER, ALLOCATABLE, DIMENSION(:) :: id
END TYPE
type m2d
integer :: idx
type(zdtyp) :: A_mat
end type m2d
contains
subroutine mfin(coarse)
type(m2d), allocatable, dimension(:), intent(inout) :: coarse
integer :: n_levels
integer :: alloc_stat
if (allocated(coarse)) then
n_levels = size(coarse)
deallocate(coarse, stat=alloc_stat) ! <=== line for which error is reported
if (alloc_stat .ne. 0) write(*,*) " deallocation error"
end if
return
end subroutine mfin
end module hdbl
The 32-bit Windows compiler, V.8.0-2, says:
PGF90-S-0000-Internal compiler error. size_of:bad dtype 297 (xmi20d.f90: 18)
PGF90-S-0000-Internal compiler error. size_of: bad dtype 0 (xmi20d.f90: 18)
PGF90-S-0000-Internal compiler error. scale_of:bad dtype 297 (xmi20d.f90: 18)
PGF90-S-0000-Internal compiler error. scale_of: bad dtype 0 (xmi20d.f90: 18)
PGF90-S-0000-Internal compiler error. size_of:bad dtype 297 (xmi20d.f90: 18)
PGF90-S-0000-Internal compiler error. size_of: bad dtype 0 (xmi20d.f90: 18)
PGF90-S-0000-Internal compiler error. scale_of:bad dtype 297 (xmi20d.f90: 18)
PGF90-S-0000-Internal compiler error. scale_of: bad dtype 0 (xmi20d.f90: 18)
0 inform, 0 warnings, 8 severes, 0 fatal for mfin