[Date Prev][Date Next][Thread Prev][Thread Next][Date Index][Thread Index]

19990315: NetCDF




On Mon, 15 Mar 1999, Brett E. McDonald wrote:

> Steve,
> 
> I will do some reading up on NetCDF so that I don't have to bug you so often.
> 
> I the meantime, I am trying to read some files available at the ABRFC:
> 
> http://www.abrfc.noaa.gov/archive/1999/jan/6hr_netcdf/
> 
> Any one of the files in this folder will do since I have to process them all.
> 
> Thanks,
> 
> Brett
> 
> 
> > Do you have a resonably small sample of what you files will look like?
> > If so, I can try to give you a skelleton for looping through the data.
> 

Brett,

I downloaded the netcdf file 01319900z.nc.gz and uncompressed it
to 01319900z.nc (using gzip).

Attatched below is a sample set of code that reads the precip
data into an array ready for you to send the data to wherever
you need to.

Compile the routine with:
f77 -o readnet readnet.f -I/upc/netcdf/include -L/upc/netcdf/lib -lnetcdf


You must use the -I to find the netcdf.inc include file. The -L
library path is where you have the netcdf.a library. Use the appropriate
paths for your system of course.

Sample running of the program for this data set:
[181]chiz --> readnet

 enter your input file
01319900z.nc                                                                  

 time of data 01319900Z
 bottom left    33.60300       106.4560    
 bottom right    32.43300       92.32200    
 top right    38.02700       90.67800    
 top left    39.42000       106.6520    
 hrapx =          335 hrapy =          159


Steve Chiswell
Unidata User Support
----------------------program readnet.f-----------------------------
      PROGRAM READNET
C     FORTRAN TEMPLATE FOR FILE= 01319900z.nc                            
      PARAMETER (NVARS= 9) !NUMBER OF VARIABLES
C     VARIABLE IDS RUN SEQUENTIALLY FROM 1 TO NVARS=  9
      INTEGER*4 RCODE
      CHARACTER*50 name(100)
C     ****VARIABLES FOR THIS NETCDF FILE****
C
      INTEGER*2   amountofprecip                 (  335,  159)
      REAL*4      lat                            (    4)
      REAL*4      lon                            (    4)
      REAL*4      true_lat                       
      REAL*4      true_lon                       
      CHARACTER*1 timeofdata                     (    9)
      CHARACTER*1 timeofcreation                 (    9)
      REAL*4      hrap_xor                       
      REAL*4      hrap_yor                       
C*************************************
      character*80 input_file
      INTEGER*4 START(10)
      INTEGER*4 COUNT(10)
      INTEGER VDIMS(10) !ALLOW UP TO 10 DIMENSIONS
      CHARACTER*31 DUMMY
      INTEGER   hrapx,hrapy
C
      CALL NCPOPT(NCVERBOSE)
      write(6,1)
 1    format(' enter your input file')
      read(5,2) input_file
 2    format(a80)
      ilen=index(input_file,'   ')
      ncid=ncopn(input_file(1:ilen-1),0,rcode)
C
C    statements to fill amountofprecip                 
C
      ivarid = ncvid(ncid,'amountofprecip',rcode)
      CALL NCVINQ(NCID,ivarid,DUMMY,NTP,NVDIM,VDIMS,NVS,RCODE)
      LENSTR=1
      DO  10 J=1,NVDIM
      CALL NCDINQ(NCID,VDIMS(J),DUMMY,NDSIZE,RCODE)
      LENSTR=LENSTR*NDSIZE
      START(J)=1
      COUNT(J)=NDSIZE
  10  CONTINUE
      CALL NCVGT(NCID,ivarid,START,COUNT,
     +amountofprecip,RCODE)
      hrapy = COUNT(2)
      hrapx = COUNT(1)

C
C    statements to fill lat                            
C
      ivarid = ncvid(ncid,'lat',rcode)
      CALL NCVINQ(NCID,ivarid,DUMMY,NTP,NVDIM,VDIMS,NVS,RCODE)
      LENSTR=1
      DO  20 J=1,NVDIM
      CALL NCDINQ(NCID,VDIMS(J),DUMMY,NDSIZE,RCODE)
      LENSTR=LENSTR*NDSIZE
      START(J)=1
      COUNT(J)=NDSIZE
  20  CONTINUE
      CALL NCVGT(NCID,ivarid,START,COUNT,
     +lat,RCODE)
C
C    statements to fill lon                            
C
      ivarid = ncvid(ncid,'lon',rcode)
      CALL NCVINQ(NCID,ivarid,DUMMY,NTP,NVDIM,VDIMS,NVS,RCODE)
      LENSTR=1
      DO  30 J=1,NVDIM
      CALL NCDINQ(NCID,VDIMS(J),DUMMY,NDSIZE,RCODE)
      LENSTR=LENSTR*NDSIZE
      START(J)=1
      COUNT(J)=NDSIZE
  30  CONTINUE
      CALL NCVGT(NCID,ivarid,START,COUNT,
     +lon,RCODE)
