Skip to content

Commit

Permalink
Added the support for CNN-based snow
Browse files Browse the repository at this point in the history
Added the support in LIS for data assimilation of CNN-based AMSR snow
retrievals

Support for the same dataset was also added in LVT

Resolves NASA-LIS#1479
  • Loading branch information
sujayvkumar committed Jan 16, 2024
1 parent 8ba221c commit 308254b
Show file tree
Hide file tree
Showing 25 changed files with 2,464 additions and 11 deletions.
339 changes: 339 additions & 0 deletions lis/dataassim/obs/AMSRcnnSnow/AMSRcnnSnowMod.F90
Original file line number Diff line number Diff line change
@@ -0,0 +1,339 @@
!-----------------------BEGIN NOTICE -- DO NOT EDIT-----------------------
! NASA Goddard Space Flight Center
! Land Information System Framework (LISF)
! Version 7.4
!
! Copyright (c) 2022 United States Government as represented by the
! Administrator of the National Aeronautics and Space Administration.
! All Rights Reserved.
!-------------------------END NOTICE -- DO NOT EDIT-----------------------
!BOP
!
! !MODULE: AMSRcnnSnowMod
!
! !DESCRIPTION:
! This module contains interfaces and subroutines to
! handle the Margulis Western US Snow Reanalysis dataset.
! Available online at: https://nsidc.org/data/WUS_UCLA_SR/versions/1
!
! !REVISION HISTORY:
! 05 Jan 2024: Sujay Kumar; Initial version
!
module AMSRcnnSnowMod
! !USES:
use ESMF
use map_utils
use LIS_constantsMod, only : LIS_CONST_PATH_LEN

implicit none

PRIVATE

!-----------------------------------------------------------------------------
! !PUBLIC MEMBER FUNCTIONS:
!-----------------------------------------------------------------------------
public :: AMSRcnnSnow_setup
!-----------------------------------------------------------------------------
! !PUBLIC TYPES:
!-----------------------------------------------------------------------------
public :: AMSRcnnSnow_struc
!EOP
type, public:: AMSRcnnSnow_dec

logical :: startMode
integer :: nc
integer :: nr
integer :: mi
real :: ssdev_inp
type(proj_info) :: proj
real :: gridDesci(50)
real, allocatable :: rlat(:)
real, allocatable :: rlon(:)
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 AMSRcnnSnow_dec

type(AMSRcnnSnow_dec),allocatable :: AMSRcnnSnow_struc(:)

contains

!BOP
!
! !ROUTINE: AMSRcnnSnow_setup
! \label{AMSRcnnSnow_setup}
!
! !INTERFACE:
subroutine AMSRcnnSnow_setup(k, OBS_State, OBS_Pert_State)
! !USES:
use LIS_coreMod
use LIS_timeMgrMod
use LIS_historyMod
use LIS_dataAssimMod
use LIS_perturbMod
use LIS_logmod
use LIS_DAobservationsMod

implicit none

! !ARGUMENTS:
integer :: k
type(ESMF_State) :: OBS_State(LIS_rc%nnest)
type(ESMF_State) :: OBS_Pert_State(LIS_rc%nnest)
!
! !DESCRIPTION:
!
! This routine completes the runtime initializations and
! creation of data strctures required for handling
! AMSRcnnSnow data.
!
! The arguments are:
! \begin{description}
! \item[OBS\_State] observation state
! \item[OBS\_Pert\_State] observation perturbations state
! \end{description}
!EOP

integer :: n,i,t,kk,c,r
real, allocatable :: obserr(:,:)
integer :: ftn
integer :: status
type(ESMF_Field) :: obsField(LIS_rc%nnest)
type(ESMF_ArraySpec) :: intarrspec, realarrspec
type(ESMF_Field) :: pertField(LIS_rc%nnest)
type(ESMF_ArraySpec) :: pertArrSpec
character(len=LIS_CONST_PATH_LEN) :: snodasobsdir
character*100 :: temp
character*1 :: vid(2)
character*40, allocatable :: vname(:)
real , allocatable :: varmin(:)
real , allocatable :: varmax(:)
type(pert_dec_type) :: obs_pert
real, pointer :: obs_temp(:,:)
real, allocatable :: ssdev(:)
real :: cornerlat1, cornerlat2
real :: cornerlon1, cornerlon2

allocate(AMSRcnnSnow_struc(LIS_rc%nnest))

call ESMF_ArraySpecSet(intarrspec,rank=1,typekind=ESMF_TYPEKIND_I4,&
rc=status)
call LIS_verify(status)

call ESMF_ArraySpecSet(realarrspec,rank=1,typekind=ESMF_TYPEKIND_R4,&
rc=status)
call LIS_verify(status)

call ESMF_ArraySpecSet(pertArrSpec,rank=2,typekind=ESMF_TYPEKIND_R4,&
rc=status)
call LIS_verify(status)

