Skip to content

Commit

Permalink
Merge pull request NASA-LIS#1110 from yhkwon81/feature/ldt-gvf-da
Browse files Browse the repository at this point in the history
New features in LDT for GVF CDF generation and SMAP_E_OPL retrievals
  • Loading branch information
emkemp authored Sep 27, 2022
2 parents 5ebddc6 + 6a4f85b commit c4fa8bb
Show file tree
Hide file tree
Showing 43 changed files with 7,945 additions and 205 deletions.
163 changes: 163 additions & 0 deletions ldt/DAobs/CDFS_GVF/CDFS_GVF_obsMod.F90
Original file line number Diff line number Diff line change
@@ -0,0 +1,163 @@
!-----------------------BEGIN NOTICE -- DO NOT EDIT-----------------------
! NASA Goddard Space Flight Center
! Land Information System Framework (LISF)
! Version 7.5
!
! Copyright (c) 2020 United States Government as represented by the
! Administrator of the National Aeronautics and Space Administration.
! All Rights Reserved.
!-------------------------END NOTICE -- DO NOT EDIT-----------------------
! !MODULE: CDFSGVFobsMod
!
! !DESCRIPTION:
! This module handles the observation plugin for the
! CDFS GVF retrievals
!
! !REVISION HISTORY:
! 04 Mar 2022: Yonghwan Kwon, Initial Specification
!
module CDFSGVFobsMod
! !USES:
use ESMF
use map_utils

implicit none

PRIVATE
!-----------------------------------------------------------------------------
! !PUBLIC MEMBER FUNCTIONS:
!-----------------------------------------------------------------------------
PUBLIC :: CDFSGVFobsinit !Initializes structures for reading CDFS GVF data
!-----------------------------------------------------------------------------
! !PUBLIC TYPES:
!-----------------------------------------------------------------------------
PUBLIC :: CDFSgvfobs !Object to hold CDFSgvf observation attributes
!EOP
type, public :: cdfsgvfdec

character*100 :: odir
integer :: nc, nr
real :: gridDesci(50)
real, allocatable :: gvfobs(:,:)
integer, allocatable :: n11(:)
integer, allocatable :: n12(:)
integer, allocatable :: n21(:)
integer, allocatable :: n22(:)
real, allocatable :: w11(:)
real, allocatable :: w12(:)
real, allocatable :: w21(:)
real, allocatable :: w22(:)

end type cdfsgvfdec

type(cdfsgvfdec),allocatable :: CDFSgvfobs(:)

contains

!BOP
!
! !ROUTINE: CDFSGVFobsinit
! \label{CDFSGVFobsinit}
!
! !INTERFACE:
subroutine CDFSGVFobsinit()
!
! !USES:
use ESMF
use LDT_coreMod
use LDT_DAobsDataMod
use LDT_timeMgrMod
use LDT_logMod

implicit none
! !ARGUMENTS:

!
! !DESCRIPTION:
! This subroutine initializes and sets up the data structures required
! for reading the CDFS GVF data.
!
!EOP

!integer :: npts
!type(ESMF_TimeInterval) :: alarmInterval
!type(ESMF_Time) :: alarmTime
integer :: status, rc
integer :: n

allocate(CDFSgvfobs(LDT_rc%nnest))

call ESMF_ConfigFindLabel(LDT_config, &
'CDFS GVF data directory:', rc=status)
do n=1,LDT_rc%nnest
call ESMF_ConfigGetAttribute(LDT_Config, CDFSgvfobs(n)%odir, &
rc=status)
call LDT_verify(status, &
'CDFS GVF data directory: not defined')
enddo

do n=1,LDT_rc%nnest

allocate(CDFSgvfobs(n)%gvfobs(LDT_rc%lnc(n),LDT_rc%lnr(n)))

CDFSgvfobs(n)%gvfobs = -9999.0

call LDT_initializeDAobsEntry(LDT_DAobsData(n)%gvf_obs, &
"-",1,1)
LDT_DAobsData(n)%gvf_obs%selectStats = 1

CDFSgvfobs(n)%nc = 7200
CDFSgvfobs(n)%nr = 3600

CDFSgvfobs(n)%gridDesci(1) = 0
CDFSgvfobs(n)%gridDesci(2) = CDFSgvfobs(n)%nc
CDFSgvfobs(n)%gridDesci(3) = CDFSgvfobs(n)%nr
CDFSgvfobs(n)%gridDesci(4) = -89.975
CDFSgvfobs(n)%gridDesci(5) = -179.975
CDFSgvfobs(n)%gridDesci(6) = 128
CDFSgvfobs(n)%gridDesci(7) = 89.975
CDFSgvfobs(n)%gridDesci(8) = 179.975
CDFSgvfobs(n)%gridDesci(9) = 0.05
CDFSgvfobs(n)%gridDesci(10) = 0.05
CDFSgvfobs(n)%gridDesci(20) = 64

