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!

Variable size array 1

Status
Not open for further replies.

fanta2

Technical User
Apr 10, 2005
78
CA
I have an array x(?). I don't know the dimension of the array before hand. While I am going through a loop I know the size.
say

do i=1, n

z = f()

if z > 0 then

x(?) = z

end if

end do

I want to start x(dimension) = 1

increase every time by 1

like


j=0
do i=1, n

z = f()

if z > 0 then

j = j+1

Re dimenion x by j

x(?) = z

end if

end do

Can any body help me how I can do this?
 
Which version of Fortran are you using? You can do it in 90/95/2003 but not in 66/77.
 
Thank you xwb - I am using Fortran 90 with Compaq Visual For. 6.6. Could you please tell me how it can be done?
 
Here is something you can use - you'll have to modify it to suit your needs. The problem with Fortran is that there is no realloc so you have to code that as well.
Code:
program main
   implicit none
   integer::dynmax, dyninc, fillmax
   integer, dimension(:), allocatable, target::dyn1, dyn2
   integer, dimension(:), pointer:: dyn
   integer::i, flip, j

   ! guess how much space you are going to use
   dynmax = 10
   dyninc = 5
   fillmax = 20
   !
   ! allocate space in dyn1
   flip = 1
   allocate (dyn1(dynmax))
   dyn =>dyn1
   !
   ! do something with the array
   do i = 1, fillmax
      if (i .gt. dynmax) then
         dynmax = dynmax + dyninc
         if (flip .eq. 1) then
            ! now use dyn2   
            allocate (dyn2(dynmax))
            dyn =>dyn2
            ! copy old to new
            do j = 1, i - 1
               dyn2(j) = dyn1(j)
            end do
            deallocate (dyn1)
         else
            ! now use dyn1
            allocate (dyn1(dynmax))
            dyn =>dyn1
            ! copy old to new
            do j = 1, i - 1
               dyn1(j) = dyn2(j)
            end do
            deallocate (dyn2)
         end if
         ! note which one we're using
         flip = 3 - flip
      end if
      ! Save the new value
      dyn(i) = i * i
   end do

   do i = 1, fillmax
      write(*,*) dyn(i)
   end do
   !
   ! deallocate the space
   if (flip .eq. 1) then
      deallocate (dyn1)
   else
      deallocate (dyn2)
   end if
   stop
end program main

If you are new to coding, you may not understand the flip trick. The flip trick flips between 1 and 2. If flip = 1, then flip = 3 - flip makes it 2. If flip = 2 then flip = 3 - flip makes it 1.
 
Again thanks xwb. I have two questions please if you can describe it a little bit.

1) I have a very large array and I am afraid that the copying process from one target to another using do loops might take a considerable time ... is there a problem if I use array assignment in stead of the do loop?

do j = 1, i - 1
dyn1(j) = dyn2(j)
end do
alternative dyn1 = dyn2

2) At the end of the fillmax loop - we can't guarantee that the array will be full - most probably it won't be full. Hence, is there a way to shrink it to the final size?
 
1) I wasn't sure whether the array processing commands were available in F90 or not. You can only do the assignment if they have the same shape. Try

dyn1(1:i) = dyn2

2) You will have to declare yet another array, do a copy and deallocate the old one. I'd normally live with the extras unless it is quite far out. It would be if you allocate 1000 at a time and only use 20.

On reallocation: you don't have to go in steps of 5 or 10. It can be as big as you wish. Some increment by percentages. Instead of dynmax = dynmax + 5, they use something like
Code:
dynmax = (dynmax * 3) / 2
 
Thanks once again! Your answer is quite helpful. I have noticed that the time required for the array assignment to copy one array to another and for the do loop for the same task takes the same time. Is there a way that we can facilitate the copying process?
 
The other way is to make a linked list then copy the linked list into the array at the end of the session. You do an alloc for every element added.

Let me know if you need a sample program.
 
Thanks again!!! I will read about linked lists and ask you if I couldn't get it.

I always appreciate your help and accurate answers!!!
 
Here again xwb! I have solved the first part of the problem using linked list .. anyone interested can go through an example in the book "introduction to programming using fortran" by Ian D Chivers. I have encountered a problem to transfer the information.

