FY4B_C_SPMS/ProduceBackground/module_read_GRAPES.f90

305 lines
12 KiB
Fortran

module module_read_NWP
use netcdf
use hdf5
use module_satalite
implicit none
!include 'netcdf.inc'
public :: init_NWP, Read_NWP, &
allocate_NWP,deallocate_nwp
integer,public :: n_lat,n_lon,nlevel
real(kind=4),public,allocatable, dimension(:,:,:) :: Tt,qt,cfract,ozonet
real(kind=4),public,allocatable, dimension(:,:,:,:) :: cloudt
real(kind=4),public,allocatable, dimension(:,:) :: LATP, LONP
real(kind=4),public,allocatable, dimension(:,:) :: tst,T2mt, q2mt, u10mt, v10mt
real(kind=4),public,allocatable, dimension(:,:) :: PSFCt,seaicet !(Pa)
real(kind=4),public,allocatable, dimension(:) :: Pt !(hPa)
real(kind=4),public,allocatable, dimension(:,:,:) :: T1,q1,cfrac1,ozone1
real(kind=4),public,allocatable, dimension(:,:,:,:) :: cloud1
real(kind=4),public,allocatable, dimension(:,:) :: ts1,T2m1, q2m1, u10m1, v10m1
real(kind=4),public,allocatable, dimension(:,:) :: PSFC1,seaice1
real(kind=4),public,allocatable, dimension(:) :: P
real(kind=4),public,allocatable, dimension(:,:,:) :: T2,q2,cfrac2,ozone2
real(kind=4),public,allocatable, dimension(:,:,:,:) :: cloud2
real(kind=4),public,allocatable, dimension(:,:) :: ts2,T2m2, q2m2, u10m2, v10m2
real(kind=4),public,allocatable, dimension(:,:) :: PSFC2,seaice2
real(kind=4),public,allocatable, dimension(:,:,:) :: T3,q3,cfrac3,ozone3
real(kind=4),public,allocatable, dimension(:,:,:,:) :: cloud3
real(kind=4),public,allocatable, dimension(:,:) :: ts3,T2m3, q2m3, u10m3, v10m3
real(kind=4),public,allocatable, dimension(:,:) :: PSFC3,seaice3
integer,private :: nx,ny,nz
integer,private :: ncid,ncerror,dimid,varid,iret
character*400,private :: invfile
contains
!=================================================================================================
!=================================================================================================
subroutine init_NWP(nwpfilename)
implicit none
character*400 :: nwpfilename
ncerror = nf90_open(trim(nwpfilename), nf90_nowrite, ncid)
ncerror = nf90_inq_dimid(ncid,'lat',dimid)
ncerror = nf90_inquire_dimension(ncid,dimid,len=ny)
ncerror = nf90_inq_dimid(ncid,'lon',dimid)
ncerror = nf90_inquire_dimension(ncid,dimid,len=nx)
ncerror = nf90_inq_dimid(ncid,'level',dimid)
ncerror = nf90_inquire_dimension(ncid,dimid,len=nz)
ncerror = nf90_close(ncid)
n_lat = ny
n_lon = nx
nlevel = nz
return
end subroutine init_NWP
!=================================================================================================
!=================================================================================================
subroutine allocate_NWP(allocstatus)
integer :: allocstatus !nx,ny,nz
allocate(Tt (nx, ny, nz))
allocate(ozonet (nx, ny, nz))
allocate(qt (nx, ny, nz))
allocate(psfct (nx, ny))
allocate(seaicet (nx, ny))
allocate(T2mt (nx, ny))
allocate(tst (nx, ny))
allocate(q2mt (nx, ny))
allocate(u10mt (nx, ny))
allocate(cloudt (nx, ny, 6, nz-1))
allocate(cfract (nx, ny, nz-1))
allocate(v10mt (nx, ny))
allocate(Pt (nz))
allocstatus = allocated
return
end subroutine allocate_NWP
!=================================================================================================
!=================================================================================================
subroutine deallocate_nwp(allocstatus)
integer :: allocstatus
deallocate(Tt )
deallocate(ozonet )
deallocate(qt )
deallocate(psfct )
deallocate(seaicet )
deallocate(T2mt )
deallocate(tst )
deallocate(q2mt )
deallocate(u10mt )
deallocate(cloudt )
deallocate(cfract )
deallocate(v10mt )
deallocate(Pt )
allocstatus = deallocated
return
end subroutine deallocate_NWP
!=================================================================================================
!=================================================================================================
Subroutine Read_NWP( &
nwpfilename , &
sfcfilename , &
imonth )
integer(kind=4) :: ncid,sfcid
integer :: ncerror,varid, len_file, ndims, dimids(4), natts, xtyp
character*10 :: vname, dimname
character*300 :: sfcfilename,nwpfilename,O3filename
integer(kind=4) :: i,j,k,ilay,ilev, nlt,imonth
real(kind=4) :: es
real(kind=4) :: q2 !water vapor pressure at 2m
real(kind=4) :: scale,offset
real(kind=4) :: scaleq,offsetq
real(kind=4) :: cc
character(len=10),allocatable,dimension(:) :: vartemp
real(kind=4),allocatable,dimension(:,:) :: Ttt
real(kind=4),allocatable,dimension(:,:) :: qtt
real(kind=4),allocatable,dimension(:,:,:,:) :: ozonett
real(kind=4),allocatable,dimension(:) :: pressor_ozone
real(kind=4),allocatable,dimension(:,:) :: sstt
real(kind=4),allocatable,dimension(:,:) :: LATPt,LONPt
real(kind=4),allocatable,dimension(:,:) :: sktt
real(kind=4),allocatable,dimension(:,:) :: T2mtt
real(kind=4),allocatable,dimension(:,:) :: q2mtt
real(kind=4),allocatable,dimension(:,:) :: u10mtt
real(kind=4),allocatable,dimension(:,:) :: v10mtt
real(kind=4),allocatable,dimension(:,:) :: seaicett
real(kind=4),allocatable,dimension(:,:) :: psfctt
real(kind=4),allocatable,dimension(:,:) :: landmasknwp
integer(kind=4) :: n_time
integer :: hdferror
integer(HID_T) :: file_id
integer(HID_T) :: dataset_id,dspace_id
integer(HSIZE_T),dimension(4) :: dims_4d
integer(HSIZE_T) :: maxdimsd(4)
O3filename = './instrument_geo/2017_monthly_ozone_profile_GRAPES.nc'
n_time = 12
allocate(ozonett (n_lon,n_lat,nlevel,n_time))
!==========================read profile=================================
ncerror = nf90_open(trim(O3filename), nf90_nowrite, ncid)
ncerror = nf90_inq_varid(ncid, 'ozone', varid)
ncerror = nf90_get_var(ncid, varid, ozonett)
ncerror = nf90_close(ncid)
ncerror = nf90_open(trim(nwpfilename), nf90_nowrite, ncid)
ncerror = nf90_inq_varid(ncid, 'T', varid)
ncerror = nf90_get_var(ncid, varid, Tt)
ncerror = nf90_get_att(ncid,varid,'scale_factor',scale)
ncerror = nf90_get_att(ncid,varid,'add_offset',offset)
where(Tt/=-32767)
Tt = Tt*scale+offset
endwhere
where(Tt==-32767)
Tt = -9999.9
endwhere
ncerror = nf90_inq_varid(ncid, 'q', varid)
ncerror = nf90_get_var(ncid, varid, qt)
ncerror = nf90_get_att(ncid,varid,'scale_factor',scaleq)
ncerror = nf90_get_att(ncid,varid,'add_offset',offsetq)
where(qt/=-32767)
qt = qt*scaleq+offsetq
endwhere
where(qt<=0.)
qt = -9999.9
endwhere
where(qt>0)
qt = qt*1e6*28.966/18.0
endwhere
ncerror = nf90_inq_varid(ncid, 'P', varid)
ncerror = nf90_get_var(ncid, varid, Pt)
ncerror = nf90_inq_varid(ncid, 'latitude', varid)
ncerror = nf90_get_var(ncid, varid, LATP)
ncerror = nf90_inq_varid(ncid, 'longitude', varid)
ncerror = nf90_get_var(ncid, varid, LONP)
!===========================================================================
!==================== read surface =========================================
ncerror = nf90_inq_varid(ncid, 'Ts', varid)
ncerror = nf90_get_var(ncid, varid, tst)
ncerror = nf90_get_att(ncid,varid,'scale_factor',scale)
ncerror = nf90_get_att(ncid,varid,'add_offset',offset)
where(tst/=-32767)
tst = tst*scale+offset
endwhere
where(tst==-32767)
tst = -9999.9
endwhere
ncerror = nf90_inq_varid(ncid, 'psfc', varid)
ncerror = nf90_get_var(ncid, varid, psfct)
ncerror = nf90_get_att(ncid,varid,'scale_factor',scale)
ncerror = nf90_get_att(ncid,varid,'add_offset',offset)
where(psfct/=-32767)
psfct = psfct*scale+offset
endwhere
where(psfct==-32767)
psfct = -9999.9
endwhere
!print*,'skt',ts(1:10,10,1)
ncerror = nf90_inq_varid(ncid, 'T2m', varid)
ncerror = nf90_get_var(ncid, varid, T2mt)
ncerror = nf90_get_att(ncid,varid,'scale_factor',scale)
ncerror = nf90_get_att(ncid,varid,'add_offset',offset)
where(T2mt/=-32767)
T2mt = T2mt*scale+offset
endwhere
where(T2mt==-32767)
T2mt = -9999.9
endwhere
ncerror = nf90_inq_varid(ncid, 'q2m', varid)
ncerror = nf90_get_var(ncid, varid, q2mt)
ncerror = nf90_get_att(ncid,varid,'scale_factor',scale)
ncerror = nf90_get_att(ncid,varid,'add_offset',offset)
where(q2mt/=-32767)
q2mt = (q2mt*scale+offset)*1e6*28.966/18.0
endwhere
where(q2mt<=0)
q2mt = -9999.9
endwhere
ncerror = nf90_inq_varid(ncid, 'u10m', varid)
ncerror = nf90_get_var(ncid, varid, u10mt)
ncerror = nf90_get_att(ncid,varid,'scale_factor',scale)
ncerror = nf90_get_att(ncid,varid,'add_offset',offset)
where(u10mt/=-32767)
u10mt = u10mt*scale+offset
endwhere
where(u10mt==-32767)
u10mt = -9999.9
endwhere
ncerror = nf90_inq_varid(ncid, 'v10m', varid)
ncerror = nf90_get_var(ncid, varid, v10mt)
ncerror = nf90_get_att(ncid,varid,'scale_factor',scale)
ncerror = nf90_get_att(ncid,varid,'add_offset',offset)
where(v10mt/=-32767)
v10mt = v10mt*scale+offset
endwhere
where(v10mt==-32767)
v10mt = -9999.9
endwhere
ncerror = nf90_close(ncid)
do i = 1, n_lat
ozonet(:,i,:) = ozonett(:,n_lat-i+1,:,imonth)*1e6*28.966/48.0 !ppmv
enddo
seaicet(:,:) = 0.0
!======================== end of read =============================================
!==================================================================================
cloudt(:,:,:,:) = 0.0
cfract(:,:,:) = 0.0
! print*,'++++',LONP(1:5,1)
! print*,'----',LATP(1,1:5)
! stop
!=====================================================
deallocate(ozonett )
return
End Subroutine Read_NWP
!=================================================================================================
!=================================================================================================
end module module_read_NWP