Tek-Tips is the largest IT community on the Internet today!

Members share and learn making Tek-Tips Forums the best source of peer-reviewed technical information on the Internet!

  • Congratulations Mike Lewis on being selected by the Tek-Tips community for having the most helpful posts in the forums last week. Way to Go!

how to avoid multiple do loops 2

Status
Not open for further replies.

raghu81

Technical User
Apr 9, 2008
28
DE
Dear all,

In a code which I have been trying to generalize,

I have an array of integers for ex.,

A = [1, 2, 3]

then I have multiple do loops as

do i1 = 1, A(1)
do i2 = 1, A(2)
do i3 = 1, A(3)
...
...
enddo
enddo
enddo

I want to generalize this code so that when I the size of the 'A' array is 4 or 5, I can do the same task without changing the code everytime.

Thank you in advance for any help.

regards,
Raghu
 
thank you GerritGroot, but i guess that does not solve the problem.
 
Maybe you can use a recursive function in fortran 90 (I personally never needed them).

I found this example googling around:
Code:
!-----Factorial------------------------------------------------------
!
!  Function to calculate factorials resursively
!
!---------------------------------------------------------------------
RECURSIVE FUNCTION Factorial(n)  RESULT(Fact)

IMPLICIT NONE
INTEGER :: Fact
INTEGER, INTENT(IN) :: n

IF (n == 0) THEN
   Fact = 1
ELSE
   Fact = n * Factorial(n-1)
END IF

END FUNCTION Factorial

Try to adapt that to your needs, repeating the recursive SIZE(A) times, letting A(i) come in as an INTEGER, INTENT(IN) and then do the DO loop inside the function. It depends on what you do inside the loop I think.
 
You could try something convoluted like this
Code:
program loopy

    integer, parameter:: depth = 3
    integer maxdim(depth)
    integer lix(depth), ix

    ! This is your A
    maxdim = (/2, 3, 5 /)

    ! Initilaize all loop counters to 0
    lix = 0

    ! First index
    ix = 1
    do while (ix .ne. 0)
        ! increment the counter
        lix(ix) = lix(ix) + 1
        if (lix(ix) .le. maxdim(ix)) then
            if (ix .eq. depth) then
                ! Do something
                print *, (lix(ii), ii = 1, depth)
            else
                ! Move to next index
                ix = ix + 1
            end if
        else
            ! end of loop - reset counter
            lix(ix) = 0
            ! Move to previous index
            ix = ix - 1
        end if
   end do 
   stop

 end program loopy
 
Dear xwb,

Excellent work, Thank you for your help. This is exactly what I needed.

Regards,
Raghu
 