I have determined my values using a linked list subroutine. In the main program, I will have to call this subroutine n times and I want to accumulate the values of x determined in each run. How can I pass each array of x to the main program and accumulate it?

Program main

integer:: x(?)
integer:: i, n

do i=1, n

call linked_list(x)

end do

! I want to accumulate the x arrays
end program main



subrouting linked_list(x)

!the values of x's are determined using listed link

end subroutine linked_list
 
Basically the question is how can I transfer an allocatable array or a pointer from the subroutine to the main program? When i make the allocatable array an intent out - it gives me an error.
 
You can't in F90. You can in F95.

What you need to do is

1) fill up the link list
2) ask the list how many items it has
3) allocate that number of items
4) pass the allocated array to the list for it to fill up

You can't fill up the array on the fly - you only do this at the end when you know how many items there are.
 
Thanks xwb! I have the linked list and I know how many number of items I have.

What I did is I declared an allocatable array and allocated it with the number of items. Then I filled the allocated array from the link list.

Then I want to pass this allocated array or the pointers? I am using F90 CVF 6.6 compiler.
 
Not sure what you're asking. Where are you passing it to? Once you have all the data in the array, free up the linked list and just use the array.
 
Sorry for the lack of clarity. I have the allocatable array (linked list) in one subroutine and I want to pass it to another subroutine and the main program for further processing. I am asking how to pass it to another subroutine and the main program. I have sketched the problem as follows.

Program Main

------

------

.......... I want to use the linked list or the allocatable array

End program main


!------------------------------
Subroutine linked_list

..... Here I have allocatable array
..... or I have a linked list

end subroutine linked_list

!------------------------------
Subroutine xy


Call linked_list() .... Here I want to use the linked list or the allocatable array

end subroutine xy

 
How is your linked list declared? There are two ways of doing this:

1) declare the head and everything follows from there
2) declare a control structure which points to the head and tail and possibly has a count.

Say the type name is LinkedList

Code:
Program Main
type (LinkedList), allocatable:: sll
------
allocate (sll)
------

call xy (sll)


End program main


!------------------------------
Subroutine linked_list (sll)
type (LinkedList), intent(inout):: sll


end subroutine linked_list

!------------------------------
Subroutine xy  (sll)
type (LinkedList), intent(inout):: sll

Call linked_list(sll)

end subroutine xy

 
Here is my head declaration:

TYPE node
INTEGER:: value
TYPE (node), POINTER :: next
END TYPE node
INTEGER :: num, b
integer, save:: i
integer, intent(in):: k
integer:: j
TYPE (node), POINTER, save:: list
TYPE (node), POINTER, save:: current

----------------------------------
I accumulate the values in the list and current pointers. I gave them a SAVE attribute because the subroutine will be called repeatedly.
 
I'm still trying to figure out what your problem is. At a guess, you have a linked list which is saved in a routine but because it is saved in the routine, you cannot get at it from any other routine.

a) If you want a structure to be accessed by more than one routine, then the structure has to be passed in. This means that you have to declare head in program and pass it in wherever you're using it. Don't bother with the save stuff.
b) If you want a routine to have mixed functionality then you have to code it as such. This means that linked_list has to have four modes: create, delete, add, extract. You pass in 3 parameters: a mode, an insert item and an array. Not all will be used; it depends on the mode.

(b) is the more complicated of the two. (a) is what I described in the 12:36 posting.


 
Sorry xwb for such a long back and forth! Anyway I really thank you for your help. Here, I have posted the whole sample code. My problem as outlined in the routines is to use the allocatable array x (or the linked list "current") in other subroutines and the main program.

I have the correct values of array x in subroutine linked_list and I want to pass these values of x to subroutine calculate and use them there. Besides, I want to use the values of x also in the main program for further calculation. Please give me a hint on how to proceed --- in Fortran 95 I can directly make allocatable array x as argument but not in Fortran-90 which I am using.


PROGRAM MAIN

IMPLICIT NONE

CALL CALCULATE

!HERE I WANT TO USE THE VALUE OF ARRAY X FROM SUBROUTINE LINKED_LIST
!OR THE WHOLE CURRENT LINKED LIST VARIABLE


END PROGRAM




SUBROUTINE CALCULATE

IMPLICIT NONE

INTEGER :: I, J, K

DO K=1, 3