call ESMF_ConfigFindLabel(LIS_config,"AMSR CNN snow depth data directory:",&
rc=status)
do n=1,LIS_rc%nnest
call ESMF_ConfigGetAttribute(LIS_config,snodasobsdir,&
rc=status)
call LIS_verify(status, 'AMSR CNN snow depth data directory: is missing')

call ESMF_AttributeSet(OBS_State(n),"Data Directory",&
snodasobsdir, rc=status)
call LIS_verify(status)
enddo

do n=1,LIS_rc%nnest
call ESMF_AttributeSet(OBS_State(n),"Data Update Status",&
.false., rc=status)
call LIS_verify(status)

call ESMF_AttributeSet(OBS_State(n),"Data Update Time",&
-99.0, rc=status)
call LIS_verify(status)

call ESMF_AttributeSet(OBS_State(n),"Data Assimilate Status",&
.false., rc=status)
call LIS_verify(status)

call ESMF_AttributeSet(OBS_State(n),"Number Of Observations",&
LIS_rc%obs_ngrid(k),rc=status)
call LIS_verify(status)

enddo

write(LIS_logunit,*)'[INFO] read AMSR CNN snow depth data specifications'

!----------------------------------------------------------------------------
! Create the array containers that will contain the observations and
! the perturbations. AMSRcnnSnow
! observations are in the grid space. Since there is only one layer
! being assimilated, the array size is LIS_rc%obs_ngrid(k).
!
!----------------------------------------------------------------------------

do n=1,LIS_rc%nnest

write(unit=temp,fmt='(i2.2)') 1
read(unit=temp,fmt='(2a1)') vid

