Changeset 1755 for trunk/MESOSCALE/LMD_MM_MARS/SRC
- Timestamp:
- Jul 25, 2017, 3:34:57 AM (8 years ago)
- Location:
- trunk/MESOSCALE/LMD_MM_MARS/SRC/WRFV2/phys
- Files:
-
- 8 edited
Legend:
- Unmodified
- Added
- Removed
-
trunk/MESOSCALE/LMD_MM_MARS/SRC/WRFV2/phys/Makefile
r1580 r1755 9 9 module_physics_addtendc.o \ 10 10 module_physics_init.o \ 11 variables_mod.o \ 11 12 update_inputs_physiq_mod.o \ 12 13 update_outputs_physiq_mod.o \ -
trunk/MESOSCALE/LMD_MM_MARS/SRC/WRFV2/phys/dynphy_wrf_mars_lmd_new/callphysiq_mod.F
r1634 r1755 13 13 14 14 SUBROUTINE call_physiq(planet_type, klon,llm,nqtot, & 15 debut_split,lafin_split, & 16 jD_cur,jH_cur_split,zdt_split, & 17 zplev_omp,zplay_omp, & 18 zpk_omp,zphi_omp,zphis_omp, & 19 presnivs_omp, & 20 zufi_omp,zvfi_omp,zrfi_omp,ztfi_omp,zqfi_omp, & 21 flxwfi_omp, & 22 zdufi_omp,zdvfi_omp,zdtfi_omp,zdqfi_omp,zdpsrf_omp) 15 debut_split,lafin_split) 23 16 17 USE variables_mod 24 18 USE physiq_mod, ONLY: physiq 25 19 IMPLICIT NONE … … 32 26 LOGICAL,INTENT(IN) :: debut_split ! .true. if very first call to physics 33 27 LOGICAL,INTENT(IN) :: lafin_split ! .true. if last call to physics 34 REAL,INTENT(IN) :: JD_cur ! Julian day35 REAL,INTENT(IN) :: JH_cur_split ! Julian hour (fraction of day)36 REAL,INTENT(IN) :: zdt_split ! time step over which the physics are evaluated37 REAL,INTENT(IN) :: zplev_omp(klon,llm+1) ! interlayer pressure (Pa)38 REAL,INTENT(IN) :: zplay_omp(klon,llm) ! mid-layer pressure (Pa)39 REAL,INTENT(INOUT) :: zpk_omp(klon,llm)40 REAL,INTENT(IN) :: zphi_omp(klon,llm) ! geopotential at midlayer41 REAL,INTENT(INOUT) :: zphis_omp(klon) ! surface geopotential42 REAL,INTENT(INOUT) :: presnivs_omp(llm) ! approximate pressure of atm. layers43 REAL,INTENT(IN) :: zufi_omp(klon,llm) ! zonal wind (m/s)44 REAL,INTENT(IN) :: zvfi_omp(klon,llm) ! meridional wind (m/s)45 REAL,INTENT(INOUT) :: zrfi_omp(klon,llm) ! relative wind vorticity, in s-146 REAL,INTENT(IN) :: ztfi_omp(klon,llm) ! temperature (K)47 REAL,INTENT(IN) :: zqfi_omp(klon,llm,nqtot) ! tracers (*/kg of air)48 REAL,INTENT(IN) :: flxwfi_omp(klon,llm) ! Vertical mass flux on lower mesh interfaces (kg/s)49 ! tendencies (in */s) from the physics:50 REAL,INTENT(OUT) :: zdufi_omp(klon,llm) ! tendency on zonal winds51 REAL,INTENT(OUT) :: zdvfi_omp(klon,llm) ! tendency on meridional winds52 REAL,INTENT(OUT) :: zdtfi_omp(klon,llm) ! tendency on temperature53 REAL,INTENT(OUT) :: zdqfi_omp(klon,llm,nqtot) ! tendency on tracers54 REAL,INTENT(OUT) :: zdpsrf_omp(klon) ! tendency on surface pressure55 28 56 29 ! ! Local variables -
trunk/MESOSCALE/LMD_MM_MARS/SRC/WRFV2/phys/dynphy_wrf_mars_lmd_new/iniphysiq_mod.F
r1634 r1755 3 3 CONTAINS 4 4 5 subroutine iniphysiq(ngrid,nlayer,nq,p hour_ini,piphysiq,&6 punjours, pdayref, ptimestep,&5 subroutine iniphysiq(ngrid,nlayer,nq,piphysiq,& 6 punjours, pdayref, & 7 7 prad,pg,pr,pcpp,iflag_phys) 8 8 … … 11 11 dtphys,daysec,day_ini,hour_ini 12 12 use update_inputs_physiq_mod, only: traceurs 13 USE variables_mod, only: phour_ini,zdt_split !! zdt_split <> pttimestep 14 !real*8,intent(in) :: ptimestep !physics time step (s) [dtphys] 13 15 14 16 implicit none … … 20 22 real,intent(in) :: punjours ! length (in s) of a standard day [daysec] 21 23 integer,intent(in) :: pdayref ! reference day of for the simulation [day_ini] 22 real,intent(in) :: ptimestep !physics time step (s) [dtphys]24 !real*8,intent(in) :: ptimestep !physics time step (s) [dtphys] 23 25 integer,intent(in) :: iflag_phys ! type of physics to be called 24 26 … … 26 28 integer,intent(in) :: nlayer ! number of atmospheric layers 27 29 integer,intent(in) :: nq ! number of tracers 28 real,intent(in) :: phour_ini ! start time (fraction of day) of the run 0=<phour_ini<130 !real,intent(in) :: phour_ini ! start time (fraction of day) of the run 0=<phour_ini<1 29 31 real,intent(in) :: piphysiq ! call physics every piphysiq dynamical timesteps 30 32 … … 38 40 !! initialize physical constants and arrays 39 41 call phys_state_var_init(ngrid,nlayer,nq, traceurs, & 40 pdayref,phour_ini,punjours, ptimestep, &42 pdayref,phour_ini,punjours,zdt_split, & 41 43 prad,pg,pr,pcpp) 42 44 … … 47 49 !! not done by init_time in phys_state_var_init 48 50 !! and supposed to be done in conf_phys (but not done in mesoscale) 49 day_step=punjours/ ptimestep51 day_step=punjours/zdt_split 50 52 iphysiq=piphysiq 51 53 ecritstart=0 !! not used in MESOSCALE -
trunk/MESOSCALE/LMD_MM_MARS/SRC/WRFV2/phys/dynphy_wrf_mars_lmd_new/update_inputs_physiq_mod.F
r1635 r1755 70 70 elaps,& 71 71 lct_input,lon_input,ls_input,& 72 ptime,pday,MY) 72 MY) 73 74 USE variables_mod, only: JD_cur,JH_cur_split,phour_ini 75 !! JD_cur <> pday ! Julian day 76 !! JH_cur_split <> ptime ! Julian hour (fraction of day) 77 78 implicit none 73 79 74 80 INTEGER, INTENT(IN) :: JULDAY, JULYR 75 81 REAL, INTENT(IN) :: GMT,elaps,lon_input,ls_input,lct_input 76 REAL,INTENT(OUT) :: pday,ptime,MY82 REAL,INTENT(OUT) :: MY 77 83 78 84 IF (JULYR .ne. 9999) THEN … … 80 86 ! specified 81 87 ! 82 ptime = (GMT + elaps/3700.) !! universal time (0<ptime<1): ptime=0.5 at 12:00 UT83 ptime = MODULO(ptime,24.) !! the two arguments of MODULO must be of the same type84 ptime = ptime/ 24.85 pday= (JULDAY - 1 + INT((3700*GMT+elaps)/88800))86 pday = MODULO(int(pday),669)88 JH_cur_split = (GMT + elaps/3700.) !! universal time (0<JH_cur_split<1): JH_cur_split=0.5 at 12:00 UT 89 JH_cur_split = MODULO(JH_cur_split,24.) !! the two arguments of MODULO must be of the same type 90 JH_cur_split = JH_cur_split / 24. 91 JD_cur = (JULDAY - 1 + INT((3700*GMT+elaps)/88800)) 92 JD_cur = MODULO(int(JD_cur),669) 87 93 MY = (JULYR-2000) + (88800.*(JULDAY - 1)+3700.*GMT+elaps)/59496000. 88 94 MY = INT(MY) … … 91 97 ! idealized 92 98 ! 93 ptime= lct_input - lon_input / 15. + elaps/3700.94 ptime = MODULO(ptime,24.)95 ptime = ptime/ 24.96 pday= floor(ls2sol(ls_input)) + INT((3700*(lct_input - lon_input / 15.) + elaps)/88800)97 pday = MODULO(int(pday),669)99 JH_cur_split = lct_input - lon_input / 15. + elaps/3700. 100 JH_cur_split = MODULO(JH_cur_split,24.) 101 JH_cur_split = JH_cur_split / 24. 102 JD_cur = floor(ls2sol(ls_input)) + INT((3700*(lct_input - lon_input / 15.) + elaps)/88800) 103 JD_cur = MODULO(int(JD_cur),669) 98 104 MY = 2024 99 !day_ini = floor(ls2sol(ls_input)) !! pdayat firstcall is day_ini105 !day_ini = floor(ls2sol(ls_input)) !! JD_cur at firstcall is day_ini 100 106 ENDIF 101 print *,'** Mars ** TIME IS', pday, ptime*24.107 print *,'** Mars ** TIME IS', JD_cur, JH_cur_split*24. 102 108 103 109 END SUBROUTINE update_inputs_physiq_time … … 721 727 722 728 END MODULE update_inputs_physiq_mod 729 -
trunk/MESOSCALE/LMD_MM_MARS/SRC/WRFV2/phys/dynphy_wrf_venus_lmd_new/callphysiq_mod.F
r1739 r1755 13 13 14 14 SUBROUTINE call_physiq(planet_type, klon,llm,nqtot, & 15 debut_split,lafin_split, & 16 jD_cur,jH_cur_split,zdt_split, & 17 zplev_omp,zplay_omp, & 18 zpk_omp,zphi_omp,zphis_omp, & 19 presnivs_omp, & 20 zufi_omp,zvfi_omp,zrfi_omp,ztfi_omp,zqfi_omp, & 21 flxwfi_omp, & 22 zdufi_omp,zdvfi_omp,zdtfi_omp,zdqfi_omp,zdpsrf_omp) 15 debut_split,lafin_split) 23 16 17 USE variables_mod 24 18 USE physiq_mod, ONLY: physiq 25 19 USE module_model_constants, only : p0,rcp,cp … … 34 28 LOGICAL,INTENT(IN) :: debut_split ! .true. if very first call to physics 35 29 LOGICAL,INTENT(IN) :: lafin_split ! .true. if last call to physics 36 REAL*8,INTENT(IN) :: JD_cur ! Julian day37 REAL*8,INTENT(IN) :: JH_cur_split ! Julian hour (fraction of day)38 REAL*8,INTENT(IN) :: zdt_split ! time step over which the physics are evaluated39 REAL*8,INTENT(IN) :: zplev_omp(klon,llm+1) ! interlayer pressure (Pa)40 REAL*8,INTENT(IN) :: zplay_omp(klon,llm) ! mid-layer pressure (Pa)41 REAL*8,INTENT(INOUT) :: zpk_omp(klon,llm)42 REAL*8,INTENT(IN) :: zphi_omp(klon,llm) ! geopotential at midlayer43 REAL*8,INTENT(INOUT) :: zphis_omp(klon) ! surface geopotential44 REAL*8,INTENT(INOUT) :: presnivs_omp(llm) ! approximate pressure of atm. layers45 REAL*8,INTENT(IN) :: zufi_omp(klon,llm) ! zonal wind (m/s)46 REAL*8,INTENT(IN) :: zvfi_omp(klon,llm) ! meridional wind (m/s)47 REAL*8,INTENT(INOUT) :: zrfi_omp(klon,llm) ! relative wind vorticity, in s-148 REAL*8,INTENT(IN) :: ztfi_omp(klon,llm) ! temperature (K)49 REAL*8,INTENT(IN) :: zqfi_omp(klon,llm,nqtot) ! tracers (*/kg of air)50 REAL*8,INTENT(IN) :: flxwfi_omp(klon,llm) ! Vertical mass flux on lower mesh interfaces (kg/s)51 ! tendencies (in */s) from the physics:52 REAL*8,INTENT(OUT) :: zdufi_omp(klon,llm) ! tendency on zonal winds53 REAL*8,INTENT(OUT) :: zdvfi_omp(klon,llm) ! tendency on meridional winds54 REAL*8,INTENT(OUT) :: zdtfi_omp(klon,llm) ! tendency on temperature55 REAL*8,INTENT(OUT) :: zdqfi_omp(klon,llm,nqtot) ! tendency on tracers56 REAL*8,INTENT(OUT) :: zdpsrf_omp(klon) ! tendency on surface pressure57 30 REAL*8 :: zplevmoy(llm+1) ! planet-averaged mean pressure (Pa) at interfaces 58 31 REAL*8 :: ztmoy(llm) -
trunk/MESOSCALE/LMD_MM_MARS/SRC/WRFV2/phys/dynphy_wrf_venus_lmd_new/iniphysiq_mod.F
r1724 r1755 3 3 CONTAINS 4 4 5 subroutine iniphysiq(ngrid,nlayer,nq,p hour_ini,piphysiq,&6 punjours, pdayref, ptimestep,&5 subroutine iniphysiq(ngrid,nlayer,nq,piphysiq,& 6 punjours, pdayref, & 7 7 prad,pg,pr,pcpp,iflag_phys) 8 8 … … 19 19 USE phys_state_var_mod 20 20 use module_model_constants, only : nu, TT00 21 USE variables_mod, only: phour_ini,zdt_split !! zdt_split <> ptimestep 22 !real*8,intent(in) :: ptimestep !physics time step (s) [dtphys] 23 21 24 implicit none 22 25 … … 27 30 REAL,intent(in) :: punjours 28 31 !DOUBLE PRECISION,intent(in) :: ptimestep 29 REAL*8,intent(in) :: phour_ini30 32 31 33 !real,intent(in) :: prad ! radius of the planet (m) … … 35 37 !real,intent(in) :: punjours ! length (in s) of a standard day [daysec] 36 38 integer,intent(in) :: pdayref ! reference day of for the simulation [day_ini] 37 real*8,intent(in) :: ptimestep !physics time step (s) [dtphys]39 !real*8,intent(in) :: ptimestep !physics time step (s) [dtphys] 38 40 integer,intent(in) :: iflag_phys ! type of physics to be called 39 41 -
trunk/MESOSCALE/LMD_MM_MARS/SRC/WRFV2/phys/dynphy_wrf_venus_lmd_new/update_inputs_physiq_mod.F
r1743 r1755 32 32 elaps,& 33 33 lct_input,lon_input,ls_input,& 34 ptime,pday,MY) 34 MY) 35 36 USE variables_mod, only: JD_cur,JH_cur_split,phour_ini 37 !! JD_cur <> pday ! Julian day 38 !! JH_cur_split <> ptime ! Julian hour (fraction of day) 35 39 36 40 implicit none … … 39 43 REAL, INTENT(IN) :: GMT,elaps,lon_input,ls_input,lct_input 40 44 REAL,INTENT(OUT) :: MY 41 REAL*8,INTENT(OUT) :: ptime,pday42 45 43 46 ! … … 45 48 ! 46 49 IF (JULYR .ne. 9999) THEN 47 ptime = (GMT + elaps/420000.) !! universal time (0<ptime<1): ptime=0.5 at 12:00 UT48 ptime = MODULO(ptime,24.) !! the two arguments of MODULO must be of the same type49 ptime = ptime/ 24.50 pday= (JULDAY - 1 + INT((420000.0*GMT+elaps)/1.008e7))51 pday = MODULO(int(pday),2)50 JH_cur_split = (GMT + elaps/420000.) !! universal time (0<JH_cur_split<1): JH_cur_split=0.5 at 12:00 UT 51 JH_cur_split = MODULO(JH_cur_split,24.) !! the two arguments of MODULO must be of the same type 52 JH_cur_split = JH_cur_split / 24. 53 JD_cur = (JULDAY - 1 + INT((420000.0*GMT+elaps)/1.008e7)) 54 JD_cur = MODULO(int(JD_cur),2) 52 55 MY = (JULYR-2000) + (1.008e7*(JULDAY - 1)+420000.0*GMT+elaps)/2.016e7 53 56 MY = INT(MY) 54 57 ELSE 55 ptime= lct_input - lon_input / 15. + elaps/(4200.)56 ptime = MODULO(ptime,2808.)57 ptime = ptime/ 2808.58 print*,' ptime',ptime59 pday = MODULO(int(pday),669)58 JH_cur_split = lct_input - lon_input / 15. + elaps/(4200.) 59 JH_cur_split = MODULO(JH_cur_split,2808.) 60 JH_cur_split = JH_cur_split / 2808. 61 print*,'JH_cur_split',JH_cur_split 62 JD_cur = MODULO(int(JD_cur),669) 60 63 MY = 2024 61 64 ENDIF -
trunk/MESOSCALE/LMD_MM_MARS/SRC/WRFV2/phys/module_lmd_driver.F.new
r1742 r1755 58 58 USE module_wrf_error 59 59 !!!!!!!! interface modules 60 USE variables_mod !! to set variables 60 61 USE update_inputs_physiq_mod !! to set inputs for physiq 61 62 USE update_outputs_physiq_mod !! to get outputs from physiq … … 138 139 ! ------> inputs: 139 140 INTEGER :: ngrid,nlayer,nq,nsoil 140 REAL*8 :: pday,ptime141 141 REAL :: MY 142 142 REAL :: phisfi_val 143 143 LOGICAL :: firstcall,lastcall 144 144 ! ---------- 145 REAL*8,DIMENSION(:,:),ALLOCATABLE :: pplev,pplay,pphi,pu,pv,pt,flxw146 REAL*8,DIMENSION(:,:,:),ALLOCATABLE :: pq147 145 148 146 ! <------ outputs: 149 147 ! physical tendencies 150 REAL*8,DIMENSION(:),ALLOCATABLE :: pdpsrf 151 REAL*8,DIMENSION(:,:),ALLOCATABLE :: pdu,pdv,pdt,pdtheta 152 REAL*8,DIMENSION(:,:,:),ALLOCATABLE :: pdq 148 REAL*8,DIMENSION(:,:),ALLOCATABLE :: pdtheta 153 149 ! ... intermediate arrays 154 150 REAL, DIMENSION(:), ALLOCATABLE :: & … … 160 156 INTEGER :: sponge_top,relax,ips,ipe,jps,jpe,kps,kpe 161 157 REAL :: elaps 162 REAL*8 :: ptimestep163 158 INTEGER :: test 164 159 REAL :: wappel_phys … … 192 187 !!!IDEALIZED IDEALIZED 193 188 194 !! arguments to physiq195 REAL*8,ALLOCATABLE :: zpk_omp(:,:)196 REAL*8,ALLOCATABLE :: zphis_omp(:) ! surface geopotential197 REAL*8,ALLOCATABLE :: presnivs_omp(:) ! approximate pressure of atm. layers198 REAL*8,ALLOCATABLE :: zrfi_omp(:,:) ! relative wind vorticity, in s-1199 189 REAL :: tk1,tk2 200 190 !================================================================== … … 264 254 !day_ini = JULDAY - 1 !! GCM convention !! pday at firstcall is day_ini 265 255 wappel_phys = RADT 266 ptimestep= dt*wappel_phys ! physical timestep (s)256 zdt_split = dt*wappel_phys ! physical timestep (s) 267 257 ngrid=(ipe-ips+1)*(jpe-jps+1) ! size of the horizontal grid 268 258 nlayer = kpe-kps+1 ! number of vertical layers: nlayermx … … 375 365 ! ALLOCATE ! 376 366 !----------! 377 !-------------------------------------------------------------------------------! 378 ! outputs: ! 379 ! pdu(ngrid,nlayermx) \ ! 380 ! pdv(ngrid,nlayermx) \ Temporal derivative of the corresponding ! 381 ! pdt(ngrid,nlayermx) / variables due to physical processes. ! 382 ! pdq(ngrid,nlayermx) / ! 383 ! pdpsrf(ngrid) / ! 384 !-------------------------------------------------------------------------------! 385 ALLOCATE(pdpsrf(ngrid)) 386 ALLOCATE(pdu(ngrid,nlayer)) 387 ALLOCATE(pdv(ngrid,nlayer)) 388 ALLOCATE(pdt(ngrid,nlayer)) 389 ALLOCATE(pdtheta(ngrid,nlayer)) 390 ALLOCATE(pdq(ngrid,nlayer,nq)) 367 !!-------------------------------------------------------------------------------! 368 !! outputs: ! 369 !! pdu(ngrid,nlayermx) \ ! 370 !! pdv(ngrid,nlayermx) \ Temporal derivative of the corresponding ! 371 !! pdt(ngrid,nlayermx) / variables due to physical processes. ! 372 !! pdq(ngrid,nlayermx) / ! 373 !! pdpsrf(ngrid) / ! 374 !!-------------------------------------------------------------------------------! 375 !ALLOCATE(pdpsrf(ngrid)) 376 !ALLOCATE(pdu(ngrid,nlayer)) 377 !ALLOCATE(pdv(ngrid,nlayer)) 378 !ALLOCATE(pdt(ngrid,nlayer)) 379 !ALLOCATE(pdtheta(ngrid,nlayer)) 380 !ALLOCATE(pdq(ngrid,nlayer,nq)) 381 CALL allocate_interface(ngrid,nlayer,nq) 391 382 !!! 392 383 !!! BIG LOOP : 1. no call for physics, used saved values … … 395 386 print *,'** ',planet_type,'** NO CALL FOR PHYSICS, go to next step...',test 396 387 #ifdef SPECIAL_NEST_SAVE 397 pdpsrf(:)=dp_save(:,id)398 pdu(:,:)=du_save(:,:,id)399 pdv(:,:)=dv_save(:,:,id)400 pdt(:,:)=dt_save(:,:,id)388 zdpsrf_omp(:)=dp_save(:,id) 389 zdufi_omp(:,:)=du_save(:,:,id) 390 zdvfi_omp(:,:)=dv_save(:,:,id) 391 zdtfi_omp(:,:)=dt_save(:,:,id) 401 392 pdtheta(:,:)=dtheta_save(:,:,id) 402 pdq(:,:,:)=dq_save(:,:,:,id)393 zdqfi_omp(:,:,:)=dq_save(:,:,:,id) 403 394 #else 404 395 print*,'else' 405 pdpsrf(:)=dp_save(:)406 pdu(:,:)=du_save(:,:)407 pdv(:,:)=dv_save(:,:)408 pdt(:,:)=dt_save(:,:)396 zdpsrf_omp(:)=dp_save(:) 397 zdufi_omp(:,:)=du_save(:,:) 398 zdvfi_omp(:,:)=dv_save(:,:) 399 zdtfi_omp(:,:)=dt_save(:,:) 409 400 pdtheta(:,:)=dtheta_save(:,:) 410 pdq(:,:,:)=dq_save(:,:,:)401 zdqfi_omp(:,:,:)=dq_save(:,:,:) 411 402 #endif 412 403 !!! … … 417 408 ! ALLOCATE ! 418 409 !----------! 419 ! inputs ...420 ALLOCATE(pplev(ngrid,nlayer+1)) !!!!!421 ALLOCATE(pplay(ngrid,nlayer)) !!!!!422 ALLOCATE(pphi(ngrid,nlayer)) !!!!!423 ALLOCATE(pu(ngrid,nlayer)) !!!!!424 ALLOCATE(pv(ngrid,nlayer)) !!!!!425 ALLOCATE(pt(ngrid,nlayer)) !!!!!426 ALLOCATE(flxw(ngrid,nlayer)) !!!!!427 ALLOCATE(pq(ngrid,nlayer,nq)) !!!!!428 ALLOCATE(zpk_omp(ngrid,nlayer))429 ALLOCATE(zphis_omp(ngrid))430 ALLOCATE(presnivs_omp(nlayer))431 ALLOCATE(zrfi_omp(ngrid,nlayer))432 410 ! interm 433 411 ALLOCATE(dz8w_prof(nlayer)) … … 461 439 elaps,& 462 440 lct_input,lon_input,ls_input,& 463 ptime,pday,MY)441 MY) 464 442 !! Fill planetary parameters in modules 465 443 !! Values defined in the module_model_constants.F WRF routine 466 444 CALL update_inputs_physiq_constants 467 445 !! Initialize physics 468 CALL iniphysiq(ngrid,nlayer,nq, ptime,wappel_phys,&469 wdaysec,floor( pday),ptimestep, &446 CALL iniphysiq(ngrid,nlayer,nq,wappel_phys,& 447 wdaysec,floor(JD_cur), & 470 448 1./reradius,g,r_d,cp,1) 449 !! Set up initial time 450 phour_ini = JH_cur_split 471 451 ENDIF allocation_firstcall 472 452 … … 492 472 !--------------------------------------! 493 473 dz8w_prof(:) = dz8w(i,kps:kpe,j) ! dz between full levels (m) 494 p8w_prof(:) = p8w(i,kps:kpe,j) ! pressure full level (Pa) >> pplev495 p_prof(:) = p(i,kps:kpe,j) ! pressure half level (Pa) >> pplay474 p8w_prof(:) = p8w(i,kps:kpe,j) ! pressure full level (Pa) >> zplev_omp 475 p_prof(:) = p(i,kps:kpe,j) ! pressure half level (Pa) >> zplay_omp 496 476 t_prof(:) = t(i,kps:kpe,j) ! temperature half level (K) >> pt 497 477 t8w_prof(:) = t8w(i,kps:kpe,j) ! temperature full level (K) 498 u_prof(:) = u(i,kps:kpe,j) ! zonal wind (A-grid: unstaggered) half level (m/s) >> pu478 u_prof(:) = u(i,kps:kpe,j) ! zonal wind (A-grid: unstaggered) half level (m/s) >> zufi_omp 499 479 v_prof(:) = v(i,kps:kpe,j) ! meridional wind (A-grid: unstaggered) half level (m/s) >> pv 500 z_prof(:) = z(i,kps:kpe,j) ! geopotential height half level (m) >> pphi/g480 z_prof(:) = z(i,kps:kpe,j) ! geopotential height half level (m) >> zphi_omp/g 501 481 502 482 !--------------------------------! … … 544 524 ! expressed with respect to the local surface ! 545 525 !---------------------------------------------! 546 pphi(subs,:) = g*( z_prof(:)-(z_prof(1)-dz8w_prof(1)/2.) )526 zphi_omp(subs,:) = g*( z_prof(:)-(z_prof(1)-dz8w_prof(1)/2.) ) 547 527 548 528 !--------------------------------! 549 529 ! Dynamic fields for LMD physics ! 550 530 !--------------------------------! 551 pplev(subs,1:nlayer) = p8w_prof(1:nlayer) !! NB: last level: no data552 pplay(subs,:) = p_prof(:)553 pt(subs,:) = t_prof(:)554 pu(subs,:) = u_prof(:)555 pv(subs,:) = v_prof(:)556 flxw (subs,:) = 0 !! NB: not used in the physics, only diagnostic...531 zplev_omp(subs,1:nlayer) = p8w_prof(1:nlayer) !! NB: last level: no data 532 zplay_omp(subs,:) = p_prof(:) 533 ztfi_omp(subs,:) = t_prof(:) 534 zufi_omp(subs,:) = u_prof(:) 535 zvfi_omp(subs,:) = v_prof(:) 536 flxwfi_omp(subs,:) = 0 !! NB: not used in the physics, only diagnostic... 557 537 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 558 538 !! for IDEALIZED CASES ONLY 559 IF (JULYR .eq. 9999) pplev(subs,nlayer+1)=0. !! pplev(subs,nlayer+1)=ptop >> NO !539 IF (JULYR .eq. 9999) zplev_omp(subs,nlayer+1)=0. !! zplev_omp(subs,nlayer+1)=ptop >> NO ! 560 540 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 561 541 562 542 ! NOTE: 563 ! IF ( pplev(subs,nlayer+1) .le. 0 ) pplev(subs,nlayer+1)=ptop543 ! IF ( zplev_omp(subs,nlayer+1) .le. 0 ) zplev_omp(subs,nlayer+1)=ptop 564 544 ! cree des diagnostics delirants et aleatoires dans le transfert radiatif 565 545 … … 567 547 ! Tracers ! 568 548 !---------! 569 pq(subs,:,:) = q_prof(:,:) !! traceurs generiques, seuls noms sont specifiques549 zqfi_omp(subs,:,:) = q_prof(:,:) !! traceurs generiques, seuls noms sont specifiques 570 550 571 551 ENDDO … … 659 639 call_physics : IF (wappel_phys .ne. 0.) THEN 660 640 !!! initialize tendencies (security) 661 pdpsrf(:)=0.662 pdu(:,:)=0.663 pdv(:,:)=0.664 pdt(:,:)=0.641 zdpsrf_omp(:)=0. 642 zdufi_omp(:,:)=0. 643 zdvfi_omp(:,:)=0. 644 zdtfi_omp(:,:)=0. 665 645 pdtheta(:,:)=0. 666 pdq(:,:,:)=0.646 zdqfi_omp(:,:,:)=0. 667 647 print *, '** ',planet_type,'** CALL TO LMD PHYSICS' 668 648 !!! … … 671 651 elaps,& 672 652 lct_input,lon_input,ls_input,& 673 ptime,pday,MY)653 MY) 674 654 !!! 675 655 CALL call_physiq(planet_type,ngrid,nlayer,nq, & 676 firstcall,lastcall, & 677 pday,ptime,ptimestep, & 678 pplev,pplay, & 679 zpk_omp,pphi,zphis_omp, & 680 presnivs_omp, & 681 pu,pv,zrfi_omp,pt,pq, & 682 flxw, & 683 pdu,pdv,pdt,pdq,pdpsrf) 656 firstcall,lastcall) 684 657 !!! 685 658 … … 687 660 #ifdef DUSTSTORM 688 661 IF (firstcall .EQV. .true.) THEN 689 pdq(:,:,:) = pdq(:,:,:) / dt662 zdqfi_omp(:,:,:) = zdqfi_omp(:,:,:) / dt 690 663 ENDIF 691 664 #endif … … 696 669 do k=kps,kpe 697 670 subs=(j-jps)*(ipe-ips+1)+(i-ips+1) 698 tk1=( pt(subs,k)**nu + nu*TT00**nu*log((p1000mb/pplay(subs,k))**rcp))**(1/nu)699 tk2=(( pt(subs,k) + pdt(subs,k))**nu + nu*TT00**nu*log((p1000mb/pplay(subs,k))**rcp))**(1/nu)671 tk1=(ztfi_omp(subs,k)**nu + nu*TT00**nu*log((p1000mb/zplay_omp(subs,k))**rcp))**(1/nu) 672 tk2=((ztfi_omp(subs,k) + zdtfi_omp(subs,k))**nu + nu*TT00**nu*log((p1000mb/zplay_omp(subs,k))**rcp))**(1/nu) 700 673 pdtheta(subs,k)=tk2-tk1 701 674 enddo … … 705 678 706 679 print *, '** ',planet_type,'** CALL TO LMD PHYSICS DONE' 707 DEALLOCATE(pplev)708 DEALLOCATE(pplay)709 DEALLOCATE(pphi)710 DEALLOCATE(pu)711 DEALLOCATE(pv)712 DEALLOCATE(pt)713 DEALLOCATE(flxw)714 DEALLOCATE(pq)715 DEALLOCATE(zpk_omp)716 DEALLOCATE(zphis_omp)717 DEALLOCATE(presnivs_omp)718 DEALLOCATE(zrfi_omp)719 680 720 681 !---------------------------------------------------------------------------------! … … 722 683 !---------------------------------------------------------------------------------! 723 684 #ifdef SPECIAL_NEST_SAVE 724 dp_save(:,id)= pdpsrf(:)725 du_save(:,:,id)= pdu(:,:)726 dv_save(:,:,id)= pdv(:,:)727 dt_save(:,:,id)= pdt(:,:)685 dp_save(:,id)=zdpsrf_omp(:) 686 du_save(:,:,id)=zdufi_omp(:,:) 687 dv_save(:,:,id)=zdvfi_omp(:,:) 688 dt_save(:,:,id)=zdtfi_omp(:,:) 728 689 dtheta_save(:,:,id)=pdtheta(:,:) 729 dq_save(:,:,:,id)= pdq(:,:,:)690 dq_save(:,:,:,id)=zdqfi_omp(:,:,:) 730 691 #else 731 dp_save(:)= pdpsrf(:)732 du_save(:,:)= pdu(:,:)733 dv_save(:,:)= pdv(:,:)734 dt_save(:,:)= pdt(:,:)692 dp_save(:)=zdpsrf_omp(:) 693 du_save(:,:)=zdufi_omp(:,:) 694 dv_save(:,:)=zdvfi_omp(:,:) 695 dt_save(:,:)=zdtfi_omp(:,:) 735 696 dtheta_save(:,:)=pdtheta(:,:) 736 dq_save(:,:,:)= pdq(:,:,:)697 dq_save(:,:,:)=zdqfi_omp(:,:,:) 737 698 #endif 738 699 … … 806 767 807 768 ! zonal wind 808 RUBLTEN(i,kps:kpe,j) = pdu(subs,kps:kpe)769 RUBLTEN(i,kps:kpe,j) = zdufi_omp(subs,kps:kpe) 809 770 ! meridional wind 810 RVBLTEN(i,kps:kpe,j) = pdv(subs,kps:kpe)771 RVBLTEN(i,kps:kpe,j) = zdvfi_omp(subs,kps:kpe) 811 772 ! potential temperature 812 773 ! (dT = dtheta * exner for isobaric coordinates or if pressure variations are negligible) … … 814 775 RTHBLTEN(i,kps:kpe,j) = pdtheta(subs,kps:kpe) 815 776 ELSE 816 RTHBLTEN(i,kps:kpe,j) = pdt(subs,kps:kpe) / exner(i,kps:kpe,j)777 RTHBLTEN(i,kps:kpe,j) = zdtfi_omp(subs,kps:kpe) / exner(i,kps:kpe,j) 817 778 ENDIF 818 779 ! update surface pressure (cf CO2 cycle in physics) 819 780 ! here dt is needed 820 PSFC(i,j)=PSFC(i,j)+ pdpsrf(subs)*dt781 PSFC(i,j)=PSFC(i,j)+zdpsrf_omp(subs)*dt 821 782 ! tracers 822 783 SCALAR(i,kps:kpe,j,1)=0. … … 831 792 SCALAR(i,1,j,2) = SCALAR(i,1,j,2) + 1. !! this tracer is emitted in the surface layer 832 793 CASE DEFAULT 833 SCALAR(i,kps:kpe,j,2:nq+1)=SCALAR(i,kps:kpe,j,2:nq+1)+ pdq(subs,kps:kpe,1:nq)*dt !!! here dt is needed794 SCALAR(i,kps:kpe,j,2:nq+1)=SCALAR(i,kps:kpe,j,2:nq+1)+zdqfi_omp(subs,kps:kpe,1:nq)*dt !!! here dt is needed 834 795 END SELECT 835 796 836 797 ENDDO 837 798 ENDDO 838 DEALLOCATE(pdpsrf) 839 DEALLOCATE(pdu) 840 DEALLOCATE(pdv) 841 DEALLOCATE(pdt) 842 DEALLOCATE(pdq) 799 CALL deallocate_interface 843 800 DEALLOCATE(pdtheta) 844 801 !!*****!!
Note: See TracChangeset
for help on using the changeset viewer.