I want to use nf90_get_var to read in
double time(sounding_id) ;
 time = 1451606399.896, 1451606399.92199, 1451606399.94902, 1451606400.00302,
    1451606400.03001, 1451606400.05701, 1451606400.22901, 1451606400.28199,
...
Why do I read all 0 values, no matter which of the following two methods?
      call check( nf90_get_var(ncid, varid, time_xhu) )
      write(*,*) "finish reading time_xhu ",time_xhu(1:2)
      count = (/  1 /)
      start = (/ 1 /)
      call check( nf90_get_var(ncid, varid, time_xhu_single,start=start,count = 
count) )
      write(*,*) "finish reading time_xhu_single ",time_xhu_single
I also attached the full script.
Thanks a lot!
Xiaoming
      program process_xco2
!       use HDF5
       use netcdf
      implicit none
! This will be the netCDF ID for the file and data variable.
      integer :: ncid, varid
      INTEGER(kind=8)     :: YYYYMMDDHHMM 
      INTEGER(kind=8)     :: YYYYMMDDHHMMSS 
      INTEGER(kind=8)     :: YYYYMMDDHHMM_pre
      INTEGER             :: Year, Month, Day, HH, MM, SS
      INTEGER             :: Year_pre, Month_pre, HH_pre, Day_pre
      integer :: i, N_count
       integer, parameter :: N_rec = 31866010! change 5->6 won't work
!      integer, parameter :: N_rec = 63147832 
!      integer(kind=8), parameter :: N_rec = 63147832 
      character(LEN=100) :: OCO_filename
      real,dimension(N_rec)     :: xco2, lat, lon
      real,dimension(N_rec)     :: time_xhu 
      real*8,dimension(1)     :: time_xhu_single 
      real                      :: XCO2_accumulate,lat_acc, lon_acc 
!      character(LEN=16), dimension(N_rec) :: date
      integer, dimension(N_rec,7) :: date
      character(N_rec) :: xco2_quality_flag
! To check the units attributes.
      character (len = *), parameter :: UNITS = "units"
      integer, parameter :: MAX_ATT_LEN = 80
      integer :: att_len
      character*(MAX_ATT_LEN) :: time_units_in
      integer :: ndims_in, nvars_in, ngatts_in, unlimdimid_in
      CHARACTER(LEN=15)            ::dname
      INTEGER                 :: dlength
      INTEGER                 :: ii 
      character(len=15) :: name
      integer :: xtype, ndims
      integer :: natts
      integer :: start(1), count(1)
      OCO_filename= "OCO-2_9_LITE_LEVEL2_extracted_2016only.nc"
      write(*,*) "will open ",trim(OCO_filename)
      call check( nf90_open(trim(OCO_filename), NF90_NOWRITE, ncid) )
      call check( nf90_inquire(ncid, ndims_in, nvars_in, ngatts_in, 
unlimdimid_in) )
      write(*,*) 
"ndims_in=",ndims_in,"nvars_in=",nvars_in,"ngatts_in",ngatts_in,"unlimdimid_in=",unlimdimid_in
      DO ii=1,ndims_in-1
       CALL check(NF90_INQUIRE_DIMENSION(ncid,ii,dname,len=dlength))
        SELECT CASE (TRIM(dname))
        CASE ('sounding_id')
         write(*,*) "dimension ",trim(dname)," is ",dlength
        CASE DEFAULT
         PRINT*,' Error while reading dimensions....'
         PRINT*,' Some dimensions are missing.   '
         PRINT*,' The program is terminating....';STOP
        END SELECT
      END DO