obsField(n) = ESMF_FieldCreate(arrayspec=realarrspec,&
grid=LIS_obsvecGrid(n,k),&
name="Observation"//vid(1)//vid(2),rc=status)
call LIS_verify(status)

!Perturbations State
write(LIS_logunit,*) '[INFO] Opening attributes for observations ',&
trim(LIS_rc%obsattribfile(k))
ftn = LIS_getNextUnitNumber()
open(ftn,file=trim(LIS_rc%obsattribfile(k)),status='old')
read(ftn,*)
read(ftn,*) LIS_rc%nobtypes(k)
read(ftn,*)

allocate(vname(LIS_rc%nobtypes(k)))
allocate(varmax(LIS_rc%nobtypes(k)))
allocate(varmin(LIS_rc%nobtypes(k)))

do i=1,LIS_rc%nobtypes(k)
read(ftn,fmt='(a40)') vname(i)
read(ftn,*) varmin(i),varmax(i)
write(LIS_logunit,*) '[INFO] ',vname(i),varmin(i),varmax(i)
enddo
call LIS_releaseUnitNumber(ftn)

allocate(ssdev(LIS_rc%obs_ngrid(k)))

if(trim(LIS_rc%perturb_obs(k)).ne."none") then
allocate(obs_pert%vname(1))
allocate(obs_pert%perttype(1))
allocate(obs_pert%ssdev(1))
allocate(obs_pert%stdmax(1))
allocate(obs_pert%zeromean(1))
allocate(obs_pert%tcorr(1))
allocate(obs_pert%xcorr(1))
allocate(obs_pert%ycorr(1))
allocate(obs_pert%ccorr(1,1))

call LIS_readPertAttributes(1,LIS_rc%obspertAttribfile(k),&
obs_pert)

! Set obs err to be uniform (will be rescaled later for each grid point).
ssdev = obs_pert%ssdev(1)
AMSRcnnSnow_struc(n)%ssdev_inp = obs_pert%ssdev(1)

pertField(n) = ESMF_FieldCreate(arrayspec=pertArrSpec,&
grid=LIS_obsensOnGrid(n,k),name="Observation"//vid(1)//vid(2),&
rc=status)
call LIS_verify(status)

! initializing the perturbations to be zero
call ESMF_FieldGet(pertField(n),localDE=0,farrayPtr=obs_temp,rc=status)
call LIS_verify(status)
obs_temp(:,:) = 0

call ESMF_AttributeSet(pertField(n),"Perturbation Type",&
obs_pert%perttype(1), rc=status)
call LIS_verify(status)

if(LIS_rc%obs_ngrid(k).gt.0) then
call ESMF_AttributeSet(pertField(n),"Standard Deviation",&
ssdev,itemCount=LIS_rc%obs_ngrid(k),rc=status)
call LIS_verify(status)
endif

call ESMF_AttributeSet(pertField(n),"Std Normal Max",&
obs_pert%stdmax(1), rc=status)
call LIS_verify(status)

call ESMF_AttributeSet(pertField(n),"Ensure Zero Mean",&
obs_pert%zeromean(1),rc=status)
call LIS_verify(status)

call ESMF_AttributeSet(pertField(n),"Temporal Correlation Scale",&
obs_pert%tcorr(1),rc=status)
call LIS_verify(status)

call ESMF_AttributeSet(pertField(n),"X Correlation Scale",&
obs_pert%xcorr(1),rc=status)

call ESMF_AttributeSet(pertField(n),"Y Correlation Scale",&
obs_pert%ycorr(1),rc=status)

call ESMF_AttributeSet(pertField(n),"Cross Correlation Strength",&
obs_pert%ccorr(1,:),itemCount=1,rc=status)

endif

deallocate(vname)
deallocate(varmax)
deallocate(varmin)
deallocate(ssdev)

enddo
write(LIS_logunit,*) &
'[INFO] Created the States to hold the AMSR CNN snow observations data'

do n=1,LIS_rc%nnest

AMSRcnnSnow_struc(n)%nc = 3599
AMSRcnnSnow_struc(n)%nr = 700

AMSRcnnSnow_struc(n)%gridDesci(1) = 0
AMSRcnnSnow_struc(n)%gridDesci(2) = AMSRcnnSnow_struc(n)%nc
AMSRcnnSnow_struc(n)%gridDesci(3) = AMSRcnnSnow_struc(n)%nr
AMSRcnnSnow_struc(n)%gridDesci(4) = 0.025
AMSRcnnSnow_struc(n)%gridDesci(5) = -179.975
AMSRcnnSnow_struc(n)%gridDesci(6) = 128
AMSRcnnSnow_struc(n)%gridDesci(7) = 69.925
AMSRcnnSnow_struc(n)%gridDesci(8) = 179.825
AMSRcnnSnow_struc(n)%gridDesci(9) = 0.1
AMSRcnnSnow_struc(n)%gridDesci(10) = 0.1
AMSRcnnSnow_struc(n)%gridDesci(20) = 64

AMSRcnnSnow_struc(n)%mi = AMSRcnnSnow_struc(n)%nc*AMSRcnnSnow_struc(n)%nr

!-----------------------------------------------------------------------------
! Use interpolation if LIS is running finer than 500 m.
!-----------------------------------------------------------------------------

allocate(AMSRcnnSnow_struc(n)%rlat(LIS_rc%obs_lnc(k)*LIS_rc%obs_lnr(k)))
allocate(AMSRcnnSnow_struc(n)%rlon(LIS_rc%obs_lnc(k)*LIS_rc%obs_lnr(k)))
allocate(AMSRcnnSnow_struc(n)%n11(LIS_rc%obs_lnc(k)*LIS_rc%obs_lnr(k)))
allocate(AMSRcnnSnow_struc(n)%n12(LIS_rc%obs_lnc(k)*LIS_rc%obs_lnr(k)))
allocate(AMSRcnnSnow_struc(n)%n21(LIS_rc%obs_lnc(k)*LIS_rc%obs_lnr(k)))
allocate(AMSRcnnSnow_struc(n)%n22(LIS_rc%obs_lnc(k)*LIS_rc%obs_lnr(k)))
allocate(AMSRcnnSnow_struc(n)%w11(LIS_rc%obs_lnc(k)*LIS_rc%obs_lnr(k)))
allocate(AMSRcnnSnow_struc(n)%w12(LIS_rc%obs_lnc(k)*LIS_rc%obs_lnr(k)))
allocate(AMSRcnnSnow_struc(n)%w21(LIS_rc%obs_lnc(k)*LIS_rc%obs_lnr(k)))
allocate(AMSRcnnSnow_struc(n)%w22(LIS_rc%obs_lnc(k)*LIS_rc%obs_lnr(k)))

call bilinear_interp_input_withgrid(&
AMSRcnnSnow_struc(n)%gridDesci(:), &
LIS_rc%obs_gridDesc(k,:),&
LIS_rc%obs_lnc(k)*LIS_rc%obs_lnr(k),&
AMSRcnnSnow_struc(n)%rlat, AMSRcnnSnow_struc(n)%rlon,&
AMSRcnnSnow_struc(n)%n11, AMSRcnnSnow_struc(n)%n12, &
AMSRcnnSnow_struc(n)%n21, AMSRcnnSnow_struc(n)%n22, &
AMSRcnnSnow_struc(n)%w11, AMSRcnnSnow_struc(n)%w12, &
AMSRcnnSnow_struc(n)%w21, AMSRcnnSnow_struc(n)%w22)


call LIS_registerAlarm("AMSRcnnSnow read alarm",&
86400.0, 86400.0)
AMSRcnnSnow_struc(n)%startMode = .true.

call ESMF_StateAdd(OBS_State(n),(/obsField(n)/),rc=status)
call LIS_verify(status)

call ESMF_StateAdd(OBS_Pert_State(n),(/pertField(n)/),rc=status)
call LIS_verify(status)

enddo


end subroutine AMSRcnnSnow_setup

end module AMSRcnnSnowMod
Loading

0 comments on commit 308254b

Please sign in to comment.