- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
ifort 10.1 compiler bug: allocated allocatable array is not allocated with openmp. The code does not violate the 2003 specs and executes fine in serial. Compiled with "-std03 -openmp -fpp -DDEBUG -g -debug all -C -CB -CU -module /tmp -error-limit 3" and executed generates an error:
forrtl: severe (408): fort: (8): Attempt to fetch from allocatable variable USEDD when it is not allocated
I am quite sure this is a bug, however, I am using a free non-commercial licence so can not access the premier support page.
Below is the code to reproduce the problem:
MODULE NS3T10 USE OMP_LIB IMPLICIT NONE CONTAINS SUBROUTINE SETUP_A INTEGER, DIMENSION(:), POINTER :: USED INTEGER, DIMENSION(:), ALLOCATABLE :: USEDD INTEGER :: NTH=1, MYID=1 !$OMP PARALLEL DEFAULT(SHARED) PRIVATE(NTH, MYID) NTH = OMP_GET_NUM_THREADS() MYID = OMP_GET_THREAD_NUM() !$OMP SINGLE PRINT *, NTH, MYID CALL RESIZE(USEDD,2) USEDD = 0 PRINT *, USEDD !$OMP END SINGLE !$OMP END PARALLEL END SUBROUTINE SETUP_A SUBROUTINE RESIZE(V,S) INTEGER, DIMENSION(:), ALLOCATABLE, INTENT(INOUT) :: V INTEGER, INTENT(IN) :: S IF(ALLOCATED(V)) DEALLOCATE(V) ALLOCATE(V(S)) PRINT *, 'RESIZE : ', S END SUBROUTINE RESIZE END MODULE NS3T10 PROGRAM NS3T USE OMP_LIB USE NS3T10 IMPLICIT NONE CALL SETUP_A END PROGRAM NS3T
Link Copied
14 Replies
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Domel,
I think you want to change
CONTAINS
SUBROUTINE SETUP_A
INTEGER, DIMENSION(:), POINTER :: USED
INTEGER, DIMENSION(:), ALLOCATABLE :: USEDD
...
to
INTEGER, DIMENSION(:), POINTER :: USED
INTEGER, DIMENSION(:), ALLOCATABLE :: USEDD
CONTAINS
SUBROUTINE SETUP_A
...
As-was, only setup would see USED and USEDD.
If that still give you problems then you may need to add an interface block
INTEGER, DIMENSION(:), POINTER :: USED
INTEGER, DIMENSION(:), ALLOCATABLE :: USEDD
CONTAINS
SUBROUTINE SETUP_A
INTERFACE
SUBROUTINE RESIZE(V,S)
INTEGER, DIMENSION(:), ALLOCATABLE, INTENT(INOUT) :: V
INTEGER, INTENT(IN) :: S
END SUBROUTINE RESIZE
END INTERFACE
...
Jim Dempsey
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
the problem occurs only when compiling with
-std03 -openmp -openmp-report1 -fpp -DDEBUG -g -debug all -C -CA -CB -CU -module /tmp -error-limit 3
and not
-openmp -openmp-report1 -fpp -DDEBUG -O3 -mtune=core2 -module /tmp -error-limit 3
Compiler bug most obviously.
-std03 -openmp -openmp-report1 -fpp -DDEBUG -g -debug all -C -CA -CB -CU -module /tmp -error-limit 3
and not
-openmp -openmp-report1 -fpp -DDEBUG -O3 -mtune=core2 -module /tmp -error-limit 3
Compiler bug most obviously.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Any licensed user can submit issues through Premier Support. If you did not sign up for a support account initially, you can do so by reregistering your serial number and checking the box for a support account.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
I can reproduce this single-threaded. The key is that you have to ask for "-check pointer" (which is implicit in -C) as well as -openmp. We've had other issues in the past where this feature improperly decided that a variable was not allocated when it was. I'll pass this on to the developers.
The easy workaround is to not use -check pointer (or specify only other -check options.)
The easy workaround is to not use -check pointer (or specify only other -check options.)
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Jim,
I don't understand your reply - why do you think restructuring the code is necessary? USEDD is used only in SETUP_A. It is passed as an argument to RESIZE but that doesn't require USEDD to be visible as a name in RESIZE.
I don't understand your reply - why do you think restructuring the code is necessary? USEDD is used only in SETUP_A. It is passed as an argument to RESIZE but that doesn't require USEDD to be visible as a name in RESIZE.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Hi, I find this is actually -g that is causing the problem for me. I am able to compile this unlucky code with -C but not with -g -C. Exact lines to be sure:
-std03 -openmp -openmp-report1 -fpp -DDEBUG -mtune=core2 -C -module /tmp -error-limit 3
will work. '-g' inserted before '-C' will break the thing. I would be very glad to have it fixed as I prefer ALLOCATABLE arrays to POINTERs.
-Dominik
-std03 -openmp -openmp-report1 -fpp -DDEBUG -mtune=core2 -C -module /tmp -error-limit 3
will work. '-g' inserted before '-C' will break the thing. I would be very glad to have it fixed as I prefer ALLOCATABLE arrays to POINTERs.
-Dominik
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
-g is a side-effect in that it implies -Od. We will fix this, but it will take a while for you to see the fix. Let me suggest that you not use -C and instead specify the specific -check options you want, without "pointer".
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Steve,
I can not find -Od option in the compiler's help. Once again, to make sure we converge, I have no problem with any of -C, -CA, -CB, -CU. I am having problems only with -g switch on the compile line, which implies -O0. Adding explicit -O1 (still keeping -g) will crash too, but not -O2 or -O3. So e.g.:
FFLAGS = -std03 -openmp -openmp-report1 -fpp -DDEBUG -debug all -g -mtune=core2 -O2 -C -CA -CB -CU -module /tmp -error-limit 3
will work
FFLAGS = -std03 -openmp -openmp-report1 -fpp -DDEBUG -debug all -g -mtune=core2 -O1 -C -CA -CB -CU -module /tmp -error-limit 3
will not, (neither will -O0).
-- Dominik
I can not find -Od option in the compiler's help. Once again, to make sure we converge, I have no problem with any of -C, -CA, -CB, -CU. I am having problems only with -g switch on the compile line, which implies -O0. Adding explicit -O1 (still keeping -g) will crash too, but not -O2 or -O3. So e.g.:
FFLAGS = -std03 -openmp -openmp-report1 -fpp -DDEBUG -debug all -g -mtune=core2 -O2 -C -CA -CB -CU -module /tmp -error-limit 3
will work
FFLAGS = -std03 -openmp -openmp-report1 -fpp -DDEBUG -debug all -g -mtune=core2 -O1 -C -CA -CB -CU -module /tmp -error-limit 3
will not, (neither will -O0).
-- Dominik
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
... and leaving out all -Cx switches completely will still crash, if -g is present. I forgot to add this important info in the previous post.
Dominik
Dominik
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
I can't reproduce that - you don't get that particular error unless -check pointer is enabled. Show me a log of the compile and run that shows the error.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Here the code again, now modified a bit to be all in one file.
MODULE NS3T10
USE OMP_LIB
IMPLICIT NONE
INTEGER, PARAMETER :: NK = 34
CONTAINS
SUBROUTINE SETUP_A
! INTEGER, DIMENSION(:), POINTER :: USED
INTEGER, DIMENSION(:), ALLOCATABLE :: USED
INTEGER :: NTH=1, MYID=1
! CALL RESIZE(USED,1)
! CALL PRINT_ADDRESS(USED)
!$OMP PARALLEL DEFAULT(SHARED) PRIVATE(NTH, MYID)
NTH = OMP_GET_NUM_THREADS()
MYID = OMP_GET_THREAD_NUM()
PRINT *, NTH, MYID
!$OMP SINGLE
! CALL PRINT_ADDRESS(USED)
! PRINT *, ALLOCATED(USED)
CALL RESIZE(USED,NTH)
! CALL PRINT_ADDRESS(USED)
USED = 10
PRINT *, USED
!$OMP END SINGLE
!$OMP END PARALLEL
! CALL PRINT_ADDRESS(USED)
END SUBROUTINE SETUP_A
SUBROUTINE RESIZE(V,S)
INTEGER, DIMENSION(:), ALLOCATABLE, INTENT(INOUT) :: V
INTEGER, INTENT(IN) :: S
IF(ALLOCATED(V)) DEALLOCATE(V)
ALLOCATE(V(S))
PRINT *, 'RESIZE : ', S
! CALL PRINT_ADDRESS(V)
END SUBROUTINE RESIZE
!
! SUBROUTINE RESIZE(V,S)
! INTEGER, DIMENSION(:), POINTER :: V
! INTEGER, INTENT(IN) :: S
! NULLIFY(V)
! ALLOCATE(V(S))
! PRINT *, 'RESIZE : ', S
! END SUBROUTINE RESIZE
END MODULE NS3T10
PROGRAM NS3T
USE OMP_LIB
USE NS3T10
IMPLICIT NONE
CALL SETUP_A
END PROGRAM NS3T
The compilation:
ifort -std03 -openmp -openmp-report1 -fpp -DDEBUG -debug all -g -mtune=core2 -module /tmp -error-limit 3 -I /scratch/domel/pack/hdf5-1.6.7/fortran/src -o /tmp/NS3T10_MAIN_TEST1.o -c NS3T10_MAIN_TEST1.f90
fortcom: Warning: NS3T10_MAIN_TEST1.f90, line 17: Fortran 2003 does not allow this statement or directive.
!$OMP PARALLEL DEFAULT(SHARED) PRIVATE(NTH, MYID)
------^
fortcom: Warning: NS3T10_MAIN_TEST1.f90, line 21: Fortran 2003 does not allow this statement or directive.
!$OMP SINGLE
------^
fortcom: Warning: NS3T10_MAIN_TEST1.f90, line 28: Fortran 2003 does not allow this statement or directive.
!$OMP END SINGLE
----------^
fortcom: Warning: NS3T10_MAIN_TEST1.f90, line 29: Fortran 2003 does not allow this statement or directive.
!$OMP END PARALLEL
------------^
NS3T10_MAIN_TEST1.f90(17): (col. 7) remark: OpenMP DEFINED REGION WAS PARALLELIZED.
icc -g -o /tmp/address.o -c address.c
ifort -std03 -openmp -openmp-report1 -fpp -DDEBUG -debug all -g -mtune=core2 -module /tmp -error-limit 3 /tmp/NS3T10_MAIN_TEST1.o /tmp/address.o -L /home/domel/pack/intel/mkl/10.0.2.018/lib/32 -lmkl_solver -lmkl_intel -lmkl_intel_thread -liomp5 -lmkl_core -lpthread -lz -o /tmp/NS3T10_TEST1
The output:
domel@x60:~/src/solve> /tmp/NS3T10_TEST1
2 0
RESIZE : 2
forrtl: severe (174): SIGSEGV, segmentation fault occurred
Image PC Routine Line&nb sp; Source
. FFFFE410 Unknown Unknown Unknown
libiomp5.so 40398C7A Unknown Unknown Unknown
libpthread.so.0 4042A192 Unknown Unknown Unknown
libc.so.6 4059A02E Unknown Unknown Unknown
forrtl: severe (174): SIGSEGV, segmentation fault occurred
Image PC Routine Line Source
. FFFFE410 Unknown Unknown Unknown
libiomp5.so 40398C7A Unknown Unknown Unknown
libpthread.so.0 4042A192 Unknown Unknown Unknown
libc.so.6 4059A02E Unknown Unknown Unknown
-- Dominik
MODULE NS3T10
USE OMP_LIB
IMPLICIT NONE
INTEGER, PARAMETER :: NK = 34
CONTAINS
SUBROUTINE SETUP_A
! INTEGER, DIMENSION(:), POINTER :: USED
INTEGER, DIMENSION(:), ALLOCATABLE :: USED
INTEGER :: NTH=1, MYID=1
! CALL RESIZE(USED,1)
! CALL PRINT_ADDRESS(USED)
!$OMP PARALLEL DEFAULT(SHARED) PRIVATE(NTH, MYID)
NTH = OMP_GET_NUM_THREADS()
MYID = OMP_GET_THREAD_NUM()
PRINT *, NTH, MYID
!$OMP SINGLE
! CALL PRINT_ADDRESS(USED)
! PRINT *, ALLOCATED(USED)
CALL RESIZE(USED,NTH)
! CALL PRINT_ADDRESS(USED)
USED = 10
PRINT *, USED
!$OMP END SINGLE
!$OMP END PARALLEL
! CALL PRINT_ADDRESS(USED)
END SUBROUTINE SETUP_A
SUBROUTINE RESIZE(V,S)
INTEGER, DIMENSION(:), ALLOCATABLE, INTENT(INOUT) :: V
INTEGER, INTENT(IN) :: S
IF(ALLOCATED(V)) DEALLOCATE(V)
ALLOCATE(V(S))
PRINT *, 'RESIZE : ', S
! CALL PRINT_ADDRESS(V)
END SUBROUTINE RESIZE
!
! SUBROUTINE RESIZE(V,S)
! INTEGER, DIMENSION(:), POINTER :: V
! INTEGER, INTENT(IN) :: S
! NULLIFY(V)
! ALLOCATE(V(S))
! PRINT *, 'RESIZE : ', S
! END SUBROUTINE RESIZE
END MODULE NS3T10
PROGRAM NS3T
USE OMP_LIB
USE NS3T10
IMPLICIT NONE
CALL SETUP_A
END PROGRAM NS3T
The compilation:
ifort -std03 -openmp -openmp-report1 -fpp -DDEBUG -debug all -g -mtune=core2 -module /tmp -error-limit 3 -I /scratch/domel/pack/hdf5-1.6.7/fortran/src -o /tmp/NS3T10_MAIN_TEST1.o -c NS3T10_MAIN_TEST1.f90
fortcom: Warning: NS3T10_MAIN_TEST1.f90, line 17: Fortran 2003 does not allow this statement or directive.
!$OMP PARALLEL DEFAULT(SHARED) PRIVATE(NTH, MYID)
------^
fortcom: Warning: NS3T10_MAIN_TEST1.f90, line 21: Fortran 2003 does not allow this statement or directive.
!$OMP SINGLE
------^
fortcom: Warning: NS3T10_MAIN_TEST1.f90, line 28: Fortran 2003 does not allow this statement or directive.
!$OMP END SINGLE
----------^
fortcom: Warning: NS3T10_MAIN_TEST1.f90, line 29: Fortran 2003 does not allow this statement or directive.
!$OMP END PARALLEL
------------^
NS3T10_MAIN_TEST1.f90(17): (col. 7) remark: OpenMP DEFINED REGION WAS PARALLELIZED.
icc -g -o /tmp/address.o -c address.c
ifort -std03 -openmp -openmp-report1 -fpp -DDEBUG -debug all -g -mtune=core2 -module /tmp -error-limit 3 /tmp/NS3T10_MAIN_TEST1.o /tmp/address.o -L /home/domel/pack/intel/mkl/10.0.2.018/lib/32 -lmkl_solver -lmkl_intel -lmkl_intel_thread -liomp5 -lmkl_core -lpthread -lz -o /tmp/NS3T10_TEST1
The output:
domel@x60:~/src/solve> /tmp/NS3T10_TEST1
2 0
RESIZE : 2
forrtl: severe (174): SIGSEGV, segmentation fault occurred
Image PC Routine Line&nb sp; Source
. FFFFE410 Unknown Unknown Unknown
libiomp5.so 40398C7A Unknown Unknown Unknown
libpthread.so.0 4042A192 Unknown Unknown Unknown
libc.so.6 4059A02E Unknown Unknown Unknown
forrtl: severe (174): SIGSEGV, segmentation fault occurred
Image PC Routine Line Source
. FFFFE410 Unknown Unknown Unknown
libiomp5.so 40398C7A Unknown Unknown Unknown
libpthread.so.0 4042A192 Unknown Unknown Unknown
libc.so.6 4059A02E Unknown Unknown Unknown
-- Dominik
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Interesting - note that that's a different error. I'll look into that.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
If you could tell me how to see some more than 'Unknown' during the crash that I get despite -g I might be of some more help (more general question/remark).
Thanks,
Dominik
Thanks,
Dominik
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
-traceback

Reply
Topic Options
- Subscribe to RSS Feed
- Mark Topic as New
- Mark Topic as Read
- Float this Topic for Current User
- Bookmark
- Subscribe
- Printer Friendly Page