! Get the varid of the data variable, based on its name.
      call check( nf90_inq_varid(ncid, "time", varid) )
      call check( nf90_inquire_variable(ncid, varid, name, xtype, ndims))
      call check( nf90_get_var(ncid, varid, time_xhu) )
      write(*,*) "finish reading time_xhu ",time_xhu(1:2)
      
      count = (/  1 /)
      start = (/ 1 /)
      call check( nf90_get_var(ncid, varid, time_xhu_single,start=start,count = 
count) )
      write(*,*) "finish reading time_xhu_single ",time_xhu_single
      call check( nf90_get_att(ncid, varid, UNITS, time_units_in) )
      call check( nf90_inquire_attribute(ncid, varid, UNITS, len = att_len) )
       write(*,*) "units=",time_units_in(1:att_len)
      call check( nf90_inq_varid(ncid, "xco2", varid) )
      call check( nf90_get_var(ncid, varid, xco2) )
      write(*,*) "finish reading xco2 ",xco2(1:2)
      
      call check( nf90_inq_varid(ncid, "longitude", varid) )
      call check( nf90_get_var(ncid, varid, lon) )
      write(*,*) "finish reading lon ",lon(1:2)
      call check( nf90_inq_varid(ncid, "latitude", varid) )
      call check( nf90_get_var(ncid, varid, lat) )
      write(*,*) "finish reading lat ",lat(1:2)
      call check( nf90_inq_varid(ncid, "date", varid) )
      call check( nf90_get_var(ncid, varid, date) )
!      call check( nf90_inq_varid(ncid, "xco2_quality_flag", varid) )
!      call check( nf90_get_var(ncid, varid, xco2_quality_flag) )
      call check( nf90_close(ncid) )
      HH_pre = 0 ! to be consistent 
      XCO2_accumulate = 0
      N_count = 0
!      open(88, 
File="oco2_LtCO2_China_150101_171231.nc_2sMean.txt",action="write")
!      open(88, 
File="oco2_LtCO2_China_150101_171231.nc_6sMean.txt",action="write")
      open(88, 
File="OCO-2_9_LITE_LEVEL2_extracted_2016only.nc_20sMean.txt",action="write")
      write(88,'(A20, 3A16)'), "YYYYMMDDHHMM", "accumu_XCO2","lat","lon"
      do i = 1, N_rec 
!        write(*,'(A15)'), date(i)
!        write(*,*) xco2_quality_flag(i:i)
        read(date(i),*) YYYYMMDDHHMMSS
!        YYYYMMDDHHMM = YYYYMMDDHHMMSS/2*2 ! 1second 7km 2s mean
!        YYYYMMDDHHMM = YYYYMMDDHHMMSS/100*100+mod(YYYYMMDDHHMMSS,100)/6*6 ! 6s 
mean
        YYYYMMDDHHMM = YYYYMMDDHHMMSS/100*100+mod(YYYYMMDDHHMMSS,100)/20*20 ! 
20s mean
!       if(xco2_quality_flag(i:i).eq."0") then
          if (YYYYMMDDHHMM_pre.ne.YYYYMMDDHHMM.and.I.gt.1) then
           XCO2_accumulate = XCO2_accumulate/N_count
           lat_acc         = lat_acc/N_count
           lon_acc         = lon_acc/N_count
           write(88,'(I20,3F16.6)'),                           
YYYYMMDDHHMM_pre, XCO2_accumulate, lat_acc, lon_acc
           write(*,'(A, I20,F18.6, 2F10.3)'),"!!!!!average!!", 
YYYYMMDDHHMM_pre, XCO2_accumulate, lat_acc, lon_acc
           XCO2_accumulate = XCO2(i)  ! restart calculation 
           lat_acc         = lat(i)  ! restart calculation 
           lon_acc         = lon(i)  ! restart calculonion 
           N_count = 1
          else
           XCO2_accumulate = XCO2_accumulate + XCO2(i)
           lat_acc         = lat_acc + lat(i)  
           lon_acc         = lon_acc + lon(i) 
           N_count = N_count + 1
          end if
         write(*,'(A,1x,A,1x,A,1x, I20,F16.6, 2F10.3,I5)') "flag ", 
xco2_quality_flag(i:i), " good!@" &
           ,YYYYMMDDHHMMSS, XCO2(i) ,lat(i),lon(i), N_count 
         YYYYMMDDHHMM_pre = YYYYMMDDHHMM
!        else
!         write(*,*) "with flag ", xco2_quality_flag(i:i), " bad!"
!        end if 
      end do 
         XCO2_accumulate = XCO2_accumulate/N_count
         lat_acc         = lat_acc/N_count
         lon_acc         = lon_acc/N_count
         write(88,'(I20,3F16.6)'),                           YYYYMMDDHHMM_pre, 
XCO2_accumulate, lat_acc, lon_acc
         write(*,'(A, I20,F18.6, 2F10.3,I5)'),"!!!!!average!!", 
YYYYMMDDHHMM_pre, XCO2_accumulate, lat_acc, lon_acc, N_count
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