Skip to content
Snippets Groups Projects
Commit 0c381c0d authored by Uwe Schulzweida's avatar Uwe Schulzweida
Browse files

No commit message

No commit message
parent 6fd4eada
No related branches found
No related tags found
No related merge requests found
......@@ -4,64 +4,65 @@ PROGRAM CDIREAD
INCLUDE 'cdi.inc'
INTEGER :: gridsize, nlevel, nvars, code
INTEGER :: i, varID, levelID
INTEGER :: gsize, nlevel, nvars, code
INTEGER :: vdate, vtime, nmiss, status, ilev
INTEGER :: streamID, varID, levelID, gridID, zaxisID
INTEGER :: tsID, vlistID, taxisID
REAL*8, ALLOCATABLE :: field(:,:)
CHARACTER(len=256) :: name, longname, units
INTEGER NLON, NLAT, NLEV, NTIME
PARAMETER (NLON = 12) ! Number of longitudes
PARAMETER (NLAT = 6) ! Number of latitudes
PARAMETER (NLEV = 5) ! Number of levels
PARAMETER (NTIME = 3) ! Number of time steps
INTEGER gridID, zaxisID1, zaxisID2, taxisID
INTEGER vlistID, varID1, varID2, streamID, tsID
INTEGER nmiss, status, vdate, vtime
REAL*8 var1(NLON*NLAT), var2(NLON*NLAT*NLEV)
! Open the dataset
! Open the dataset
streamID = streamOpenRead("example.nc")
IF ( streamID < 0 ) THEN
WRITE(0,*) cdiStringError(streamID)
STOP
END IF
! Get the variable list of the dataset
! Get the variable list of the dataset
vlistID = streamInqVlist(streamID)
nvars = vlistNvars(vlistID)
WRITE(*,*) 'nvars: ', nvars
DO varID = 0, nvars-1
code = vlistInqVarCode(vlistID, varID)
CALL vlistInqVarName(vlistID, varID, name)
CALL vlistInqVarLongname(vlistID, varID, longname)
CALL vlistInqVarUnits(vlistID, varID, units)
WRITE(*,*) varID, code, TRIM(name), TRIM(longname), TRIM(units)
WRITE(*,*) 'Parameter: ', varID+1, code, TRIM(name), ' ', TRIM(longname), ' ', TRIM(units)
END DO
! Get the Time axis form the variable list
taxisID = vlistInqTaxis(vlistID)
! Loop over the number of time steps
DO tsID = 0, NTIME-1
! Inquire the time step
status = streamInqTimestep(streamID, tsID)
! Get the verification date and time
vdate = taxisInqVdate(taxisID)
vtime = taxisInqVtime(taxisID)
! Read var1 and var2
CALL streamReadVar(streamID, varID1, var1, nmiss)
CALL streamReadVar(streamID, varID2, var2, nmiss)
! Get the Time axis form the variable list
taxisID = vlistInqTaxis(vlistID)
! Loop over the time steps
DO tsID = 0, 999999
! Read the time step
status = streamInqTimestep(streamID, tsID)
IF ( status == 0 ) exit
! Get the verification date and time
vdate = taxisInqVdate(taxisID)
vtime = taxisInqVtime(taxisID)
WRITE(*,*) 'Timestep: ', tsID+1, vdate, vtime
! Read the variables at the current timestep
DO varID = 0, nvars-1
gridID = vlistInqVarGrid(vlistID, varID)
gsize = gridInqSize(gridID)
zaxisID = vlistInqVarZaxis(vlistID, varID)
nlevel = zaxisInqSize(zaxisID)
ALLOCATE(field(gsize, nlevel))
CALL streamReadVar(streamID, varID, field, nmiss)
DO ilev = 1, nlevel
WRITE(*,*) ' var=', varID+1, ' level=', ilev, ':', MINVAL(field(:,ilev)), MAXVAL(field(:,ilev))
END DO
DEALLOCATE(field)
END DO
END DO
! Close the input stream
CALL streamClose(streamID)
END PROGRAM CDIREAD
! Close the input stream
CALL streamClose(streamID)
END PROGRAM CDIREAD
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment