Intel® Fortran Compiler
Build applications that can scale for the future with optimized code designed for Intel® Xeon® and compatible processors.
29277 Discussions

ALLOCATING a string array in a subroutine and returning it to the caller

Intel_C_Intel
Employee
686 Views

I wrote a relatively simple routine to open a text file, count the number of lines, allocate a string array with enough elements for each line, read in the file line-by-line to the array and return the array to the caller. The guts of the routine is given below (renamed for this example to DimArray).

After I wrote it I found in the FORTRAN help that this type of allocation is not allowed. I was a bit surprised at this because I thought the compiler could have checked and issued a warning. Anyway, can anyone tell me why it is not allowed? The routine I wrote has been working perfectly, returning the text file is a string array and all the data seems to exist uncorrupted in the caller etc etc.

Below is the simplified code which from what I understand is not acceptable F90. So how can I write a general routine to do what I want?

From the program (source code in some other file)

PROGRAM Blah
USE Utils

CHARACTER*(1024), ALLOCATABLE :: sDefaultAPL(:)
INTEGER nNumLines

!Read and store the file in an array (1 element for each line in the file)
CALL DimArray(sArray, nNumLines)

...


In Utils.for, Module Utils.
SUBROUTINE DimArray (sFile, nNumLines)
IMPLICIT NONE

!Arguments
CHARACTER*(*), ALLOCATABLE, INTENT(OUT) :: sFile(:)
INTEGER nNumLines

!Local variables
INTEGER nStat

!Deallocate the array
IF ( ALLOCATED(sFile) ) THEN
DEALLOCATE(sFile, STAT=nStat)
IF (nStat .NE. 0) STOP "DimArray: Cannot Deallocate"
ENDIF

!For the purposes of this example hard code the dimanesion
nNumLines = 123

!Allocate the array
ALLOCATE (sFile(1:nNumLines), STAT=nStat)
IF (nStat .NE. 0) STOP "DimArray: Cannot Allocate"

RETURN

END SUBROUTINE

Many thanks

Jonathan

0 Kudos
6 Replies
Steven_L_Intel1
Employee
686 Views
What aspect of this do you think is not allowed? Is it the ALLOCATABLE argument? This is not standard Fortran 95 but it is standard Fortran 2003 and many compilers support it.
0 Kudos
Jugoslav_Dujic
Valued Contributor II
686 Views
Let me clarify: there were actually several stages in the Fortran Standards after f95 regarding allocatables:
  1. TR15581 (TR=technical report) was a ISO J3 Working Group document which specifed the additional properties of allocatables, whereby they're allowed as:
    1. dummy arguments
    2. function results
    3. components of derived TYPEs
  2. Fortran 2003, incorporated TR15581, and, in addition, specified:
    1. assignment of allocatables, whereby the left-hand side allocatable is automagically re-allocated to the size and shape of the right-hand side array expression
    2. character scalars of allocatable length, (declared as character(LEN=:), allocatable)
All modern compilers, IVF included, implemented the TR15581 by now. None (or a few) implemented the full F2003 features. The "Fortran help" you refer to is possibly outdated a bit.

See also here.
0 Kudos
Intel_C_Intel
Employee
686 Views

Hi Steve, JD,

Many thanks for your replies which both seem to point to the same thing. I've not done any FORTRAN in anger for about 5-6 years and things have moved on.

I wrote the routine in Jan this year using the Compaq compiler and then just recently reviewed what I had done and recompiled using IVF. The reason I was concerned was because of what I read in theLanguage Reference Manual- and I thought I read it in Compaq & Intel versions but perhaps it was just the Compaq one - and that would possibly explain the mystery

To quote the Compaq lang ref as I have it to hand: "Although most types of arrays can be used as dummy arguments, allocatable arrays cannot be dummy arguments..."

So, from what you are saying - what the routine is trying to do is absolutely fine (these days)? Actually, I'll paste the real routine at the end as it will make more sense (as you can see it is rather old-style FORTRAN).

Thank you for your help

Jonathan

SUBROUTINE ReadTextFileToArray(sFilename, sFile, nNumLines)
IMPLICIT NONE
c.....Arguments
CHARACTER*(*) sFilename
CHARACTER*(*), ALLOCATABLE, INTENT(OUT) :: sFile(:)
INTEGER*4 nNumLines
c.....Local variables
INTEGER*4 nFileUnit !Unit on which default apl is opened
INTEGER*4 ioCheck
INTEGER*4 nStat
INTEGER*4 I
CHARACTER*1 sLine !Only needs to be 1 char, for line counting only
c.....Functions
INTEGER*4 Fn_FreeUnit
LOGICAL*4 FileExists !.TRUE. if the file has been found
c.....Constants
c.....Debug/Log

!Default return values (always deallocate the array)
nNumLines = 0
IF ( ALLOCATED(sFile) ) THEN
DEALLOCATE(sFile, STAT=nStat)
!Sanity check: if we cannot deallocate we must stop because this is serious
IF (nStat .NE. 0) STOP "ReadTextFileToArray: Cannot Deallocate"
ENDIF

!Sanity check: does the file even exist
IF ( .NOT. FileExists(sFilename) ) THEN
WRITE(6,*) 'Error (ReadTextFileToArray): Cannot find file'
  ; WRITE(6,*) TRIM(sFilename)
RETURN
ENDIF

!Open the file
nFileUnit = Fn_FreeUnit()
OPEN(UNIT = nFileUnit
^ ,FILE = sFilename
^ ,RECL = 88064
^ ,ACCESS= 'SEQUENTIAL'
^ ,STATUS= 'OLD'
^ ,FORM = 'FORMATTED'
^ ,IOSTAT= ioCheck
^ ,ERR = 666
^ )

!Count the lines in the file
I = 0
DO WHILE (.NOT. EOF(nFileUnit))
I=I+1
READ(nFileUnit, '(A)') sLine
END DO

!allocate the array
ALLOCATE (sFile(1:I), STAT=nStat)
IF (nStat .NE. 0) STOP "ReadTextFileToArray: Cannot Allocate"

!Rewind to the start of the file and read it intot he new array
REWIND(nFileUnit)
I = 0
DO WHILE (.NOT. EOF(nFileUnit))
I=I+1
READ(nFileUnit,'(A)') sFile(I)
END DO

!Close the file
CLOSE(unit = nFileUnit
^ ,err = 667
^ ,ioStat = ioCheck
^ )

!Set the return line count, useful for the caller to check for zero etc
nNumLines = I

RETURN

666 CONTINUE !Error handler for the OPEN
WRITE(6,*) 'Error (ReadTextFileToArray): OPEN file failed'
IF ( ioCheck .GT. 0) THEN
WRITE(6,*) 'OPEN ioCheck error: ', ioCheck
ELSEIF ( ioCheck .EQ. -1) THEN
WRITE(6,*) 'OPEN End of File condition reached'
ELSEIF ( ioCheck .EQ. -2) THEN
WRITE(6,*) 'OPEN End of Record condition reached'
ELSE
!This should not happen, but report anyway
WRITE(6,*) 'OPEN negative ioCheck error: ', ioCheck
ENDIF
RETURN

667 CONTINUE !Error handler for the CLOSE
WRITE(6,*) 'Error (ReadTextFileToArray): CLOSE file failed'
IF ( ioCheck .GT. 0) THEN
WRITE(6,*) 'CLOSE ioCheck error: ', ioCheck
ELSE
!This should not happen, but report anyway
WRITE(6,*) 'CLOSE negative ioCheck error: ', ioCheck
ENDIF
RETURN

END SUBROUTINE

0 Kudos
Steven_L_Intel1
Employee
686 Views
This feature was added to CVF after the manual was last revised, though when we last left CVF, the implementation had numerous bugs. I'll comment that the check to see if sFile is allocated is unnecessary (though harmless) - as an INTENT(OUT) argument, it is automatically deallocated if needed on entry to the routine.
0 Kudos
Intel_C_Intel
Employee
686 Views

Hi Steve,

Thanks for info re. CVF. At the moment the program compiles on CVF and I tested compiling the procedure alone on IVF. From what you say I should probably do whatever is nec. to compile the whole project on IVF rather than leave it like this under CVF? Or do you think it would be ok for this one application? (you may not wish to comment on that!)

Thanks too for comment on deallocation - I know what happened, the INTENT statement was a late addition which I added to try and provoke the compiler to warn me about what I was doing (I still thought it was illegal, so expected it to moan at me).

This is the first time I've been to the Intel forums, and it's good to see your name there and that the listings seem very alive and active.

Cheers

Jonathan

0 Kudos
Steven_L_Intel1
Employee
686 Views
I would very much recommend your moving everything to IVF at a pace that is convenient for you. It will save you from having to deal with bugs in the allocatable argument feature and have you use a current and supported product.
0 Kudos
Reply