When calling a subroutine that "exits early" due to failed input parameter value validation I get:
Unhandled exception at 0x003d0541 in vmpsI.exe: 0xC0000005: Access violation reading location 0xfffffffc.
The subroutine and calling program are attached.
o When calling the subroutine with a value of N less than 6 the runtime error is ALWAYS encountered.
o When calling with N=6 it OCCASIONALLY will return to the calling program as expected.
o ONCE I got a fatal heap corruption error.
o The SUBROUTINE follows. Note that "SomeArray" must be declared to generate the RTE.
! ThisIsBS.
!
! Minimal routine to generate the WTF runtime error.
SUBROUTINE ThisIsBS(S, N, D, H1Vals, H2Vals, info)
IMPLICIT NONE
! Generic two-dimensional array.
TYPE Array2d
SEQUENCE
DOUBLE PRECISION, ALLOCATABLE, DIMENSION(:,:) :: val
END TYPE Array2d
INTEGER, INTENT(IN) :: S
INTEGER, INTENT(IN) :: N
INTEGER, INTENT(IN) :: D
DOUBLE PRECISION, DIMENSION(S,S), INTENT(IN) :: H1Vals
DOUBLE PRECISION, DIMENSION(S,S), INTENT(IN) :: H2Vals
INTEGER, INTENT(OUT) :: info
DOUBLE PRECISION :: foo
INTEGER :: bar
INTEGER :: baz
! This is an array that WOULD HAVE been used later in the subroutine
! had the validations passed. So please don't submit this code to
! TheDailyWTF.com. I just ripped out EVERYTHING from the subroutine
! but this, WHICH IS BLOWING THIS DAMNED THING UP!!!!!!!!!!!!!!!!!!!
TYPE(Array2d), DIMENSION(0:N+1,1:N) :: SomeArray
! Initialize the return value.
info = 0
! Ensure the value of N is valid.
IF (N < 4) THEN
info = -1
GOTO 999
ENDIF
! Ensure the value of D is greater than zero.
IF (D < 1) THEN
info = -2
GOTO 999
ENDIF
! Ensure the value of D is a power of 2.
IF (D /= 2**INT(LOG(D*1.) / LOG(2.))) THEN
info = -3
GOTO 999
ENDIF
! Ensure the values of N and D are valid and compatible. Specifically
! D may not be "too big" for N.
IF (D > 2**INT((N-4)/2)) THEN
info = -4
GOTO 999
ENDIF
999 RETURN
END
o The calling program follows.
! Run Variational Matrix Product States (VMPS).
!
! This program will run the VMPS routine.
PROGRAM RunVMPS
IMPLICIT NONE
! The number of spin states per particle.
INTEGER, PARAMETER :: S=2
! The number of particles in the chain.
INTEGER :: N
! The maximum bond dimension.
INTEGER :: D
! The values of the matrix elements of the DxD one- and two-body operators that
! make up the nearest neighbor Hamiltonian (for spin 1/2):
!
! | <up|O|up> <up|O|dn> |
! | <dn|O|up> <dn|O|dn> |
!
! Here we define two arrays:
! o H1Vals for the matrix elements of the one-body operator.
! o H2Vals for the matrix elements of the two-body operator.
DOUBLE PRECISION, DIMENSION(S,S) :: H1Vals
DOUBLE PRECISION, DIMENSION(S,S) :: H2Vals
! Return value from the VMPS routine.
INTEGER :: info
! Initialize the matrix elements of the operators.
! Since the values in Fortran arrays are stored in column major order, these
! values correspond to <up|O|up>, <dn|)|up>, <up|O|dn>, and <dn|O|dn>,
! respectively. To convert these values into their 2x2 matrix we use:
!
! TRANSPOSE(RESHAPE(..., (/ 2, 2 /)))
!
H1Vals = TRANSPOSE(RESHAPE((/ -1.0d0, 0.0d0, 0.0d0, 1.0d0 /), (/ 2, 2 /)))
H2Vals = TRANSPOSE(RESHAPE((/ 0.0d0, 1.0d0, 1.0d0, 0.0d0 /), (/ 2, 2 /)))
WRITE(*,*) "I am alive."
N=4
D=3
CALL ThisIsBS(S,N,D,H1Vals,H2Vals,info)
WRITE(*,*) "I am dead."
STOP
END
My environment:
o Windows 7 Ultimate 64 bit SP1
o Visual Studio 2010 Premium
o Intel(R) Visual Fortran Package ID: w_fcompxe_2013_sp1.1.139
o Intel(R) Visual Fortran Composer XE 2013 SP1 Update 1 Integration for Microsoft Visual Studio* 2010, 14.0.0074.2010, Copyright (C) 2002-2013 Intel Corporation