Intel® Fortran Compiler
Build applications that can scale for the future with optimized code designed for Intel® Xeon® and compatible processors.

Access violation error when subroutine is called

Jon_D
New Contributor I
346 Views

Stripped-down code shown below is generating "access violation" run-time error when ReadAttribute subroutine is called. The error occurs when the program is compiled with IVF 17.0 but not with IVF 16.0. Maybe a bug in the compiler?

Thanks!

 

MODULE HDF5_CLASS
    IMPLICIT NONE

  TYPE :: HDF5FileType
  CONTAINS
      PROCEDURE,PASS :: New             => New_HDF5File
      PROCEDURE,PASS :: ReadAttribute
      GENERIC        :: ReadData        => ReadAttribute                                         
  END TYPE HDF5FileType
    
CONTAINS    

  SUBROUTINE New_HDF5File(ThisFile,FileName,lInputFile,AccessType,Status) 
    CLASS(HDF5FileType)                  :: ThisFile
    CHARACTER(LEN=*),INTENT(IN)          :: FileName 
    LOGICAL,INTENT(IN)                   :: lInputFile
    CHARACTER(LEN=*),OPTIONAL,INTENT(IN) :: AccessType  
    INTEGER,OPTIONAL,INTENT(OUT)         :: Status

    CHARACTER(LEN=11) :: cAttributesDir
    LOGICAL           :: TrackTime
    
    cAttributesDir = '/Attributes'        
    CALL ThisFile%ReadAttribute(cAttributesDir,'TimeStep%TrackTime',ScalarAttrData=TrackTime)

  END SUBROUTINE New_HDF5File

  
  SUBROUTINE ReadAttribute(ThisFile,cGrpOrDset,cAttrName,ScalarAttrData,ArrayAttrData)
    CLASS(HDF5FileType),INTENT(IN) :: ThisFile
    CHARACTER(LEN=*),INTENT(IN)    :: cGrpOrDset,cAttrName
    CLASS(*),OPTIONAL,INTENT(OUT)  :: ScalarAttrData,ArrayAttrData(:)    
  END SUBROUTINE ReadAttribute
    
END MODULE HDF5_CLASS
    
    
PROGRAM Test
    USE HDF5_CLASS
    IMPLICIT NONE
    
    TYPE(HDF5FileType) :: ThisFile
    
    CALL ThisFile%New('SomeFileName',.TRUE.)
    
END

 

0 Kudos
4 Replies
Kevin_D_Intel
Employee
346 Views

Yes, possibly. I reproduced the fault with our latest 17.0 update 1 but cannot reproduce it with our internal 17.0 development build so there may already be a fix coming. I reported it to Development and will let you know. Thank you for the convenient reproducer.

(Internal tracking id: DPD200416622)

0 Kudos
Kevin_D_Intel
Employee
346 Views

Development confirmed this instance is similar to an earlier reported instance (here) and that a fix is expected in our next PSXE 2017 Update 2 tentatively due to release in the next month.

As a work around in the meantime, the error is avoidable by filling all the optional dummy args for the call as shown in the revision to your test case below (see ! work around for added/changed lines).

MODULE HDF5_CLASS 
    IMPLICIT NONE 

  TYPE :: HDF5FileType 
  CONTAINS 
      PROCEDURE,PASS :: New             => New_HDF5File 
      PROCEDURE,PASS :: ReadAttribute 
      GENERIC        :: ReadData        => ReadAttribute                                         
  END TYPE HDF5FileType 
    
CONTAINS     

  SUBROUTINE New_HDF5File(ThisFile,FileName,lInputFile,AccessType,Status) 
    CLASS(HDF5FileType)                  :: ThisFile 
    CHARACTER(LEN=*),INTENT(IN)          :: FileName 
    LOGICAL,INTENT(IN)                   :: lInputFile 
    CHARACTER(LEN=*),OPTIONAL,INTENT(IN) :: AccessType   
    INTEGER,OPTIONAL,INTENT(OUT)         :: Status 

    CHARACTER(LEN=11) :: cAttributesDir 
    LOGICAL           :: TrackTime 
    character(len=8) :: ArrAttrData(2)               ! work around

    cAttributesDir = '/Attributes' 
    ArrAttrData(:) = ['/Attrib0','/Attrib1']         ! work around
            
    CALL ThisFile%ReadAttribute(cAttributesDir,'TimeStep%TrackTime',ScalarAttrData=TrackTime,ArrayAttrData=ArrAttrData)                                    ! work around

  END SUBROUTINE New_HDF5File 

  
  SUBROUTINE ReadAttribute(ThisFile,cGrpOrDset,cAttrName,ScalarAttrData,ArrayAttrData) 
    CLASS(HDF5FileType),INTENT(IN) :: ThisFile 
    CHARACTER(LEN=*),INTENT(IN)    :: cGrpOrDset,cAttrName 
    CLASS(*),OPTIONAL,INTENT(OUT)  :: ScalarAttrData,ArrayAttrData(:)     
  END SUBROUTINE ReadAttribute 
    
END MODULE HDF5_CLASS 
    
    
PROGRAM Test 
    USE HDF5_CLASS 
    IMPLICIT NONE 
    
    TYPE(HDF5FileType) :: ThisFile 
    integer status                                               ! work around
    status = 0                                                   ! work around
    CALL ThisFile%New('SomeFileName',.TRUE.,'Default',status)    ! work around
    print *,"OK" 
    
END 

 

0 Kudos
Mark_H_
Beginner
346 Views

I noticed an inconsistent declaration in your code:

22     character(len=7) :: ArrAttrData(2)               ! work around
23  
24     cAttributesDir = '/Attributes'
25     ArrAttrData(:) = ['/Attrib0','/Attrib1']         ! work around

 

You have "len=7" and the data strings are of "len=8". Not sure if this is causing your error though.

0 Kudos
Kevin_D_Intel
Employee
346 Views

Thank you. I corrected that above. That was a mistake in the work around code provided and not in the OP's code and not related to the original error.

0 Kudos
Reply