Changeset 3780 for LMDZ6/trunk/libf/phylmd/dyn1d
- Timestamp:
- Oct 22, 2020, 2:50:18 PM (4 years ago)
- Location:
- LMDZ6/trunk/libf/phylmd/dyn1d
- Files:
-
- 10 edited
Legend:
- Unmodified
- Added
- Removed
-
LMDZ6/trunk/libf/phylmd/dyn1d/1DUTILS.h
r3686 r3780 233 233 CALL getin('ok_flux_surf',ok_flux_surf) 234 234 235 !Config Key = ok_forc_tsurf 236 !Config Desc = forcage ou non par la Ts 237 !Config Def = false 238 !Config Help = forcage ou non par la Ts 239 ok_forc_tsurf=.false. 240 CALL getin('ok_forc_tsurf',ok_forc_tsurf) 241 235 242 !Config Key = ok_prescr_ust 236 243 !Config Desc = ustar impose ou non … … 239 246 ok_prescr_ust = .false. 240 247 CALL getin('ok_prescr_ust',ok_prescr_ust) 248 249 250 !Config Key = ok_prescr_beta 251 !Config Desc = betaevap impose ou non 252 !Config Def = false 253 !Config Help = betaevap impose ou non 254 ok_prescr_beta = .false. 255 CALL getin('ok_prescr_beta',ok_prescr_beta) 241 256 242 257 !Config Key = ok_old_disvert … … 280 295 !Config Desc = surface temperature 281 296 !Config Def = 290. 282 !Config Help = not used if type_ts_forcing=1 in lmdz1d.F297 !Config Help = surface temperature 283 298 tsurf = 290. 284 299 CALL getin('tsurf',tsurf) … … 297 312 zsurf = 0. 298 313 CALL getin('zsurf',zsurf) 314 ! EV pour accord avec format standard 315 CALL getin('zorog',zsurf) 316 299 317 300 318 !Config Key = rugos … … 359 377 qsolinp = 1. 360 378 CALL getin('qsolinp',qsolinp) 379 380 381 382 !Config Key = betaevap 383 !Config Desc = beta for actual evaporation when prescribed 384 !Config Def = 1.0 385 !Config Help = 386 betaevap = 1. 387 CALL getin('betaevap',betaevap) 361 388 362 389 !Config Key = zpicinp … … 520 547 CALL getin('forc_ustar',forc_ustar) 521 548 IF (forc_ustar .EQ. 1) ok_prescr_ust=.true. 549 522 550 523 551 !Config Key = nudging_u … … 1248 1276 END 1249 1277 1250 ! ======================================================================1251 SUBROUTINE read_tsurf1d(knon,sst_out)1252 1253 ! This subroutine specifies the surface temperature to be used in 1D simulations1254 1255 USE dimphy, ONLY : klon1256 1257 INTEGER, INTENT(IN) :: knon ! nomber of points on compressed grid1258 REAL, DIMENSION(klon), INTENT(OUT) :: sst_out ! tsurf used to force the single-column model1259 1260 INTEGER :: i1261 ! COMMON defined in lmdz1d.F:1262 real ts_cur1263 common /sst_forcing/ts_cur1264 1265 DO i = 1, knon1266 sst_out(i) = ts_cur1267 ENDDO1268 1269 END SUBROUTINE read_tsurf1d1270 1278 !!====================================================================== 1279 ! SUBROUTINE read_tsurf1d(knon,sst_out) 1280 ! 1281 !! This subroutine specifies the surface temperature to be used in 1D simulations 1282 ! 1283 ! USE dimphy, ONLY : klon 1284 ! 1285 ! INTEGER, INTENT(IN) :: knon ! nomber of points on compressed grid 1286 ! REAL, DIMENSION(klon), INTENT(OUT) :: sst_out ! tsurf used to force the single-column model 1287 ! 1288 ! INTEGER :: i 1289 !! COMMON defined in lmdz1d.F: 1290 ! real ts_cur 1291 ! common /sst_forcing/ts_cur 1292 1293 ! DO i = 1, knon 1294 ! sst_out(i) = ts_cur 1295 ! ENDDO 1296 ! 1297 ! END SUBROUTINE read_tsurf1d 1298 ! 1271 1299 !=============================================================== 1272 1300 subroutine advect_vert(llm,w,dt,q,plev) -
LMDZ6/trunk/libf/phylmd/dyn1d/1D_decl_cases.h
r3686 r3780 34 34 real w_mod(llm), t_mod(llm),q_mod(llm) 35 35 real u_mod(llm),v_mod(llm), ht_mod(llm),vt_mod(llm),ug_mod(llm),vg_mod(llm) 36 real temp_nudg_mod(llm),qv_nudg_mod(llm),u_nudg_mod(llm),v_nudg_mod(llm)36 real temp_nudg_mod(llm),qv_nudg_mod(llm),u_nudg_mod(llm),v_nudg_mod(llm) 37 37 real hq_mod(llm),vq_mod(llm),qv_mod(llm),ql_mod(llm),qt_mod(llm) 38 38 real th_mod(llm) 39 39 40 real ts_cur 41 common /sst_forcing/ts_cur ! also in read_tsurf1d.F 40 ! EV comment these lines 41 ! real ts_cur 42 ! common /sst_forcing/ts_cur ! also in read_tsurf1d.F 42 43 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 43 44 ! Declarations specifiques au cas RICO -
LMDZ6/trunk/libf/phylmd/dyn1d/1D_interp_cases.h
r3686 r3780 1 1 2 2 print*,'FORCING CASE forcing_case2' 3 3 ! print*, & 4 4 ! & '#### ITAP,day,day1,(day-day1)*86400,(day-day1)*86400/pdt_cas=', & … … 28 28 & ,dth_prof_cas,hth_prof_cas,vth_prof_cas,lat_prof_cas & 29 29 & ,sens_prof_cas,ustar_prof_cas,uw_prof_cas,vw_prof_cas,q1_prof_cas,q2_prof_cas,tke_prof_cas) 30 31 t s_cur= ts_prof_cas30 ! EV tg instead of ts_cur 31 tg = ts_prof_cas 32 32 ! psurf=plev_prof_cas(1) 33 33 psurf=ps_prof_cas -
LMDZ6/trunk/libf/phylmd/dyn1d/1D_read_forc_cases.h
r3686 r3780 70 70 71 71 ! initial and boundary conditions : 72 ! 72 ! tsurf = ts_prof_cas 73 73 psurf = ps_prof_cas 74 ts_cur = ts_prof_cas 74 !EV tg instead of ts_cur 75 tg = ts_prof_cas 76 print*, 'tg=', tg 77 75 78 do l = 1, llm 76 79 temp(l) = t_mod_cas(l) … … 108 111 IF (ok_prescr_ust) THEN 109 112 ust=ustar_prof_cas 110 print *,'ust=',ust111 113 ENDIF 112 114 115 113 116 endif !forcing_SCM -
LMDZ6/trunk/libf/phylmd/dyn1d/mod_1D_cases_read_std.F90
r3688 r3780 92 92 REAL, ALLOCATABLE :: time_val(:) 93 93 94 print*,'ON EST VRAIMENT LA'94 print*,'ON EST VRAIMENT DASN MOD_1D_CASES_READ_STD' 95 95 fich_cas='cas.nc' 96 96 print*,'fich_cas ',fich_cas … … 924 924 ! enddo 925 925 926 ! print*, 'plev_prof_cas', plev_prof_cas 927 ! print*, 'play', play 926 928 do l = 1, llm 927 929 … … 951 953 952 954 frac = (plev_prof_cas(k2)-play(l))/(plev_prof_cas(k2)-plev_prof_cas(k1)) 955 953 956 t_mod_cas(l)= t_prof_cas(k2) - frac*(t_prof_cas(k2)-t_prof_cas(k1)) 954 957 theta_mod_cas(l)= th_prof_cas(k2) - frac*(th_prof_cas(k2)-th_prof_cas(k1)) … … 1075 1078 enddo ! l 1076 1079 1080 1077 1081 return 1078 1082 end SUBROUTINE interp2_case_vertical_std -
LMDZ6/trunk/libf/phylmd/dyn1d/old_1D_decl_cases.h
r3593 r3780 37 37 real th_mod(llm) 38 38 39 real ts_cur40 common /sst_forcing/ts_cur ! also in read_tsurf1d.F39 !real ts_cur 40 !common /sst_forcing/ts_cur ! also in read_tsurf1d.F 41 41 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 42 42 ! Declarations specifiques au cas RICO -
LMDZ6/trunk/libf/phylmd/dyn1d/old_1D_interp_cases.h
r3593 r3780 62 62 & ,ts_prof,plev_prof,t_prof,q_prof,u_prof,v_prof,w_prof & 63 63 & ,ht_prof,vt_prof,hq_prof,vq_prof) 64 65 if (type_ts_forcing.eq.1) t s_cur = ts_prof ! SST used in read_tsurf1d64 ! EV: tg instead of ts_cur 65 if (type_ts_forcing.eq.1) tg = ts_prof ! 66 66 67 67 ! vertical interpolation: … … 113 113 ! print *,'llm l omega_profd',llm,l,omega_profd(l) 114 114 ! enddo 115 116 if (type_ts_forcing.eq.1) t s_cur = tg_prof ! SST used in read_tsurf1d115 ! EV tg instead of ts_cur 116 if (type_ts_forcing.eq.1) tg = tg_prof ! SST used 117 117 118 118 ! vertical interpolation: … … 206 206 & ,ug_gabls4,vg_gabls4,ht_gabls4,hq_gabls4,tg_gabls4 & 207 207 & ,ug_profg,vg_profg,ht_profg,hq_profg,tg_profg) 208 209 if (type_ts_forcing.eq.1) t s_cur = tg_prof ! SST used in read_tsurf1d208 !EV tg instead of ts_cur 209 if (type_ts_forcing.eq.1) tg = tg_prof ! SST used 210 210 211 211 ! vertical interpolation: … … 499 499 & ,nlev_sandu & 500 500 & ,ts_sandu,ts_prof) 501 502 if (type_ts_forcing.eq.1) t s_cur= ts_prof ! SST used in read_tsurf1d501 ! EV tg instead of ts_cur 502 if (type_ts_forcing.eq.1) tg = ts_prof ! SST used in read_tsurf1d 503 503 504 504 ! vertical interpolation: … … 582 582 & ,ufa_astex,vfa_astex,div_prof,ts_prof,ug_prof,vg_prof & 583 583 & ,ufa_prof,vfa_prof) 584 585 if (type_ts_forcing.eq.1) ts_cur = ts_prof ! SST used in read_tsurf1d 586 584 ! EV tg instead of ts_cur 585 if (type_ts_forcing.eq.1) tg = ts_prof ! SST used 587 586 ! vertical interpolation: 588 587 CALL interp_astex_vertical(play,nlev_astex,plev_profa & … … 675 674 & ,dtrad_prof_cas,dq_prof_cas,hq_prof_cas,vq_prof_cas,lat_prof_cas & 676 675 & ,sens_prof_cas,ustar_prof_cas,uw_prof_cas,vw_prof_cas,q1_prof_cas,q2_prof_cas) 677 678 ts_cur = ts_prof_cas 676 ! EV tg instead of ts_cur 677 678 tg = ts_prof_cas 679 679 psurf=plev_prof_cas(1) 680 680 … … 850 850 & ,dth_prof_cas,hth_prof_cas,vth_prof_cas,lat_prof_cas & 851 851 & ,sens_prof_cas,ustar_prof_cas,uw_prof_cas,vw_prof_cas,q1_prof_cas,q2_prof_cas,tke_prof_cas) 852 853 ts_cur = ts_prof_cas 852 ! EV tg instead of ts_cur 853 854 tg = ts_prof_cas 854 855 ! psurf=plev_prof_cas(1) 855 856 psurf=ps_prof_cas -
LMDZ6/trunk/libf/phylmd/dyn1d/old_1D_read_forc_cases.h
r3679 r3780 875 875 876 876 ! initial and boundary conditions : 877 ! tsurf = ts_prof_cas 878 ts_cur = ts_prof_cas 877 ! tsurf = ts_prof_cas 878 ! EV tg instead of ts_cur 879 tg= ts_prof_cas 879 880 psurf=plev_prof_cas(1) 880 881 write(*,*) 'SST initiale: ',tsurf … … 965 966 ! initial and boundary conditions : 966 967 ! tsurf = ts_prof_cas 967 ts_cur = ts_prof_cas 968 ! EV tg instead of ts_cur 969 tg = ts_prof_cas 968 970 psurf=plev_prof_cas(1) 969 971 write(*,*) 'SST initiale: ',tsurf … … 1063 1065 ! initial and boundary conditions : 1064 1066 ! tsurf = ts_prof_cas 1065 ts_cur = ts_prof_cas 1067 ! EV tg instead of ts_cur 1068 1069 tg = ts_prof_cas 1066 1070 psurf=plev_prof_cas(1) 1067 1071 write(*,*) 'SST initiale: ',tsurf -
LMDZ6/trunk/libf/phylmd/dyn1d/old_lmdz1d.F90
r3594 r3780 728 728 729 729 !Al1 pour SST forced, appell?? depuis ocean_forced_noice 730 ts_cur = tsurf ! SST used in read_tsurf1d 730 ! EV tg instead of ts_cur 731 732 tg = tsurf ! SST used in read_tsurf1d 731 733 !===================================================================== 732 734 ! Initialisation de la physique : … … 791 793 792 794 fder=0. 795 print *, 'snsrf', snsrf 793 796 snsrf(1,:)=snowmass ! masse de neige des sous surface 794 797 qsurfsrf(1,:)=qsurf ! humidite de l'air des sous surface … … 841 844 end if 842 845 843 844 846 print*,'nat_surf,pctsrf(1,is_oce),pctsrf(1,is_ter)',nat_surf & 845 847 & ,pctsrf(1,is_oce),pctsrf(1,is_ter) … … 851 853 ! 6 albedo, mais on peut quand meme tourner avec 852 854 ! moins. Seules les 2 ou 4 premiers seront lus 855 print*, 'les albedos sont sont', albedo, falb_dir 853 856 falb_dir=albedo 854 857 falb_dif=albedo 858 print*, falb_dir 855 859 rugoro=rugos 856 860 t_ancien(1,:)=temp(:) … … 913 917 v_ancien(1,:)=v(:) 914 918 915 u10m=0.916 v10m=0.917 ale_wake=0.918 ale_bl_stat=0.919 u10m=0. 920 v10m=0. 921 ale_wake=0. 922 ale_bl_stat=0. 919 923 920 924 !------------------------------------------------------------------------ -
LMDZ6/trunk/libf/phylmd/dyn1d/scm.F90
r3693 r3780 75 75 real :: zcufi = 1. 76 76 real :: zcvfi = 1. 77 78 !- real :: nat_surf79 !- logical :: ok_flux_surf80 !- real :: fsens81 !- real :: flat82 !- real :: tsurf83 !- real :: rugos84 !- real :: qsol(1:2)85 !- real :: qsurf86 !- real :: psurf87 !- real :: zsurf88 !- real :: albedo89 !-90 !- real :: time = 0.91 !- real :: time_ini92 !- real :: xlat93 !- real :: xlon94 !- real :: wtsurf95 !- real :: wqsurf96 !- real :: restart_runoff97 !- real :: xagesno98 !- real :: qsolinp99 !- real :: zpicinp100 !-101 77 real :: fnday 102 78 real :: day, daytime … … 141 117 logical :: forcing_case2 = .false. 142 118 logical :: forcing_SCM = .false. 143 integer :: type_ts_forcing ! 0 = SST constant; 1 = SST read from a file144 ! (cf read_tsurf1d.F)145 119 146 120 !flag forcings … … 148 122 logical :: nudge_thermo=.false. 149 123 logical :: cptadvw=.true. 124 125 150 126 !===================================================================== 151 127 ! DECLARATIONS FOR EACH CASE … … 248 224 ! 249 225 integer :: it_end ! iteration number of the last call 250 !Al1 226 !Al1,plev,play,phi,phis,presnivs, 251 227 integer ecrit_slab_oc !1=ecrit,-1=lit,0=no file 252 228 data ecrit_slab_oc/-1/ … … 278 254 d_v_age(:)=0. 279 255 256 280 257 ! Initialization of Common turb_forcing 281 258 dtime_frcg = 0. … … 290 267 ! OPTIONS OF THE 1D SIMULATION (lmdz1d.def => unicol.def) 291 268 !--------------------------------------------------------------------- 292 !Al1293 269 call conf_unicol 294 270 !Al1 moves this gcssold var from common fcg_gcssold to … … 296 272 ! -------------------------------------------------------------------- 297 273 close(1) 298 !Al1299 274 write(*,*) 'lmdz1d.def lu => unicol.def' 300 275 … … 302 277 year_ini_cas=1997 303 278 ! It is possible that those parameters are run twice. 304 305 279 ! A REVOIR : LIRE PEUT ETRE AN MOIS JOUR DIRECETEMENT 280 281 306 282 call getin('anneeref',year_ini_cas) 307 283 call getin('dayref',day_deb) … … 309 285 call getin('time_ini',heure_ini_cas) 310 286 311 type_ts_forcing = 0 312 IF (nat_surf==0) type_ts_forcing=1 ! SST forcee sur OCEAN 313 print*,'NATURE DE LA SURFACE ',nat_surf 287 print*,'NATURE DE LA SURFACE ',nat_surf 314 288 ! 315 289 ! Initialization of the logical switch for nudging 290 316 291 jcode = iflag_nudge 317 292 do i = 1,nudge_max … … 319 294 jcode = jcode/10 320 295 enddo 321 !--------------------------------------------------------------------- 296 !----------------------------------------------------------------------- 322 297 ! Definition of the run 323 !--------------------------------------------------------------------- 298 !----------------------------------------------------------------------- 324 299 325 300 call conf_gcm( 99, .TRUE. ) … … 343 318 allocate( phy_flic(year_len)) ! Fraction de glace 344 319 phy_flic(:)=0.0 320 321 345 322 !----------------------------------------------------------------------- 346 323 ! Choix du calendrier … … 373 350 ! Le numero du jour est dans "day". L heure est traitee separement. 374 351 ! La date complete est dans "daytime" (l'unite est le jour). 352 353 375 354 if (nday>0) then 376 355 fnday=nday … … 409 388 ! Initialization of dimensions, geometry and initial state 410 389 !--------------------------------------------------------------------- 411 ! 390 ! call init_phys_lmdz(1,1,llm,1,(/1/)) ! job now done via iniphysiq 412 391 ! but we still need to initialize dimphy module (klon,klev,etc.) here. 413 392 call init_dimphy1D(1,llm) … … 446 425 !!! Feedback forcing values for Gateaux differentiation (al1) 447 426 !!!===================================================================== 448 !!! Surface Planck forcing bracketing call radiation449 !! surf_Planck = 0.450 !! surf_Conv = 0.451 !! write(*,*) 'Gateaux-dif Planck,Conv:',surf_Planck,surf_Conv452 !!! a mettre dans le lmdz1d.def ou autre453 !!454 427 !! 455 428 qsol = qsolinp … … 469 442 ENDIF 470 443 print*,'Flux sol ',fsens,flat 471 !! ok_flux_surf=.false.472 !! fsens=-wtsurf*rcpd*rho(1)473 !! flat=-wqsurf*rlvtt*rho(1)474 !!!!475 444 476 445 ! Vertical discretization and pressure levels at half and mid levels: … … 496 465 plev =ap+bp*psurf 497 466 play = 0.5*(plev(1:llm)+plev(2:llm+1)) 498 zlay=-rd*300.*log(play/psurf)/rg ! moved after reading profiles 467 zlay=-rd*300.*log(play/psurf)/rg ! moved after reading profiles. 499 468 500 469 IF (forcing_type .eq. 59) THEN … … 527 496 print*,'mxcalc=',mxcalc 528 497 ! print*,'zlay=',zlay(mxcalc) 529 print*,'play=',play(mxcalc) 530 531 !Al1 pour SST forced, appell?? depuis ocean_forced_noice 532 ts_cur = tsurf ! SST used in read_tsurf1d 498 ! print*,'play=',play(mxcalc) 499 500 !! When surface temperature is forced 501 tg= tsurf ! surface T used in read_tsurf1d 502 503 533 504 !===================================================================== 534 505 ! Initialisation de la physique : … … 546 517 ! airefi,zcufi,zcvfi initialises au debut de ce programme 547 518 ! rday,ra,rg,rd,rcpd declares dans YOMCST.h et calcules dans suphel.F 519 520 548 521 day_step = float(nsplit_phys)*day_step/float(iphysiq) 549 522 write (*,*) 'Time step divided by nsplit_phys (=',nsplit_phys,')' … … 563 536 ! e.g. for cell boundaries, which are meaningless in 1D; so pad these 564 537 ! with '0.' when necessary 538 565 539 call iniphysiq(iim,jjm,llm, & 566 540 1,comm_lmdz, & … … 653 627 ! 6 albedo, mais on peut quand meme tourner avec 654 628 ! moins. Seules les 2 ou 4 premiers seront lus 629 print*, 'les albedos sont', albedo 655 630 falb_dir=albedo 656 631 falb_dif=albedo … … 664 639 prw_ancien = 0. 665 640 !jyg< 666 !! 641 !! pbl_tke(:,:,:)=1.e-8 667 642 pbl_tke(:,:,:)=0. 668 pbl_tke(:,2,:)=1.e-2 643 ! EV: pourquoi???? 644 ! pbl_tke(:,2,:)=1.e-2 669 645 PRINT *, ' pbl_tke dans lmdz1d ' 670 646 if (prt_level .ge. 5) then … … 675 651 676 652 !>jyg 677 678 653 rain_fall=0. 679 654 snow_fall=0. … … 715 690 v_ancien(1,:)=v(:) 716 691 717 u10m=0.718 v10m=0.719 ale_wake=0.720 ale_bl_stat=0.692 u10m=0. 693 v10m=0. 694 ale_wake=0. 695 ale_bl_stat=0. 721 696 722 697 !------------------------------------------------------------------------ … … 738 713 ! to be set at some arbitratry convenient values. 739 714 !------------------------------------------------------------------------ 740 !Al1 =============== restart option ========================== 715 !Al1 =============== restart option ====================================== 741 716 if (.not.restart) then 742 717 iflag_pbl = 5 … … 803 778 print*,'plev,play,phi,phis,presnivs,u,v,temp,q,omega2' 804 779 print*,'temp(1),q(1,1),u(1),v(1),plev(1),phis :' 805 print*,temp(1),q(1,1),u(1),v(1),plev(1),phis 780 print*,temp(1),q(1,1),u(1),v(1),plev(1),phis(1) 806 781 ! raz for safety 807 782 do l=1,llm … … 809 784 enddo 810 785 endif 811 ! Al1================ end restart =================================786 !====================== end restart ================================= 812 787 IF (ecrit_slab_oc.eq.1) then 813 788 open(97,file='div_slab.dat',STATUS='UNKNOWN') … … 820 795 CALL iophys_ini 821 796 #endif 797 798 !===================================================================== 822 799 ! START OF THE TEMPORAL LOOP : 823 800 !===================================================================== 824 801 825 802 it_end = nint(fnday*day_step) 826 !test JLD it_end = 10827 803 do while(it.le.it_end) 828 804 … … 832 808 print*,'PAS DE TEMPS ',timestep 833 809 endif 834 !Al1 demande de restartphy.nc835 810 if (it.eq.it_end) lastcall=.True. 836 811 … … 844 819 ! Geopotential : 845 820 !--------------------------------------------------------------------- 846 821 ! phis(1)=zsurf*RG 822 ! phi(1)=phis(1)+RD*temp(1)*(plev(1)-play(1))/(.5*(plev(1)+play(1))) 847 823 phi(1)=RD*temp(1)*(plev(1)-play(1))/(.5*(plev(1)+play(1))) 824 848 825 do l = 1, llm-1 849 826 phi(l+1)=phi(l)+RD*(temp(l)+temp(l+1))* & 850 827 & (play(l)-play(l+1))/(play(l)+play(l+1)) 851 828 enddo 829 852 830 853 831 !--------------------------------------------------------------------- … … 950 928 sfdt = sin(0.5*fcoriolis*timestep) 951 929 cfdt = cos(0.5*fcoriolis*timestep) 952 ! print *,'fcoriolis,sfdt,cfdt,timestep',fcoriolis,sfdt,cfdt,timestep 953 ! 930 954 931 d_u_age(1:mxcalc)= -2.*sfdt/timestep* & 955 932 & (sfdt*(u(1:mxcalc)-ug(1:mxcalc)) - & … … 1030 1007 temp(1:mxcalc)=temp(1:mxcalc)+timestep*( & 1031 1008 & dt_phys(1:mxcalc) & 1032 & +d_t_adv(1:mxcalc) &1033 & +d_t_nudge(1:mxcalc) 1009 & +d_t_adv(1:mxcalc) & 1010 & +d_t_nudge(1:mxcalc) & 1034 1011 & +dt_cooling(1:mxcalc)) ! Taux de chauffage ou refroid. 1035 1012 1036 1013 1037 ! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!1014 !======================================================================= 1038 1015 !! CONSERVE EN ATTENDANT QUE LE CAS EN QUESTION FONCTIONNE EN STD !! 1039 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 1040 ! endif ! forcing_sandu or forcing_astex 1041 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 1016 !======================================================================= 1042 1017 1043 1018 teta=temp*(pzero/play)**rkappa 1044 ! 1019 1045 1020 !--------------------------------------------------------------------- 1046 1021 ! Nudge soil temperature if requested … … 1080 1055 1081 1056 ! incremente day time 1082 ! print*,'daytime bef',daytime,1./day_step1083 1057 daytime = daytime+1./day_step 1084 !Al1dbg1085 1058 day = int(daytime+0.1/day_step) 1086 1059 ! time = max(daytime-day,0.0) … … 1088 1061 !cc time = real(mod(it,day_step))/day_step 1089 1062 time = time_ini/24.+real(mod(it,day_step))/day_step 1090 ! print*,'daytime nxt time',daytime,time1091 1063 it=it+1 1092 1064 1093 1065 enddo 1094 1066 1095 !Al11096 1067 if (ecrit_slab_oc.ne.-1) close(97) 1097 1068 1098 1069 !Al1 Call to 1D equivalent of dynredem (an,mois,jour,heure ?) 1099 ! ------------------------------------- 1070 ! --------------------------------------------------------------------------- 1100 1071 call dyn1dredem("restart1dyn.nc", & 1101 1072 & plev,play,phi,phis,presnivs, &
Note: See TracChangeset
for help on using the changeset viewer.