- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
I am developing a fortran code with multi-level recursions (at times, it is expected to go 8000+ levels deep) using compiler 12.1. From the forum topics I learnt that, using heap arrays is a good practice. But is there any other tip/trick which I should be taking care not to run into problem.
Link Copied
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
What arguments are passed into and returned from each recursion? (show the call and the dummy and data declarations)
Does the recursion make use of ~large temporary storage? (such as a scratch array)
Is preservation of this temporary storage necessary as you recurs deeper? (prior values of scratch array required on return)
Is, or at what point, parallelization involved?
There isn't a single tip/trick. What you need to do is highly dependent upon the answers to above questions (and others yet to be asked).
Is recursion absolutely necessary, or is it merely convenient?
Jim Dempsey
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Thank you Jim. Here's what routine looks like.
RECURSIVE SUBROUTINE recur_3d(sp,ep,t1,t2,t5,t6,t7,t10,t11)
USE mod_globalvars, ONLY: x,y,z,a,b,c !real*8(1 to 20000) - constant
USE mod_globalvars, ONLY: tpi !integer(1 to 2000) - constant
USE mod_globalvars, ONLY: tp,vtp,ind1,ind2,path1,path2,mean1,mean2 !integer or real*8(1 to 20000) - updates with every call
IMPLICIT NONE
INTEGER, INTENT(IN) :: sp,ep
INTEGER, INTENT(INOUT) :: t1,t2,t5,t6,t7,t10,t11
CALL recur_3d(tp(t5-1),vtp(t5-1),t1,t2,t5,t6,t7,t10,t11)
...
CALL recur_3d(tp(m),ind1(b2),t1,t2,t5,t6,t7,t10,t11)
...
CALL recur_3d(ind2(b2),vtp(m),t1,t2,t5,t6,t7,t10,t11)
All the local variables used in last row were updated in every recursion. Due to some proprietary content, I am unable to share the entire code.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
See if you can use the ideas in https://en.wikipedia.org/wiki/Tail_call .
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Something like this may be of use:
module YourModule ! Generic interface recur_3d INTERFACE recur_3d ! Explicit interface with all arguments RECURSIVE SUBROUTINE recur_3d_all(sp,ep,t1x,t2x,t5x,t6x,t7x,t10x,t11x) IMPLICIT NONE INTEGER, INTENT(IN) :: sp,ep INTEGER, INTENT(INOUT) :: t1x,t2x,t5x,t6x,t7x,t10x,t11x END SUBROUTINE recur_3d_all ! ! Explicit interface with few arguments RECURSIVE SUBROUTINE recur_3d_few(sp,ep) USE mod_globalvars, ONLY: x,y,z,a,b,c !real*8(1 to 20000) - constant USE mod_globalvars, ONLY: tpi !integer(1 to 2000) - constant USE mod_globalvars, ONLY: tp,vtp,ind1,ind2,path1,path2,mean1,mean2 !integer or real*8(1 to 20000) - updates with every call IMPLICIT NONE INTEGER, INTENT(IN) :: sp,ep END SUBROUTINE recur_3d_few END INTERFACE ! module scoped context variables INTEGER, PRIVATE :: t1,t2,t5,t6,t7,t10,t11 CONTAINS RECURSIVE SUBROUTINE recur_3d_all(sp,ep,t1x,t2x,t5x,t6x,t7x,t10x,t11x) IMPLICIT NONE INTEGER, INTENT(IN) :: sp,ep INTEGER, INTENT(INOUT) :: t1,t2,t5,t6,t7,t10,t11 t1 = t1x; t2=t2x; t5=t5x; t6=t6x; t7=t7x; t10=t10x; t11=t11x recur_3d(sp,ep) t1x = t1; t2x=t2; t5x=t5; t6x=t6; t7x=t7; t10x=t10; t11x=t11 END SUBROUTINE recur_3d_all RECURSIVE SUBROUTINE recur_3d_few(sp,ep) USE mod_globalvars, ONLY: x,y,z,a,b,c !real*8(1 to 20000) - constant USE mod_globalvars, ONLY: tpi !integer(1 to 2000) - constant USE mod_globalvars, ONLY: tp,vtp,ind1,ind2,path1,path2,mean1,mean2 !integer or real*8(1 to 20000) - updates with every call IMPLICIT NONE INTEGER, INTENT(IN) :: sp,ep CALL recur_3d(tp(t5-1),vtp(t5-1)) ... CALL recur_3d(tp(m),ind1(b2)) ... CALL recur_3d(ind2(b2),vtp(m)) END SUBROUTINE recur_3d_few end module YourModule PROGRAM YourProbram USE YourModule ... ! use initial call arguments here CALL recur_3d(ind2(b2),vtp(m),t1,t2,t5,t6,t7,t10,t11)
Jim Dempsey

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