- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Hi,
I have a segment of code, that has been running fine for a while.
I got a stack overflow error when run with large arrays.
Here is the code:
ALLOCATE(xa(na))
xa = [x(1:n-1)-x(n), x, x(2:n)+x(n)] <<<< Stack over flow on this line
In the stack overflow case, n=44836 and na=134506
If i cange the code to this it will run:
ALLOCATE(xa(na))
xa(:n-1) = x(:n-1)-x(n)
xa(n:2*n-1) = x
xa(2*n:3*n-2) = x(2:)+x(n)
Is the latter the preferable method?
Are the pieces in the brackets assembled on the stack, thus the stack overflow?
Should i increase the stack size?
thanks,
rob
Link Copied
2 Replies
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Apparently, the array constructor creates a temporary copy of the array, as you mentioned. If you prefer the notation and don't mind the extra time spent, you should set a larger stack size, or set /heap-arrays.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Thanks Tim. So if i increased the stack size, the code would run slower? I need the code to run as fast as possible, so i guess i'll stick with the new notation.
Also, i'm getting the same error again in a call to another function and i can't figure this one out.
////////////////////////////////////////////////
Here is the calling function:
SUBROUTINE calcspline(y2, n,x,y,Dx1,Dxn,closeends)
! computes spline of a set of data
!----------------------------------------------------------------------------------------------------------------------------------------------------
!-------------------------------------------------------------- begin common mod files --------------------------------------------------------------
USE OUTFILES
!-------------------------------------------------------------- end common mod files --------------------------------------------------------------
!----------------------------------------------------------------------------------------------------------------------------------------------------
IMPLICIT NONE
!----------------------------------------------------------------------------------------------------------------------------------------------------
!--------------------------------------------------------- begin define function parameters ---------------------------------------------------------
INTEGER, INTENT(IN) :: n ! array length
REAL*8, INTENT(IN), DIMENSION(n) :: x ! independent vector
REAL*8, INTENT(IN), DIMENSION(n) :: y ! dependent vector
REAL*8, INTENT(IN) :: Dx1 ! delta (dx) at first element (x(1))
REAL*8, INTENT(IN) :: Dxn ! delta (dx) at last element (x(n))
INTEGER, INTENT(IN) :: closeends ! 1 = closed - continuous loop; 2 = open ends
REAL*8, INTENT(OUT), DIMENSION(n) :: y2 ! second derivative (d^2y/d^2x) y vector with respect to x vector
!--------------------------------------------------------- end define function parameters ---------------------------------------------------------
!----------------------------------------------------------------------------------------------------------------------------------------------------
!----------------------------------------------------------------------------------------------------------------------------------------------------
!---------------------------------------------------------- begin define local variables ----------------------------------------------------------
REAL*8 DyDx1 ! derivative (dy/dx) at first element (x(1))
REAL*8 DyDxn ! derivative (dy/dx) at last element (x(n))
INTEGER na ! appended array length
REAL*8, ALLOCATABLE :: xa(:) ! independent vector with appendages on front and rear
REAL*8, ALLOCATABLE :: ya(:) ! dependent vector with appendages on front and rear
REAL*8, ALLOCATABLE :: y2a(:) ! second derivative (d^2y/d^2x) y vector with respect to x vector with appendages on front and rear
!REAL*8 xa(3*n-2) ! independent vector with appendages on front and rear
!REAL*8 ya(3*n-2) ! dependent vector with appendages on front and rear
!REAL*8 y2a(3*n-2) ! second derivative (d^2y/d^2x) y vector with respect to x vector with appendages on front and rear
!---------------------------------------------------------- end define local variables ----------------------------------------------------------
!----------------------------------------------------------------------------------------------------------------------------------------------------
DyDx1 = ( y(2)-y(n-1) )/Dx1 ! only for closed circuit!
DyDxn = DyDx1
na = 3*n-2
ALLOCATE(xa(na))
ALLOCATE(ya(na))
ALLOCATE(y2a(na))
!xa = [x(1:n-1)-x(n), x, x(2:n)+x(n)]
xa(:n-1) = x(:n-1)-x(n)
xa(n:2*n-1) = x
xa(2*n:3*n-2) = x(2:)+x(n)
!ya = [y(:n-1), y, y(2:)]
ya(:n-1) = y(:n-1)
ya(n:2*n-1) = y
ya(2*n:3*n-2) = y(2:)
CALL spline(y2a, na,xa,ya,DyDx1,DyDxn)
y2 = y2a(n:2*n) ! crop appendages
DEALLOCATE(xa)
DEALLOCATE(ya)
DEALLOCATE(y2a)
ENDSUBROUTINE calcspline
////////////////////////////////////////////////////////////////////////////
Here is the called function:
SUBROUTINE spline(y2, n,x,y,yp1,ypn)
IMPLICIT NONE
! computes second derivative of interpolating function. ends have zero second derivative.
!----------------------------------------------------------------------------------------------------------------------------------------------------
!--------------------------------------------------------- begin define function parameters ---------------------------------------------------------
INTEGER, INTENT(IN) :: n ! array length
REAL*8, INTENT(IN), DIMENSION(n) :: x ! independent vector
REAL*8, INTENT(IN), DIMENSION(n) :: y ! dependent vector
REAL*8, INTENT(IN) :: yp1 ! derivative (dy/dx) at first element (x(1))
REAL*8, INTENT(IN) :: ypn ! derivative (dy/dx) at last element (x(n))
REAL*8, INTENT(OUT), DIMENSION(n) :: y2 ! second derivative (d^2y/d^2x) y vector with respect to x vector
!--------------------------------------------------------- end define function parameters ---------------------------------------------------------
!----------------------------------------------------------------------------------------------------------------------------------------------------
!----------------------------------------------------------------------------------------------------------------------------------------------------
!---------------------------------------------------------- begin define local variables ----------------------------------------------------------
REAL*8 p
REAL*8 qn
REAL*8 sig
REAL*8 un
REAL*8 u(n)
INTEGER i
!---------------------------------------------------------- end define local variables ----------------------------------------------------------
!----------------------------------------------------------------------------------------------------------------------------------------------------
IF (n==0) THEN
RETURN
ENDIF
IF (yp1 > 0.99D30) THEN
y2(1) = 0.D0
u(1) = 0.D0
ELSE
y2(1) = -0.5D0
u(1) = ( 3.D0/(x(2)-x(1)) ) * ( (y(2)-y(1))/(x(2)-x(1)) - yp1 )
!sig = (x(1)-x(n-1))/(x(2)-x(n-1))
!p = sig*y2(n-1) + 2.D0
!y2(1) = (sig-1.D0)/p
!u(1) = ( 6.D0*( (y(2)-y(1))/(x(2)-x(1)) - (y(1)-y(n-1))/(x(1)-x(n-1)) )/(x(2)-x(n-1)) - sig*u(n-1) )/p
ENDIF
DO i=2,n-1
sig = (x(i)-x(i-1))/(x(i+1)-x(i-1))
p = sig*y2(i-1) + 2.D0
y2(i) = (sig-1.D0)/p
u(i) = ( 6.D0*( (y(i+1)-y(i))/(x(i+1)-x(i)) - (y(i)-y(i-1))/(x(i)-x(i-1)) )/(x(i+1)-x(i-1)) - sig*u(i-1) )/p
ENDDO
IF (ypn > 0.99D30) THEN
qn = 0.D0
un = 0.D0
ELSE
qn = 0.5D0
un = ( 3.D0/(x(n)-x(n-1)) ) * ( ypn - (y(n)-y(n-1))/(x(n)-x(n-1)) )
ENDIF
IF (n==1) THEN
y2(n) = 0.D0
ELSE
y2(n) = (un-qn*u(n-1))/(qn*y2(n-1)+1.D0)
ENDIF
DO i=n-1,1,-1 ! back substitution loop of tridiagnal algorithm
y2(i) = y2(i)*y2(i+1)+u(i)
ENDDO
ENDSUBROUTINE spline
//////////////////////////////////////////////////////////////////////////////
I get the same crash before the first execution line in subroutine spline (i break it at line 1, then it crashes when i "step over"). Am i not declaring the dummy arguments correctly in subroutine spline?
thanks,
rob
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