SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
zoom_pgd_town.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 zoom_pgd_town (B, DGCT, DGMT, T, TGD, TGDPE, TGR, TGRPE, &
7  bop, bdd, dtb, dtco, dtt, ug, u, tgdo, tgdp, tg, &
8  top, tvg, &
9  hprogram,hinifile,hinifiletype,hfile,hfiletype,oecoclimap,ogarden)
10 ! ###########################################################
11 
12 !!
13 !! PURPOSE
14 !! -------
15 !! This program prepares the physiographic data fields.
16 !!
17 !! METHOD
18 !! ------
19 !!
20 !! EXTERNAL
21 !! --------
22 !!
23 !!
24 !! IMPLICIT ARGUMENTS
25 !! ------------------
26 !!
27 !!
28 !! REFERENCE
29 !! ---------
30 !!
31 !! AUTHOR
32 !! ------
33 !!
34 !! V. Masson Meteo-France
35 !!
36 !! MODIFICATION
37 !! ------------
38 !!
39 !! Original 13/10/03
40 !----------------------------------------------------------------------------
41 !
42 !* 0. DECLARATION
43 ! -----------
44 !
45 !
46 !
47 !
48 USE modd_bem_n, ONLY : bem_t
51 USE modd_teb_n, ONLY : teb_t
58 USE modd_data_bem_n, ONLY : data_bem_t
60 USE modd_data_teb_n, ONLY : data_teb_t
62 USE modd_surf_atm_n, ONLY : surf_atm_t
65 USE modd_teb_grid_n, ONLY : teb_grid_t
68 !
69 USE yomhook ,ONLY : lhook, dr_hook
70 USE parkind1 ,ONLY : jprb
71 !
72 USE modi_zoom_pgd_teb
73 !
74 IMPLICIT NONE
75 !
76 !* 0.1 Declaration of dummy arguments
77 ! ------------------------------
78 !
79 !
80 TYPE(bem_t), INTENT(INOUT) :: b
81 TYPE(diag_cumul_teb_t), INTENT(INOUT) :: dgct
82 TYPE(diag_misc_teb_t), INTENT(INOUT) :: dgmt
83 TYPE(teb_t), INTENT(INOUT) :: t
84 TYPE(teb_garden_pgd_evol_t), INTENT(INOUT) :: tgdpe
85 TYPE(teb_garden_t), INTENT(INOUT) :: tgd
86 TYPE(teb_greenroof_t), INTENT(INOUT) :: tgr
87 TYPE(teb_greenroof_pgd_evol_t), INTENT(INOUT) :: tgrpe
88 TYPE(bem_options_t), INTENT(INOUT) :: bop
89 TYPE(bld_desc_t), INTENT(INOUT) :: bdd
90 TYPE(data_bem_t), INTENT(INOUT) :: dtb
91 TYPE(data_cover_t), INTENT(INOUT) :: dtco
92 TYPE(data_teb_t), INTENT(INOUT) :: dtt
93 TYPE(surf_atm_grid_t), INTENT(INOUT) :: ug
94 TYPE(surf_atm_t), INTENT(INOUT) :: u
95 TYPE(teb_garden_options_t), INTENT(INOUT) :: tgdo
96 TYPE(teb_garden_pgd_t), INTENT(INOUT) :: tgdp
97 TYPE(teb_grid_t), INTENT(INOUT) :: tg
98 TYPE(teb_options_t), INTENT(INOUT) :: top
99 TYPE(teb_veg_options_t), INTENT(INOUT) :: tvg
100 !
101  CHARACTER(LEN=6), INTENT(IN) :: hprogram ! program calling
102  CHARACTER(LEN=28), INTENT(IN) :: hinifile ! input atmospheric file name
103  CHARACTER(LEN=6), INTENT(IN) :: hinifiletype! input atmospheric file type
104  CHARACTER(LEN=28), INTENT(IN) :: hfile ! output file name
105  CHARACTER(LEN=6), INTENT(IN) :: hfiletype ! output file type
106 LOGICAL, INTENT(IN) :: oecoclimap ! flag to use ecoclimap
107 LOGICAL, INTENT(IN) :: ogarden ! flag to use garden
108 REAL(KIND=JPRB) :: zhook_handle
109 !
110 !
111 !* 0.2 Declaration of local variables
112 ! ------------------------------
113 !
114 !------------------------------------------------------------------------------
115 IF (lhook) CALL dr_hook('ZOOM_PGD_TOWN',0,zhook_handle)
116 IF (u%CTOWN=='NONE ') THEN
117  IF (lhook) CALL dr_hook('ZOOM_PGD_TOWN',1,zhook_handle)
118  RETURN
119 ELSE IF (u%CTOWN=='FLUX ') THEN
120  IF (lhook) CALL dr_hook('ZOOM_PGD_TOWN',1,zhook_handle)
121  RETURN
122 ELSE IF (u%CTOWN=='TEB ') THEN
123  CALL zoom_pgd_teb(b, dgct, dgmt, t, tgd, tgdpe, tgr, tgrpe, &
124  bop, bdd, dtb, dtco, dtt, ug, u, tgdo, tgdp, tg, &
125  top, tvg, &
126  hprogram,hinifile,hinifiletype,oecoclimap,ogarden)
127 END IF
128 IF (lhook) CALL dr_hook('ZOOM_PGD_TOWN',1,zhook_handle)
129 !
130 !_______________________________________________________________________________
131 !
132 END SUBROUTINE zoom_pgd_town
subroutine zoom_pgd_teb(B, DGCT, DGMT, T, TGD, TGDPE, TGR, TGRPE, BOP, BDD, DTB, DTCO, DTT, UG, U, TGDO, TGDP, TG, TOP, TVG, HPROGRAM, HINIFILE, HINIFILETYPE, OECOCLIMAP, OGARDEN)
Definition: zoom_pgd_teb.F90:6
subroutine zoom_pgd_town(B, DGCT, DGMT, T, TGD, TGDPE, TGR, TGRPE, BOP, BDD, DTB, DTCO, DTT, UG, U, TGDO, TGDP, TG, TOP, TVG, HPROGRAM, HINIFILE, HINIFILETYPE, HFILE, HFILETYPE, OECOCLIMAP, OGARDEN)