SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
modn_teb_greenroofn.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 ! ##################
7 ! ##################
8 !
9 !!**** *MODN_TEB_GREENROOF_n* - declaration of namelist NAM_TEBn
10 !!
11 !! PURPOSE
12 !! -------
13 ! The purpose of this module is to specify the namelist NAM_TEB_GREENROOFn
14 !
15 !!
16 !!** IMPLICIT ARGUMENTS
17 !! ------------------
18 !!
19 !! REFERENCE
20 !! ---------
21 !! Based on modn_tebn
22 !!
23 !! AUTHOR
24 !! ------
25 !! C. de Munck & A. Lemonsu *Meteo France*
26 !!
27 !! MODIFICATIONS
28 !! -------------
29 !! Original 07/2011
30 !-------------------------------------------------------------------------------
31 !
32 !* 0. DECLARATIONS
33 ! ------------
34 !
35 !
36 USE yomhook ,ONLY : lhook, dr_hook
37 USE parkind1 ,ONLY : jprb
38 !
39 IMPLICIT NONE
40 !
41  CHARACTER(LEN=4) :: CSCOND_GR
42  CHARACTER(LEN=4) :: CRUNOFF_GR
43  CHARACTER(LEN=3) :: CKSAT_GR
44 LOGICAL :: LSOC_GR
45  CHARACTER(LEN=3) :: CHORT_GR
46 !
47 namelist/nam_teb_greenroofn/crunoff_gr,cscond_gr,cksat_gr,lsoc_gr,chort_gr
48 !
49  CONTAINS
50 !
51 ! subroutine INIT !
52 SUBROUTINE init_nam_teb_greenroofn (TGRO)
53 !
55 !
56  IMPLICIT NONE
57 
58 !
59  TYPE(teb_greenroof_options_t), INTENT(INOUT) :: tgro
60  REAL(KIND=JPRB) :: zhook_handle
61 
62  IF (lhook) CALL dr_hook('MODN_TEB_GREENROOF_N:INIT_NAM_TEB_GREENROOFN',0,zhook_handle)
63  cscond_gr = tgro%CSCOND_GR
64  crunoff_gr = tgro%CRUNOFF_GR
65  cksat_gr = tgro%CKSAT_GR
66  lsoc_gr = tgro%LSOC_GR
67  chort_gr = tgro%CHORT_GR
68 IF (lhook) CALL dr_hook('MODN_TEB_GREENROOF_N:INIT_NAM_TEB_GREENROOFN',1,zhook_handle)
69 END SUBROUTINE init_nam_teb_greenroofn
70 
71 ! subroutine UPDATE !
72 SUBROUTINE update_nam_teb_greenroofn (TGRO)
73 !
75 !
76  IMPLICIT NONE
77 
78 !
79  TYPE(teb_greenroof_options_t), INTENT(INOUT) :: tgro
80  REAL(KIND=JPRB) :: zhook_handle
81 
82  IF (lhook) CALL dr_hook('MODN_TEB_GREENROOF_N:UPDATE_NAM_TEB_GREENROOFN',0,zhook_handle)
83  tgro%CSCOND_GR = cscond_gr
84  tgro%CRUNOFF_GR = crunoff_gr
85  tgro%CKSAT_GR = cksat_gr
86  tgro%LSOC_GR = lsoc_gr
87  tgro%CHORT_GR = chort_gr
88 IF (lhook) CALL dr_hook('MODN_TEB_GREENROOF_N:UPDATE_NAM_TEB_GREENROOFN',1,zhook_handle)
89 END SUBROUTINE update_nam_teb_greenroofn
90 
91 END MODULE modn_teb_greenroof_n
subroutine update_nam_teb_greenroofn(TGRO)
subroutine init_nam_teb_greenroofn(TGRO)