program read_srb_rel3_qcsw_daily_nc use netcdf implicit none character (200) :: path_in, file_in, file_out integer :: month, year, rec integer :: ndmn(12)=(/31,28,31,30,31,30,31,31,30, & 31,30,31/) character(4) :: cyear character(2) :: cmon ! netCDF id integer :: ncid ! dimension ids integer :: lat_dim, lon_dim, time_dim integer, parameter :: NDIMS = 3 integer, parameter :: NLVLS = 1, NLATS = 180, NLONS = 360 character (len = *), parameter :: LAT_NAME = "lat" character (len = *), parameter :: LON_NAME = "lon" character (len = *), parameter :: time_name = "time" integer :: NRECS ! The start and count arrays will tell the netCDF library where to ! read our data. integer :: start(NDIMS), count(NDIMS) ! In addition to the latitude and longitude dimensions, we will also ! create latitude and longitude variables which will hold the actual ! latitudes and longitudes. Since they hold data about the ! coordinate system, the netCDF term for these is: "coordinate ! variables." real :: lats(NLATS), lons(NLONS) character (len = *), parameter :: toadn_name="sw_toa_dn" character (len = *), parameter :: csfcdn_name="clr_sw_sfc_dn" character (len = *), parameter :: psfcdn_name="prist_sw_sfc_dn" character (len = *), parameter :: sfcdn_name="sw_sfc_dn" character (len = *), parameter :: sw_sfc_net_name="sw_sfc_net" character (len = *), parameter :: alb_name="sw_sfc_alb" ! variable ids integer :: lat_id, lon_id, time_id, sw_sfc_net_id, sw_sfc_dn_id, & prist_sw_sfc_dn_id, sw_sfc_alb_id, clr_sw_sfc_dn_id, sw_toa_dn_id double precision :: time real, dimension(nlons,nlats) :: sw_sfc_net, sw_sfc_dn, & prist_sw_sfc_dn, sw_sfc_alb, clr_sw_sfc_dn, sw_toa_dn integer :: dimids(NDIMS) ! To check the units attributes. character (80) :: sw_sfc_net_units_in, sw_sfc_dn_units_in, & prist_sw_sfc_dn_units_in, sw_sfc_alb_units_in, & clr_sw_sfc_dn_units_in, sw_toa_dn_units_in character (80) :: lat_units_in, lon_units_in month=2 year=1984 write (cyear,"(i4)") year write (cmon,"(i2.2)") month NRECS=ndmn(month) if (month.eq.2.and.mod(year,4).eq.0) NRECS=ndmn(month)+1 path_in='/SCF2/RADAPP/srb/NetCDF/QCSW/1984/' file_in=trim(path_in)//'srb_rel3.0_qcsw_daily_'//cyear//cmon//'.nc' print*,trim(file_in) ! Open the file. call check( nf90_open(file_in, nf90_nowrite, ncid)) ! Get the varids of the latitude and longitude coordinate variables. call check( nf90_inq_varid(ncid, LAT_NAME, lat_id) ) call check( nf90_inq_varid(ncid, LON_NAME, lon_id) ) ! Read the latitude and longitude data. call check( nf90_get_var(ncid, lat_id, lats) ) call check( nf90_get_var(ncid, lon_id, lons) ) ! Read the time information. call check( nf90_inq_varid(ncid, time_name, time_id) ) call check( nf90_get_var(ncid, time_id, time) ) ! Get the varids of the variables call check( nf90_inq_varid(ncid, sfcdn_name, sw_sfc_dn_id) ) call check( nf90_inq_varid(ncid, sw_sfc_net_name, sw_sfc_net_id) ) call check( nf90_inq_varid(ncid, psfcdn_name, prist_sw_sfc_dn_id) ) call check( nf90_inq_varid(ncid, csfcdn_name, clr_sw_sfc_dn_id) ) call check( nf90_inq_varid(ncid, alb_name, sw_sfc_alb_id) ) call check( nf90_inq_varid(ncid, toadn_name, sw_toa_dn_id) ) ! Read the units call check( nf90_get_att(ncid, sw_sfc_dn_id, 'units', sw_sfc_dn_units_in) ) call check( nf90_get_att(ncid, sw_sfc_net_id, 'units', sw_sfc_net_units_in) ) call check( nf90_get_att(ncid, prist_sw_sfc_dn_id, 'units', prist_sw_sfc_dn_units_in) ) call check( nf90_get_att(ncid, clr_sw_sfc_dn_id, 'units', clr_sw_sfc_dn_units_in) ) call check( nf90_get_att(ncid, sw_sfc_alb_id, 'units', sw_sfc_alb_units_in) ) call check( nf90_get_att(ncid, sw_toa_dn_id, 'units', sw_toa_dn_units_in) ) count = (/ NLONS, NLATS, 1 /) start = (/ 1, 1, 1 /) ! Read the variables do rec = 1, NRECS start(3)=rec call check( nf90_get_var(ncid, sw_sfc_dn_id, sw_sfc_dn,start=start,& count=count) ) call check( nf90_get_var(ncid, sw_sfc_net_id, sw_sfc_net,start=start,& count=count) ) call check( nf90_get_var(ncid, prist_sw_sfc_dn_id, prist_sw_sfc_dn,start=start,& count=count) ) call check( nf90_get_var(ncid, clr_sw_sfc_dn_id, clr_sw_sfc_dn,start=start,& count=count) ) call check( nf90_get_var(ncid, sw_sfc_alb_id, sw_sfc_alb,start=start,& count=count) ) call check( nf90_get_var(ncid, sw_toa_dn_id, sw_toa_dn,start=start,& count=count) ) end do call check( nf90_close(ncid) ) contains !***************************************** subroutine check(status) integer, intent ( in) :: status if(status /= nf90_noerr) then print *, trim(nf90_strerror(status)) stop "Stopped" end if end subroutine check !***************************************** end program read_srb_rel3_qcsw_daily_nc