SURFEX v8.1
General documentation of Surfex
update_data_cover.F90
Go to the documentation of this file.
1 !SFX_LIC Copyright 1994-2014 CNRS, Meteo-France and Universite Paul Sabatier
2 !SFX_LIC This is part of the SURFEX software governed by the CeCILL-C licence
3 !SFX_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt
4 !SFX_LIC for details. version 1.
5 ! #########
6  SUBROUTINE update_data_cover (DTCO, DTV, KDIM, KPATCH, OMEB_PATCH, &
7  KYEAR)
8 ! #########################
9 !
10 !!**** *INI_DATA_COVER* initializes cover-field correspondance arrays
11 !!
12 !! PURPOSE
13 !! -------
14 !!
15 !! METHOD
16 !! ------
17 !!
18 !!
19 !! EXTERNAL
20 !! --------
21 !!
22 !! IMPLICIT ARGUMENTS
23 !! ------------------
24 !!
25 !! REFERENCE
26 !! ---------
27 !!
28 !! AUTHOR
29 !! ------
30 !!
31 !! V. Masson Meteo-France
32 !!
33 !! MODIFICATION
34 !! ------------
35 !!
36 !! Original 09/2008
37 !! P. Samuelsson 10/2014 MEB
38 !----------------------------------------------------------------------------
39 !
40 !* 0. DECLARATION
41 ! -----------
42 !
43 !
44 !
46 USE modd_data_isba_n, ONLY : data_isba_t
47 USE modd_sfx_grid_n, ONLY : grid_t
48 !
52 !
53 USE yomhook ,ONLY : lhook, dr_hook
54 USE parkind1 ,ONLY : jprb
55 !
56 USE modi_ecoclimap2_lai
57 !
58 USE modi_ini_data_param
59 USE modi_fix_meb_veg
60 !
61 IMPLICIT NONE
62 !
63 !* 0.1 Declaration of arguments
64 ! ------------------------
65 !
66 !
67 TYPE(data_cover_t), INTENT(INOUT) :: DTCO
68 TYPE(data_isba_t), INTENT(INOUT) :: DTV
69 INTEGER, INTENT(IN) :: KDIM
70 !
71 LOGICAL, DIMENSION(:), POINTER :: OMEB_PATCH
72 INTEGER, INTENT(IN) :: KPATCH
73 !
74 INTEGER, INTENT(IN) :: KYEAR ! new year
75 REAL(KIND=JPRB) :: ZHOOK_HANDLE
76 !
77 !
78 !* 0.2 Declaration of local variables
79 ! ------------------------------
80 !
81 INTEGER :: ISIZE_LMEB_PATCH ! Number of patches with MEB=true
82 !
83 !* 0.3 Declaration of namelists
84 ! ------------------------
85 !
86 !-------------------------------------------------------------------------------
87 IF (lhook) CALL dr_hook('UPDATE_DATA_COVER',0,zhook_handle)
88 IF (kyear /= dtco%NYEAR) THEN
89  dtco%NYEAR = kyear
90  CALL ecoclimap2_lai(dtco%NYEAR)
91  CALL ini_data_param(plai=xdata_lai, ph_tree=xdata_h_tree, pveg_out=xdata_veg, &
92  pgreen=xdata_green, pz0=xdata_z0, pemis_eco=xdata_emis_eco, &
93  plaimin_out=xdata_laimin, pz0litter=xdata_z0litter, ph_veg=xdata_h_veg )
94 !
95  IF (ASSOCIATED(omeb_patch)) THEN
96  isize_lmeb_patch=count(omeb_patch(:))
97  ELSE
98  isize_lmeb_patch=0
99  END IF
100 !
101  IF (isize_lmeb_patch>0) THEN
102  CALL fix_meb_veg(dtv, kdim, omeb_patch, &
103  kpatch)
104  ENDIF
105 !
106 END IF
107 IF (lhook) CALL dr_hook('UPDATE_DATA_COVER',1,zhook_handle)
108 !-------------------------------------------------------------------------------
109 
110 END SUBROUTINE update_data_cover
subroutine fix_meb_veg(DTV, KDIM, OMEB_PATCH, KPATCH)
Definition: fix_meb_veg.F90:7
real, dimension(:,:,:), allocatable xdata_z0
subroutine update_data_cover(DTCO, DTV, KDIM, KPATCH, OMEB_PATCH,
real, dimension(:,:), allocatable xdata_laimin
integer, parameter jprb
Definition: parkind1.F90:32
subroutine ecoclimap2_lai(KYEAR)
real, dimension(:,:,:), allocatable xdata_veg
logical lhook
Definition: yomhook.F90:15
real, dimension(:,:,:), allocatable xdata_h_veg
real, dimension(:,:), allocatable xdata_h_tree
real, dimension(:,:,:), allocatable xdata_green
real, dimension(:,:,:), allocatable xdata_lai
real, dimension(:,:,:), allocatable xdata_z0litter
real, dimension(:,:,:), allocatable xdata_emis_eco
subroutine ini_data_param(PLAI, PH_TREE, PALBNIR_VEG, PALBVIS_VEG, PALBUV_VEG, PR
static int count
Definition: memory_hook.c:21