DustBunnie
Technical User
Hello FORTRAN Gurus,
I am out of practice but am starting to program again and have a question. First, I’ll explain what I am trying to do. I have 3 sets of 30yrs of daily input data. What I’d like to do is read a subset of these input files and append these subset data to a new single output file.
Thus far I have written code to step through the input files using a do loop and read the data. Once I get this running I’ll work on building the output file.
I’m running in to an allocation problem. From what I’ve read once the procedure is completed I thought the array would be deallocated. But once I get to the second file in the do loop (1981_16.pnt) I get a fatal error caused by the RDATA still being allocated.
I am using the NAG builder to create the program.
Any assistance would be much appreciated
CODE:
MODULE DATA_READER_MODULE
!supplied by NAG support to read 1981_15.pnt formatted files
IMPLICIT NONE
CONTAINS
SUBROUTINE READ_DATA(FNAME,NAMES,RDATA,ERROR)
CHARACTER(LEN=*), INTENT(IN) :: FNAME
CHARACTER(LEN=16), INTENT(OUT), ALLOCATABLE :: NAMES)
DOUBLE PRECISION, ALLOCATABLE :: RDATA,
LOGICAL, INTENT(OUT) :: ERROR
INTEGER :: NUM_ROWS=0
CHARACTER(LEN=256) :: ROWBUFF
INTEGER I
ERROR=.FALSE.
OPEN(1,FILE=FNAME)
DO
READ(1,FMT='(A)',ERR=20,END=20)ROWBUFF
NUM_ROWS=NUM_ROWS+1
ENDDO
20 IF(NUM_ROWS==0)THEN
ERROR=.TRUE.
CLOSE(1)
RETURN
ENDIF
CLOSE(1)
ALLOCATE(NAMES(NUM_ROWS),RDATA(NUM_ROWS,4))
OPEN(1,FILE=FNAME)
DO I=1,NUM_ROWS
READ(1,FMT='(A)')ROWBUFF
NAMES(I)=ROWBUFF(1:16)
READ(ROWBUFF(18:27),FMT=*)RDATA(I,1)
READ(ROWBUFF(29:37),FMT=*)RDATA(I,2)
READ(ROWBUFF(40:43),FMT=*)RDATA(I,3)
READ(ROWBUFF(47:51),FMT=*)RDATA(I,4)
ENDDO
CLOSE(1)
END SUBROUTINE
END MODULE
Program main_name
!this program is the first draft of trying to assign a file name
!first name is 1981_15.pnt
use Data_reader_module
Implicit none
character(len=12)::Fname !to be used in module read data
character(len=11)::fileN
character(len=12)::fileNN
character(len=4):: year
!character(len=4)::exten='.pnt' !note extension on input files
DOUBLE PRECISION, ALLOCATABLE :: RDATA,
CHARACTER(LEN=16), ALLOCATABLE :: NAMES)
LOGICAL ERROR
INTEGER ::IROW ! not used in this test ios
Integer :: i, j, nday
! collect relevent data from user, year, and number of days
Print *, 'type in the 4 digit year'
Read *, year !(unit=11, fmt='(a)', iostat=ios)
Print *, 'type in the last day number of the data set (e.g. 121 or 122)'
Read*, nday !(unit=12, fmt="(I3)", iostat=ios)note double quotes in format statement for integer
Do 5 i=15, 99 !do loop based on starting at jan 15 (i=15) to day 99
write(fileN, 10)year, i
print *, fileN !print to screen so user can see what file is being processed
fname=fileN
CALL READ_DATA(FNAME,NAMES,RDATA,ERROR)
IF(.NOT.ERROR)THEN
DO IROW=1,SIZE(NAMES,DIM=1)
PRINT *,NAMES(IROW),RDATA(IROW,
ENDDO
ENDIF
5 continue
Do 15 j=100, nday !do loop picking up from day 100 to user defines end day
write(fileNN, 100)year,j
print *, fileNN !print to screen so user can see what file is being processed
fname=fileNN
CALL READ_DATA(FNAME,NAMES,RDATA,ERROR)
IF(.NOT.ERROR)THEN
DO IROW=1,SIZE(NAMES,DIM=1)
PRINT *,NAMES(IROW),RDATA(IROW,
ENDDO
ENDIF
15 continue
10 format(a4,'_',I2,'.pnt') ! format for input files with day numbers up to 99
100 format (a4,'_',I3,'.pnt') ! format for input files with day numbers 100 and up
end program main_name
I am out of practice but am starting to program again and have a question. First, I’ll explain what I am trying to do. I have 3 sets of 30yrs of daily input data. What I’d like to do is read a subset of these input files and append these subset data to a new single output file.
Thus far I have written code to step through the input files using a do loop and read the data. Once I get this running I’ll work on building the output file.
I’m running in to an allocation problem. From what I’ve read once the procedure is completed I thought the array would be deallocated. But once I get to the second file in the do loop (1981_16.pnt) I get a fatal error caused by the RDATA still being allocated.
I am using the NAG builder to create the program.
Any assistance would be much appreciated
Code:
CODE:
MODULE DATA_READER_MODULE
!supplied by NAG support to read 1981_15.pnt formatted files
IMPLICIT NONE
CONTAINS
SUBROUTINE READ_DATA(FNAME,NAMES,RDATA,ERROR)
CHARACTER(LEN=*), INTENT(IN) :: FNAME
CHARACTER(LEN=16), INTENT(OUT), ALLOCATABLE :: NAMES)
DOUBLE PRECISION, ALLOCATABLE :: RDATA,
LOGICAL, INTENT(OUT) :: ERROR
INTEGER :: NUM_ROWS=0
CHARACTER(LEN=256) :: ROWBUFF
INTEGER I
ERROR=.FALSE.
OPEN(1,FILE=FNAME)
DO
READ(1,FMT='(A)',ERR=20,END=20)ROWBUFF
NUM_ROWS=NUM_ROWS+1
ENDDO
20 IF(NUM_ROWS==0)THEN
ERROR=.TRUE.
CLOSE(1)
RETURN
ENDIF
CLOSE(1)
ALLOCATE(NAMES(NUM_ROWS),RDATA(NUM_ROWS,4))
OPEN(1,FILE=FNAME)
DO I=1,NUM_ROWS
READ(1,FMT='(A)')ROWBUFF
NAMES(I)=ROWBUFF(1:16)
READ(ROWBUFF(18:27),FMT=*)RDATA(I,1)
READ(ROWBUFF(29:37),FMT=*)RDATA(I,2)
READ(ROWBUFF(40:43),FMT=*)RDATA(I,3)
READ(ROWBUFF(47:51),FMT=*)RDATA(I,4)
ENDDO
CLOSE(1)
END SUBROUTINE
END MODULE
Program main_name
!this program is the first draft of trying to assign a file name
!first name is 1981_15.pnt
use Data_reader_module
Implicit none
character(len=12)::Fname !to be used in module read data
character(len=11)::fileN
character(len=12)::fileNN
character(len=4):: year
!character(len=4)::exten='.pnt' !note extension on input files
DOUBLE PRECISION, ALLOCATABLE :: RDATA,
CHARACTER(LEN=16), ALLOCATABLE :: NAMES)
LOGICAL ERROR
INTEGER ::IROW ! not used in this test ios
Integer :: i, j, nday
! collect relevent data from user, year, and number of days
Print *, 'type in the 4 digit year'
Read *, year !(unit=11, fmt='(a)', iostat=ios)
Print *, 'type in the last day number of the data set (e.g. 121 or 122)'
Read*, nday !(unit=12, fmt="(I3)", iostat=ios)note double quotes in format statement for integer
Do 5 i=15, 99 !do loop based on starting at jan 15 (i=15) to day 99
write(fileN, 10)year, i
print *, fileN !print to screen so user can see what file is being processed
fname=fileN
CALL READ_DATA(FNAME,NAMES,RDATA,ERROR)
IF(.NOT.ERROR)THEN
DO IROW=1,SIZE(NAMES,DIM=1)
PRINT *,NAMES(IROW),RDATA(IROW,
ENDDO
ENDIF
5 continue
Do 15 j=100, nday !do loop picking up from day 100 to user defines end day
write(fileNN, 100)year,j
print *, fileNN !print to screen so user can see what file is being processed
fname=fileNN
CALL READ_DATA(FNAME,NAMES,RDATA,ERROR)
IF(.NOT.ERROR)THEN
DO IROW=1,SIZE(NAMES,DIM=1)
PRINT *,NAMES(IROW),RDATA(IROW,
ENDDO
ENDIF
15 continue
10 format(a4,'_',I2,'.pnt') ! format for input files with day numbers up to 99
100 format (a4,'_',I3,'.pnt') ! format for input files with day numbers 100 and up
end program main_name