! DebugBug.f90 ! ! FUNCTIONS: ! DebugBug - Entry point of console application. ! module IGES !************************************************************************* ! Debug Watch error reproducer !************************************************************************* ! This code is a stripped down version of a module that I used for storing CAD ! Model information. ! I removed various defintions until the error no longer appeared and then stepped back ! to reproduce the error ! Error occurs when trying to Watch the ival or rval allocatable arrays defined in the ! PARA_DATA user defined type. ! The integer(2) :: on = 0 causes the problem. It is not related to integer type, just its ! presence within the DIR_PARA data structure ! After Commenting it out the elements of pm can be examined as expected. ! ! Stephen Sutcliffe (04-Aug-2020) ! ! I hope this helps Intel to resolve this annoying problem. type PARA_DATA integer :: ni = 0 integer :: nr = 0 real(8),allocatable :: rval(:) integer,allocatable :: ival(:) end type ! Data Structures type DIR_PARA integer(2) :: on = 0 ! HINT: Comment this variable out and debugger watch seems to work ok type(PARA_DATA) :: pm ! Parameter Data end type type(DIR_PARA),allocatable :: dr(:) integer :: ndr = 0 type IGES_OBJECT integer :: ndr = 0 type(DIR_PARA),allocatable :: dr(:) ! Data end type integer :: nIgo = 0 type(IGES_OBJECT),allocatable :: igo(:) contains subroutine igo_AllocPrm(drobj,ni,nr,ier) !************************************************************* ! Allocate Parameter Arrays !************************************************************* implicit none ! Arguments type(DIR_PARA),intent(inout) :: drobj integer,intent(in) :: ni integer,intent(in) :: nr integer,intent(out) :: ier ! Initialise ier = 0 drobj%pm%ni = ni drobj%pm%nr = nr if(allocated(drobj%pm%ival)) deallocate(drobj%pm%ival) if(drobj%pm%ni.gt.0) then allocate(drobj%pm%ival(drobj%pm%ni),stat=ier) if(ier.eq.0) then drobj%pm%ival = 0 endif endif if(allocated(drobj%pm%rval)) deallocate(drobj%pm%rval) if(drobj%pm%nr.gt.0) then allocate(drobj%pm%rval(drobj%pm%nr),stat=ier) if(ier.eq.0) then drobj%pm%rval = 0 endif endif return end subroutine end module !**************************************************************************** ! PROGRAM: DebugBug ! PURPOSE: Entry point for the console application. !**************************************************************************** program DebugBug use IGES implicit none ! Variables integer :: ier integer :: i,j,k ! Initialise nIgo = 3 ! Body of DebugBug allocate(igo(nIgo),stat=ier) if(ier.ne.0) goto 999 do i = 1 , nIgo igo(i)%ndr = i allocate(igo(i)%dr(igo(i)%ndr),stat=ier) if(ier.ne.0) goto 999 do j = 1 , igo(i)%ndr igo(i)%dr(j)%pm%ni = 4 igo(i)%dr(j)%pm%nr = 2 call igo_AllocPrm(igo(i)%dr(j),4,2,ier) if(ier.ne.0) goto 999 do k = 1 , igo(i)%dr(j)%pm%ni igo(i)%dr(j)%pm%ival(k) = -k enddo do k = 1 , igo(i)%dr(j)%pm%nr igo(i)%dr(j)%pm%rval(k) = float(k)**2 enddo enddo enddo print *, 'End Test' if(allocated(Igo)) deallocate (igo) stop 999 continue print *, 'Allocation Error Occured' stop end program DebugBug