pgi stack overflow: thread, max, used, request

Hi, I am having a run time error I dont under stand and I dont know how to find out what is causing it.

error: in routine octree_search_particle there is a stack overflow: thread 7, max 1024KB, used 0KB, request 208B

the message make no sense as there is non used and the subroutine request is well within memory max.

the program is complied with the following options

fedora 20
pgf90 14.10-0 64-bit target on x86-64 Linux -tp sandybridge

F90FLAGS = -Mpreprocess -g -mp -r8 -DLinux -DnoReturnDamp -Kieee -Mchkptr -Mchkstk -Mbounds -traceback

and run with the following parameters

  • OMP_NUM_THREADS=“8”, export OMP_NUM_THREADS
    OMP_NESTED=“TRUE”, export OMP_NESTED
    OMP_MAX_ACTIVE_LEVELS=“10”, export OMP_MAX_ACTIVE_LEVELS
    OMP_STACKSIZE=“1G”, export OMP_STACKSIZE
    ulimit -s unlimited

the memory usage was reports as mem kb = 9,915,484 on a machine with 128gb memory

the subroutine in question is an octree search routine which search thought a tree making a list of alll the partilces it find storing the list in massive. the section which uses this code is multithreaded and massive storage array is thread privated. I dont understand why the routine would break like this. I wanted to use allinea to debug my code but their memory debugger isnt up to the task and has a memory leak. I dont know how to find the source of the crash.

The memory debugging library (dmalloc - a replacement of regular malloc/free) is far less aggressive on reusing deallocated blocks. It can only do so if the size of new allocations match the size of previously freed blocks. Your executable is continuously requesting allocations with a very high variability of sizes, and therefore the amount of reuse is low and memory usage increases.

I have post the subroutine in question bellow.

RECURSIVE SUBROUTINE  Octree_search_particle(BoxNumber, Particle, Search_distance, search_pad) !search by particle
	use Main
	IMPLICIT NONE
	INTEGER, INTENT(in) :: BoxNumber, Particle
	REAL*8 :: Search_distance
	Logical :: WhichBoxes(8)
	INTEGER ::  ii, ParticleCheck, StoreNumber
	REAL*8:: d_XYZ_octree(3), D_octree_2,D_octree, delta_octree, search_pad
	
	!check depth and if bottom return
	IF (Octree(boxNumber)%Depth == DepthMax) Then
		StoreNumber = Octree(BoxNumber)%StoreNum
		DO ii=Octree_Store_reference(1,StoreNumber) , Octree_Store_reference(3,StoreNumber)
			ParticleCheck = Octree_store_current(ii)
			
			IF(ParticleCheck < 1) Cycle !dont check your self or any particle bellow high or negative etc...
			IF(ParticleCheck == Particle) Cycle !dont check your self or any particle bellow high or negative etc...
			IF(unborn(ParticleCheck)) CYCLE
			d_XYZ_octree(1:3) = XYZ(1:3,ParticleCheck) - XYZ(1:3,Particle)
			D_octree_2 = DOT_PRODUCT(d_XYZ_octree,d_XYZ_octree)
			D_octree =  DSQRT(D_octree_2)!Pythagoras(dx,dy,dz)
			delta_octree =   D_octree - r(Particle) - r(ParticleCheck) 
			IF (delta_octree < Search_distance) THEN 
				Massive_store(massive_nb) = ParticleCheck
				massive_nb = massive_nb + 1
				IF (massive_nb > massive_lenght) CAll massive_Grow
			END IF
		END DO
		Return
	END IF
	
	
	!logic search 
	!!!!6---8!!
	!!!/!!!/!!! 
	!!5---7!!!!
	!!!!!!!!!!! y split 
	!!!!2---4!!
	!!!/!!!/!!!
	!!1---3!!!!
	
	
	!rules out boxes which cant be true.
	WhichBoxes = .false.
	!Split boxes in X
	
	IF ((XYZ(1,Particle) - search_pad) > Octree(BoxNumber)%x(2)) Then
		WhichBoxes(1:2) = .true.; WhichBoxes(5:6) = .true.
	Else IF ((XYZ(1,Particle) + search_pad) < Octree(BoxNumber)%x(2)) Then
		WhichBoxes(3:4) = .true.; WhichBoxes(7:8) = .true.
	END IF	
	
	!split boxes in y
	IF ((XYZ(2,Particle) - search_pad) > Octree(BoxNumber)%y(2)) Then
		WhichBoxes(1:4) = .true.
	Else IF ((XYZ(2,Particle) + search_pad) < Octree(BoxNumber)%y(2)) Then
		WhichBoxes(5:8) = .true.
	END IF	
	
	!split boxes in z
	
	IF ((XYZ(3,Particle) - search_pad) > Octree(BoxNumber)%z(2)) Then
		WhichBoxes(1) = .true.; WhichBoxes(3) = .true.; WhichBoxes(5) = .true.; WhichBoxes(7) = .true.
	Else IF((XYZ(3,Particle) + search_pad) < Octree(boxNumber)%z(2)) Then
		WhichBoxes(2) = .true.; WhichBoxes(4) = .true.; WhichBoxes(6) = .true.; WhichBoxes(8) = .true.
	END IF
	
	!debug = 0
	DO ii = 1, 8
		IF (WhichBoxes(ii)) CYCLE !not searched
		IF (Octree(boxNumber)%ChildList(ii) < 1) cycle !CHILD DOES NOT EXSIT
		CAll Octree_search_particle(Octree(boxNumber)%ChildList(ii), Particle, Search_distance,search_pad) !search for particle
	END DO 
END SUBROUTINE  Octree_search_particle

Hi BeverleyWilliams51212,

I’ve seen this type of false positive once before. In that case, the application was using a shared object (.so) that was linked against the PGI OpenMP shared runtime library. However, the main application was statically linked against the static OpenMP runtime library. It is this mismatch that caused the problem.

Does your application use an OpenMP enabled shared object? If so, then the solution is to link the main application using the shared runtime by adding the flag “-fpic”.

  • Mat