if(LDT_isLDTatAfinerResolution(n,0.05)) then

allocate(CDFSgvfobs(n)%n11(LDT_rc%lnc(n)*LDT_rc%lnr(n)))
allocate(CDFSgvfobs(n)%n12(LDT_rc%lnc(n)*LDT_rc%lnr(n)))
allocate(CDFSgvfobs(n)%n21(LDT_rc%lnc(n)*LDT_rc%lnr(n)))
allocate(CDFSgvfobs(n)%n22(LDT_rc%lnc(n)*LDT_rc%lnr(n)))
allocate(CDFSgvfobs(n)%w11(LDT_rc%lnc(n)*LDT_rc%lnr(n)))
allocate(CDFSgvfobs(n)%w12(LDT_rc%lnc(n)*LDT_rc%lnr(n)))
allocate(CDFSgvfobs(n)%w21(LDT_rc%lnc(n)*LDT_rc%lnr(n)))
allocate(CDFSgvfobs(n)%w22(LDT_rc%lnc(n)*LDT_rc%lnr(n)))

call bilinear_interp_input (n, &
CDFSgvfobs(n)%gridDesci,&
CDFSgvfobs(n)%n11,&
CDFSgvfobs(n)%n12,&
CDFSgvfobs(n)%n21,&
CDFSgvfobs(n)%n22,&
CDFSgvfobs(n)%w11,&
CDFSgvfobs(n)%w12,&
CDFSgvfobs(n)%w21,&
CDFSgvfobs(n)%w22)

else

allocate(CDFSgvfobs(n)%n11(CDFSgvfobs(n)%nc*&
CDFSgvfobs(n)%nr))

call upscaleByAveraging_input (&
CDFSgvfobs(n)%gridDesci,&
LDT_rc%gridDesc(n,:),&
CDFSgvfobs(n)%nc*&
CDFSgvfobs(n)%nr,&
LDT_rc%lnc(n)*LDT_rc%lnr(n),&
CDFSgvfobs(n)%n11)

endif
enddo
end subroutine CDFSGVFobsinit

end module CDFSGVFobsMod
209 changes: 209 additions & 0 deletions ldt/DAobs/CDFS_GVF/readCDFS_GVFObs.F90
Original file line number Diff line number Diff line change
@@ -0,0 +1,209 @@
!-----------------------BEGIN NOTICE -- DO NOT EDIT-----------------------
! NASA Goddard Space Flight Center
! Land Information System Framework (LISF)
! Version 7.5
!
! Copyright (c) 2020 United States Government as represented by the
! Administrator of the National Aeronautics and Space Administration.
! All Rights Reserved.
!-------------------------END NOTICE -- DO NOT EDIT-----------------------
#include "LDT_misc.h"
!BOP
!
! !ROUTINE: readCDFS_GVFObs
! \label{readCDFS_GVFObs}
!
! !REVISION HISTORY:
! 4 Mar 2022: Yonghwan Kwon, Initial Specification
!
! !INTERFACE:
subroutine readCDFS_GVFObs(n)
! !USES:
use ESMF
use LDT_coreMod
use LDT_logMod
use LDT_DAobsDataMod
use CDFSGVFobsMod

implicit none
! !ARGUMENTS:
integer, intent(in) :: n
!
! !DESCRIPTION:
!
! This subroutine provides the data reader for
! CDFS Green Vegetation Fraction (GVF) data
!
!EOP

real :: timenow
logical :: alarmCheck
logical :: file_exists
integer :: c,r
character*100 :: fname
real :: gvfobs(LDT_rc%lnc(n)*LDT_rc%lnr(n))

!-----------------------------------------------------------------------
! It is assumed that CDF is computed using daily observations.
!-----------------------------------------------------------------------
CDFSgvfobs(n)%gvfobs = LDT_rc%udef
gvfobs= LDT_rc%udef

call create_CDFSgvf_filename(CDFSgvfobs(n)%odir, &
LDT_rc%yr, LDT_rc%mo, LDT_rc%da,&
fname)

inquire(file=trim(fname),exist=file_exists)
if(file_exists) then

write(LDT_logunit,*) '[INFO] Reading ',trim(fname)
call read_CDFS_GVF_data(n, fname, gvfobs)
write(LDT_logunit,*) '[INFO] Finished reading ',trim(fname)

do r=1,LDT_rc%lnr(n)
do c=1,LDT_rc%lnc(n)
if(gvfobs(c+(r-1)*LDT_rc%lnc(n)).ne.-9999.0) then
CDFSgvfobs(n)%gvfobs(c,r) = gvfobs(c+(r-1)*LDT_rc%lnc(n))
endif
enddo
enddo
endif

call LDT_logSingleDAobs(n,LDT_DAobsData(n)%gvf_obs,&
CDFSgvfobs(n)%gvfobs,vlevel=1)

end subroutine readCDFS_GVFObs