CALL LINKED_LIST(K)


!HERE I WANT TO USE THE VALUE OF ARRAY X FROM LINKED_LIST SUBROUTINE
!OR THE WHOLE CURRENT LINKED LIST VARIABLE

END DO


END SUBROUTINE


SUBROUTINE LINKED_LIST(K)

IMPLICIT NONE

TYPE NODE
INTEGER :: VALUE
TYPE (NODE), POINTER :: NEXT
END TYPE NODE

INTEGER :: NUM, J
INTEGER, SAVE:: I
INTEGER, INTENT(IN):: K
TYPE (NODE), POINTER, SAVE:: LIST, CURRENT

INTEGER, ALLOCATABLE:: X:))

IF (K==1) NULLIFY(LIST)

IF (K==1) I=0

DO
READ *, NUM
IF (NUM == 0) EXIT
ALLOCATE(CURRENT)
CURRENT%VALUE = NUM
CURRENT%NEXT => LIST
LIST => CURRENT

I = I + 1

END DO


CURRENT => LIST

J = 0

IF (K==3) THEN

PRINT *, "I", I

ALLOCATE(X(I))

DO
IF (.NOT. ASSOCIATED(CURRENT)) EXIT

!PRINT *, CURRENT%VALUE

J = J + 1


X(J) = CURRENT%VALUE

PRINT *, J, X(J)

CURRENT => CURRENT%NEXT

END DO

END IF


END SUBROUTINE LINKED_LIST
 
Solution (b) of 04Mar 14:22 posting
Code:
PROGRAM MAIN

    IMPLICIT NONE

    CALL CALCULATE

    !XWB X cannot be used here unless linked_list is called at this level
    !XWB to obtain the size and extract the contents

END PROGRAM
    
        
SUBROUTINE CALCULATE 

    IMPLICIT NONE

    INTEGER :: I, J, K
    INTEGER, PARAMETER:: LLADD=1, LLGET=2, LLSIZE=3  !XWB
    INTEGER, ALLOCATABLE :: X(:) !XWB
    
    !XWB Fill up the array    
    CALL LINKED_LIST(LLADD, J, X)

    !XWB Find out how big the array is
    CALL LINKED_LIST (LLSIZE, J, X)
    
    !XWB Allocate an array for the result
    ALLOCATE (X(J))
    
    !XWB Extract the array
    CALL LINKED_LIST (LLGET, J, X)
    
    !XWB Do whatever you want with X
    
    
    !XWB Release X
    DEALLOCATE (X)

END SUBROUTINE


SUBROUTINE LINKED_LIST(FUNC, K, X)
    IMPLICIT NONE

    TYPE NODE
        INTEGER :: VALUE 
        TYPE (NODE), POINTER :: NEXT 
    END TYPE NODE

    INTEGER :: NUM, J
    INTEGER, SAVE:: I
    
    INTEGER, INTENT(IN)::FUNC  !!XWB - what to do
    INTEGER, INTENT(OUT):: K   !!XWB - integer result
    INTEGER, INTENT(OUT) :: X(:)            !!XWB - array result
    INTEGER, PARAMETER:: LLADD=1, LLGET=2, LLSIZE=3 !! XWB
    TYPE (NODE), POINTER, SAVE:: LIST, CURRENT

    IF (FUNC .EQ. LLADD) THEN
       ! K and X not used
       NULLIFY(LIST) 
       I=0
       DO
          READ *, NUM 
          IF (NUM == 0) EXIT 
          ALLOCATE(CURRENT) 
          CURRENT%VALUE = NUM 
          CURRENT%NEXT => LIST 
          LIST => CURRENT 

          I = I + 1
       END DO
  
   ELSEIF (FUNC .EQ. LLSIZE) THEN
      ! x not used
      PRINT *, "I", I
      K = I
   ELSE
      ! FUNC .EQ. LLGET
      ! k not used
      J = 0
        
      CURRENT => LIST 
      DO J = 1, I
         !PRINT *, CURRENT%VALUE 
         X(J) = CURRENT%VALUE
         PRINT *, J,  X(J)
         CURRENT => CURRENT%NEXT 
      END DO

  END IF
END SUBROUTINE LINKED_LIST
 
Status
Not open for further replies.

Part and Inventory Search

Sponsor

Back
Top