C
C    statements to fill true_lat                       
C
      ivarid = ncvid(ncid,'true_lat',rcode)
      CALL NCVINQ(NCID,ivarid,DUMMY,NTP,NVDIM,VDIMS,NVS,RCODE)
      LENSTR=1
      DO  40 J=1,NVDIM
      CALL NCDINQ(NCID,VDIMS(J),DUMMY,NDSIZE,RCODE)
      LENSTR=LENSTR*NDSIZE
      START(J)=1
      COUNT(J)=NDSIZE
  40  CONTINUE
      CALL NCVGT(NCID,ivarid,START,COUNT,
     +true_lat,RCODE)
C
C    statements to fill true_lon                       
C
      ivarid = ncvid(ncid,'true_lon',rcode)
      CALL NCVINQ(NCID,ivarid,DUMMY,NTP,NVDIM,VDIMS,NVS,RCODE)
      LENSTR=1
      DO  50 J=1,NVDIM
      CALL NCDINQ(NCID,VDIMS(J),DUMMY,NDSIZE,RCODE)
      LENSTR=LENSTR*NDSIZE
      START(J)=1
      COUNT(J)=NDSIZE
  50  CONTINUE
      CALL NCVGT(NCID,ivarid,START,COUNT,
     +true_lon,RCODE)
C
C    statements to fill timeofdata                     
C
      ivarid = ncvid(ncid,'timeofdata',rcode)
      CALL NCVINQ(NCID,ivarid,DUMMY,NTP,NVDIM,VDIMS,NVS,RCODE)
      LENSTR=1
      DO  60 J=1,NVDIM
      CALL NCDINQ(NCID,VDIMS(J),DUMMY,NDSIZE,RCODE)
      LENSTR=LENSTR*NDSIZE
      START(J)=1
      COUNT(J)=NDSIZE
  60  CONTINUE
      CALL NCVGTC(NCID,ivarid,START,COUNT,
     +timeofdata,LENSTR,RCODE)
C
C    statements to fill timeofcreation                 
C
      ivarid = ncvid(ncid,'timeofcreation',rcode)
      CALL NCVINQ(NCID,ivarid,DUMMY,NTP,NVDIM,VDIMS,NVS,RCODE)
      LENSTR=1
      DO  70 J=1,NVDIM
      CALL NCDINQ(NCID,VDIMS(J),DUMMY,NDSIZE,RCODE)
      LENSTR=LENSTR*NDSIZE
      START(J)=1
      COUNT(J)=NDSIZE
  70  CONTINUE
      CALL NCVGTC(NCID,ivarid,START,COUNT,
     +timeofcreation,LENSTR,RCODE)
C
C    statements to fill hrap_xor                       
C
      ivarid = ncvid(ncid,'hrap_xor',rcode)
      CALL NCVINQ(NCID,ivarid,DUMMY,NTP,NVDIM,VDIMS,NVS,RCODE)
      LENSTR=1
      DO  80 J=1,NVDIM
      CALL NCDINQ(NCID,VDIMS(J),DUMMY,NDSIZE,RCODE)
      LENSTR=LENSTR*NDSIZE
      START(J)=1
      COUNT(J)=NDSIZE
  80  CONTINUE
      CALL NCVGT(NCID,ivarid,START,COUNT,
     +hrap_xor,RCODE)
C
C    statements to fill hrap_yor                       
C
      ivarid = ncvid(ncid,'hrap_yor',rcode)
      CALL NCVINQ(NCID,ivarid,DUMMY,NTP,NVDIM,VDIMS,NVS,RCODE)
      LENSTR=1
      DO  90 J=1,NVDIM
      CALL NCDINQ(NCID,VDIMS(J),DUMMY,NDSIZE,RCODE)
      LENSTR=LENSTR*NDSIZE
      START(J)=1
      COUNT(J)=NDSIZE
  90  CONTINUE
      CALL NCVGT(NCID,ivarid,START,COUNT,
     +hrap_yor,RCODE)

C
C     following code: checks output code code against current input file
C
C
      call ncinq(ncid,ndims,nvarsc,ngatts,nrecdim,rcode)
      if(nvarsc.ne.nvars) write(6,110)
  110 format('number of variables has changed')
C
      CALL NCCLOS(NCID,RCODE)
C
C
C     HERE IS WHERE YOU WRITE STATEMENTS TO USE THE DATA
C
        write(*,*) 'time of data ',timeofdata

        write(*,*) 'bottom left ',lat(1),lon(1)
        write(*,*) 'bottom right ',lat(2),lon(2)
        write(*,*) 'top right ',lat(3),lon(3)
        write(*,*) 'top left ',lat(4),lon(4)

        write(*,*) 'hrapx = ',hrapx,' hrapy = ',hrapy

C       Precip array is amountofprecip(x,y)
c       do i=1,hrapy
c          do j = 1,hrapx
c             write(*,*) '(',j,i,')',amountofprecip(j,i)
c          end do
c       end do
        
C
C
      STOP
      END