Search code examples
memory-managementfortranallocationfortran95

Read array of unknown size from keyboard


I want to insert an unknown number of values in an array (no matter the order). I could first read how many values are to be inserted, then allocate the allocatable array, and finally read its values, as in the following code

PROGRAM try
IMPLICIT NONE
INTEGER :: N
REAL, DIMENSION(:), ALLOCATABLE :: x
WRITE (*,*) "how many values?"
READ (*,*) N
ALLOCATE(x(N))
WRITE (*,*) "insert the values"
READ (*,*) x
END PROGRAM

What if I want to insert the values without declaring how many before allocating the array? I think I should use a DO WHILE cycle to insert the values in ascending order, till a descending value is insert, thus indicating the sequence is ended. I think a part of the code would be the following,

index = 1
WRITE(*,*) x
READ(*,*) x(index)
exit = .FALSE.
DO WHILE (exit.EQV..FALSE.)
    index = index + 1
    READ(*,*) x(index)
    IF (x(index)>x(index-1)) THEN
        exit = .TRUE.
        index = index - 1
    END IF
END DO

How to declare the array x?


Solution

  • I tried with the following solution, building on the concept "a lot of memory allocation and reallocation" expressed by @High Performance Mark.

    PROGRAM COEFFS
    
    USE COMPACT
    
    IMPLICIT NONE
    
    REAL, DIMENSION(:), ALLOCATABLE :: x,x2
    INTEGER :: nL,nR,nT,index,oL,oR
    LOGICAL :: exit
    
    WRITE(*,*) "Input an increasing sequence of reals (end the sequence &
            & with the first decreasing element, which will be discarded):"
    
    index = 1
    ALLOCATE(x(index))
    READ(*,*) x(index)
    ALLOCATE(x2(index))
    x2 = x
    DEALLOCATE(x)
    exit = .FALSE.
    DO WHILE (exit.EQV..FALSE.)
        index = index + 1
        ALLOCATE(x(index))
        x(1:index-1) = x2
        READ(*,*) x(index)
        DEALLOCATE(x2)
        ALLOCATE(x2(index))
        x2 = x
        DEALLOCATE(x)
        IF (x2(index)<x2(index-1)) THEN
            exit = .TRUE.
            index = index - 1
            ALLOCATE(x(index))
            x = x2(1:index)
        END IF
    END DO
    DEALLOCATE(x2)
    
    WRITE(*,*) "x = ", x
    
    END PROGRAM
    

    With the array being input by keyboard, I don't think allocation/reallocation is a problem, since it happens at a much higher speed than that of my fingers typing the values, doesn't it? Still I think the code could be made better. For instance, using two arrays is the only way to take advantage of allocation/reallocation?