SURFEX v8.1
General documentation of Surfex
writesurf_pgd_teb_gardenn.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_garden_n (HSELECT, TOP, T, KTIME, IO, K, P, HPROGRAM)
7 ! ###############################################
8 !
9 !!**** *WRITE_PGD_TEB_GARDEN_n* - writes ISBA fields describing urban gardens
10 !!
11 !! PURPOSE
12 !! -------
13 !!
14 !!** METHOD
15 !! ------
16 !!
17 !! EXTERNAL
18 !! --------
19 !!
20 !!
21 !! IMPLICIT ARGUMENTS
22 !! ------------------
23 !!
24 !! REFERENCE
25 !! ---------
26 !!
27 !!
28 !! AUTHOR
29 !! ------
30 !! A. Lemonsu & C. de Munck *Meteo France*
31 !!
32 !! MODIFICATIONS
33 !! -------------
34 !! Original 06/2011
35 !!
36 !-------------------------------------------------------------------------------
37 !
38 !* 0. DECLARATIONS
39 ! ------------
40 !
41 !
43 USE modd_teb_n, ONLY : teb_t
44 !
46 USE modd_isba_n, ONLY : isba_k_t, isba_p_t
47 !
48 USE modd_surf_par, ONLY : xundef, nundef
49 !
51 !
52 USE yomhook ,ONLY : lhook, dr_hook
53 USE parkind1 ,ONLY : jprb
54 !
55 IMPLICIT NONE
56 !
57 !* 0.1 Declarations of arguments
58 ! -------------------------
59 !
60  CHARACTER(LEN=*), DIMENSION(:), INTENT(IN) :: HSELECT
61 !
62 TYPE(teb_options_t), INTENT(INOUT) :: TOP
63 TYPE(teb_t), INTENT(INOUT) :: T
64 !
65 INTEGER, INTENT(IN) :: KTIME
66 !
67 TYPE(isba_options_t), INTENT(INOUT) :: IO
68 TYPE(isba_k_t), INTENT(INOUT) :: K
69 TYPE(isba_p_t), INTENT(INOUT) :: P
70 !
71  CHARACTER(LEN=6), INTENT(IN) :: HPROGRAM ! program calling
72 !
73 !* 0.2 Declarations of local variables
74 ! -------------------------------
75 !
76 INTEGER :: IRESP ! IRESP : return-code if a problem appears
77  CHARACTER(LEN=12) :: YRECFM ! Name of the article to be read
78  CHARACTER(LEN=100):: YCOMMENT ! Comment string
79  CHARACTER(LEN=4 ) :: YLVL
80 !
81 REAL, DIMENSION(:), ALLOCATABLE :: ZWORK
82 INTEGER :: JJ, JL
83 !
84 REAL(KIND=JPRB) :: ZHOOK_HANDLE
85 !
86 !-------------------------------------------------------------------------------
87 !
88 IF (lhook) CALL dr_hook('WRITESURF_PGD_TEB_GARDEN_N',0,zhook_handle)
89 !
90 !* soil scheme option
91 !
92 yrecfm='GD_ISBA'
93 ycomment=yrecfm
94  CALL write_surf(hselect, hprogram,yrecfm,io%CISBA,iresp,hcomment=ycomment)
95 !
96 !* Reference grid for DIF
97 !
98 IF(io%CISBA=='DIF') THEN
99  DO jl=1,io%NGROUND_LAYER
100  WRITE(ylvl,'(I4)') jl
101  yrecfm='GD_SGRID'//adjustl(ylvl(:len_trim(ylvl)))
102  ycomment='Depth of TEB Garden soilgrid layer '//adjustl(ylvl(:len_trim(ylvl)))
103  CALL write_surf(hselect, hprogram,yrecfm,io%XSOILGRID(jl),iresp,hcomment=ycomment)
104  END DO
105 ENDIF
106 !
107 !* number of soil layers
108 !
109 yrecfm='GD_LAYER'
110 ycomment=yrecfm
111  CALL write_surf(hselect, hprogram,yrecfm,io%NGROUND_LAYER,iresp,hcomment=ycomment)
112 !
113 !* number of time data for vegetation characteristics (VEG, LAI, EMIS, Z0)
114 !
115 yrecfm='GD_NTIME'
116 ycomment=yrecfm
117  CALL write_surf(hselect, hprogram,yrecfm,ktime,iresp,hcomment=ycomment)
118 !
119 ! * clay fraction
120 !
121 yrecfm='GD_CLAY'
122 ycomment='X_Y_GD_CLAY'
123  CALL write_surf(hselect,hprogram,yrecfm,k%XCLAY(:,1),iresp,hcomment=ycomment)
124 !
125 ! * sand fraction
126 !
127 yrecfm='GD_SAND'
128 ycomment='X_Y_GD_SAND'
129  CALL write_surf(hselect,hprogram,yrecfm,k%XSAND(:,1),iresp,hcomment=ycomment)
130 !
131 ! * orographic runoff coefficient
132 !
133 yrecfm='GD_RUNOFFB'
134 ycomment='X_Y_GD_RUNOFFB'
135  CALL write_surf(hselect,hprogram,yrecfm,k%XRUNOFFB,iresp,hcomment=ycomment)
136 !
137 ! * subgrid drainage coefficient
138 !
139 yrecfm='GD_WDRAIN'
140 ycomment='X_Y_GD_WDRAIN'
141  CALL write_surf(hselect,hprogram,yrecfm,k%XWDRAIN,iresp,hcomment=ycomment)
142 !
143 IF (lhook) CALL dr_hook('WRITESURF_PGD_TEB_GARDEN_N',1,zhook_handle)
144 !-------------------------------------------------------------------------------
145 !
146 END SUBROUTINE writesurf_pgd_teb_garden_n
subroutine writesurf_pgd_teb_garden_n(HSELECT, TOP, T, KTIME, IO,
real, parameter xundef
integer, parameter jprb
Definition: parkind1.F90:32
integer, parameter nundef
logical lhook
Definition: yomhook.F90:15