Skip to content
Snippets Groups Projects
Commit 3aa1dd8b authored by RODIER Quentin's avatar RODIER Quentin
Browse files

R.Schoetter 05/05/2022: Bugfix: Update halo for vegetation drag variables

parent cb781d76
No related branches found
No related tags found
No related merge requests found
...@@ -73,12 +73,14 @@ SUBROUTINE DRAG_VEG(PTSTEP,PUT,PVT,PTKET,ODEPOTREE, PVDEPOTREE, & ...@@ -73,12 +73,14 @@ SUBROUTINE DRAG_VEG(PTSTEP,PUT,PVT,PTKET,ODEPOTREE, PVDEPOTREE, &
! P. Wautelet 28/01/2020: use the new data structures and subroutines for budgets for U ! P. Wautelet 28/01/2020: use the new data structures and subroutines for budgets for U
! C. Lac 02/2020: correction missing condition for budget on RC and SV ! C. Lac 02/2020: correction missing condition for budget on RC and SV
! P. Wautelet 04/02/2021: budgets: bugfixes for LDRAGTREE if LIMA + small optimisations and verifications ! P. Wautelet 04/02/2021: budgets: bugfixes for LDRAGTREE if LIMA + small optimisations and verifications
! R. Schoetter 04/2022: bug add update halo for vegetation drag variables
!!--------------------------------------------------------------- !!---------------------------------------------------------------
! !
! !
!* 0. DECLARATIONS !* 0. DECLARATIONS
! ------------ ! ------------
! !
USE MODD_ARGSLIST_ll, ONLY: LIST_ll
use modd_budget, only: lbudget_u, lbudget_v, lbudget_rc, lbudget_sv, lbudget_tke, & use modd_budget, only: lbudget_u, lbudget_v, lbudget_rc, lbudget_sv, lbudget_tke, &
NBUDGET_U, NBUDGET_V, NBUDGET_RC, NBUDGET_SV1, NBUDGET_TKE, & NBUDGET_U, NBUDGET_V, NBUDGET_RC, NBUDGET_SV1, NBUDGET_TKE, &
tbudgets tbudgets
...@@ -96,6 +98,7 @@ USE MODD_VEG_n ...@@ -96,6 +98,7 @@ USE MODD_VEG_n
use mode_budget, only: Budget_store_init, Budget_store_end use mode_budget, only: Budget_store_init, Budget_store_end
use mode_msg use mode_msg
USE MODE_ll
USE MODI_MNHGET_SURF_PARAM_n USE MODI_MNHGET_SURF_PARAM_n
USE MODI_SHUMAN USE MODI_SHUMAN
...@@ -125,8 +128,10 @@ REAL, DIMENSION(:,:,:,:), INTENT(INOUT) :: PSVS ...@@ -125,8 +128,10 @@ REAL, DIMENSION(:,:,:,:), INTENT(INOUT) :: PSVS
! !
!* 0.2 Declarations of local variables : !* 0.2 Declarations of local variables :
! !
INTEGER :: IIU,IJU,IKU,IKV ! array size along the k direction INTEGER :: IIU,IJU,IKU,IKV ! array size along the k direction
INTEGER :: JI, JJ, JK ! loop index INTEGER :: JI, JJ, JK ! loop index
INTEGER :: IINFO_ll
TYPE(LIST_ll), POINTER :: TZFIELDS_ll ! list of fields to exchange
! !
! !
REAL, DIMENSION(SIZE(PUT,1),SIZE(PUT,2),SIZE(PUT,3)) :: & REAL, DIMENSION(SIZE(PUT,1),SIZE(PUT,2),SIZE(PUT,3)) :: &
...@@ -186,6 +191,16 @@ WHERE ( ZLAI (:,:) > (XUNDEF-1.) ) ZLAI (:,:) = 0.0 ...@@ -186,6 +191,16 @@ WHERE ( ZLAI (:,:) > (XUNDEF-1.) ) ZLAI (:,:) = 0.0
ZUT_SCAL(:,:,:) = MXF(PUT(:,:,:)) ZUT_SCAL(:,:,:) = MXF(PUT(:,:,:))
ZVT_SCAL(:,:,:) = MYF(PVT(:,:,:)) ZVT_SCAL(:,:,:) = MYF(PVT(:,:,:))
ZTKET(:,:,:) = PTKET(:,:,:) ZTKET(:,:,:) = PTKET(:,:,:)
!
! Update halo
!
NULLIFY(TZFIELDS_ll)
CALL ADD3DFIELD_ll( TZFIELDS_ll, ZUT_SCAL, 'DRAG_VEG::ZUT_SCAL')
CALL ADD3DFIELD_ll( TZFIELDS_ll, ZVT_SCAL, 'DRAG_VEG::ZVT_SCAL')
CALL ADD3DFIELD_ll( TZFIELDS_ll, ZTKET , 'DRAG_VEG::ZTKET' )
CALL UPDATE_HALO_ll(TZFIELDS_ll,IINFO_ll)
CALL CLEANLIST_ll(TZFIELDS_ll)
!
!------------------------------------------------------------------------------- !-------------------------------------------------------------------------------
! !
!* 1. Computations of wind tendency due to canopy drag !* 1. Computations of wind tendency due to canopy drag
...@@ -243,6 +258,15 @@ ENDDO ...@@ -243,6 +258,15 @@ ENDDO
! To exclude the first vertical level already dealt in rain_ice or rain_c2r2_khko ! To exclude the first vertical level already dealt in rain_ice or rain_c2r2_khko
GDEP(:,:,2) = .FALSE. GDEP(:,:,2) = .FALSE.
! !
! Update halo
!
NULLIFY(TZFIELDS_ll)
CALL ADD3DFIELD_ll( TZFIELDS_ll, ZCDRAG , 'DRAG_VEG::ZCDRAG')
CALL ADD3DFIELD_ll( TZFIELDS_ll, ZDENSITY, 'DRAG_VEG::ZDENSITY')
CALL UPDATE_HALO_ll(TZFIELDS_ll,IINFO_ll)
CALL CLEANLIST_ll(TZFIELDS_ll)
!
!
!* 1.2 Drag force by wall surfaces !* 1.2 Drag force by wall surfaces
! --------------------------- ! ---------------------------
! !
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment