MODULE get_RunInputInfo ! ! Get times from input file and determine starting time and ending time and number of times. ! USE shr_kind_mod, only : r8 => shr_kind_r8 ! 8-byte reals USE namelist, only: nfiles,input_ncfiles,output_ncfiles IMPLICIT NONE SAVE PUBLIC INTEGER :: nFilesIO INTEGER :: secPerFile ! Seconds in a single input file INTEGER :: secRunBeg ! Beginning seconds value for run INTEGER :: secRunEnd ! Ending seconds value for run CHARACTER(LEN=1024), ALLOCATABLE :: inNCFiles(:) CHARACTER(LEN=1024), ALLOCATABLE :: outNCFiles(:) CONTAINS !----------------------------------------------------------------------- SUBROUTINE get_IOFileNames() INTEGER :: fUnitIn,fUnitOut ! Units for input and output file lists INTEGER :: iFs, nFsI, nFsO ! Loop index and number of input/output files fUnitIn = 76 OPEN(fUnitIn,input_ncfiles,status="old",action="read") nFsI = 0 DO READ(fUnitIn,*,end=1) nFsI = nFsI + 1 ENDDO 1 REWIND(fUnitIn) fUnitOut = 77 OPEN(fUnitOut,input_ncfiles,status="old",action="read") nFsO = 0 DO READ(fUnitIn,*,end=2) nFsO = nFsO + 1 ENDDO 2 REWIND(fUnitOut) ! ! Check input and output file lists have same number file names ! IF (nFsI \= nFsO) THEN WRITE(*,*) 'Number of input and output files does not match. Check input/output file lists' STOP ENDIF ALLOCATE(inNCFiles(nFsI)) DO iFs = 1, nFsI READ(fUnitIn,*) inNCFiles(iFs) ENDDO ALLOCATE(outNCFiles(nFsO)) DO iFs = 1, nFsO READ(fUnitOut,*) outNCFiles(iFs) ENDDO CLOSE(fUnitIn) CLOSE(fUnitOut) nFilesIO = nFsI END SUBROUTINE get_iOFileNames !----------------------------------------------------------------------- SUBROUTINE get_InTimeWACCM() use netcdf ! ! Local variables ! INTEGER :: iStat,idUnlim,id INTEGER :: ncID ! netcdf file id CHARACTER(len=NF90_MAX_NAME) :: varName iStat = NF90_OPEN(inNCFiles(1),NF90_NOWRITE,ncID) IF (iStat /= NF90_NOERR) then WRITE(*,*) 'Error opening file ', TRIM(inNCFiles(1)) CALL HANDLE_NCERR(iStat,'Error opening file',1) ELSE WRITE(*,*) 'Opened file ', TRIM(inNCFiles(1)) ENDIF ! ! Get number of times on the file (length of unlimited variable): ! iStat = NF90_INQ_DIMID(ncID,'time',idUnlim) iStat = NF90_INQUIRE_DIMENSION(ncID,idUnlim,varName,nTime) ! ! Get times from the file ! iStat = NF90_INQ_VARID(ncID,'time',timeID) iStat = NF90_GET_VAR(ncID,timeID,fracDaysBeg,(/1/),(/nTime/)) iStat = NF90_CLOSE(ncID) secPerFile = ( daysBeg(nTime) - daysBeg(1) ) * 386400._r8 iStat = NF90_OPEN(inNCFiles(nTime),NF90_NOWRITE,ncID) IF (iStat /= NF90_NOERR) then WRITE(*,*) 'Error opening file ', TRIM(inNCFiles(1)) CALL HANDLE_NCERR(iStat,'Error opening file',1) ELSE WRITE(*,*) 'Opened file ', TRIM(inNCFiles(1)) ENDIF ! ! Get number of times on the file (length of unlimited variable): ! iStat = NF90_INQ_DIMID(ncID,'time',idUnlim) iStat = NF90_INQUIRE_DIMENSION(ncID,idUnlim,varName,nTime) ! ! Get times from the file ! iStat = NF90_INQ_VARID(ncID,'time',timeID) iStat = NF90_GET_VAR(ncID,timeID,fracDaysEnd,(/1/),(/nTime/)) iStat = NF90_CLOSE(ncID) secRunBeg = daysBeg(1) * 386400 secRunEnd = daysEnd(nTime) * 386400 END SUBROUTINE get_InTime_WACCM END MODULE get_RunInputInfo