LMDZ
VARxSV.F90
Go to the documentation of this file.
1 MODULE varxsv
2 
3 USE var_sv, only : klonv, nsol, nsno, nb_wri
4 
5 IMPLICIT NONE
6 ! +--SISVAT INPUT Variables
7 ! + -----------------------------
8 
9  INTEGER, DIMENSION(:),ALLOCATABLE,SAVE :: lsmask ! Land-Sea Mask
10 !$OMP THREADPRIVATE(LSmask)
11  INTEGER, DIMENSION(:),ALLOCATABLE,SAVE :: isotsv ! Soil Type
12 !$OMP THREADPRIVATE(isotSV)
13  INTEGER, DIMENSION(:),ALLOCATABLE,SAVE :: iwafsv ! Soil Drainage:(1,0)=(y,n)
14 !$OMP THREADPRIVATE(iWaFSV)
15  INTEGER, DIMENSION(:),ALLOCATABLE,SAVE :: ivgtsv ! Vegetation Type
16 !$OMP THREADPRIVATE(ivgtSV)
17 
18  REAL, DIMENSION(:),ALLOCATABLE,SAVE :: coszsv ! Cosine of Sun zenithal Angle
19 !$OMP THREADPRIVATE(coszSV)
20  REAL, DIMENSION(:),ALLOCATABLE,SAVE :: sol_sv ! Downward Solar Radiation
21 !$OMP THREADPRIVATE(sol_SV)
22  REAL, DIMENSION(:),ALLOCATABLE,SAVE :: ird_sv ! Downward Longwave Radiation
23 !$OMP THREADPRIVATE(IRd_SV)
24 
25  REAL, DIMENSION(:),ALLOCATABLE,SAVE :: drr_sv ! Rain Intensity [kg/m2/s]
26 !$OMP THREADPRIVATE(drr_SV)
27  REAL, DIMENSION(:),ALLOCATABLE,SAVE :: dsn_sv ! Snow Intensity [kg/m2/s]
28 !$OMP THREADPRIVATE(dsn_SV)
29  REAL, DIMENSION(:),ALLOCATABLE,SAVE :: dsnbsv ! Idem, fraction, from Drift [-]
30 !$OMP THREADPRIVATE(dsnbSV)
31  REAL, DIMENSION(:),ALLOCATABLE,SAVE :: esnbsv ! Idem, fraction, from Drift [-]
32 !$OMP THREADPRIVATE(esnbSV)
33  REAL, DIMENSION(:),ALLOCATABLE,SAVE :: dbs_sv ! Drift Amount [kg/m2]
34 !$OMP THREADPRIVATE(dbs_SV)
35  REAL, DIMENSION(:),ALLOCATABLE,SAVE :: brossv ! Buffer Snow Layer Density
36 !$OMP THREADPRIVATE(BrosSV)
37  REAL, DIMENSION(:),ALLOCATABLE,SAVE :: bg1ssv ! Buffer Snow Layer Dendr/Sphe[-]
38 !$OMP THREADPRIVATE(BG1sSV)
39  REAL, DIMENSION(:),ALLOCATABLE,SAVE :: bg2ssv ! Buffer Snow Layer Spher/Size[-][0.0001m]
40 !$OMP THREADPRIVATE(BG2sSV)
41  REAL, DIMENSION(:),ALLOCATABLE,SAVE :: dz0_sv ! dz0(Sastrugi dh) [m]
42 !$OMP THREADPRIVATE(dz0_SV)
43 
44  REAL, DIMENSION(:),ALLOCATABLE,SAVE :: cld_sv ! Cloudiness (seen from SBL)
45 !$OMP THREADPRIVATE(cld_SV)
46  REAL, DIMENSION(:),ALLOCATABLE,SAVE :: za__sv ! SBL Height
47 !$OMP THREADPRIVATE(za__SV)
48  REAL, DIMENSION(:),ALLOCATABLE,SAVE :: vv__sv !(SBL Top) Wind Velocity
49 !$OMP THREADPRIVATE(VV__SV)
50  REAL, DIMENSION(:),ALLOCATABLE,SAVE :: vvs_sv !(Sastr,V) Relevance
51 !$OMP THREADPRIVATE(VVs_SV)
52  REAL, DIMENSION(:),ALLOCATABLE,SAVE :: rrs_sv !(Sastr,V) Counter
53 !$OMP THREADPRIVATE(RRs_SV)
54  REAL, DIMENSION(:),ALLOCATABLE,SAVE :: dds_sv !(Sastr,V) Angle
55 !$OMP THREADPRIVATE(DDs_SV)
56  REAL, DIMENSION(:),ALLOCATABLE,SAVE :: tat_sv ! SBL Top Temperature
57 !$OMP THREADPRIVATE(TaT_SV)
58  REAL, DIMENSION(:),ALLOCATABLE,SAVE :: exnrsv ! Exner Potential
59 !$OMP THREADPRIVATE(ExnrSV)
60  REAL, DIMENSION(:),ALLOCATABLE,SAVE :: dsdtsv ! Sensible Heat Flux T Derivat.
61 !$OMP THREADPRIVATE(dSdTSV)
62  REAL, DIMENSION(:),ALLOCATABLE,SAVE :: dldtsv ! Latent Heat Flux T Derivat.
63 !$OMP THREADPRIVATE(dLdTSV)
64  REAL, DIMENSION(:),ALLOCATABLE,SAVE :: rht_sv ! SBL Top Air Density
65 !$OMP THREADPRIVATE(rhT_SV)
66  REAL, DIMENSION(:),ALLOCATABLE,SAVE :: qat_sv ! SBL Top Specific Humidity
67 !$OMP THREADPRIVATE(QaT_SV)
68  REAL, DIMENSION(:),ALLOCATABLE,SAVE :: dqa_sv ! SBL Flux Limitation of Qa
69 !$OMP THREADPRIVATE(dQa_SV)
70  REAL, DIMENSION(:),ALLOCATABLE,SAVE :: qsnosv ! SBL Mean Snow Content
71 !$OMP THREADPRIVATE(qsnoSV)
72 
73  REAL, DIMENSION(:),ALLOCATABLE,SAVE :: lai0sv ! Nominal Leaf Area Index
74 !$OMP THREADPRIVATE(LAI0SV)
75  REAL, DIMENSION(:),ALLOCATABLE,SAVE :: glf0sv ! Green Leaf Fraction
76 !$OMP THREADPRIVATE(glf0SV)
77 
78  REAL, DIMENSION(:),ALLOCATABLE,SAVE :: alb0sv ! Soil Albedo
79 !$OMP THREADPRIVATE(alb0SV)
80  REAL, DIMENSION(:),ALLOCATABLE,SAVE :: slopsv ! Snow/Ice/Soil-Water Surf. Slope
81 !$OMP THREADPRIVATE(slopSV)
82 
83 
84  REAL,SAVE :: zsblsv ! SBL Height (Initial Value)
85 !$OMP THREADPRIVATE(zSBLSV)
86  REAL,SAVE :: dt__sv ! Time Step
87 !$OMP THREADPRIVATE(dt__SV)
88  CHARACTER (len=18),SAVE :: dahost ! Date Host Model
89 !$OMP THREADPRIVATE(daHost)
90 
91 
92 ! +--SISVAT INPUT/OUTPUT Variables
93 ! + -----------------------------
94 
95  INTEGER, DIMENSION(:),ALLOCATABLE,SAVE :: isnosv ! Nb of Ice/Snow Layers
96 !$OMP THREADPRIVATE(isnoSV)
97  INTEGER, DIMENSION(:),ALLOCATABLE,SAVE :: ispisv ! Uppermost superimposed ice
98 !$OMP THREADPRIVATE(ispiSV)
99  INTEGER, DIMENSION(:),ALLOCATABLE,SAVE :: iicesv ! Nb of Ice Layers
100 !$OMP THREADPRIVATE(iiceSV)
101  INTEGER ,ALLOCATABLE,SAVE :: istosv(:,:) ! Snow Layer History
102 !$OMP THREADPRIVATE(istoSV)
103 
104  REAL, DIMENSION(:),ALLOCATABLE,SAVE :: alb_sv ! Surface-Canopy Albedo
105 !$OMP THREADPRIVATE(alb_SV)
106  REAL, DIMENSION(:),ALLOCATABLE,SAVE :: emi_sv ! Surface-Canopy Emissivity
107 !$OMP THREADPRIVATE(emi_SV)
108  REAL, DIMENSION(:),ALLOCATABLE,SAVE :: irs_sv ! Soil IR Flux
109 !$OMP THREADPRIVATE(IRs_SV)
110  REAL, DIMENSION(:),ALLOCATABLE,SAVE :: lmo_sv ! Monin-Obukhov Scale
111 !$OMP THREADPRIVATE(LMO_SV)
112  REAL, DIMENSION(:),ALLOCATABLE,SAVE :: us__sv ! Friction Velocity
113 !$OMP THREADPRIVATE(us__SV)
114  REAL, DIMENSION(:),ALLOCATABLE,SAVE :: uts_sv ! Temperature Turbulent Scale
115 !$OMP THREADPRIVATE(uts_SV)
116  REAL, DIMENSION(:),ALLOCATABLE,SAVE :: cutssv ! Temperature Turbulent Scale C.
117 !$OMP THREADPRIVATE(cutsSV)
118  REAL, DIMENSION(:),ALLOCATABLE,SAVE :: uqs_sv ! Spec.Humid. Turbulent Scale
119 !$OMP THREADPRIVATE(uqs_SV)
120  REAL, DIMENSION(:),ALLOCATABLE,SAVE :: uss_sv ! Blow.Snow Turbulent Scale
121 !$OMP THREADPRIVATE(uss_SV)
122  REAL, DIMENSION(:),ALLOCATABLE,SAVE :: usthsv ! Blowing Snow Erosion Thresh.
123 !$OMP THREADPRIVATE(usthSV)
124  REAL, DIMENSION(:),ALLOCATABLE,SAVE :: rcdmsv ! Square Root Contribut. Drag_m
125 !$OMP THREADPRIVATE(rCDmSV)
126  REAL, DIMENSION(:),ALLOCATABLE,SAVE :: rcdhsv ! Square Root Contribut. Drag_h
127 !$OMP THREADPRIVATE(rCDhSV)
128  REAL, DIMENSION(:),ALLOCATABLE,SAVE :: z0m_sv ! Momentum Roughness Length
129 !$OMP THREADPRIVATE(Z0m_SV)
130  REAL, DIMENSION(:),ALLOCATABLE,SAVE :: z0mmsv ! z0(Momentum, Time Mean) [m]
131 !$OMP THREADPRIVATE(Z0mmSV)
132  REAL, DIMENSION(:),ALLOCATABLE,SAVE :: z0mnsv ! z0(Momentum, instanta.) [m]
133 !$OMP THREADPRIVATE(Z0mnSV)
134  REAL, DIMENSION(:),ALLOCATABLE,SAVE :: z0rosv ! Subgrid Topo Roughness Length
135 !$OMP THREADPRIVATE(Z0roSV)
136  REAL, DIMENSION(:),ALLOCATABLE,SAVE :: z0sasv ! z0(Sastrugi h) [m]
137 !$OMP THREADPRIVATE(Z0SaSV)
138  REAL, DIMENSION(:),ALLOCATABLE,SAVE :: z0e_sv ! z0(Snow eroded) [m]
139 !$OMP THREADPRIVATE(Z0e_SV)
140  REAL, DIMENSION(:),ALLOCATABLE,SAVE :: z0emsv ! z0(Snow eroded, Time Mean) [m]
141 !$OMP THREADPRIVATE(Z0emSV)
142  REAL, DIMENSION(:),ALLOCATABLE,SAVE :: z0ensv ! z0(Snow eroded, instanta.) [m]
143 !$OMP THREADPRIVATE(Z0enSV)
144  REAL, DIMENSION(:),ALLOCATABLE,SAVE :: z0h_sv ! Heat Roughness Length
145 !$OMP THREADPRIVATE(Z0h_SV)
146  REAL, DIMENSION(:),ALLOCATABLE,SAVE :: z0hmsv ! z0(Heat, Time Mean) [m]
147 !$OMP THREADPRIVATE(Z0hmSV)
148  REAL, DIMENSION(:),ALLOCATABLE,SAVE :: z0hnsv ! z0(Heat, instanta.) [m]
149 !$OMP THREADPRIVATE(Z0hnSV)
150 
151  REAL, DIMENSION(:),ALLOCATABLE,SAVE :: sncasv ! Canopy Snow Thickness
152 !$OMP THREADPRIVATE(snCaSV)
153  REAL, DIMENSION(:),ALLOCATABLE,SAVE :: rrcasv ! Canopy Water Content
154 !$OMP THREADPRIVATE(rrCaSV)
155  REAL, DIMENSION(:),ALLOCATABLE,SAVE :: psivsv ! Leaf Water Potential
156 !$OMP THREADPRIVATE(psivSV)
157  REAL, DIMENSION(:),ALLOCATABLE,SAVE :: tvegsv ! Vegetation Temperature
158 !$OMP THREADPRIVATE(TvegSV)
159 
160  REAL ,ALLOCATABLE,SAVE :: tsissv(:,:) ! Snow/Ice/Soil-Water Temperature
161 !$OMP THREADPRIVATE(TsisSV)
162  REAL ,ALLOCATABLE,SAVE :: ro__sv(:,:) ! Snow/Ice/Soil-Water VolumicMass
163 !$OMP THREADPRIVATE(ro__SV)
164  REAL,ALLOCATABLE,SAVE :: eta_sv(:,:) ! Snow/Ice/Soil Water Content
165 !$OMP THREADPRIVATE(eta_SV)
166  REAL,ALLOCATABLE,SAVE :: g1snsv(:,:) ! Snow Dendricity/Sphericity
167 !$OMP THREADPRIVATE(G1snSV)
168  REAL,ALLOCATABLE,SAVE :: g2snsv(:,:) ! Snow Sphericity/Size
169 !$OMP THREADPRIVATE(G2snSV)
170  REAL,ALLOCATABLE,SAVE :: dzsnsv(:,:) ! Snow Layer Thickness
171 !$OMP THREADPRIVATE(dzsnSV)
172  REAL,ALLOCATABLE,SAVE :: agsnsv(:,:) ! Snow Age
173 !$OMP THREADPRIVATE(agsnSV)
174  REAL, DIMENSION(:),ALLOCATABLE,SAVE :: bufssv ! Snow Buffer Layer
175 !$OMP THREADPRIVATE(BufsSV)
176  REAL, DIMENSION(:),ALLOCATABLE,SAVE :: rusnsv ! Surficial Water
177 !$OMP THREADPRIVATE(rusnSV)
178  REAL, DIMENSION(:),ALLOCATABLE,SAVE :: swf_sv ! Normalized Decay
179 !$OMP THREADPRIVATE(SWf_SV)
180  REAL, DIMENSION(:),ALLOCATABLE,SAVE :: sws_sv ! Surficial Water Status
181 !$OMP THREADPRIVATE(SWS_SV)
182  REAL, DIMENSION(:),ALLOCATABLE,SAVE :: hfrasv ! Frazil Thickness
183 !$OMP THREADPRIVATE(HFraSV)
184 
185  REAL, DIMENSION(:),ALLOCATABLE,SAVE :: zwe_sv ! Current Snow Thickness [mmWE]
186 !$OMP THREADPRIVATE(zWE_SV)
187  REAL, DIMENSION(:),ALLOCATABLE,SAVE :: zwecsv ! Compacted Snow Thickness [mmWE]
188 !$OMP THREADPRIVATE(zWEcSV)
189  REAL, DIMENSION(:),ALLOCATABLE,SAVE :: wem_sv ! Only Melting [mmWE]
190 !$OMP THREADPRIVATE(wem_SV)
191  REAL, DIMENSION(:),ALLOCATABLE,SAVE :: wer_sv ! Refreezing [mmWE]
192 !$OMP THREADPRIVATE(wer_SV)
193  REAL, DIMENSION(:),ALLOCATABLE,SAVE :: wes_sv ! Sublimation [mmWE]
194 !$OMP THREADPRIVATE(wes_SV)
195 
196 
197 ! +--SISVAT OUTPUT Variables
198 ! + -----------------------------
199 
200  INTEGER,DIMENSION(nb_wri),SAVE :: no__sv ! OUTPUT file Unit Number
201 !$OMP THREADPRIVATE(no__SV)
202  INTEGER,DIMENSION(nb_wri),SAVE :: i___sv ! OUTPUT point i Coordinate
203 !$OMP THREADPRIVATE(i___SV)
204  INTEGER,DIMENSION(nb_wri),SAVE :: j___sv ! OUTPUT point j Coordinate
205 !$OMP THREADPRIVATE(j___SV)
206  INTEGER,DIMENSION(nb_wri),SAVE :: n___sv ! OUTPUT point n Coordinate
207 !$OMP THREADPRIVATE(n___SV)
208  INTEGER,DIMENSION(nb_wri),SAVE :: lwrisv ! OUTPUT point vec Index
209 !$OMP THREADPRIVATE(lwriSV)
210 !
211  INTEGER, DIMENSION(:),ALLOCATABLE,SAVE :: ii__sv ! WORK point i Coordinate
212 !$OMP THREADPRIVATE(ii__SV)
213  INTEGER, DIMENSION(:),ALLOCATABLE,SAVE :: jj__sv ! WORK point j Coordinate
214 !$OMP THREADPRIVATE(jj__SV)
215  INTEGER, DIMENSION(:),ALLOCATABLE,SAVE :: nn__sv ! WORK point n Coordinate
216 !$OMP THREADPRIVATE(nn__SV)
217 
218  REAL, DIMENSION(:),ALLOCATABLE,SAVE :: iru_sv ! UPward IR Flux (effective)
219 !$OMP THREADPRIVATE(IRu_SV)
220  REAL, DIMENSION(:),ALLOCATABLE,SAVE :: hsalsv ! Saltating Layer Height
221 !$OMP THREADPRIVATE(hSalSV)
222  REAL, DIMENSION(:),ALLOCATABLE,SAVE :: qsalsv ! Saltating Snow Concentration
223 !$OMP THREADPRIVATE(qSalSV)
224  REAL, DIMENSION(:),ALLOCATABLE,SAVE :: rnofsv ! RunOFF Intensity
225 !$OMP THREADPRIVATE(RnofSV)
226 
227 CONTAINS
228 
229 
230 
231  SUBROUTINE init_varxsv
232  IMPLICIT NONE
233 
234  INTEGER :: ikl
235 
236  ALLOCATE(lsmask(klonv)) ! Land-Sea Mask
237  ALLOCATE(isotsv(klonv)) ! Soil Type
238  ALLOCATE(iwafsv(klonv)) ! Soil Drainage:(1,0)=(y,n)
239  ALLOCATE(ivgtsv(klonv)) ! Vegetation Type
240 
241  ALLOCATE(coszsv(klonv)) ! Cosine of Sun zenithal Angle
242  ALLOCATE(sol_sv(klonv)) ! Downward Solar Radiation
243  ALLOCATE(ird_sv(klonv)) ! Downward Longwave Radiation
244 
245  ALLOCATE(drr_sv(klonv)) ! Rain Intensity [kg/m2/s]
246  ALLOCATE(dsn_sv(klonv)) ! Snow Intensity [kg/m2/s]
247  ALLOCATE(dsnbsv(klonv)) ! Idem, from Drift [kg/m2]
248  ALLOCATE(esnbsv(klonv)) ! Idem, from Drift [kg/m2]
249  ALLOCATE(dbs_sv(klonv)) ! Drift Amount [kg/m2]
250  ALLOCATE(brossv(klonv))
251  ALLOCATE(bg1ssv(klonv))
252  ALLOCATE(bg2ssv(klonv))
253  ALLOCATE(dz0_sv(klonv)) ! dz0(Sastrugi dh) [m]
254 
255  ALLOCATE(cld_sv(klonv)) ! Cloudiness (seen from SBL)
256  ALLOCATE(za__sv(klonv)) ! SBL Height
257  ALLOCATE(vv__sv(klonv)) !(SBL Top) Wind Velocity
258  ALLOCATE(vvs_sv(klonv))
259  ALLOCATE(rrs_sv(klonv))
260  ALLOCATE(dds_sv(klonv))
261  ALLOCATE(tat_sv(klonv)) ! SBL Top Temperature
262  ALLOCATE(exnrsv(klonv)) ! Exner Potential
263  ALLOCATE(dsdtsv(klonv)) ! Sensible Heat Flux T Derivat.
264  ALLOCATE(dldtsv(klonv)) ! Latent Heat Flux T Derivat.
265  ALLOCATE(rht_sv(klonv)) ! SBL Top Air Density
266  ALLOCATE(qat_sv(klonv)) ! SBL Top Specific Humidity
267  ALLOCATE(dqa_sv(klonv)) ! SBL Flux Limitation of Qa
268  ALLOCATE(qsnosv(klonv)) ! SBL Mean Snow Content
269 
270  ALLOCATE(lai0sv(klonv)) ! Nominal Leaf Area Index
271  ALLOCATE(glf0sv(klonv)) ! Green Leaf Fraction
272 
273  ALLOCATE(alb0sv(klonv)) ! Soil Albedo
274  ALLOCATE(slopsv(klonv)) ! Snow/Ice/Soil-Water Surf. Slope
275 
276 
277 
278 ! +--SISVAT INPUT/OUTPUT Variables
279 ! + -----------------------------
280 
281  ALLOCATE(isnosv(klonv)) ! Nb of Ice/Snow Layers
282  ALLOCATE(ispisv(klonv)) ! Uppermost superimposed ice
283  ALLOCATE(iicesv(klonv)) ! Nb of Ice Layers
284  ALLOCATE(istosv(klonv,0:nsno)) ! Snow Layer History
285 
286  ALLOCATE(alb_sv(klonv)) ! Surface-Canopy Albedo
287  ALLOCATE(emi_sv(klonv)) ! Surface-Canopy Emissivity
288  ALLOCATE(irs_sv(klonv)) ! Soil IR Flux
289  ALLOCATE(lmo_sv(klonv)) ! Monin-Obukhov Scale
290  ALLOCATE(us__sv(klonv)) ! Friction Velocity
291  ALLOCATE(uts_sv(klonv)) ! Temperature Turbulent Scale
292  ALLOCATE(cutssv(klonv)) ! Temperature Turbulent Scale C.
293  ALLOCATE(uqs_sv(klonv)) ! Spec.Humid. Turbulent Scale
294  ALLOCATE(uss_sv(klonv)) ! Blow.Snow Turbulent Scale
295  ALLOCATE(usthsv(klonv)) ! Blowing Snow Erosion Thresh.
296  ALLOCATE(rcdmsv(klonv)) ! Square Root Contribut. Drag_m
297  ALLOCATE(rcdhsv(klonv)) ! Square Root Contribut. Drag_h
298  ALLOCATE(z0m_sv(klonv)) ! Momentum Roughness Length
299  ALLOCATE(z0mmsv(klonv)) ! z0(Momentum, Time Mean) [m]
300  ALLOCATE(z0mnsv(klonv)) ! z0(Momentum, instanta.) [m]
301  ALLOCATE(z0rosv(klonv)) ! Subgrid Topo Roughness Length
302  ALLOCATE(z0sasv(klonv)) ! z0(Sastrugi h) [m]
303  ALLOCATE(z0e_sv(klonv)) ! z0(Snow eroded) [m]
304  ALLOCATE(z0emsv(klonv)) ! z0(Snow eroded, Time Mean) [m]
305  ALLOCATE(z0ensv(klonv)) ! z0(Snow eroded, instanta.) [m]
306  ALLOCATE(z0h_sv(klonv)) ! Heat Roughness Length
307  ALLOCATE(z0hmsv(klonv)) ! z0(Heat, Time Mean) [m]
308  ALLOCATE(z0hnsv(klonv)) ! z0(Heat, instanta.) [m]
309 
310  ALLOCATE(sncasv(klonv)) ! Canopy Snow Thickness
311  ALLOCATE(rrcasv(klonv)) ! Canopy Water Content
312  ALLOCATE(psivsv(klonv)) ! Leaf Water Potential
313  ALLOCATE(tvegsv(klonv)) ! Vegetation Temperature
314 
315  ALLOCATE(tsissv(klonv,-nsol:nsno)) ! Snow/Ice/Soil-Water Temperature
316  ALLOCATE(ro__sv(klonv,-nsol:nsno)) ! Snow/Ice/Soil-Water VolumicMass
317  ALLOCATE(eta_sv(klonv,-nsol:nsno)) ! Snow/Ice/Soil Water Content
318  ALLOCATE(g1snsv(klonv, 0:nsno)) ! Snow Dendricity/Sphericity
319  ALLOCATE(g2snsv(klonv, 0:nsno)) ! Snow Sphericity/Size
320  ALLOCATE(dzsnsv(klonv, 0:nsno)) ! Snow Layer Thickness
321  ALLOCATE(agsnsv(klonv, 0:nsno)) ! Snow Age
322  ALLOCATE(bufssv(klonv)) ! Snow Buffer Layer
323  ALLOCATE(rusnsv(klonv)) ! Surficial Water
324  ALLOCATE(swf_sv(klonv)) ! Normalized Decay
325  ALLOCATE(sws_sv(klonv)) ! Surficial Water Status
326  ALLOCATE(hfrasv(klonv)) ! Frazil Thickness
327 
328  ALLOCATE(zwe_sv(klonv)) ! Current Snow Thickness [mmWE]
329  ALLOCATE(zwecsv(klonv)) ! Compacted Snow Thickness [mmWE]
330  ALLOCATE(wem_sv(klonv)) ! Only Melting [mmWE]
331  ALLOCATE(wer_sv(klonv)) ! Refreezing [mmWE]
332  ALLOCATE(wes_sv(klonv)) ! Sublimation [mmWE]
333 
334 
335 ! +--SISVAT OUTPUT Variables
336 ! + -----------------------------
337 
338 !
339  ALLOCATE(ii__sv(klonv)) ! WORK point i Coordinate
340  ALLOCATE(jj__sv(klonv)) ! WORK point j Coordinate
341  ALLOCATE(nn__sv(klonv)) ! WORK point n Coordinate
342 
343  ALLOCATE(iru_sv(klonv)) ! UPward IR Flux (effective)
344  ALLOCATE(hsalsv(klonv)) ! Saltating Layer Height
345  ALLOCATE(qsalsv(klonv)) ! Saltating Snow Concentration
346  ALLOCATE(rnofsv(klonv)) ! RunOFF Intensity
347 
348  DO ikl=1,klonv
349  lsmask(ikl) = 0
350  isotsv(ikl) = 0
351  iwafsv(ikl) = 0
352  ivgtsv(ikl) = 0
353  isnosv(ikl) = 0
354  ispisv(ikl) = 0
355  iicesv(ikl) = 0
356  istosv(ikl,:) = 0
357  ii__sv(ikl) = 0
358  jj__sv(ikl) = 0
359  nn__sv(ikl) = 0
360  END DO
361  END SUBROUTINE init_varxsv
362 
363 
364 
365 END MODULE varxsv
real, dimension(:), allocatable, save brossv
Definition: VARxSV.F90:35
integer, dimension(:), allocatable, save nn__sv
Definition: VARxSV.F90:215
real, dimension(:), allocatable, save wer_sv
Definition: VARxSV.F90:191
real, dimension(:), allocatable, save tvegsv
Definition: VARxSV.F90:157
real, dimension(:), allocatable, save dsdtsv
Definition: VARxSV.F90:60
Definition: VARxSV.F90:1
real, dimension(:), allocatable, save exnrsv
Definition: VARxSV.F90:58
real, dimension(:), allocatable, save bufssv
Definition: VARxSV.F90:174
integer, dimension(:,:), allocatable, save istosv
Definition: VARxSV.F90:101
real, dimension(:), allocatable, save sol_sv
Definition: VARxSV.F90:20
real, dimension(:,:), allocatable, save agsnsv
Definition: VARxSV.F90:172
real, dimension(:,:), allocatable, save dzsnsv
Definition: VARxSV.F90:170
real, dimension(:), allocatable, save alb_sv
Definition: VARxSV.F90:104
real, dimension(:), allocatable, save lai0sv
Definition: VARxSV.F90:73
integer, dimension(:), allocatable, save isnosv
Definition: VARxSV.F90:95
integer, dimension(:), allocatable, save isotsv
Definition: VARxSV.F90:11
real, dimension(:), allocatable, save dsnbsv
Definition: VARxSV.F90:29
real, dimension(:), allocatable, save sncasv
Definition: VARxSV.F90:151
real, dimension(:), allocatable, save sws_sv
Definition: VARxSV.F90:180
real, dimension(:), allocatable, save z0mmsv
Definition: VARxSV.F90:130
integer, dimension(:), allocatable, save iicesv
Definition: VARxSV.F90:99
real, dimension(:,:), allocatable, save g1snsv
Definition: VARxSV.F90:166
real, dimension(:), allocatable, save hsalsv
Definition: VARxSV.F90:220
real, dimension(:,:), allocatable, save tsissv
Definition: VARxSV.F90:160
real, dimension(:), allocatable, save uts_sv
Definition: VARxSV.F90:114
subroutine init_varxsv
Definition: VARxSV.F90:232
integer, dimension(nb_wri), save no__sv
Definition: VARxSV.F90:200
real, dimension(:), allocatable, save tat_sv
Definition: VARxSV.F90:56
real, dimension(:), allocatable, save iru_sv
Definition: VARxSV.F90:218
real, dimension(:), allocatable, save zwe_sv
Definition: VARxSV.F90:185
integer, dimension(nb_wri), save lwrisv
Definition: VARxSV.F90:208
real, dimension(:), allocatable, save wes_sv
Definition: VARxSV.F90:193
real, dimension(:), allocatable, save zwecsv
Definition: VARxSV.F90:187
Definition: VAR_SV.F90:1
real, dimension(:), allocatable, save psivsv
Definition: VARxSV.F90:155
real, dimension(:), allocatable, save cld_sv
Definition: VARxSV.F90:44
character(len=18), save dahost
Definition: VARxSV.F90:88
real, dimension(:), allocatable, save dds_sv
Definition: VARxSV.F90:54
real, dimension(:), allocatable, save alb0sv
Definition: VARxSV.F90:78
real, dimension(:), allocatable, save rusnsv
Definition: VARxSV.F90:176
real, dimension(:), allocatable, save glf0sv
Definition: VARxSV.F90:75
real, dimension(:), allocatable, save bg2ssv
Definition: VARxSV.F90:39
real, dimension(:), allocatable, save z0ensv
Definition: VARxSV.F90:142
integer, dimension(nb_wri), save j___sv
Definition: VARxSV.F90:204
real, dimension(:), allocatable, save usthsv
Definition: VARxSV.F90:122
real, dimension(:), allocatable, save z0h_sv
Definition: VARxSV.F90:144
integer, dimension(:), allocatable, save iwafsv
Definition: VARxSV.F90:13
real, dimension(:), allocatable, save hfrasv
Definition: VARxSV.F90:182
integer, dimension(:), allocatable, save ivgtsv
Definition: VARxSV.F90:15
integer, parameter nsno
Definition: VAR_SV.F90:11
integer, dimension(nb_wri), save i___sv
Definition: VARxSV.F90:202
real, dimension(:), allocatable, save za__sv
Definition: VARxSV.F90:46
real, dimension(:), allocatable, save vv__sv
Definition: VARxSV.F90:48
integer, dimension(:), allocatable, save ispisv
Definition: VARxSV.F90:97
real, dimension(:), allocatable, save z0hnsv
Definition: VARxSV.F90:148
real, dimension(:), allocatable, save qsnosv
Definition: VARxSV.F90:70
integer, dimension(:), allocatable, save jj__sv
Definition: VARxSV.F90:213
real, dimension(:), allocatable, save rht_sv
Definition: VARxSV.F90:64
integer, dimension(nb_wri), save n___sv
Definition: VARxSV.F90:206
real, dimension(:), allocatable, save rnofsv
Definition: VARxSV.F90:224
integer, parameter nsol
Definition: VAR_SV.F90:10
real, dimension(:), allocatable, save wem_sv
Definition: VARxSV.F90:189
real, dimension(:), allocatable, save rcdmsv
Definition: VARxSV.F90:124
real, dimension(:), allocatable, save cutssv
Definition: VARxSV.F90:116
integer, save klonv
Definition: VAR_SV.F90:13
real, dimension(:), allocatable, save z0hmsv
Definition: VARxSV.F90:146
real, dimension(:), allocatable, save ird_sv
Definition: VARxSV.F90:22
real, dimension(:), allocatable, save dz0_sv
Definition: VARxSV.F90:41
real, dimension(:), allocatable, save dbs_sv
Definition: VARxSV.F90:33
real, dimension(:), allocatable, save z0sasv
Definition: VARxSV.F90:136
real, dimension(:), allocatable, save drr_sv
Definition: VARxSV.F90:25
integer, dimension(:), allocatable, save ii__sv
Definition: VARxSV.F90:211
real, dimension(:), allocatable, save dqa_sv
Definition: VARxSV.F90:68
real, dimension(:,:), allocatable, save ro__sv
Definition: VARxSV.F90:162
real, dimension(:), allocatable, save irs_sv
Definition: VARxSV.F90:108
real, dimension(:), allocatable, save lmo_sv
Definition: VARxSV.F90:110
real, dimension(:), allocatable, save z0m_sv
Definition: VARxSV.F90:128
real, dimension(:), allocatable, save rrs_sv
Definition: VARxSV.F90:52
real, dimension(:), allocatable, save dsn_sv
Definition: VARxSV.F90:27
integer, dimension(:), allocatable, save lsmask
Definition: VARxSV.F90:9
real, save zsblsv
Definition: VARxSV.F90:84
real, dimension(:), allocatable, save uqs_sv
Definition: VARxSV.F90:118
real, dimension(:), allocatable, save z0rosv
Definition: VARxSV.F90:134
real, dimension(:), allocatable, save us__sv
Definition: VARxSV.F90:112
real, dimension(:), allocatable, save qsalsv
Definition: VARxSV.F90:222
real, dimension(:), allocatable, save uss_sv
Definition: VARxSV.F90:120
real, dimension(:), allocatable, save slopsv
Definition: VARxSV.F90:80
real, dimension(:), allocatable, save rcdhsv
Definition: VARxSV.F90:126
integer, parameter nb_wri
Definition: VAR_SV.F90:12
real, dimension(:,:), allocatable, save eta_sv
Definition: VARxSV.F90:164
real, dimension(:), allocatable, save z0mnsv
Definition: VARxSV.F90:132
real, dimension(:), allocatable, save qat_sv
Definition: VARxSV.F90:66
real, save dt__sv
Definition: VARxSV.F90:86
real, dimension(:), allocatable, save rrcasv
Definition: VARxSV.F90:153
real, dimension(:), allocatable, save emi_sv
Definition: VARxSV.F90:106
real, dimension(:), allocatable, save coszsv
Definition: VARxSV.F90:18
real, dimension(:), allocatable, save dldtsv
Definition: VARxSV.F90:62
real, dimension(:), allocatable, save swf_sv
Definition: VARxSV.F90:178
real, dimension(:,:), allocatable, save g2snsv
Definition: VARxSV.F90:168
real, dimension(:), allocatable, save z0e_sv
Definition: VARxSV.F90:138
real, dimension(:), allocatable, save esnbsv
Definition: VARxSV.F90:31
real, dimension(:), allocatable, save vvs_sv
Definition: VARxSV.F90:50
real, dimension(:), allocatable, save z0emsv
Definition: VARxSV.F90:140
real, dimension(:), allocatable, save bg1ssv
Definition: VARxSV.F90:37