The algorithm presented by xwb is very interesting - I bookmarked it.
GerritGroot speaked about possible recursive solution. Yes it's possible to replace the while-loop with recursive call, however I thing the iterative approach presented by xwb is nicer and better to understand ...
Code:
[COLOR=#a020f0]program[/color] loopy_main
  [COLOR=#2e8b57][b]integer[/b][/color], [COLOR=#2e8b57][b]parameter[/b][/color]:: depth [COLOR=#804040][b]=[/b][/color] [COLOR=#ff00ff]3[/color]
  [COLOR=#2e8b57][b]integer[/b][/color] maxdim(depth)
  [COLOR=#2e8b57][b]integer[/b][/color] lix(depth), ix

  [COLOR=#0000ff]! This is your A[/color]
  maxdim [COLOR=#804040][b]=[/b][/color] ([COLOR=#804040][b]/[/b][/color][COLOR=#ff00ff]2[/color], [COLOR=#ff00ff]3[/color], [COLOR=#ff00ff]5[/color][COLOR=#804040][b]/[/b][/color])

  [COLOR=#0000ff]! Initilaize all loop counters to 0[/color]
  lix [COLOR=#804040][b]=[/b][/color] [COLOR=#ff00ff]0[/color]
  
  [COLOR=#0000ff]! call recursive subroutine loopy[/color]
  [COLOR=#a020f0]call[/color] loopy(depth, maxdim, lix, [COLOR=#ff00ff]1[/color])

[COLOR=#a020f0]end program[/color] loopy_main

[COLOR=#a020f0]recursive[/color] [COLOR=#a020f0]subroutine[/color] loopy(depth, maxdim, lix, ix)
  [COLOR=#2e8b57][b]integer[/b][/color], [COLOR=#2e8b57][b]intent[/b][/color]([COLOR=#2e8b57][b]in[/b][/color])     :: depth
  [COLOR=#2e8b57][b]integer[/b][/color], [COLOR=#2e8b57][b]intent[/b][/color]([COLOR=#2e8b57][b]in[/b][/color])     :: maxdim(depth)
  [COLOR=#2e8b57][b]integer[/b][/color], [COLOR=#2e8b57][b]intent[/b][/color]([COLOR=#2e8b57][b]inout[/b][/color])  :: lix(depth), ix

  [COLOR=#804040][b]if[/b][/color] (ix [COLOR=#804040][b].ne.[/b][/color] [COLOR=#ff00ff]0[/color]) [COLOR=#804040][b]then[/b][/color]
    lix(ix) [COLOR=#804040][b]=[/b][/color] lix(ix) [COLOR=#804040][b]+[/b][/color] [COLOR=#ff00ff]1[/color] [COLOR=#0000ff]! increment the counter[/color]
    [COLOR=#804040][b]if[/b][/color] (lix(ix) [COLOR=#804040][b].le.[/b][/color] maxdim(ix)) [COLOR=#804040][b]then[/b][/color]
      [COLOR=#804040][b]if[/b][/color] (ix [COLOR=#804040][b].eq.[/b][/color] depth) [COLOR=#804040][b]then[/b][/color]
          [COLOR=#0000ff]! Do something[/color]
          [COLOR=#804040][b]print[/b][/color] [COLOR=#804040][b]*[/b][/color], (lix(ii), ii [COLOR=#804040][b]=[/b][/color] [COLOR=#ff00ff]1[/color], depth)
      [COLOR=#804040][b]else[/b][/color]
          ix [COLOR=#804040][b]=[/b][/color] ix [COLOR=#804040][b]+[/b][/color] [COLOR=#ff00ff]1[/color] [COLOR=#0000ff]! Move to next index[/color]
      [COLOR=#804040][b]end if[/b][/color]
    [COLOR=#804040][b]else[/b][/color]
      lix(ix) [COLOR=#804040][b]=[/b][/color] [COLOR=#ff00ff]0[/color] [COLOR=#0000ff]! end of loop - reset counter[/color]
      ix [COLOR=#804040][b]=[/b][/color] ix [COLOR=#804040][b]-[/b][/color] [COLOR=#ff00ff]1[/color] [COLOR=#0000ff]! Move to previous index[/color]
    [COLOR=#804040][b]end if[/b][/color]
    [COLOR=#0000ff]! recursion[/color]
    [COLOR=#a020f0]call[/color] loopy(depth, maxdim, lix, ix)
  [COLOR=#804040][b]end if[/b][/color] 
[COLOR=#a020f0]end subroutine[/color] loopy
 
If you wish to use recursion, it is actually simpler than that
Code:
program loopy_main
  integer, parameter:: depth = 3
  integer maxdim(depth)
  integer lix(depth), ix

  ! This is your A
  maxdim = (/2, 3, 5/)

  ! Initilaize all loop counters to 0
  lix = 0
  
  ! call recursive subroutine loopy
  call loopy(depth, maxdim, lix, 1)
  stop
  
end program loopy_main

recursive subroutine loopy(depth, maxdim, lix, ix)
   integer, intent(in)     :: depth
   integer, intent(in)     :: maxdim(depth), ix
   integer, intent(inout)  :: lix(depth)

   do jj = 1, maxdim(ix)
      lix(ix) = jj
      if (ix .eq. depth) then
         ! Do something
         print *, (lix(ii), ii = 1, depth)
      else
         ! next loop
         call loopy(depth, maxdim, lix, ix + 1)
      end if
   end do
end subroutine loopy
 
Unlike the non-recursive version, you do not need to backgrack. The thing about recursive algorithms is you have to think of everything locally (ix is now just in instead of inout)

If you're using the Intel compilers, make sure that default save variables are not set. If save variables are required, they should be set explicitly. If they are set in the compilation, it can have you foxed for ages.
 
This completely changed my mind: the recursive solution is very simple - like the recursive factorial.
It's simpler then the iterative solution ... but one need to think recursive :)
 
Well, in fact, to the contrary of what I said before, I used a recursive procedure once, yeaaars ago, but changed it finally for something in which I could get around it.

I found that the recursive procedure was much much slower after compiling than what mikrom calls the iterative solution.

I didn't have much programming experience at the time (and still don't have it...) so I can't conclude that it was because of the recursive.

I don't know whether ye've got similar experiences, or wheter compilers use to handle recursives in a less efficient way.
 
From an application point of view, the version based of the recursive routine is compact. Thanx to GerritGroot, xwb and mikrom.

 
The difference between recursive and non recursive is the stack handling. With recursive, the compiler handles the stack, non-recursive - you handle the stack and any backtracking. On the older Fortran compilers (circa 1976), when everything was done in Fortran, you had to tell the compiler how deep the recursion went.

Even though the code is more compact in a recursive solution, there is a recursive subroutine call involved, which makes it slower - it has to create stuff on the stack and pass parameters in. On exit, it pops the stack. You have to weigh this stack handling against your local arrays and variable backtracking to see which is more efficient. The scales can go either way.

Sometimes, recursion is totally unnecessary as it can be handled using a simple loop. When the loop handling gets convoluted/complicated, or you don't know how deep the nesting can go, then it is a good time to think of recursion.
 
Status
Not open for further replies.

Part and Inventory Search

Sponsor

Back
Top