!BOP
!
! !ROUTINE: read_CDFS_GVF_data
! \label{read_CDFS_GVF_data}
!
! !INTERFACE:
subroutine read_CDFS_GVF_data(n, fname, gvfobs_ip)
!
! !USES:

use LDT_coreMod
use LDT_logMod
use LDT_timeMgrMod
use CDFSGVFobsMod

implicit none
!
! !INPUT PARAMETERS:
!
integer :: n
character (len=*) :: fname
real :: gvfobs_ip(LDT_rc%lnc(n)*LDT_rc%lnr(n))
!
! !DESCRIPTION:
! This subroutine reads the CDFS GVF file
!
! The arguments are:
! \begin{description}
! \item[n] index of the nest
! \item[fname] name of the CDFS GVF file
! \item[gvtobs\_ip] GVF data processed to the LIS domain
! \end{description}
!
!
!EOP

! !USES:
integer, parameter :: nc=7200, nr=3600
real*4 :: gvf_raw(CDFSgvfobs(n)%nc,CDFSgvfobs(n)%nr)
real :: gvf_in(CDFSgvfobs(n)%nc*CDFSgvfobs(n)%nr)
logical*1 :: gvf_data_b(CDFSgvfobs(n)%nc*CDFSgvfobs(n)%nr)
logical*1 :: gvfobs_b_ip(LDT_rc%lnc(n)*LDT_rc%lnr(n))
integer :: gvfid
integer :: ios, nid
integer :: c,r
integer :: ftn1

ftn1 = LDT_getNextUnitNumber()
open(unit=ftn1,file=fname,form='unformatted',access='direct',convert='little_endian',recl=4*nc*nr,status='old')
read(ftn1, rec=1) gvf_raw
close(1)
call LDT_releaseUnitNumber(ftn1)

do r=1,CDFSgvfobs(n)%nr
do c=1,CDFSgvfobs(n)%nc
if (gvf_raw(c,r)>=0.and.&
gvf_raw(c,r)<=100) then
gvf_in(c+(r-1)*CDFSgvfobs(n)%nc) = gvf_raw(c,r)
gvf_data_b(c+(r-1)*CDFSgvfobs(n)%nc) = .true.
else
gvf_in(c+(r-1)*CDFSgvfobs(n)%nc) = LDT_rc%udef
gvf_data_b(c+(r-1)*CDFSgvfobs(n)%nc) = .false.
endif
enddo
enddo

!--------------------------------------------------------------------------
! Interpolate to the LDT running domain
!--------------------------------------------------------------------------
if(LDT_isLDTatAfinerResolution(n,0.05)) then
call bilinear_interp(LDT_rc%gridDesc(n,:),&
gvf_data_b, gvf_in, gvfobs_b_ip, gvfobs_ip, &
CDFSgvfobs(n)%nc*CDFSgvfobs(n)%nr, &
LDT_rc%lnc(n)*LDT_rc%lnr(n), &
LDT_domain(n)%lat, LDT_domain(n)%lon,&
CDFSgvfobs(n)%w11,CDFSgvfobs(n)%w12,&
CDFSgvfobs(n)%w21,CDFSgvfobs(n)%w22,&
CDFSgvfobs(n)%n11,CDFSgvfobs(n)%n12,&
CDFSgvfobs(n)%n21,CDFSgvfobs(n)%n22,LDT_rc%udef,ios)
else
call upscaleByAveraging(CDFSgvfobs(n)%nc*CDFSgvfobs(n)%nr,&
LDT_rc%lnc(n)*LDT_rc%lnr(n), &
LDT_rc%udef, CDFSgvfobs(n)%n11,&
gvf_data_b,gvf_in, gvfobs_b_ip, gvfobs_ip)
endif

end subroutine read_CDFS_GVF_data


!BOP
! !ROUTINE: create_CDFSgvf_filename
! \label{create_CDFSgvf_filename}
!
! !INTERFACE:
subroutine create_CDFSgvf_filename(ndir,yr,mo,da,filename)
! !USES:

implicit none
! !ARGUMENTS:
character(len=*) :: filename
integer :: yr, mo, da
character (len=*) :: ndir
!
! !DESCRIPTION:
! This subroutine creates the CDFS GVF filename
! based on the time and date
!
! The arguments are:
! \begin{description}
! \item[ndir] name of the CDFS GVF data directory
! \item[yr] current year
! \item[mo] current month
! \item[da] current day
! \item[filename] Generated CDFS GVF filename
! \end{description}
!EOP

character*4 :: yyyy
character*2 :: mm,dd

write(unit=yyyy, fmt='(i4.4)') yr
write(unit=mm, fmt='(i2.2)') mo
write(unit=dd, fmt='(i2.2)') da

filename = trim(ndir)//'/'//trim(yyyy)//'/green.'//&
trim(yyyy)//trim(mm)//trim(dd)//'.1gd4r'

end subroutine create_CDFSgvf_filename





Loading

0 comments on commit c4fa8bb

Please sign in to comment.