SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
read_pgd_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 ! #########
6  SUBROUTINE read_pgd_teb_greenroof_n (CHT, DTCO, DTGR, GBGR, U, TGRO, TGRP, TG, &
7  hprogram,kversion)
8 ! #########################################
9 !
10 !!**** *READ_PGD_TEB_GREENROOF_n* - routine to initialise ISBA physiographic variables
11 !!
12 !! PURPOSE
13 !! -------
14 !!
15 !!** METHOD
16 !! ------
17 !!
18 !! EXTERNAL
19 !! --------
20 !!
21 !!
22 !! IMPLICIT ARGUMENTS
23 !! ------------------
24 !!
25 !! REFERENCE
26 !! ---------
27 !! based on read_pgd_teb_gardenn
28 !!
29 !! AUTHOR
30 !! ------
31 !! C. de Munck & A. Lemonsu *Meteo France*
32 !!
33 !! MODIFICATIONS
34 !! -------------
35 !! Original 07/2011
36 !-------------------------------------------------------------------------------
37 !
38 !* 0. DECLARATIONS
39 ! ------------
40 !
41 !
42 !
43 !
44 !
45 USE modd_ch_teb_n, ONLY : ch_teb_t
49 USE modd_surf_atm_n, ONLY : surf_atm_t
52 USE modd_teb_grid_n, ONLY : teb_grid_t
53 !
54 USE modd_isba_par, ONLY : xoptimgrid
55 !
57 USE modi_read_pgd_teb_greenroof_par_n
58 !
59 !
60 !
61 USE yomhook ,ONLY : lhook, dr_hook
62 USE parkind1 ,ONLY : jprb
63 !
64 USE modi_get_type_dim_n
65 !
66 IMPLICIT NONE
67 !
68 !* 0.1 Declarations of arguments
69 ! -------------------------
70 !
71 !
72 TYPE(ch_teb_t), INTENT(INOUT) :: cht
73 TYPE(data_cover_t), INTENT(INOUT) :: dtco
74 TYPE(data_teb_greenroof_t), INTENT(INOUT) :: dtgr
75 TYPE(gr_biog_greenroof_t), INTENT(INOUT) :: gbgr
76 TYPE(surf_atm_t), INTENT(INOUT) :: u
77 TYPE(teb_greenroof_options_t), INTENT(INOUT) :: tgro
78 TYPE(teb_greenroof_pgd_t), INTENT(INOUT) :: tgrp
79 TYPE(teb_grid_t), INTENT(INOUT) :: tg
80 !
81  CHARACTER(LEN=6), INTENT(IN) :: hprogram ! calling program
82 INTEGER, INTENT(IN) :: kversion ! version of SURFEX of the file being read
83 !
84 !* 0.2 Declarations of local variables
85 ! -------------------------------
86 !
87 INTEGER :: iresp ! Error code after redding
88 !
89  CHARACTER(LEN=12) :: yrecfm ! Name of the article to be read
90 !
91 !
92 INTEGER :: jlayer ! loop counter on layers ! not used
93 REAL(KIND=JPRB) :: zhook_handle
94 !
95 !-------------------------------------------------------------------------------
96 !
97 !* 1D physical dimension
98 !
99 IF (lhook) CALL dr_hook('READ_PGD_TEB_GREENROOF_N',0,zhook_handle)
100 yrecfm='SIZE_TOWN'
101  CALL get_type_dim_n(dtco, u, &
102  'TOWN ',tg%NDIM)
103 !
104 !
105 !* 2. Initialisation of ISBA options for greenroofs
106 ! ---------------------------------------------
107 !
108 !
109 yrecfm='GR_ISBA'
110  CALL read_surf(&
111  hprogram,yrecfm,tgro%CISBA_GR,iresp)
112 !
113 yrecfm='GR_SCOND'
114  CALL read_surf(&
115  hprogram,yrecfm,tgro%CSCOND_GR,iresp)
116 !
117 !* 3. Physiographic data fields:
118 ! -------------------------
119 !
120 !* orographic runoff coefficient
121 !
122 ALLOCATE(tgrp%XRUNOFFB_GR(tg%NDIM))
123 yrecfm='GR_RUNOFFB'
124  CALL read_surf(&
125  hprogram,yrecfm,tgrp%XRUNOFFB_GR,iresp)
126 !
127 !* subgrid drainage coefficient
128 !
129 ALLOCATE(tgrp%XWDRAIN_GR(tg%NDIM))
130 IF (kversion<=6) THEN
131  tgrp%XWDRAIN_GR = 0.
132 ELSE
133  yrecfm='GR_WDRAIN'
134  CALL read_surf(&
135  hprogram,yrecfm,tgrp%XWDRAIN_GR,iresp)
136 ENDIF
137 !
138 !-------------------------------------------------------------------------------
139 !* biogenic chemical emissions
140 !
141 IF (cht%LCH_BIO_FLUX) THEN
142  ALLOCATE(gbgr%XISOPOT(tg%NDIM))
143  yrecfm='E_ISOPOT'
144  CALL read_surf(&
145  hprogram,yrecfm,gbgr%XISOPOT,iresp)
146  !
147  ALLOCATE(gbgr%XMONOPOT(tg%NDIM))
148  yrecfm='E_MONOPOT'
149  CALL read_surf(&
150  hprogram,yrecfm,gbgr%XMONOPOT,iresp)
151 ELSE
152  ALLOCATE(gbgr%XISOPOT (0))
153  ALLOCATE(gbgr%XMONOPOT(0))
154 END IF
155 !
156 !-------------------------------------------------------------------------------
157 !
158 !* 4. Physiographic data fields not to be computed by ecoclimap
159 ! ---------------------------------------------------------
160 !
161 !
162 !LPAR_GREENROOF = .FALSE.
163 !IF (KVERSION>=7) THEN
164 ! YRECFM='PAR_GREENROOF'
165 ! CALL READ_SURF(HPROGRAM,YRECFM,LPAR_GREENROOF,IRESP)
166 !END IF
167 !
168 !IF (LPAR_GREENROOF) CALL READ_PGD_TEB_GREENROOF_PAR_n(HPROGRAM)
169 !
171  dtgr, tgro, tg, &
172  hprogram)
173 !
174 IF (lhook) CALL dr_hook('READ_PGD_TEB_GREENROOF_N',1,zhook_handle)
175 !
176 !
177 !-------------------------------------------------------------------------------
178 !
179 END SUBROUTINE read_pgd_teb_greenroof_n
subroutine get_type_dim_n(DTCO, U, HTYPE, KDIM)
subroutine read_pgd_teb_greenroof_par_n(DTGR, TGRO, TG, HPROGRAM)
subroutine read_pgd_teb_greenroof_n(CHT, DTCO, DTGR, GBGR, U, TGRO, TGRP, TG, HPROGRAM, KVERSION)