writing fortran programs to read netcdf files
Stergios Misios
stergios.misios at ZMAW.DE
Thu Apr 2 15:45:42 EDT 2009
hi
Find bellow an example for reading a variable which is assumed to have a
(lon,lat,lev,time) format from a netcdf file.
I am programming with netcdf F90 library. You must have it somewhere.
When you compile (lets say intel compiler)
ifort -I/sw/etch-ia32/netcdf-3.6.2-intel/include
-L/sw/etch-ia32/netcdf-3.6.2-intel/lib -lnetcdff -lnetcdf
In my case i use the netcdf-3.6.2 netcdf library
The writing can be done with something similar, i guess...
fname : the netcdf file
var_name: the variable you 'd like to extract
ff: the matrix
ist : the number of time step
I hope it helps,
Stergios
p.s. You may consider to use for IO only purpose something less
complicated like Python and PyNGL module while make the filtering in a
Fortran environment...
================================================
SUBROUTINE readstepnc4(fname,var_name,ff,ist)
! A condensed way to read a variable form netcdf file
! it is implied that the format is ff(lon,lat,lev,timesteps)
! Author: Stergios Misios, Nov-2008
IMPLICIT NONE
! declare calling variables
CHARACTER(LEN=*),INTENT(in) :: fname
CHARACTER(LEN=*),INTENT(in) :: var_name
REAL,DIMENSION(:,:,:),INTENT(out) :: ff
INTEGER,INTENT(in) :: ist
! declare local variables
INTEGER :: nc_id,var_id,ndim,nvar,nattr,unlim_id,fmt
CHARACTER(LEN=15) ::dname
INTEGER :: dlength
REAL,DIMENSION(:,:,:),ALLOCATABLE::var_dummy
INTEGER :: ii,status,lo,la,le,ti
REAL :: sf,ofs
CALL check(nf90_open(fname,nf90_nowrite,nc_id))
CALL check(nf90_inquire(nc_id,ndim,nvar))
! take the dimension names and lengths
DO ii=1,ndim
CALL check(NF90_INQUIRE_DIMENSION(nc_id,ii,dname,len=dlength))
SELECT CASE (TRIM(dname))
CASE ('lon','LON','Lon','Longitude','longitude','LONGITUDE')
lo=dlength
CASE ('lat','LAT','Lat','Latitude','latitude','LATITUDE')
la=dlength
CASE ('lev','Lev','LEV','level','levelist','Level')
le=dlength
CASE ('time','Time','TIME')
ti=dlength
CASE DEFAULT
PRINT*,' Error while reading dimensions....'
PRINT*,' Some dimensions are missing. '
PRINT*,' The program is terminating....';STOP
END SELECT
END DO
! allocate the matrix for reading data. The definition is
! var_dummy(nlon,lat,nlev,timesteps)
ALLOCATE(var_dummy(lo,la,le))
! Read all data
CALL check(nf90_inq_varid(nc_id,TRIM(var_name),var_id))
CALL
check(nf90_get_var(nc_id,var_id,var_dummy,start=(/1,1,1,ist/),count=(/lo,la,le,1/)))
! asking if there are the scale_factor and add_offset attributes
status = nf90_get_att(nc_id,var_id,"scale_factor",sf)
IF (status == -43) sf=1.0
status = nf90_get_att(nc_id,var_id,"add_offset",ofs)
IF (status == -43) ofs = 0.0
ff=sf*var_dummy+ofs
call check(nf90_close(nc_id))
PRINT*,'Reading step ',ist
PRINT*,''
DEALLOCATE(var_dummy)
END SUBROUTINE readstepnc4
More information about the gradsusr
mailing list