- Timestamp:
- Jul 4, 2024, 4:14:10 PM (5 months ago)
- Location:
- trunk/LMDZ.MARS
- Files:
-
- 5 edited
Legend:
- Unmodified
- Added
- Removed
-
trunk/LMDZ.MARS/changelog.txt
r3385 r3393 4674 4674 == 19/06/2024 == JBC 4675 4675 Update of the "run.def.1d" file in the deftank. 4676 4677 == 19/06/2024 == JL 4678 Update of non-orographic gravity waves mixing scheme. 1)mixing in potential 4679 temperature are added. 2)all mixing in q,u,theta now are implemented by AR-1 4680 algorithm. Tests (MY29,MY32-35) runs show that this implementation has limited 4681 impact to the temperature/tides fields. -
trunk/LMDZ.MARS/libf/phymars/nonoro_gwd_mix_mod.F90
r3263 r3393 5 5 REAL,allocatable,save :: du_eddymix_gwd(:,:) ! Zonal wind tendency due to GWD 6 6 REAL,allocatable,save :: dv_eddymix_gwd(:,:) ! Meridional wind tendency due to GWD 7 REAL,allocatable,save :: dh_eddymix_gwd(:,:) ! PT tendency due to GWD 8 REAL,allocatable,save :: dq_eddymix_gwd(:,:,:) ! tracers tendency due to GWD 7 9 REAL,allocatable,save :: de_eddymix_rto(:,:) ! Meridional wind tendency due to GWD 8 10 REAL,allocatable,save :: df_eddymix_flx(:,:) ! Meridional wind tendency due to GWD … … 11 13 LOGICAL, save :: calljliu_gwimix ! flag for using non-orographic GW-induced mixing 12 14 13 !$OMP THREADPRIVATE(du_eddymix_gwd,dv_eddymix_gwd,d e_eddymix_rto,df_eddymix_flx,calljliu_gwimix)15 !$OMP THREADPRIVATE(du_eddymix_gwd,dv_eddymix_gwd,dh_eddymix_gwd,dq_eddymix_gwd,de_eddymix_rto,df_eddymix_flx,calljliu_gwimix) 14 16 !,east_gwstress,west_gwstress) 15 17 … … 17 19 18 20 SUBROUTINE NONORO_GWD_MIX(ngrid,nlayer,DTIME,nq,cpnew, rnew, pp, & 19 zmax_therm, pt, pu, pv, pq, p dt, pdu, pdv, pdq,&21 zmax_therm, pt, pu, pv, pq, pht, pdt, pdu, pdv, pdq, pdht, & 20 22 d_pq, d_t, d_u, d_v) 21 23 … … 29 31 !--------------------------------------------------------------------------------- 30 32 31 use comcstfi_h, only: g, pi, r 33 use comcstfi_h, only: g, pi, r,rcp 32 34 USE ioipsl_getin_p_mod, ONLY : getin_p 33 35 use vertical_layers_mod, only : presnivs … … 62 64 REAL, intent(in):: pv(ngrid,nlayer) ! Meridional winds at full levels(m/s) 63 65 REAL, INTENT(IN) :: pq(ngrid,nlayer,nq) ! advected field nq 66 REAL, INTENT(IN) :: pht(ngrid,nlayer) ! advected field of potential temperature 67 REAL, INTENT(IN) :: pdht(ngrid,nlayer) ! tendancy of potential temperature 64 68 REAL, INTENT(IN) :: pdq(ngrid,nlayer,nq)! tendancy field pq 65 69 REAL,INTENT(in) :: pdt(ngrid,nlayer) ! Tendency on temperature (K/s) … … 74 78 REAL, intent(out):: d_v(ngrid, nlayer) ! Tendency on meridional wind (m/s/s) due to gravity waves 75 79 REAL, INTENT(out) :: d_pq(ngrid,nlayer,nq)! tendancy field pq 80 REAL :: d_h(ngrid, nlayer) ! Tendency on PT (T/s/s) due to gravity waves mixing 76 81 ! 0.3 INTERNAL ARRAYS 77 82 REAL :: TT(ngrid, nlayer) ! Temperature at full levels … … 79 84 REAL :: UU(ngrid, nlayer) ! Zonal wind at full levels 80 85 REAL :: VV(ngrid, nlayer) ! Meridional winds at full levels 86 REAL :: HH(ngrid, nlayer) ! potential temperature at full levels 81 87 REAL :: BVLOW(ngrid) ! initial N at each grid (not used) 82 88 … … 127 133 REAL u_eddy_mix_p(NW, ngrid) ! Zonal Diffusion coefficients 128 134 REAL v_eddy_mix_p(NW, ngrid) ! Meridional Diffusion coefficients 135 REAL h_eddy_mix_p(NW, ngrid) ! potential temperature DC 129 136 Real u_eddy_mix_tot(ngrid, nlayer+1) ! Total zonal D 130 137 Real v_eddy_mix_tot(ngrid, nlayer+1) ! Total meridional D 138 Real h_eddy_mix_tot(ngrid, nlayer+1) ! Total PT D 131 139 REAL U_shear(ngrid,nlayer) 132 140 Real wwp_vertical_tot(nlayer+1, NW, ngrid) ! Total meridional D … … 246 254 vv(:,:)=pv(:,:)+dtime*pdv(:,:) 247 255 zq(:,:,:)=pq(:,:,:)+dtime*pdq(:,:,:) 256 hh(:,:)=pht(:,:)+dtime*pdht(:,:) 248 257 ! Compute the real mass density by rho=p/R(T)T 249 258 DO ll=1,nlayer … … 610 619 u_eddy_mix_tot(:, :) = 0. 611 620 v_eddy_mix_tot(:, :) = 0. 621 h_eddy_mix_tot(:, :) = 0. 612 622 u_eddy_mix_p(:, :)=0. 613 623 v_eddy_mix_p(:, :)=0. 624 h_eddy_mix_p(:, :)=0. 614 625 d_eddy_mix_tot_ll(:,:,:)=0. 615 626 pq_eddy_mix_p(:,:,:)=0. … … 627 638 /(ZH(:, LL + 1) - ZH(:, LL)) & 628 639 *SIGN(1.,intr_freq_p(JW, :)) * SIN(ZP(JW, :)) 640 h_eddy_mix_p(JW, :) = d_eddy_mix(JW,:)*(HH(:, LL + 1) - HH(:, LL)) & 641 /(ZH(:, LL + 1) - ZH(:, LL)) & 642 *SIGN(1.,intr_freq_p(JW, :)) * SIN(ZP(JW, :)) 643 629 644 ENDDO 630 645 u_eddy_mix_tot(:, LL+1)=0. 631 646 v_eddy_mix_tot(:, LL+1)=0. 647 h_eddy_mix_tot(:, LL+1)=0. 632 648 DO JW=1,NW 633 649 u_eddy_mix_tot(:, LL+1) = u_eddy_mix_tot(:, LL+1) + u_eddy_mix_p(JW, :) 634 650 v_eddy_mix_tot(:, LL+1) = v_eddy_mix_tot(:, LL+1) + v_eddy_mix_p(JW, :) 651 h_eddy_mix_tot(:, LL+1) = h_eddy_mix_tot(:, LL+1) + h_eddy_mix_p(JW, :) 635 652 ENDDO 636 653 DO JW=1,NW … … 699 716 u_eddy_mix_tot(:, nlayer + 1) = 0. 700 717 v_eddy_mix_tot(:, nlayer + 1) = 0. 718 h_eddy_mix_tot(:, nlayer + 1) = 0. 701 719 pq_eddy_mix_tot(:, nlayer + 1,:)=0. 702 720 ! Here, big change compared to FLott version: … … 706 724 u_eddy_mix_tot(:, LL) = 0. 707 725 v_eddy_mix_tot(:, LL) = 0. 726 h_eddy_mix_tot(:, LL) = 0. 708 727 end DO 709 728 … … 718 737 * (PH(:,LL)-PH(:,LL-1)) / (PH(:,LAUNCH)-PH(:,max(1,LAUNCH-3))) 719 738 v_eddy_mix_tot(:, LL) = v_eddy_mix_tot(:, LL - 1) + v_eddy_mix_tot(:, LAUNCH) & 739 * (PH(:,LL)-PH(:,LL-1)) / (PH(:,LAUNCH)-PH(:,max(1,LAUNCH-3))) 740 h_eddy_mix_tot(:, LL) = h_eddy_mix_tot(:, LL - 1) + h_eddy_mix_tot(:, LAUNCH) & 720 741 * (PH(:,LL)-PH(:,LL-1)) / (PH(:,LAUNCH)-PH(:,max(1,LAUNCH-3))) 721 742 end DO … … 751 772 !d_v(:, LL) = (v_eddy_mix_tot(:, LL + 1) - v_eddy_mix_tot(:, LL)) & 752 773 ! / (ZH(:, LL + 1) - ZH(:, LL)) 774 d_h(:, LL) = (h_eddy_mix_tot(:, LL + 1) - h_eddy_mix_tot(:, LL)) & 775 / (ZH(:, LL + 1) - ZH(:, LL)) 753 776 ENDDO 754 777 … … 761 784 !df_eddymix_flx(:,:) = u_eddy_mix_tot(:,:) 762 785 !d_pq(:, :, :)=0. 763 d_t(:,:) = 0.786 !d_t(:,:) = 0. 764 787 !d_v(:,:) = 0. 765 788 !zustr(:) = 0. … … 779 802 call write_output('du_eddymix_gwd','Tendency on U due to nonoro GW', 'm.s-2',du_eddymix_gwd(:,:)) 780 803 !call write_output('dv_eddymix_gwd','Tendency on V due to nonoro GW', 'm.s-2',dv_eddymix_gwd(:,:)) 781 782 804 d_h(:,:) = DTIME/DELTAT/REAL(NW) * d_h(:,:) & 805 + (1.-DTIME/DELTAT) * dh_eddymix_gwd(:,:) 806 do ii=1,ngrid 807 d_t(ii,:) = d_h(ii,:) * (PP(ii,:) / PH(ii,1))**rcp 808 enddo 809 810 dh_eddymix_gwd(:,:)=d_h(:,:) 811 812 DO QQ=1,NQ 813 d_pq(:, :, QQ) =DTIME/DELTAT/REAL(NW) * d_pq(:, :, QQ) & 814 + (1.-DTIME/DELTAT) * dq_eddymix_gwd(:, :, QQ) 815 endDO 783 816 784 817 END SUBROUTINE NONORO_GWD_MIX … … 789 822 ! Subroutines used to allocate/deallocate module variables 790 823 ! ======================================================== 791 SUBROUTINE ini_nonoro_gwd_mix(ngrid,nlayer )824 SUBROUTINE ini_nonoro_gwd_mix(ngrid,nlayer,nq) 792 825 793 826 IMPLICIT NONE … … 795 828 INTEGER, INTENT (in) :: ngrid ! number of atmospheric columns 796 829 INTEGER, INTENT (in) :: nlayer ! number of atmospheric layers 830 INTEGER, INTENT (in) :: nq ! number of atmospheric tracers 797 831 798 832 allocate(du_eddymix_gwd(ngrid,nlayer)) 799 833 allocate(dv_eddymix_gwd(ngrid,nlayer)) 834 allocate(dh_eddymix_gwd(ngrid,nlayer)) 835 allocate(dq_eddymix_gwd(ngrid,nlayer,nq)) 800 836 allocate(de_eddymix_rto(ngrid,nlayer+1)) 801 837 allocate(df_eddymix_flx(ngrid,nlayer+1)) … … 816 852 if (allocated(du_eddymix_gwd)) deallocate(du_eddymix_gwd) 817 853 if (allocated(dv_eddymix_gwd)) deallocate(dv_eddymix_gwd) 854 if (allocated(dh_eddymix_gwd)) deallocate(dh_eddymix_gwd) 855 if (allocated(dq_eddymix_gwd)) deallocate(dq_eddymix_gwd) 818 856 if (allocated(de_eddymix_rto)) deallocate(de_eddymix_rto) 819 857 if (allocated(df_eddymix_flx)) deallocate(df_eddymix_flx) -
trunk/LMDZ.MARS/libf/phymars/phyetat0_mod.F90
r3350 r3393 24 24 use nonoro_gwd_ran_mod, only: du_nonoro_gwd, dv_nonoro_gwd 25 25 use nonoro_gwd_mix_mod, only: du_eddymix_gwd, dv_eddymix_gwd, de_eddymix_rto, & 26 df_eddymix_flx !dr_depflux_gwd26 df_eddymix_flx, dh_eddymix_gwd, dq_eddymix_gwd 27 27 use compute_dtau_mod, only: dtau 28 28 use dust_rad_adjust_mod, only: dust_rad_adjust_prev,dust_rad_adjust_next … … 623 623 624 624 if (startphy_file) then 625 call get_field("dh_eddymix_gwd",dh_eddymix_gwd,found,indextime) 626 if (.not.found) then 627 write(*,*) "phyetat0: <dh_eddymix_gwd> not in file" 628 dh_eddymix_gwd(:,:)=0. 629 endif 630 else 631 dh_eddymix_gwd(:,:)=0. 632 endif ! if (startphy_file) 633 write(*,*) "phyetat0: Memory of PT tendency due to non-orographic GW mixing" 634 write(*,*) " <dh_eddymix_gwd> range:", & 635 minval(dh_eddymix_gwd), maxval(dh_eddymix_gwd) 636 637 638 if (startphy_file) then 625 639 call get_field("dv_nonoro_gwd",dv_nonoro_gwd,found,indextime) 626 640 if (.not.found) then … … 648 662 minval(dv_eddymix_gwd), maxval(dv_eddymix_gwd) 649 663 664 if (startphy_file) then 665 call get_field("dq_eddymix_gwd",dq_eddymix_gwd,found,indextime) 666 if (.not.found) then 667 write(*,*) "phyetat0: <dq_eddymix_gwd> not in file" 668 dq_eddymix_gwd(:,:,:)=0. 669 endif 670 else ! ! if (startphy_file) 671 dq_eddymix_gwd(:,:,:)=0. 672 endif ! if (startphy_file) 673 write(*,*) "phyetat0: Memory of tracers tendency due to non-orographic GW mixing" 674 write(*,*) " <dq_eddymix_gwd> range:", & 675 minval(dq_eddymix_gwd), maxval(dq_eddymix_gwd) 676 677 650 678 !if (startphy_file) then 651 679 ! call get_field("dr_depflux_gwd",dr_depflux_gwd,found,indextime) -
trunk/LMDZ.MARS/libf/phymars/phys_state_var_init_mod.F90
r3316 r3393 174 174 ! allocate arrays in "nonoro_gwd_mix_mod" 175 175 call end_nonoro_gwd_mix 176 call ini_nonoro_gwd_mix(ngrid,nlayer )176 call ini_nonoro_gwd_mix(ngrid,nlayer,nq) 177 177 178 178 ! allocate arrays in "dust_param_mod" -
trunk/LMDZ.MARS/libf/phymars/physiq_mod.F
r3369 r3393 1690 1690 & zplay, 1691 1691 & zmax_th, 1692 & pt, pu, pv, pq, 1692 & pt, pu, pv, pq, zh, 1693 1693 !loss, chemical reaction loss rates 1694 & pdt, pdu, pdv, pdq, 1694 & pdt, pdu, pdv, pdq, zdh, 1695 1695 ! zustrhi,zvstrhi, 1696 1696 & zdq_mix, d_t_mix, d_u_mix, d_v_mix)
Note: See TracChangeset
for help on using the changeset viewer.