SURFEX v8.1
General documentation of Surfex
writesurf_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_teb_garden_n (HSELECT, OSNOWDIMNC, IO, S, PEK, HPROGRAM,HPATCH)
7 ! #####################################
8 !
9 !!**** *WRITESURF_TEB_GARDEN_n* - writes ISBA prognostic fields
10 !!
11 !!
12 !! PURPOSE
13 !! -------
14 !!
15 !!** METHOD
16 !! ------
17 !!
18 !! EXTERNAL
19 !! --------
20 !!
21 !!
22 !! IMPLICIT ARGUMENTS
23 !! ------------------
24 !!
25 !! REFERENCE
26 !! ---------
27 !!
28 !!
29 !! AUTHOR
30 !! ------
31 !! V. Masson *Meteo France*
32 !!
33 !! MODIFICATIONS
34 !! -------------
35 !! Original 01/2003
36 !! P. LeMoigne 12/2004 : correct dimensionning if more than 10 layers in
37 !! the soil (diffusion version)
38 !! B. Decharme 2008 : Floodplains
39 !! B. Decharme 01/2009 : Optional Arpege deep soil temperature write
40 !! B. Decharme 09/2012 : suppress NWG_LAYER (parallelization problems)
41 !-------------------------------------------------------------------------------
42 !
43 !* 0. DECLARATIONS
44 ! ------------
45 !
47 USE modd_isba_n, ONLY : isba_pe_t, isba_s_t
48 !
49 USE modd_surf_par, ONLY : nundef
50 !
52 USE modi_writesurf_gr_snow
53 USE modd_dst_surf
54 !
55 USE yomhook ,ONLY : lhook, dr_hook
56 USE parkind1 ,ONLY : jprb
57 !
58 IMPLICIT NONE
59 !
60 !* 0.1 Declarations of arguments
61 ! -------------------------
62 !
63 !
64  CHARACTER(LEN=*), DIMENSION(:), INTENT(IN) :: HSELECT
65 LOGICAL, INTENT(IN) :: OSNOWDIMNC
66 !
67 TYPE(isba_options_t), INTENT(IN) :: IO
68 TYPE(isba_s_t), INTENT(INOUT) :: S
69 TYPE(isba_pe_t), INTENT(IN) :: PEK
70 !
71  CHARACTER(LEN=6), INTENT(IN) :: HPROGRAM ! program calling
72  CHARACTER(LEN=3), INTENT(IN) :: HPATCH ! current teb patch
73 !
74 !* 0.2 Declarations of local variables
75 ! -------------------------------
76 !
77 INTEGER, DIMENSION(SIZE(PEK%XTG,1)) :: IMASK_P
78 INTEGER :: IRESP ! IRESP : return-code if a problem appears
79  CHARACTER(LEN=12) :: YRECFM ! Name of the article to be read
80  CHARACTER(LEN=100):: YCOMMENT ! Comment string
81  CHARACTER(LEN=14) :: YFORM ! Writing format
82  CHARACTER(LEN=4 ) :: YLVL
83 !
84 INTEGER :: JL, JI ! loop counter on soil layers
85 !
86 REAL, DIMENSION(:),ALLOCATABLE :: ZWORK ! 2D array to write data in file
87 !
88 INTEGER :: JNBIOMASS
89 REAL(KIND=JPRB) :: ZHOOK_HANDLE
90 !
91 !------------------------------------------------------------------------------
92 !
93 !* 2. Prognostic fields:
94 ! -----------------
95 !
96 IF (lhook) CALL dr_hook('WRITESURF_TEB_GARDEN_N',0,zhook_handle)
97 ALLOCATE(zwork(SIZE(pek%XTG,1)))
98 !* soil temperatures
99 !
100 DO jl=1,io%NGROUND_LAYER
101  WRITE(ylvl,'(I2)') jl
102  yrecfm=hpatch//'GD_TG'//adjustl(ylvl(:len_trim(ylvl)))
103  yrecfm=adjustl(yrecfm)
104  yform='(A11,I1.1,A4)'
105  IF (jl >= 10) yform='(A11,I2.2,A4)'
106  WRITE(ycomment,fmt=yform) 'X_Y_GD_TG',jl,' (K)'
107  zwork=pek%XTG(:,jl)
108  CALL write_surf(hselect,hprogram,yrecfm,zwork,iresp,hcomment=ycomment)
109 END DO
110 !
111 !
112 !* soil liquid water content
113 !
114 DO jl=1,io%NGROUND_LAYER
115  WRITE(ylvl,'(I2)') jl
116  yrecfm=hpatch//'GD_WG'//adjustl(ylvl(:len_trim(ylvl)))
117  yrecfm=adjustl(yrecfm)
118  yform='(A11,I1.1,A8)'
119  IF (jl >= 10) yform='(A11,I2.2,A8)'
120  WRITE(ycomment,fmt=yform) 'X_Y_GD_WG',jl,' (m3/m3)'
121  zwork=pek%XWG(:,jl)
122  CALL write_surf(hselect,hprogram,yrecfm,zwork,iresp,hcomment=ycomment)
123 END DO
124 !
125 !
126 !* soil ice water content
127 !
128 DO jl=1,io%NGROUND_LAYER
129  WRITE(ylvl,'(I2)') jl
130  yrecfm=hpatch//'GD_WGI'//adjustl(ylvl(:len_trim(ylvl)))
131  yrecfm=adjustl(yrecfm)
132  yform='(A11,I1.1,A8)'
133  IF (jl >= 10) yform='(A11,I2.2,A8)'
134  WRITE(ycomment,yform) 'X_Y_GD_WGI',jl,' (m3/m3)'
135  zwork=pek%XWGI(:,jl)
136  CALL write_surf(hselect,hprogram,yrecfm,zwork,iresp,hcomment=ycomment)
137 END DO
138 !
139 DEALLOCATE(zwork)
140 !
141 !* water intercepted on leaves
142 !
143 yrecfm=hpatch//'GD_WR'
144 yrecfm=adjustl(yrecfm)
145 ycomment='X_Y_GD_WR (kg/m2)'
146  CALL write_surf(hselect,hprogram,yrecfm,pek%XWR(:),iresp,hcomment=ycomment)
147 !
148 !* Leaf Area Index
149 !
150 IF (io%CPHOTO/='NON' .AND. io%CPHOTO/='AST') THEN
151  yrecfm=hpatch//'GD_LAI'
152  yrecfm=adjustl(yrecfm)
153  ycomment='X_Y_GD_LAI (m2/m2)'
154  CALL write_surf(hselect,hprogram,yrecfm,pek%XLAI(:),iresp,hcomment=ycomment)
155 END IF
156 !
157 IF (io%CPHOTO=='NIT') THEN
158  !
159  DO jnbiomass=1,io%NNBIOMASS
160  WRITE(ylvl,'(I1)') jnbiomass
161  yrecfm=hpatch//'GD_BIOMA'//adjustl(ylvl(:len_trim(ylvl)))
162  yrecfm=adjustl(yrecfm)
163  yform='(A11,I1.1,A8)'
164  WRITE(ycomment,fmt=yform) 'X_Y_BIOMASS',jnbiomass,' (kg/m2)'
165  CALL write_surf(hselect,hprogram,yrecfm,pek%XBIOMASS(:,jnbiomass),iresp,hcomment=ycomment)
166  END DO
167  !
168  !
169  DO jnbiomass=2,io%NNBIOMASS
170  WRITE(ylvl,'(I1)') jnbiomass
171  yrecfm=hpatch//'GD_RESPI'//adjustl(ylvl(:len_trim(ylvl)))
172  yrecfm=adjustl(yrecfm)
173  yform='(A16,I1.1,A10)'
174  WRITE(ycomment,fmt=yform) 'X_Y_RESP_BIOMASS',jnbiomass,' (kg/m2/s)'
175  CALL write_surf(hselect,hprogram,yrecfm,pek%XRESP_BIOMASS(:,jnbiomass),iresp,hcomment=ycomment)
176  END DO
177  !
178 END IF
179 !
180 !* aerodynamical resistance
181 !
182 yrecfm=hpatch//'GD_RES'
183 yrecfm=adjustl(yrecfm)
184 ycomment='X_Y_GD_RESA (s/m)'
185  CALL write_surf(hselect,hprogram,yrecfm,pek%XRESA(:),iresp,hcomment=ycomment)
186 !
187 !* snow mantel
188 !
189 yrecfm='GD'
190 DO ji = 1,SIZE(imask_p)
191  imask_p(ji) = ji
192 ENDDO
193  CALL writesurf_gr_snow(osnowdimnc, hselect, hprogram, yrecfm, hpatch,&
194  SIZE(pek%XTG,1), imask_p, 0, pek%TSNOW, s%XWSN_WR, &
195  s%XRHO_WR, s%XHEA_WR, s%XAGE_WR, s%XSG1_WR, s%XSG2_WR, &
196  s%XHIS_WR, s%XALB_WR)
197 !
198 IF (lhook) CALL dr_hook('WRITESURF_TEB_GARDEN_N',1,zhook_handle)
199 !
200 !-------------------------------------------------------------------------------
201 !
202 END SUBROUTINE writesurf_teb_garden_n
subroutine writesurf_teb_garden_n(HSELECT, OSNOWDIMNC, IO, S, PEK
integer, parameter jprb
Definition: parkind1.F90:32
integer, parameter nundef
logical lhook
Definition: yomhook.F90:15
subroutine writesurf_gr_snow(OSNOWDIMNC, HSELECT, HPROGRAM, HSURF