10 USE ioipsl
, only: ju2ymds,
ymds2ju, ioconf_calendar
40 #include "dimensions.h"
52 #include "tsoilnudge.h"
53 #include "fcg_gcssold.h"
70 integer,
parameter :: ngrid=1
109 integer :: kmax =
llm
110 integer llm700,nq1,nq2
111 INTEGER,
PARAMETER :: nlev_max=1000, nqmx=1000
113 real height(nlev_max),tttprof(nlev_max),qtprof(nlev_max)
114 real uprof(nlev_max),vprof(nlev_max),e12prof(nlev_max)
115 real ugprof(nlev_max),vgprof(nlev_max),wfls(nlev_max)
116 real dqtdxls(nlev_max),dqtdyls(nlev_max)
117 real dqtdtls(nlev_max),thlpcar(nlev_max)
118 real qprof(nlev_max,nqmx)
121 logical :: forcing_les = .
false.
122 logical :: forcing_armcu = .
false.
123 logical :: forcing_rico = .
false.
124 logical :: forcing_radconv = .
false.
125 logical :: forcing_toga = .
false.
126 logical :: forcing_twpice = .
false.
127 logical :: forcing_amma = .
false.
128 logical :: forcing_dice = .
false.
129 logical :: forcing_GCM2SCM = .
false.
130 logical :: forcing_GCSSold = .
false.
131 logical :: forcing_sandu = .
false.
132 logical :: forcing_astex = .
false.
133 logical :: forcing_fire = .
false.
134 logical :: forcing_case = .
false.
135 integer :: type_ts_forcing
145 logical :: nudge_wind=.
true.
146 logical :: nudge_thermo=.
false.
147 logical :: cptadvw=.
true.
152 #include "1D_decl_cases.h"
158 parameter (nudge_max=9)
159 integer :: inudge_RHT=1
160 integer :: inudge_UV=2
161 logical :: nudge(nudge_max)
172 real :: playd(
llm),zlayd(
llm),ap_amma(
llm+1),bp_amma(
llm+1),poub
181 real :: rlat_rad(1),rlon_rad(1)
182 real :: omega(
llm+1),omega2(
llm),rho(
llm+1)
183 real :: ug(
llm),vg(
llm),fcoriolis
185 real :: du_phys(
llm),dv_phys(
llm),dt_phys(
llm)
187 real :: dt_cooling(
llm),d_th_adv(
llm),d_t_nudge(
llm)
188 real :: d_u_nudge(
llm),d_v_nudge(
llm)
189 real :: du_adv(
llm),dv_adv(
llm)
190 real :: du_age(
llm),dv_age(
llm)
194 REAL,
ALLOCATABLE,
DIMENSION(:,:):: q
195 REAL,
ALLOCATABLE,
DIMENSION(:,:):: dq
196 REAL,
ALLOCATABLE,
DIMENSION(:,:):: dq_dyn
197 REAL,
ALLOCATABLE,
DIMENSION(:,:):: d_q_adv
198 REAL,
ALLOCATABLE,
DIMENSION(:,:):: d_q_nudge
204 real :: run_off_lic_0(1)
205 real :: fder(1),snsrf(1,
nbsrf),qsurfsrf(1,
nbsrf)
206 real :: tsoil(1,nsoilmx,
nbsrf)
212 logical :: ok_writedem =.
true.
213 real :: sollw_in = 0.
214 real :: solsw_in = 0.
219 logical :: firstcall=.
true.
220 logical :: lastcall=.
false.
227 integer,
parameter :: yd = 360
228 real :: phy_nat (yd) = 0.0
231 real :: phy_bil (yd) = 1.0
233 real :: phy_ice (yd) = 0.0
234 real :: phy_fter(yd) = 0.0
235 real :: phy_foce(yd) = 0.0
236 real :: phy_fsic(yd) = 0.0
237 real :: phy_flic(yd) = 0.0
242 integer :: k,l,i,it=1,mxcalc
246 REAL dudyn(
iim+1,jjmp1,
llm)
249 integer ecrit_slab_oc
250 data ecrit_slab_oc/-1/
271 turb_fcg_gcssold=.
false.
281 turb_fcg_gcssold = xturb_fcg_gcssold
285 write(*,*)
'lmdz1d.def lu => unicol.def'
341 if (forcing_type .eq.0)
THEN
343 elseif (forcing_type .eq.1)
THEN
344 forcing_radconv = .
true.
345 elseif (forcing_type .eq.2)
THEN
346 forcing_toga = .
true.
347 elseif (forcing_type .eq.3)
THEN
348 forcing_gcm2scm = .
true.
349 elseif (forcing_type .eq.4)
THEN
350 forcing_twpice = .
true.
351 elseif (forcing_type .eq.5)
THEN
352 forcing_rico = .
true.
353 elseif (forcing_type .eq.6)
THEN
354 forcing_amma = .
true.
355 elseif (forcing_type .eq.7)
THEN
356 forcing_dice = .
true.
357 elseif (forcing_type .eq.101)
THEN
358 forcing_case = .
true.
364 elseif (forcing_type .eq.102)
THEN
365 forcing_case = .
true.
371 elseif (forcing_type .eq.40)
THEN
372 forcing_gcssold = .
true.
373 elseif (forcing_type .eq.50)
THEN
374 forcing_fire = .
true.
375 elseif (forcing_type .eq.59)
THEN
376 forcing_sandu = .
true.
377 elseif (forcing_type .eq.60)
THEN
378 forcing_astex = .
true.
379 elseif (forcing_type .eq.61)
THEN
380 forcing_armcu = .
true.
381 IF(
llm.NE.19.AND.
llm.NE.40) stop
'Erreur nombre de niveaux !!'
383 write (*,*)
'ERROR : unknown forcing_type ', forcing_type
384 stop
'Forcing_type should be 0,1,2,3,4,5,6 or 40,59,60,61'
386 print*,
"forcing type=",forcing_type
394 if (forcing_toga.or.forcing_sandu.or.forcing_astex .or. forcing_dice) &
395 & type_ts_forcing = 1
400 nudge(i) = mod(jcode,10) .ge. 1
413 if (calend ==
'earth_360d')
then
414 call ioconf_calendar(
'360d')
415 write(*,*)
'CALENDRIER CHOISI: Terrestre a 360 jours/an'
416 else if (calend ==
'earth_365d')
then
417 call ioconf_calendar(
'noleap')
418 write(*,*)
'CALENDRIER CHOISI: Terrestre a 365 jours/an'
419 else if (calend ==
'earth_366d')
then
420 call ioconf_calendar(
'all_leap')
421 write(*,*)
'CALENDRIER CHOISI: Terrestre bissextile'
422 else if (calend ==
'gregorian')
then
423 call ioconf_calendar(
'gregorian')
424 write(*,*)
'CALENDRIER CHOISI: Gregorien'
426 write (*,*)
'ERROR : unknown calendar ', calend
427 stop
'calend should be 360d,earth_365d,earth_366d,gregorian'
442 print *,
'fnday=',fnday
445 IF(forcing_type .EQ. 61) fnday=53100./86400.
447 IF(forcing_type .EQ. 6) fnday=64800./86400.
459 IF (forcing_type .eq.2)
THEN
464 ELSEIF (forcing_type .eq.4)
THEN
467 & (year_ini_twpi,mth_ini_twpi,day_ini_twpi,heure_ini_twpi &
469 ELSEIF (forcing_type .eq.6)
THEN
474 ELSEIF (forcing_type .eq.7)
THEN
479 ELSEIF (forcing_type .gt.100)
THEN
486 print*,
'time case 2',day_ini_cas,day_ju_ini_cas
487 ELSEIF (forcing_type .eq.59)
THEN
490 & (year_ini_sandu,mth_ini_sandu,day_ini_sandu, &
491 & time_ini*3600.,day_ju_ini_sandu)
493 ELSEIF (forcing_type .eq.60)
THEN
496 & (year_ini_astex,mth_ini_astex,day_ini_astex, &
497 & time_ini*3600.,day_ju_ini_astex)
499 ELSEIF (forcing_type .eq.61)
THEN
502 & (year_ini_armcu,mth_ini_armcu,day_ini_armcu,heure_ini_armcu &
506 daytime = day + time_ini/24.
508 call ju2ymds(daytime,year_print, month_print,day_print,sec_print)
509 print *,
' Time of beginning : ', &
510 & year_print, month_print, day_print, sec_print
521 if (
nqtot>nqmx) stop
'Augmenter nqmx dans lmdz1d.F'
542 if (ngrid.ne.
klon)
then
543 print*,
'stop in inifis'
544 print*,
'Probleme de dimensions :'
545 print*,
'ngrid = ',ngrid
546 print*,
'klon = ',
klon
560 qsurf = fq_sat(tsurf,psurf/100.)
566 rho(1)=psurf/(rd*tsurf*(1.+(rv/rd-1.)*qsurf))
571 IF(.NOT.
ok_flux_surf.or.max(abs(wtsurf),abs(wqsurf))>0.)
THEN
572 fsens=-wtsurf*rcpd*rho(1)
573 flat=-wqsurf*rlvtt*rho(1)
574 print *,
'Flux: ok_flux wtsurf wqsurf',
ok_flux_surf,wtsurf,wqsurf
576 print*,
'Flux sol ',fsens,
flat
587 IF (ok_old_disvert)
THEN
589 print *,
'On utilise disvert0'
592 print *,
'On utilise disvert'
599 play = 0.5*(plev(1:
llm)+plev(2:
llm+1))
600 zlay=-rd*300.*log(play/psurf)/
rg
602 IF (forcing_type .eq. 59)
THEN
604 write(*,*)
'***********************'
606 write(*,*)
'l,play(l),presnivs(l): ',l,play(l),
presnivs(l)
607 if (trouve_700 .and. play(l).le.70000)
then
609 print *,
'llm700,play=',llm700,play(l)/100.
613 write(*,*)
'***********************'
621 #include "1D_read_forc_cases.h"
623 if (forcing_gcm2scm)
then
624 write (*,*)
'forcing_GCM2SCM not yet implemented'
625 stop
'in initialization'
628 print*,
'mxcalc=',mxcalc
630 print*,
'play=',play(mxcalc)
650 write (*,*)
'Time step divided by nsplit_phys (=',
nsplit_phys,
')'
652 dtime_frcg = timestep
657 rlat_rad(1)=
rlat(1)*rpi/180.
658 rlon_rad(1)=
rlon(1)*rpi/180.
660 ! ehouarn:
iniphysiq requires arrays related to(3d) dynamics grid,
661 ! e.
g. for cell boundaries, which are meaningless in 1d; so pad these
662 ! with
'0.' when necessary
666 (/rlat_rad(1),0./),(/0./), &
667 (/0.,0./),(/rlon_rad(1),0./), &
668 (/ (/airefi,0./),(/0.,0./) /), &
669 (/zcufi,0.,0.,0./), &
672 print*,
'apres iniphysiq'
681 if (ok_writedem)
then
689 run_off_lic_0(1) = restart_runoff
718 print*,
'avant phyredem'
720 if (nat_surf.eq.0.)
then
728 print*,
'nat_surf,pctsrf(1,is_oce),pctsrf(1,is_ter)',nat_surf &
797 if (.not.restart)
then
801 print*,
'callin surf final'
803 print*,
'after surf final'
808 print*,
'apres phyredem'
821 phy_nat(i) = nat_surf
832 call writelim (1,phy_nat,phy_alb,phy_sst,phy_bil,phy_rug, &
833 & phy_ice,phy_fter,phy_foce,phy_flic,phy_fsic)
839 print*,
'call to restart dyn 1d'
840 Call dyn1deta0(
"start1dyn.nc",plev,play,phi,phis,
presnivs, &
843 print*,
'fnday,annee_ref,day_ref,day_ini', &
848 daytime = day + time_ini/24.
851 call ju2ymds(daytime, an, mois, jour, heure)
852 print *,
' Time of beginning : y m d h',an, mois,jour,heure/3600.
857 print*,
'****** intialised fields from restart1dyn *******'
858 print*,
'plev,play,phi,phis,presnivs,u,v,temp,q,omega2'
859 print*,
'temp(1),q(1,1),u(1),v(1),plev(1),phis :'
860 print*,temp(1),q(1,1),u(1),v(1),plev(1),phis
867 IF (ecrit_slab_oc.eq.1)
then
868 open(97,file=
'div_slab.dat',status=
'UNKNOWN')
869 elseif (ecrit_slab_oc.eq.0)
then
870 open(97,file=
'div_slab.dat',status=
'OLD')
876 if (nudge(inudge_rht))
then
877 call nudge_rht_init(plev,play,temp,q(:,1),t_targ,rh_targ)
879 if (nudge(inudge_uv))
then
880 call nudge_uv_init(plev,play,u,v,u_targ,v_targ)
887 do while(it.le.nint(fnday*
day_step))
890 print*,
'XXXXXXXXXXXXXXXXXXX ITAP,day,time=', &
892 print*,
'PAS DE TEMPS ',timestep
901 #include "1D_interp_cases.h"
903 if (forcing_gcm2scm)
then
904 write (*,*)
'forcing_GCM2SCM not yet implemented'
912 phi(1)=rd*temp(1)*(plev(1)-play(1))/(.5*(plev(1)+play(1)))
914 phi(l+1)=phi(l)+rd*(temp(l)+temp(l+1))* &
915 & (play(l)-play(l+1))/(play(l)+play(l+1))
922 print *,
' avant physiq : -------- day time ',day,time
923 write(*,*)
'firstcall,lastcall,phis', &
924 & firstcall,lastcall,phis
925 write(*,
'(a10,2a4,4a13)')
'BEFOR1 IT=',
'it',
'l', &
926 &
'presniv',
'plev',
'play',
'phi'
927 write(*,
'(a10,2i4,4f13.2)') (
'BEFOR1 IT= ',it,l, &
929 write(*,
'(a11,2a4,a11,6a8)')
'BEFOR2',
'it',
'l', &
930 &
'presniv',
'u',
'v',
'temp',
'q1',
'q2',
'omega2'
931 write(*,
'(a11,2i4,f11.2,5f8.2,e10.2)') (
'BEFOR2 IT= ',it,l, &
932 &
presnivs(l),u(l),v(l),temp(l),q(l,1),q(l,2),omega2(l),l=1,
llm)
940 firstcall,lastcall, day,time,timestep, &
942 u,v, rot, temp,q,omega2, &
943 du_phys,dv_phys,dt_phys,dq,dpsrf, &
951 write(*,
'(a11,2a4,4a13)')
'AFTER1 IT=',
'it',
'l', &
952 &
'presniv',
'plev',
'play',
'phi'
953 write(*,
'(a11,2i4,4f13.2)') (
'AFTER1 it= ',it,l, &
955 write(*,
'(a11,2a4,a11,6a8)')
'AFTER2',
'it',
'l', &
956 &
'presniv',
'u',
'v',
'temp',
'q1',
'q2',
'omega2'
957 write(*,
'(a11,2i4,f11.2,5f8.2,e10.2)') (
'AFTER2 it= ',it,l, &
958 &
presnivs(l),u(l),v(l),temp(l),q(l,1),q(l,2),omega2(l),l=1,
llm)
959 write(*,
'(a11,2a4,a11,5a8)')
'AFTER3',
'it',
'l', &
960 &
'presniv',
'du_phys',
'dv_phys',
'dt_phys',
'dq1',
'dq2'
961 write(*,
'(a11,2i4,f11.2,5f8.2)') (
'AFTER3 it= ',it,l, &
962 &
presnivs(l),86400*du_phys(l),86400*dv_phys(l), &
963 & 86400*dt_phys(l),86400*dq(l,1),dq(l,2),l=1,
llm)
964 write(*,*)
'dpsrf',dpsrf
970 fcoriolis=2.*sin(rpi*xlat/180.)*romega
971 if (forcing_radconv .or. forcing_fire)
then
979 if (forcing_toga .or. forcing_gcssold .or. forcing_twpice &
980 & .or.forcing_amma)
then
981 fcoriolis=0.0 ; ug=0. ; vg=0.
983 if(forcing_rico)
then
987 IF (
prt_level >= 1) print*,
'fcoriolis, xlat,mxcalc ', &
988 fcoriolis, xlat,mxcalc
990 du_age(1:mxcalc)=fcoriolis*(v(1:mxcalc)-vg(1:mxcalc))
991 dv_age(1:mxcalc)=-fcoriolis*(u(1:mxcalc)-ug(1:mxcalc))
997 sfdt = sin(0.5*fcoriolis*timestep)
998 cfdt = cos(0.5*fcoriolis*timestep)
1001 du_age(1:mxcalc)= -2.*sfdt/timestep* &
1002 & (sfdt*(u(1:mxcalc)-ug(1:mxcalc)) - &
1003 & cfdt*(v(1:mxcalc)-vg(1:mxcalc)) )
1006 dv_age(1:mxcalc)= -2.*sfdt/timestep* &
1007 & (cfdt*(u(1:mxcalc)-ug(1:mxcalc)) + &
1008 & sfdt*(v(1:mxcalc)-vg(1:mxcalc)) )
1018 if (nudge(inudge_rht))
then
1019 call nudge_rht(timestep,plev,play,t_targ,rh_targ,temp,q(:,1), &
1020 & d_t_nudge,d_q_nudge(:,1))
1022 if (nudge(inudge_uv))
then
1023 call nudge_uv(timestep,plev,play,u_targ,v_targ,u,v, &
1024 & d_u_nudge,d_v_nudge)
1039 if (forcing_sandu .OR. forcing_astex)
then
1040 #include "1D_nudge_sandu_astex.h"
1042 u(1:mxcalc)=u(1:mxcalc) + timestep*( &
1043 & du_phys(1:mxcalc) &
1044 & +du_age(1:mxcalc)+du_adv(1:mxcalc) &
1045 & +d_u_nudge(1:mxcalc) )
1046 v(1:mxcalc)=v(1:mxcalc) + timestep*( &
1047 & dv_phys(1:mxcalc) &
1048 & +dv_age(1:mxcalc)+dv_adv(1:mxcalc) &
1049 & +d_v_nudge(1:mxcalc) )
1050 q(1:mxcalc,:)=q(1:mxcalc,:)+timestep*( &
1052 & +d_q_adv(1:mxcalc,:) &
1053 & +d_q_nudge(1:mxcalc,:) )
1057 &
'physiq-> temp(1),dt_phys(1),d_th_adv(1),dt_cooling(1) ', &
1058 & temp(1),dt_phys(1),d_th_adv(1),dt_cooling(1)
1059 print* ,
'dv_phys=',dv_phys
1060 print* ,
'dv_age=',dv_age
1061 print* ,
'dv_adv=',dv_adv
1062 print* ,
'd_v_nudge=',d_v_nudge
1067 temp(1:mxcalc)=temp(1:mxcalc)+timestep*( &
1068 & dt_phys(1:mxcalc) &
1069 & +d_th_adv(1:mxcalc) &
1070 & +d_t_nudge(1:mxcalc) &
1071 & +dt_cooling(1:mxcalc))
1075 teta=temp*(pzero/play)**rkappa
1106 print*,
'Pas de temps final ',it
1107 call ju2ymds(daytime, an, mois, jour, heure)
1108 print*,
'a la date : a m j h',an, mois, jour ,heure/3600.
1119 time = time_ini/24.+
real(mod(it,
day_step))/day_step
1126 if (ecrit_slab_oc.ne.-1)
close(97)
1130 call dyn1dredem(
"restart1dyn.nc", &
1132 & u,v,temp,q,omega2)
1138 #include "1DUTILS.h"
real, dimension(:,:), allocatable, save q_ancien
real, dimension(:,:), allocatable, save w01
real, dimension(:,:), allocatable, save clwcon
subroutine iniphysiq(iim, jjm, nlayer, nbp, communicator, punjours, pdayref, ptimestep, rlatu, rlatv, rlonu, rlonv, aire, cu, cv, prad, pg, pr, pcpp, iflag_phys)
real, dimension(:,:), allocatable, save du_gwd_front
integer, parameter is_ter
real, dimension(:), allocatable, save f0
!$Id zjulian!correction pour l heure initiale!jyg!jyg CALL ymds2ju(annee_ref, 1, day_ref, hour, zjulian)!jyg CALL histbeg_phy("histrac"
logical nudge_tsoil integer isoil_nudge real tau_soil_nudge common tsoilnudge nudge_tsoil
real, dimension(:), allocatable, save zval
real, dimension(:), allocatable, save zsig
logical nudge_tsoil integer isoil_nudge real tau_soil_nudge common tsoilnudge isoil_nudge
real, dimension(:), allocatable, save snow_fall
real, dimension(:,:,:), allocatable, save falb_dir
real, dimension(:,:), allocatable, save wake_deltaq
!$Id mode_top_bound COMMON comconstr g
real, dimension(:), allocatable, save rain_fall
real, dimension(:,:), allocatable, save sig1
real, dimension(:,:), allocatable, save t_ancien
subroutine fonte_neige_init(restart_runoff)
real, dimension(:), allocatable, save zmea
subroutine phyredem(fichnom)
real, dimension(:,:), allocatable, save pctsrf
subroutine abort_gcm(modname, message, ierr)
!$Id Turb_fcg_gcssold get_uvd hqturb_gcssold endif!large scale llm day day1 day day1 *dt_toga endif!time annee_ref dt_toga u_toga vq_toga w_prof vq_prof llm day day1 day day1 *dt_dice endif!time annee_ref dt_dice swup_dice vg_dice omega_dice tg_prof vg_profd w_profd omega_profd!do llm!print llm l llm
real, dimension(:), allocatable, save radsol
real, dimension(:,:), allocatable, save entr_therm
integer::year_ini_cas!initial year of the case integer::mth_ini_cas!initial month of the case integer::day_deb!initial day of the case real::heure_ini_cas!start time of the case real::pdt_cas!forcing_frequency real::day_ju_ini_cas!julian day of initial day of the case common date_cas year_ini_cas
subroutine fonte_neige_final(restart_runoff)
real, dimension(:,:,:), allocatable, save ftsoil
real, dimension(:), allocatable, save qsol
real, dimension(:,:,:), allocatable, save pbl_tke
real, dimension(:), allocatable, save sollw
real, dimension(:,:), allocatable, save rnebcon
real, dimension(:), allocatable, save sollwdown
real, dimension(:), allocatable, save wake_s
real, dimension(:), allocatable, save ale_bl
real, dimension(:), allocatable, save wake_cstar
integer::year_ini_cas!initial year of the case integer::mth_ini_cas!initial month of the case integer::day_deb!initial day of the case real::heure_ini_cas!start time of the case real::pdt_cas!forcing_frequency real::day_ju_ini_cas!julian day of initial day of the case common date_cas day_deb
!$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
subroutine init_dimphy(klon0, klev0)
real, dimension(:,:), allocatable, save delta_tsurf
real, dimension(:,:,:), allocatable, save wake_delta_pbl_tke
real, dimension(:), allocatable, save alp_bl
real, dimension(:,:), allocatable, save z0m
real, dimension(:), allocatable, save zmasq
!$Id Turb_fcg_gcssold get_uvd hqturb_gcssold endif!large scale llm day day1 day day1 *dt_toga endif!time annee_ref day_ju_ini_toga
subroutine physiq(nlon, nlev, debut, lafin, jD_cur, jH_cur, pdtphys, paprs, pplay, pphi, pphis, presnivs, u, v, rot, t, qx, flxmass_w, d_u, d_v, d_t, d_qx, d_ps, dudyn)
real, dimension(:), allocatable, save rugoro
integer, parameter is_lic
real, dimension(:), allocatable, save zpic
!Declarations specifiques au cas Toga character *::fich_toga!integer nlev_prof nt_toga day_ini_toga
subroutine writelim(klon, phy_nat, phy_alb, phy_sst, phy_bil, phy_rug, phy_ice, phy_fter, phy_foce, phy_flic, phy_fsic)
real, dimension(:), allocatable, save rlon
!$Id ok_orolf LOGICAL ok_limitvrai LOGICAL ok_all_xml INTEGER iflag_ener_conserv REAL co2_ppm
real, dimension(:,:), allocatable, save fm_therm
real, dimension(:), allocatable, save solsw
real, dimension(:), allocatable, save zgam
!FH On elimine toutes les clefs physiques dans la dynamique prt_level
!$Id Turb_fcg_gcssold get_uvd hqturb_gcssold endif!large scale llm day day1 day day1 *dt_toga endif!time annee_ref year_ini_toga
!$Header!integer nvarmx parameter(nfmx=10, imx=200, jmx=150, lmx=200, nvarmx=1000) real xd(imx
real, dimension(:), allocatable, save wake_fip
subroutine conf_gcm(tapedef, etatinit)
!$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
!$Id Turb_fcg_gcssold get_uvd hqturb_gcssold endif!large scale llm day day1 day day1 *dt_toga endif!time annee_ref dt_toga ts_toga
character(len=6), save type_ocean
real, dimension(:,:,:), allocatable, save falb_dif
real, dimension(:), allocatable, save rlat
subroutine phys_state_var_end
!$Id Turb_fcg_gcssold get_uvd hqturb_gcssold endif!large scale llm day day1 day day1 *dt_toga endif!time annee_ref dt_toga u_toga vq_toga w_prof vq_prof llm day day1 day day1 *dt_dice endif!time annee_ref year_ini_dice
real, dimension(:,:), allocatable, save du_gwd_rando
real, dimension(:), allocatable, save wake_pe
integer, save nsplit_phys
c c zjulian c cym CALL iim cym klev iim
real, dimension(:,:), allocatable, save agesno
subroutine phys_state_var_init()
real, dimension(:,:), allocatable, save ratqs
real, dimension(:), allocatable, save ale_bl_trig
real, dimension(:), allocatable, save zstd
subroutine pbl_surface_init(fder_rst, snow_rst, qsurf_rst, ftsoil_rst)
subroutine pbl_surface_final(fder_rst, snow_rst, qsurf_rst, ftsoil_rst)
integer, parameter is_sic
real, dimension(:,:), allocatable, save fevap
real, dimension(:), allocatable, save zmax0
nrlmd
integer::year_ini_cas!initial year of the case integer::mth_ini_cas!initial month of the case integer::day_deb!initial day of the case real::heure_ini_cas!start time of the case real::pdt_cas!forcing_frequency real::day_ju_ini_cas!julian day of initial day of the case common date_cas pdt_cas
real, dimension(:,:), allocatable, save z0h
real, dimension(:,:), allocatable, save ftsol
real, dimension(:,:), allocatable, save u_ancien
real, dimension(:), allocatable, save zthe
integer, parameter is_oce
real, dimension(:,:), allocatable, save detr_therm
real, dimension(:,:), allocatable, save v_ancien
!$Id Turb_fcg_gcssold get_uvd hqturb_gcssold endif!large scale llm day day1 day day1 *dt_toga endif!time annee_ref dt_toga u_toga vq_toga w_prof vq_prof llm day day1 day day1 *dt_dice endif!time annee_ref day_ju_ini_dice
integer::year_ini_cas!initial year of the case integer::mth_ini_cas!initial month of the case integer::day_deb!initial day of the case real::heure_ini_cas!start time of the case real::pdt_cas!forcing_frequency real::day_ju_ini_cas!julian day of initial day of the case common date_cas mth_ini_cas
integer::year_ini_cas!initial year of the case integer::mth_ini_cas!initial month of the case integer::day_deb!initial day of the case real::heure_ini_cas!start time of the case real::pdt_cas!forcing_frequency real::day_ju_ini_cas!julian day of initial day of the case common date_cas heure_ini_cas
real, dimension(:,:), allocatable, save wake_deltat