SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
writesurf_pgd_teb_vegn.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 writesurf_pgd_teb_veg_n (DGU, U, &
7  dtgd, tgdo, tgdp, tvg, &
8  hprogram)
9 ! ###############################################
10 !
11 !!**** *WRITE_PGD_TEB_VEG_n* - writes ISBA fields describing urban gardens
12 !!
13 !! PURPOSE
14 !! -------
15 !!
16 !!** METHOD
17 !! ------
18 !!
19 !! EXTERNAL
20 !! --------
21 !!
22 !!
23 !! IMPLICIT ARGUMENTS
24 !! ------------------
25 !!
26 !! REFERENCE
27 !! ---------
28 !!
29 !!
30 !! AUTHOR
31 !! ------
32 !! A. Lemonsu & C. de Munck *Meteo France*
33 !!
34 !! MODIFICATIONS
35 !! -------------
36 !! Original 06/2011
37 !!
38 !-------------------------------------------------------------------------------
39 !
40 !* 0. DECLARATIONS
41 ! ------------
42 !
43 !
44 !
45 !
46 !
48 USE modd_surf_atm_n, ONLY : surf_atm_t
49 !
54 !
56 !
57 USE yomhook ,ONLY : lhook, dr_hook
58 USE parkind1 ,ONLY : jprb
59 !
60 IMPLICIT NONE
61 !
62 !* 0.1 Declarations of arguments
63 ! -------------------------
64 !
65 !
66 !
67 TYPE(diag_surf_atm_t), INTENT(INOUT) :: dgu
68 TYPE(surf_atm_t), INTENT(INOUT) :: u
69 !
70 TYPE(data_teb_garden_t), INTENT(INOUT) :: dtgd
71 TYPE(teb_garden_options_t), INTENT(INOUT) :: tgdo
72 TYPE(teb_garden_pgd_t), INTENT(INOUT) :: tgdp
73 TYPE(teb_veg_options_t), INTENT(INOUT) :: tvg
74 !
75  CHARACTER(LEN=6), INTENT(IN) :: hprogram ! program calling
76 !
77 !* 0.2 Declarations of local variables
78 ! -------------------------------
79 !
80 INTEGER :: iresp ! IRESP : return-code if a problem appears
81  CHARACTER(LEN=12) :: yrecfm ! Name of the article to be read
82  CHARACTER(LEN=100):: ycomment ! Comment string
83  CHARACTER(LEN=4 ) :: ylvl
84 !
85 INTEGER :: jj, jlayer
86 !
87 REAL(KIND=JPRB) :: zhook_handle
88 !
89 !-------------------------------------------------------------------------------
90 !
91 IF (lhook) CALL dr_hook('WRITESURF_PGD_TEB_VEG_N',0,zhook_handle)
92 !
93 !* soil scheme option
94 !
95 yrecfm='GD_ISBA'
96 ycomment=yrecfm
97  CALL write_surf(dgu, u, &
98  hprogram,yrecfm,tvg%CISBA,iresp,hcomment=ycomment)
99 !
100 !* Reference grid for DIF
101 !
102 IF(tvg%CISBA=='DIF') THEN
103  DO jlayer=1,tgdo%NGROUND_LAYER
104  WRITE(ylvl,'(I4)') jlayer
105  yrecfm='GD_SGRID'//adjustl(ylvl(:len_trim(ylvl)))
106  ycomment='Depth of TEB Garden soilgrid layer '//adjustl(ylvl(:len_trim(ylvl)))
107  CALL write_surf(dgu, u, &
108  hprogram,yrecfm,tgdo%XSOILGRID(jlayer),iresp,hcomment=ycomment)
109  END DO
110 ENDIF
111 !
112 !* number of soil layers
113 !
114 yrecfm='GD_LAYER'
115 ycomment=yrecfm
116  CALL write_surf(dgu, u, &
117  hprogram,yrecfm,tgdo%NGROUND_LAYER,iresp,hcomment=ycomment)
118 !
119 !* number of time data for vegetation characteristics (VEG, LAI, EMIS, Z0)
120 !
121 yrecfm='GD_NTIME'
122 ycomment=yrecfm
123  CALL write_surf(dgu, u, &
124  hprogram,yrecfm,dtgd%NTIME,iresp,hcomment=ycomment)
125 !
126 ! * clay fraction
127 !
128 yrecfm='GD_CLAY'
129 ycomment='X_Y_GD_CLAY'
130  CALL write_surf(dgu, u, &
131  hprogram,yrecfm,tgdp%XCLAY(:,1),iresp,hcomment=ycomment)
132 !
133 ! * sand fraction
134 !
135 yrecfm='GD_SAND'
136 ycomment='X_Y_GD_SAND'
137  CALL write_surf(dgu, u, &
138  hprogram,yrecfm,tgdp%XSAND(:,1),iresp,hcomment=ycomment)
139 !
140 ! * orographic runoff coefficient
141 !
142 yrecfm='GD_RUNOFFB'
143 ycomment='X_Y_GD_RUNOFFB'
144  CALL write_surf(dgu, u, &
145  hprogram,yrecfm,tgdp%XRUNOFFB,iresp,hcomment=ycomment)
146 !
147 ! * subgrid drainage coefficient
148 !
149 yrecfm='GD_WDRAIN'
150 ycomment='X_Y_GD_WDRAIN'
151  CALL write_surf(dgu, u, &
152  hprogram,yrecfm,tgdp%XWDRAIN,iresp,hcomment=ycomment)
153 !
154 !
155 IF (lhook) CALL dr_hook('WRITESURF_PGD_TEB_VEG_N',1,zhook_handle)
156 !-------------------------------------------------------------------------------
157 !
158 END SUBROUTINE writesurf_pgd_teb_veg_n
subroutine writesurf_pgd_teb_veg_n(DGU, U, DTGD, TGDO, TGDP, TVG, HPROGRAM)