12 SUBROUTINE surf_sisvat(knon,rlon,rlat, ikl2i, itime, dtime, debut, lafin, &
13 rmu0, swdown, lwdown, pexner, ps, p1lay, &
14 precip_rain, precip_snow, precip_snow_adv, snow_adv, &
15 bl_height, wind_velo, temp_air, dens_air, spechum, tsurf, &
16 rugos, snow_cont_air, alb_soil, slope, cloudf, &
17 radsol, qsol, tsoil, snow, snowhgt, qsnow, to_ice, sissnow, agesno, &
18 acoefh, acoefq, bcoefh, bcoefq, cdragh, &
19 runoff_lic, evap, fluxsens, fluxlat, dflux_s, dflux_l, &
20 tsurf_new, alb1, alb2, alb3, &
21 emis_new, z0_new, qsurf)
114 INTEGER,
INTENT(IN) :: knon
115 INTEGER,
INTENT(IN) :: itime
116 REAL,
INTENT(IN) :: dtime
117 LOGICAL,
INTENT(IN) :: debut
118 LOGICAL,
INTENT(IN) :: lafin
120 INTEGER,
DIMENSION(klon),
INTENT(IN) :: ikl2i
121 REAL,
DIMENSION(klon),
INTENT(IN) :: rlon, rlat
122 REAL,
DIMENSION(klon),
INTENT(IN) :: rmu0
123 REAL,
DIMENSION(klon),
INTENT(IN) :: swdown
124 REAL,
DIMENSION(klon),
INTENT(IN) :: lwdown
125 REAL,
DIMENSION(klon),
INTENT(IN) :: pexner
126 REAL,
DIMENSION(klon),
INTENT(IN) :: precip_rain, precip_snow
127 REAL,
DIMENSION(klon),
INTENT(IN) :: precip_snow_adv, snow_adv
129 REAL,
DIMENSION(klon),
INTENT(IN) :: bl_height, wind_velo
130 REAL,
DIMENSION(klon),
INTENT(IN) :: temp_air, spechum, ps,p1lay
131 REAL,
DIMENSION(klon),
INTENT(IN) :: dens_air, tsurf
132 REAL,
DIMENSION(klon),
INTENT(IN) :: rugos,snow_cont_air
133 REAL,
DIMENSION(klon),
INTENT(IN) :: alb_soil, slope
134 REAL,
DIMENSION(klon),
INTENT(IN) :: cloudf
135 REAL,
DIMENSION(klon),
INTENT(IN) :: AcoefH, AcoefQ
136 REAL,
DIMENSION(klon),
INTENT(IN) :: BcoefH, BcoefQ
137 REAL,
DIMENSION(klon),
INTENT(IN) :: cdragh
140 REAL,
DIMENSION(klon,nsoilmx),
INTENT(OUT) :: tsoil
141 REAL,
DIMENSION(klon),
INTENT(OUT) :: qsol
142 REAL,
DIMENSION(klon),
INTENT(INOUT) :: snow
143 REAL,
DIMENSION(klon),
INTENT(IN) :: radsol
146 REAL,
DIMENSION(klon),
INTENT(OUT) :: alb1
147 REAL,
DIMENSION(klon),
INTENT(OUT) :: alb2,alb3
148 REAL,
DIMENSION(klon),
INTENT(OUT) :: emis_new
149 REAL,
DIMENSION(klon),
INTENT(OUT) :: z0_new
150 REAL,
DIMENSION(klon),
INTENT(OUT) :: runoff_lic
151 REAL,
DIMENSION(klon),
INTENT(OUT) :: dflux_s
152 REAL,
DIMENSION(klon),
INTENT(OUT) :: dflux_l
153 REAL,
DIMENSION(klon),
INTENT(OUT) :: fluxsens
154 REAL,
DIMENSION(klon),
INTENT(OUT) :: fluxlat
155 REAL,
DIMENSION(klon),
INTENT(OUT) :: evap
156 REAL,
DIMENSION(klon),
INTENT(OUT) :: agesno
157 REAL,
DIMENSION(klon),
INTENT(OUT) :: tsurf_new
158 REAL,
DIMENSION(klon),
INTENT(OUT) :: qsurf
159 REAL,
DIMENSION(klon),
INTENT(OUT) :: qsnow
160 REAL,
DIMENSION(klon),
INTENT(OUT) :: snowhgt
161 REAL,
DIMENSION(klon),
INTENT(OUT) :: to_ice
162 REAL,
DIMENSION(klon),
INTENT(OUT) :: sissnow
232 CHARACTER(len=20) :: fichnom, fn_outfor
233 INTEGER :: i, ig, ikl, isl, isn, nt
234 INTEGER :: gp_outfor, un_outfor
236 REAL,
PARAMETER :: f1=0.5
237 REAL,
PARAMETER :: sn_upp=5000.,sn_low=500.
238 REAL,
PARAMETER :: sn_add=400.,sn_div=2.
241 REAL,
PARAMETER :: c1_zuo=12.960e+4, c2_zuo=2.160e+6
242 REAL,
PARAMETER :: c3_zuo=1.400e+2, czemin=1.e-3
249 REAL,
DIMENSION(klon) :: eps0SL
250 REAL :: zsigma, Ua_min, Us_min
252 REAL,
DIMENSION(nsoilmx),
SAVE :: dz1,dz2
254 LOGICAL,
SAVE :: firstcall=.
true.,snomod, ok_outfor=.
false.
276 fn_outfor=
'outfor_SV.dat'
302 write(*,*)
'klon',
klon,
'klonv',
klonv,
'knon',knon
319 dz_dsv(isl) = 0.5e-3*dz2(1-isl)
321 dz1_sv(ikl,isl) = dz1(1-isl)
322 dz2_sv(ikl,isl) = dz2(1-isl)
331 alb0sv(ikl) = alb_soil(ikl)
335 -eps0sl(ikl)*
rsigma*temp_air(ikl) &
336 *temp_air(ikl)*temp_air(ikl)*temp_air(ikl)
337 tvegsv(ikl) = temp_air(ikl)
340 tsissv(ikl,isl) = temp_air(ikl)
354 +c2_zuo*exp(-c3_zuo*abs(
slopsv(ikl)))))
361 v__mem(ikl,nt)=wind_velo(ikl)
362 t__mem(ikl,nt)=temp_air(ikl)-tsurf(ikl)
374 open(
unit=un_outfor,status=
'new',file=fn_outfor)
378 write(un_outfor,501) fn_outfor, ikl, rlon(ig),rlat(ig)
379 501
format(/,a18,/,
'Grid point ',i4,
' Long',f9.4,
' Lat ',f9.4 &
380 & ,/,
'++++++++++++++++++++++++++++++++++++++++++++++', &
381 &
'++++++++++++++++++++++++++++++++++++++++++++++', &
382 &
'++++++++++++++++++++++++++++++++++++++++++++++', &
383 & /,
' SWdown + IRdown + Wind + Temp. + Humid. ', &
384 &
'+ Press +Precip_l+Precip_s+ Tsrf + Clouds +' &
385 &
'+ Zenith + BLhgt + Densair+ Exner +' &
386 & ,/,
' sol_SV + IRd_SV + VV__SV + TaT_SV + QaT_SV ', &
387 &
'+ ps__SV + drr_SV + dsn_SV + Tsf_SV + cld_SV +' &
388 &
'+ coszSV + za__SV + rhT_SV + ExnrSV+' &
389 & ,/,
' W/m2 + W/m2 + m/s + K + kg/kg ', &
390 &
'+ Pa + kg/m2/s+ kg/m2/s+ K + /1 +' &
391 &
'+ - + m + kg/m3 + +' &
392 & ,/,
'++++++++++++++++++++++++++++++++++++++++++++++', &
393 &
'++++++++++++++++++++++++++++++++++++++++++++++', &
394 &
'++++++++++++++++++++++++++++++++++++++++++++++')
401 print*,
'On debranche sisvatetat0'
424 za__sv(ikl) = bl_height(ikl)
427 ua_min = 0.2 * sqrt(
za__sv(ikl) )
428 vv__sv(ikl) = max(ua_min, wind_velo(ikl))
431 tat_sv(ikl) = temp_air(ikl)
433 rht_sv(ikl) = dens_air(ikl)
434 qat_sv(ikl) = spechum(ikl)
441 coszsv(ikl) = max(czemin,rmu0(ikl))
450 drr_sv(ikl) = precip_rain(ikl)
451 dsn_sv(ikl) = precip_snow(ikl)
461 alb0sv(ikl) = alb_soil(ikl)
471 IF (.not.firstcall)
THEN
511 5000
format(f8.3,
' ',f8.3,
' ',f8.4,
' ',f8.4,
' ',f10.8,
' ',f8.1,
' ', &
512 & f8.6,
' ',f8.6,
' ',f8.4,
' ',f8.6,
' ',f8.6,
' ',f8.3,
' ', &
537 runoff_lic(ikl) =
rnofsv(ikl)*dtime
538 dflux_s(ikl) =
dsdtsv(ikl)
539 dflux_l(ikl) =
dldtsv(ikl)
540 fluxsens(ikl) =
hss_sv(ikl)
541 fluxlat(ikl) =
hls_sv(ikl)
555 sissnow(ikl) = sissnow(ikl)+
dzsnsv(ikl,isn)*
ro__sv(ikl,isn)
558 IF (sissnow(ikl) .LE. sn_low)
THEN
559 IF (
isnosv(ikl).GE.1)
THEN
563 write(*,*)
'Attention, bare ice... point ',ikl
578 IF (sissnow(ikl) .ge. sn_upp)
THEN
585 sissnow(ikl) = sissnow(ikl)+
dzsnsv(ikl,isn)*
ro__sv(ikl,isn)
587 snowhgt(ikl) = snowhgt(ikl)+
dzsnsv(ikl,isn)
588 qsnow(ikl) = qsnow(ikl)+1e03*
eta_sv(ikl,isn)*
dzsnsv(ikl,isn)
590 snow(ikl) = sissnow(ikl)+
toicsv(ikl)
596 tsoil(ikl,1-isl) =
tsissv(ikl,isl)
597 qsol(ikl) = qsol(ikl) &
607 tsurf_new(ikl) =
tsfnsv(ikl)
614 emis_new(ikl) = eps0sl(ikl)
687 fichnom =
"restartsis.nc"
690 close(
unit=un_outfor)
716 REAL,
DIMENSION(nsoilmx),
INTENT(OUT) :: dz2, dz1
717 REAL,
INTENT(OUT) :: lambda
723 REAL fz,rk,fz1,rk1,rk2
724 REAL min_period, dalph_soil
727 fz(rk)=fz1*(dalph_soil**rk-1.)/(dalph_soil-1.)
758 fz1=sqrt(min_period/3.14)
763 dz2(jk)=fz(rk1)-fz(rk2)
768 dz1(jk)=1./(fz(rk1)-fz(rk2))
771 print*,
'full layers, intermediate layers (seconds)'
777 fz(rk1)*fz(rk2)*3.14,fz(rk)*fz(rk)*3.14
839 INTEGER,
INTENT(IN) :: knon
844 INTEGER :: ivt ,ist ,ivg ,ikl ,isl ,isn ,ikh
845 INTEGER :: misl_2,nisl_2
847 REAL :: d__eta,eta__1,eta__2,Khyd_1,Khyd_2
848 REAL,
PARAMETER :: RHsMin= 0.001
850 REAL :: a_Khyd,b_Khyd
1015 write(*,
'(/a)')
'ROOT PROFILES (Jackson, 1996) :'
1019 DO isl = 0, -
nsol, -1
1020 IF (ivt .ne. 0)
THEN
1023 zdepth = zdepth +
dz_dsv(isl)*100
1028 write(*,
'(a,i2,a,i3,a,99f10.5:)') &
1029 &
' RF__SV(', ivt,
',', -
nsol,
':0) =',
rf__sv(ivt,:)
1050 psimax = -(log(rhsmin))/7.2e-5
1069 & *(eta__1 **(2. *
bchdsv(ist)+3.))
1071 & *(eta__2 **(2. *
bchdsv(ist)+3.))
1073 a_khyd = (khyd_2-khyd_1)/d__eta
1074 b_khyd = khyd_1-a_khyd *eta__1
1083 eta__1 = eta__1 + d__eta
1084 eta__2 = eta__2 + d__eta
1197 include
"netcdf.inc"
1201 include
"clesphys.h"
1202 include
"thermcell.h"
1206 CHARACTER(LEN=*) :: fichnom
1209 INTEGER,
DIMENSION(klon),
INTENT(IN) :: ikl2i
1210 REAL,
DIMENSION(klon) :: rlon
1211 REAL,
DIMENSION(klon) :: rlat
1214 REAL,
DIMENSION(klon) :: isno
1215 REAL,
DIMENSION(klon) :: ispi
1216 REAL,
DIMENSION(klon) :: iice
1217 REAL,
DIMENSION(klon) :: rusn
1218 REAL,
DIMENSION(klon, nsno) :: isto
1220 REAL,
DIMENSION(klon, nsismx) :: Tsis
1221 REAL,
DIMENSION(klon, nsismx) :: eta
1222 REAL,
DIMENSION(klon, nsismx) :: ro
1224 REAL,
DIMENSION(klon, nsno) :: dzsn
1225 REAL,
DIMENSION(klon, nsno) :: G1sn
1226 REAL,
DIMENSION(klon, nsno) :: G2sn
1227 REAL,
DIMENSION(klon, nsno) :: agsn
1229 REAL,
DIMENSION(klon) :: toic
1237 INTEGER :: isl, ikl, i, isn , errT, erreta, errro, errdz, snopts
1238 CHARACTER (len=2) :: str2
1256 IF (.NOT. found)
THEN
1257 print*,
'phyetat0: Le champ <n_snows> est absent'
1258 print *,
'fichier startsisvat non compatible avec sisvatetat0'
1271 IF (.NOT. found)
THEN
1272 print*,
'phyetat0: Le champ <to_ice> est absent'
1292 WRITE(str2,
'(i2.2)') isn
1296 print*,
"Trop de couches"
1302 WRITE(str2,
'(i2.2)') isn
1306 print*,
"Trop de couches"
1312 WRITE(str2,
'(i2.2)') isn
1316 print*,
"Trop de couches"
1322 WRITE(str2,
'(i2.2)') isn
1326 print*,
"Trop de couches"
1332 WRITE(str2,
'(i2.2)') isn
1336 print*,
"Trop de couches"
1342 WRITE(str2,
'(i2.2)') isn
1346 print*,
"Trop de couches"
1352 WRITE(str2,
'(i2.2)') isn
1356 print*,
"Trop de couches"
1362 WRITE(str2,
'(i2.2)') isn
1366 print*,
"Trop de couches"
1370 write(*,*)
'Read ',fichnom,
' finished!!'
1394 isnosv(ikl) = int(isno(i))
1395 ispisv(ikl) = int(ispi(i))
1396 iicesv(ikl) = int(iice(i))
1419 IF (
eta_sv(ikl,isl) <= 1.e-6)
THEN
1423 IF (
tsissv(ikl,isl) <= 1.)
THEN
1429 write(*,*)
'Copy histo', ikl
1441 IF (isto(i,isn) > 10.)
THEN
1442 write(*,*)
'Irregular isto',ikl,i,isn,isto(i,isn)
1446 istosv(ikl,isn) = int(isto(i,isn))
1447 ro__sv(ikl,isn) = ro(i,isn)
1448 eta_sv(ikl,isn) = eta(i,isn)
1449 tsissv(ikl,isn) = tsis(i,isn)
1451 IF (
tsissv(ikl,isn) <= 1.)
THEN
1455 IF (
tsissv(ikl,isn) <= 1.)
THEN
1458 IF (
eta_sv(ikl,isn) < 1.e-9)
THEN
1462 IF (
ro__sv(ikl,isn) <= 10.)
THEN
1466 write(*,*)ikl,i,isn,tsis(i,isn),g1sn(i,isn)
1467 g1snsv(ikl,isn) = g1sn(i,isn)
1468 g2snsv(ikl,isn) = g2sn(i,isn)
1469 dzsnsv(ikl,isn) = dzsn(i,isn)
1474 agsnsv(ikl,isn) = agsn(i,isn)
1504 include
"netcdf.inc"
1507 include
"clesphys.h"
1508 include
"thermcell.h"
1513 CHARACTER(LEN=*) :: fichnom
1514 INTEGER,
DIMENSION(klon),
INTENT(IN) :: ikl2i
1515 REAL,
DIMENSION(klon),
INTENT(IN) :: rlon
1516 REAL,
DIMENSION(klon),
INTENT(IN) :: rlat
1519 REAL,
DIMENSION(klon) :: isno
1520 REAL,
DIMENSION(klon) :: ispi
1521 REAL,
DIMENSION(klon) :: iice
1522 REAL,
DIMENSION(klon, nsnowmx) :: isto
1524 REAL,
DIMENSION(klon, nsismx) :: Tsis
1525 REAL,
DIMENSION(klon, nsismx) :: eta
1526 REAL,
DIMENSION(klon, nsnowmx) :: dzsn
1527 REAL,
DIMENSION(klon, nsismx) :: ro
1528 REAL,
DIMENSION(klon, nsnowmx) :: G1sn
1529 REAL,
DIMENSION(klon, nsnowmx) :: G2sn
1530 REAL,
DIMENSION(klon, nsnowmx) :: agsn
1531 REAL,
DIMENSION(klon) :: IRs
1532 REAL,
DIMENSION(klon) :: LMO
1533 REAL,
DIMENSION(klon) :: rusn
1534 REAL,
DIMENSION(klon) :: toic
1535 REAL,
DIMENSION(klon) :: Bufs
1536 REAL,
DIMENSION(klon) :: alb1,alb2,alb3
1537 REAL,
DIMENSION(klon, 9) :: rlength
1538 REAL,
DIMENSION(klon, 5) :: turb_vel
1540 INTEGER isl, ikl, i, isn
1541 CHARACTER (len=2) :: str2
1600 isto(i,isn) = 1.*
istosv(ikl,isn)
1601 ro(i,isn) =
ro__sv(ikl,isn)
1602 eta(i,isn) =
eta_sv(ikl,isn)
1603 tsis(i,isn) =
tsissv(ikl,isn)
1604 g1sn(i,isn) =
g1snsv(ikl,isn)
1605 g2sn(i,isn) =
g2snsv(ikl,isn)
1606 dzsn(i,isn) =
dzsnsv(ikl,isn)
1607 agsn(i,isn) =
agsnsv(ikl,isn)
1620 "Longitudes de la grille physique",rlon)
1621 CALL put_field(
"latitude",
"Latitudes de la grille physique",rlat)
1623 CALL put_field(
"n_snows",
"number of snow/ice layers",isno)
1624 CALL put_field(
"n_ice_top",
"number of top ice layers",ispi)
1625 CALL put_field(
"n_ice",
"number of ice layers",iice)
1626 CALL put_field(
"IR_soil",
"Soil IR flux",irs)
1627 CALL put_field(
"LMO",
"Monin-Obukhov Scale",lmo)
1628 CALL put_field(
"surf_water",
"Surficial water",rusn)
1629 CALL put_field(
"snow_buffer",
"Snow buffer layer",bufs)
1630 CALL put_field(
"alb_1",
"albedo sw",alb1)
1631 CALL put_field(
"alb_2",
"albedo nIR",alb2)
1632 CALL put_field(
"alb_3",
"albedo fIR",alb3)
1633 CALL put_field(
"to_ice",
"Snow passed to ice",toic)
1649 WRITE(str2,
'(i2.2)') isn
1651 "Age de la neige layer No."//str2, &
1654 print*,
"Trop de couches"
1660 WRITE(str2,
'(i2.2)') isn
1662 "Snow/ice thickness layer No."//str2, &
1665 print*,
"Trop de couches"
1671 WRITE(str2,
'(i2.2)') isn
1673 "Snow Property 2, layer No."//str2, &
1676 print*,
"Trop de couches"
1682 WRITE(str2,
'(i2.2)') isn
1684 "Snow Property 1, layer No."//str2, &
1687 print*,
"Trop de couches"
1693 WRITE(str2,
'(i2.2)') isn
1695 "Soil/snow water content layer No."//str2, &
1698 print*,
"Trop de couches"
1704 WRITE(str2,
'(i2.2)') isn
1706 "Snow density layer No."//str2, &
1709 print*,
"Trop de couches"
1715 WRITE(str2,
'(i2.2)') isn
1717 "Soil/snow temperature layer No."//str2, &
1720 print*,
"Trop de couches"
1726 WRITE(str2,
'(i2.2)') isn
1728 "Snow history layer No."//str2, &
1731 print*,
"Trop de couches"
real, dimension(:,:), allocatable, save t__mem
real, dimension(0:nsot, 0:nkhy) akdtsv
real, dimension(:), allocatable, save brossv
real, dimension(:), allocatable, save bcohsv
real, dimension(0:nvgt), parameter rbtdsv
integer, parameter nsnowmx
real, dimension(:), allocatable, save vvmmem
real, dimension(:), allocatable, save tvegsv
real, dimension(:), allocatable, save dsdtsv
real, dimension(:,:), allocatable, save dz1_sv
real, dimension(0:nsot) rocssv
real, dimension(:), allocatable, save ps__sv
real, dimension(:), allocatable, save p1l_sv
real, dimension(-nsol:0) dzavsv
real, dimension(-nsol:0) dz_8sv
real, dimension(:), allocatable, save exnrsv
real, dimension(0:nsot) etamsv
real, dimension(:), allocatable, save bufssv
integer, dimension(:,:), allocatable, save istosv
real, dimension(:), allocatable, save sol_sv
subroutine, public open_startphy(filename)
real, dimension(:,:), allocatable, save agsnsv
real, dimension(:,:), allocatable, save dzsnsv
real, dimension(:,:), allocatable, save rootsv
real, dimension(:), allocatable, save rsolsv
real, dimension(:), allocatable, save lai0sv
integer, dimension(:), allocatable, save isnosv
integer, dimension(:), allocatable, save isotsv
real, dimension(:), allocatable, save dsnbsv
real, dimension(:), allocatable, save bcoqsv
integer, parameter nsismx
real, dimension(:), allocatable, save sncasv
real, dimension(:), allocatable, save sws_sv
integer, dimension(:), allocatable, save iicesv
real, dimension(:,:), allocatable, save g1snsv
real, dimension(-nsol:0) dzmisv
real, dimension(:,:), allocatable, save tsissv
real, dimension(:), allocatable, save uts_sv
real, dimension(:), allocatable, save toicsv
real, dimension(:), allocatable, save tat_sv
subroutine get_soil_levels(dz1, dz2, lambda)
real, dimension(:), allocatable, save acoqsv
real, dimension(:,:), allocatable, save dz2_sv
real, dimension(-nsol:0) dzi_sv
real, dimension(:), allocatable, save zwecsv
real, dimension(:), allocatable, save psivsv
real, dimension(:), allocatable, save cld_sv
real, dimension(0:nsot, 0:nkhy) bkdtsv
!$Id itapm1 ENDIF!IM on interpole les champs sur les niveaux STD de pression!IM a chaque pas de temps de la physique c!positionnement de l argument logique a false c!pour ne pas recalculer deux fois la meme chose!c!a cet effet un appel a plevel_new a ete deplace c!a la fin de la serie d appels c!la boucle DO nlevSTD a ete internalisee c!dans d ou la creation de cette routine c c!CALL false
real, dimension(:), allocatable, save dds_sv
real, dimension(:), allocatable, save alb0sv
real, dimension(:), allocatable, save rusnsv
real, dimension(:), allocatable, save glf0sv
real, dimension(:), allocatable, save acohsv
real, dimension(:), allocatable, save bg2ssv
real, dimension(-nsol:0) dziisv
subroutine sisvat(SnoMod, BloMod, jjtime)
subroutine sisvatredem(fichnom, ikl2i, rlon, rlat)
real, dimension(:), allocatable, save z0h_sv
integer, dimension(:), allocatable, save iwafsv
integer, dimension(:), allocatable, save ivgtsv
real, dimension(0:nvgt,-nsol:0) rf__sv
real, dimension(-nsol:0) dz78sv
real, dimension(0:nsot), parameter ks_dsv
real, dimension(:), allocatable, save hss_sv
real, dimension(:), allocatable, save za__sv
real, dimension(:), allocatable, save vv__sv
real, dimension(:), allocatable, save tsf_sv
integer, dimension(:), allocatable, save ispisv
real, dimension(:), allocatable, save qsnosv
real, dimension(:), allocatable, save rht_sv
real, dimension(:), allocatable, save dtmmem
real, dimension(0:nsot) s2__sv
real, dimension(:), allocatable, save rnofsv
integer, dimension(-nsol:0) islmsv
real, dimension(:), allocatable, save ird_sv
real, dimension(0:nsot), parameter etadsv
real, dimension(-nsol:0) dz34sv
real, dimension(:), allocatable, save dbs_sv
!$Id itapm1 ENDIF!IM on interpole les champs sur les niveaux STD de pression!IM a chaque pas de temps de la physique c!positionnement de l argument logique a false c!pour ne pas recalculer deux fois la meme chose!c!a cet effet un appel a plevel_new a ete deplace c!a la fin de la serie d appels c!la boucle DO nlevSTD a ete internalisee c!dans d ou la creation de cette routine c c!CALL ulevSTD CALL &zphi philevSTD CALL &zx_rh rhlevSTD!DO klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon du jour ou toutes les read_climoz CALL true
real, dimension(0:nsot), parameter psidsv
real, dimension(:), allocatable, save drr_sv
real, dimension(:,:), allocatable, save ro__sv
real, dimension(:), allocatable, save irs_sv
real, dimension(:), allocatable, save lmo_sv
real, dimension(:), allocatable, save cdh_sv
real, dimension(:), allocatable, save z0m_sv
real, dimension(:), allocatable, save alb2sv
real, dimension(:), allocatable, save rrs_sv
integer, dimension(-nsol:0) islpsv
real, dimension(:), allocatable, save dsn_sv
subroutine sisvat_ini(knon)
real, dimension(-nsol:0) dtz_sv
integer, dimension(:), allocatable, save lsmask
real, dimension(0:nsot) s1__sv
real, dimension(:), allocatable, save uqs_sv
real, dimension(:), allocatable, save us__sv
real, dimension(:), allocatable, save uss_sv
real, dimension(:), allocatable, save slopsv
integer, parameter ntaver
integer, dimension(nsno) isnpsv
real, dimension(0:nsot), parameter bchdsv
logical, save is_mpi_root
real, dimension(-nsol:0) dz_dsv
real, dimension(:,:), allocatable, save eta_sv
real, dimension(:), allocatable, save qat_sv
real, dimension(:,:), allocatable, save zzsnsv
real, dimension(:), allocatable, save tsfnsv
real, dimension(:), allocatable, save rrcasv
real, dimension(:,:), allocatable, save v__mem
real, dimension(:), allocatable, save alb1sv
real, dimension(:), allocatable, save alb3sv
subroutine surf_sisvat(knon, rlon, rlat, ikl2i, itime, dtime, debut, lafin, rmu0, swdown, lwdown, pexner, ps, p1lay, precip_rain, precip_snow, precip_snow_adv, snow_adv, bl_height, wind_velo, temp_air, dens_air, spechum, tsurf, rugos, snow_cont_air, alb_soil, slope, cloudf, radsol, qsol, tsoil, snow, snowhgt, qsnow, to_ice, sissnow, agesno, AcoefH, AcoefQ, BcoefH, BcoefQ, cdragh, runoff_lic, evap, fluxsens, fluxlat, dflux_s, dflux_l, tsurf_new, alb1, alb2, alb3, emis_new, z0_new, qsurf)
real, dimension(:), allocatable, save coszsv
subroutine sisvatetat0(fichnom, ikl2i)
!$Id!Thermodynamical constants for t0 real clmci real epsi
!$Header!integer nvarmx s s unit
real, dimension(:), allocatable, save hls_sv
real, dimension(:), allocatable, save dldtsv
real, dimension(:), allocatable, save swf_sv
real, dimension(:,:), allocatable, save g2snsv
subroutine, public open_restartphy(filename)
real, dimension(:), allocatable, save esnbsv
real, dimension(:), allocatable, save vvs_sv
real, dimension(:), allocatable, save bg1ssv