Changeset 1236 for trunk/LMDZ.MARS/libf
- Timestamp:
- May 5, 2014, 11:38:51 AM (11 years ago)
- Location:
- trunk/LMDZ.MARS/libf/phymars
- Files:
-
- 1 added
- 6 deleted
- 5 edited
Legend:
- Unmodified
- Added
- Removed
-
trunk/LMDZ.MARS/libf/phymars/meso_inc/meso_inc_les.F
r790 r1236 2 2 3 3 DO ig=1,ngrid 4 !! sensible heat flux in W/m25 6 sensheat(ig) = zflubid(ig)-capcal(ig)*zdtsdif(ig)4 !!! sensible heat flux in W/m2 5 ! 6 ! sensheat(ig) = zflubid(ig)-capcal(ig)*zdtsdif(ig) 7 7 8 8 !! u star in similarity theory in m/s … … 16 16 DO ig=1,ngrid 17 17 18 ! New SL parametrization, correct formulation for sensheat :19 20 sensheat(ig) = (pplay(ig,1)/(r*pt(ig,1)))*cpp21 & *sqrt(pu(ig,1)*pu(ig,1) + pv(ig,1)*pv(ig,1)22 & + (log(1.+0.7*wstar(ig) + 2.3*wstar(ig)**2))**2)23 & *zcdh(ig)*(tsurf(ig)-zh(ig,1))18 !! New SL parametrization, correct formulation for sensheat : 19 ! 20 ! sensheat(ig) = (pplay(ig,1)/(r*pt(ig,1)))*cpp 21 ! & *sqrt(pu(ig,1)*pu(ig,1) + pv(ig,1)*pv(ig,1) 22 ! & + (log(1.+0.7*wstar(ig) + 2.3*wstar(ig)**2))**2) 23 ! & *zcdh(ig)*(tsurf(ig)-zh(ig,1)) 24 24 25 25 ! New SL parametrization, ustar is more accurately computed in vdif_cd : … … 40 40 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 41 41 !!! LES LES 42 IF ( flag_LES) THEN42 IF (turb_resolved) THEN 43 43 44 44 write (*,*) '************************************************' … … 49 49 write (*,*) '************************************************' 50 50 51 DO ig=1,ngrid52 wstar(ig)=0. !! no additional gustiness needed in surface layer (see vdifc.F)53 DO l=1,nlayer54 zdvdif(ig,l) = 0.55 zdudif(ig,l) = 0.56 zdhdif(ig,l) = 0.57 ENDDO58 ENDDO59 51 IF (lifting .and. doubleq) THEN 60 52 !! lifted dust is injected in the first layer. -
trunk/LMDZ.MARS/libf/phymars/physiq.F
r1233 r1236 6 6 $ ,pu,pv,pt,pq 7 7 $ ,pw 8 $ ,pdu,pdv,pdt,pdq,pdpsrf,tracerdyn 9 #ifdef MESOSCALE 10 $ ,output_tab2d, output_tab3d, flag_LES 11 #endif 12 $ ) 8 $ ,pdu,pdv,pdt,pdq,pdpsrf,tracerdyn) 13 9 14 10 use tracer_mod, only: noms, mmol, igcm_co2, igcm_n2, … … 32 28 use dimradmars_mod, only: tauscaling, aerosol, 33 29 & dtrad, fluxrad_sky, fluxrad, albedo 34 use turb_mod, only: q2, wstar, hfmax_th 30 use turb_mod, only: q2, wstar, ustar, sensibFlux, 31 & zmax_th, hfmax_th, turb_resolved 35 32 use planete_h, only: aphelie, periheli, year_day, peri_day, 36 33 & obliquit … … 39 36 use comsoil_h, only: mlayer,layer 40 37 use surfdat_h, only: z0_default 38 use comm_wrf 41 39 #else 42 40 use phyredem, only: physdem0, physdem1 … … 170 168 !#include "slope.h" 171 169 172 #ifdef MESOSCALE173 #include "wrf_output_2d.h"174 #include "wrf_output_3d.h"175 !#include "advtrac.h" !!! this is necessary for tracers (in dyn3d)176 #include "meso_inc/meso_inc_var.F"177 #endif178 179 170 c Arguments : 180 171 c ----------- … … 359 350 c Variables for PBL 360 351 REAL zz1(ngrid) 361 REAL lmax_th_out(ngrid) ,zmax_th(ngrid)352 REAL lmax_th_out(ngrid) 362 353 REAL pdu_th(ngrid,nlayer),pdv_th(ngrid,nlayer) 363 354 REAL pdt_th(ngrid,nlayer),pdq_th(ngrid,nlayer,nq) … … 371 362 REAL T_out1(ngrid) 372 363 REAL, ALLOCATABLE, DIMENSION(:) :: z_out ! height of interpolation between z0 and z1 [meters] 373 REAL ustar(ngrid),tstar(ngrid) ! friction velocity and friction potential temp364 REAL tstar(ngrid) ! friction velocity and friction potential temp 374 365 REAL L_mo(ngrid),vhf(ngrid),vvv(ngrid) 375 366 ! REAL zu2(ngrid) 376 REAL sensibFlux(ngrid)377 367 378 368 c======================================================================= … … 812 802 enddo 813 803 814 815 #ifdef MESOSCALE816 IF (.not.flag_LES) THEN817 #endif818 804 c ---------------------- 819 805 c Treatment of a special case : using new surface layer (Richardson based) … … 822 808 c a unit subgrid gustiness. Remember that thermals should be used we using the 823 809 c Richardson based surface layer model. 824 IF ( .not.calltherm .and. callrichsl ) THEN 810 IF ( .not.calltherm 811 . .and. callrichsl 812 . .and. .not.turb_resolved) THEN 825 813 DO ig=1, ngrid 826 814 IF (zh(ig,1) .lt. tsurf(ig)) THEN … … 834 822 ENDIF 835 823 c ---------------------- 836 #ifdef MESOSCALE837 ENDIF838 #endif839 824 840 825 IF (tke_heat_flux .ne. 0.) THEN … … 851 836 $ zdum1,zdum2,zdh,pdq,zflubid, 852 837 $ zdudif,zdvdif,zdhdif,zdtsdif,q2, 853 & zdqdif,zdqsdif,wstar,zcdv,zcdh,hfmax_th,sensibFlux 854 #ifdef MESOSCALE 855 & ,flag_LES 856 #endif 857 & ) 858 838 & zdqdif,zdqsdif,wstar,zcdv,zcdh,hfmax_th,sensibFlux) 859 839 860 840 #ifdef MESOSCALE 861 841 #include "meso_inc/meso_inc_les.F" 862 842 #endif 863 DO l=1,nlayer 843 844 DO ig=1,ngrid 845 zdtsurf(ig)=zdtsurf(ig)+zdtsdif(ig) 846 ENDDO 847 848 IF (.not.turb_resolved) THEN 849 DO l=1,nlayer 864 850 DO ig=1,ngrid 865 851 pdv(ig,l)=pdv(ig,l)+zdvdif(ig,l) … … 869 855 zdtdif(ig,l)=zdhdif(ig,l)*zpopsk(ig,l) ! for diagnostic only 870 856 ENDDO 871 ENDDO872 873 DO ig=1,ngrid874 zdtsurf(ig)=zdtsurf(ig)+zdtsdif(ig)875 857 ENDDO 876 858 877 if (tracer) then 878 #ifdef MESOSCALE 879 IF (.not.flag_LES) THEN 880 #endif 859 if (tracer) then 881 860 DO iq=1, nq 882 861 DO l=1,nlayer … … 891 870 ENDDO 892 871 ENDDO 893 #ifdef MESOSCALE 872 end if ! of if (tracer) 894 873 ENDIF 895 #endif896 end if ! of if (tracer)897 874 898 875 ELSE … … 901 878 s (fluxrad(ig)+fluxgrd(ig))/capcal(ig) 902 879 ENDDO 903 #ifdef MESOSCALE 904 IF (flag_LES) THEN 905 write(*,*) 'LES mode !' 880 IF (turb_resolved) THEN 881 write(*,*) 'Turbulent-resolving mode !' 906 882 write(*,*) 'Please set calldifv to T in callphys.def' 907 883 STOP 908 884 ENDIF 909 #endif910 885 ENDIF ! of IF (calldifv) 911 886 … … 914 889 c ----------------------------- 915 890 916 if(calltherm ) then891 if(calltherm .and. .not.turb_resolved) then 917 892 918 893 call calltherm_interface(ngrid,nlayer,nq, … … 949 924 lmax_th_out(:)=real(lmax_th(:)) 950 925 951 926 else !of if calltherm 952 927 lmax_th(:)=0 953 928 wstar(:)=0. 954 929 hfmax_th(:)=0. 955 930 lmax_th_out(:)=0. 956 931 end if 957 932 958 933 c----------------------------------------------------------------------- … … 1143 1118 END IF ! of IF (sedimentation) 1144 1119 1145 c Add lifted dust to tendancies after sedimentation in the LES 1146 #ifdef MESOSCALE 1147 #include "meso_inc/meso_inc_lift_les.F" 1148 #endif 1120 c Add lifted dust to tendancies after sedimentation in the LES (AC) 1121 IF (turb_resolved) THEN 1122 DO iq=1, nq 1123 DO l=1,nlayer 1124 DO ig=1,ngrid 1125 pdq(ig,l,iq)=pdq(ig,l,iq)+ zdqdif(ig,l,iq) 1126 ENDDO 1127 ENDDO 1128 ENDDO 1129 DO iq=1, nq 1130 DO ig=1,ngrid 1131 dqsurf(ig,iq)=dqsurf(ig,iq) + zdqsdif(ig,iq) 1132 ENDDO 1133 ENDDO 1134 ENDIF 1149 1135 1150 1136 c … … 1885 1871 !endif of ifndef MESOSCALE 1886 1872 1887 1888 1889 1873 #ifdef MESOSCALE 1890 !!! 1891 !!! OUTPUT FIELDS 1892 !!! 1893 !wtsurf(1:ngrid) = tsurf(1:ngrid) !! surface temperature 1894 !wco2ice(1:ngrid) = co2ice(1:ngrid) !! co2 ice 1895 TAU_lay(:)=tau(:,1)!!true opacity (not a reference like tauref) 1896 IF (tracer) THEN 1897 mtot(1:ngrid) = mtot(1:ngrid) * 1.e6 / rho_ice 1898 icetot(1:ngrid) = icetot(1:ngrid) * 1.e6 / rho_ice 1899 !! JF 1874 1875 !! see comm_wrf. 1876 !! not needed when an array is already in a shared module. 1877 !! --> example : hfmax_th, zmax_th 1878 1879 !state real HR_SW ikj misc 1 - h "HR_SW" "HEATING RATE SW" "K/s" 1880 comm_HR_SW(1:ngrid,1:nlayer) = zdtsw(1:ngrid,1:nlayer) 1881 !state real HR_LW ikj misc 1 - h "HR_LW" "HEATING RATE LW" "K/s" 1882 comm_HR_LW(1:ngrid,1:nlayer) = zdtlw(1:ngrid,1:nlayer) 1883 !state real SWDOWNZ ij misc 1 - h "SWDOWNZ" "DOWNWARD SW FLUX AT SURFACE" "W m-2" 1884 comm_SWDOWNZ(1:ngrid) = fluxsurf_sw_tot(1:ngrid) 1885 !state real TAU_DUST ij misc 1 - h "TAU_DUST" "REFERENCE VISIBLE DUST OPACITY" "" 1886 comm_TAU_DUST(1:ngrid) = tauref(1:ngrid) 1887 !state real RDUST ikj misc 1 - h "RDUST" "DUST RADIUS" "m" 1888 comm_RDUST(1:ngrid,1:nlayer) = rdust(1:ngrid,1:nlayer) 1889 !state real QSURFDUST ij misc 1 - h "QSURFDUST" "DUST MASS AT SURFACE" "kg m-2" 1900 1890 IF (igcm_dust_mass .ne. 0) THEN 1901 qsurfdust(1:ngrid) = qsurf(1:ngrid,igcm_dust_mass) 1891 comm_QSURFDUST(1:ngrid) = qsurf(1:ngrid,igcm_dust_mass) 1892 ELSE 1893 comm_QSURFDUST(1:ngrid) = 0. 1902 1894 ENDIF 1903 IF (igcm_h2o_ice .ne. 0) THEN 1904 qsurfice(1:ngrid) = qsurf(1:ngrid,igcm_h2o_ice) 1905 vmr=1.e6 * zq(1:ngrid,1:nlayer,igcm_h2o_ice) 1906 . *mmean(1:ngrid,1:nlayer) / mmol(igcm_h2o_ice) 1895 !state real MTOT ij misc 1 - h "MTOT" "TOTAL MASS WATER VAPOR in pmic" "pmic" 1896 comm_MTOT(1:ngrid) = mtot(1:ngrid) * 1.e6 / rho_ice 1897 !state real ICETOT ij misc 1 - h "ICETOT" "TOTAL MASS WATER ICE" "kg m-2" 1898 comm_ICETOT(1:ngrid) = icetot(1:ngrid) * 1.e6 / rho_ice 1899 !state real VMR_ICE ikj misc 1 - h "VMR_ICE" "VOL. MIXING RATIO ICE" "ppm" 1900 IF (igcm_h2o_ice .ne. 0) THEN 1901 comm_VMR_ICE(1:ngrid,1:nlayer) = 1.e6 1902 . * zq(1:ngrid,1:nlayer,igcm_h2o_ice) 1903 . * mmean(1:ngrid,1:nlayer) / mmol(igcm_h2o_ice) 1904 ELSE 1905 comm_VMR_ICE(1:ngrid,1:nlayer) = 0. 1907 1906 ENDIF 1908 !! Dust quantity integration along the vertical axe 1909 dustot(:)=0 1910 IF (igcm_dust_mass .ne. 0) THEN 1911 do ig=1,ngrid 1912 do l=1,nlayer 1913 dustot(ig) = dustot(ig) + 1914 & zq(ig,l,igcm_dust_mass) 1915 & * (zplev(ig,l) - zplev(ig,l+1)) / g 1916 enddo 1917 enddo 1918 ENDIF 1919 ENDIF 1920 !! TAU water ice as seen by TES 1921 if (activice) tauTES = taucloudtes 1922 c AUTOMATICALLY GENERATED FROM REGISTRY 1923 #include "fill_save.inc" 1907 !state real TAU_ICE ij misc 1 - h "TAU_ICE" "CLOUD OD at 825 cm-1 TES" "" 1908 comm_TAU_ICE(1:ngrid) = taucloudtes(1:ngrid) 1909 !state real RICE ikj misc 1 - h "RICE" "ICE RADIUS" "m" 1910 comm_RICE(1:ngrid,1:nlayer) = rice(1:ngrid,1:nlayer) 1924 1911 #else 1925 1912 #ifndef MESOINI -
trunk/LMDZ.MARS/libf/phymars/turb_mod.F90
r1224 r1236 4 4 REAL,SAVE,ALLOCATABLE :: q2(:,:) ! Turbulent Kinetic Energy 5 5 REAL,allocatable,SAVE :: l0(:) 6 REAL,SAVE,ALLOCATABLE :: ustar(:) 6 7 REAL,SAVE,ALLOCATABLE :: wstar(:) 7 8 REAL,SAVE,ALLOCATABLE :: hfmax_th(:) 9 REAL,SAVE,ALLOCATABLE :: zmax_th(:) 10 REAL,SAVE,ALLOCATABLE :: sensibFlux(:) 11 LOGICAL :: turb_resolved = .false. 12 ! this is a flag to say 'turbulence is resolved' 13 ! mostly for LES use. default is FALSE (for GCM and mesoscale) 8 14 9 15 contains … … 18 24 allocate(l0(ngrid)) 19 25 allocate(wstar(ngrid)) 26 allocate(ustar(ngrid)) 20 27 allocate(hfmax_th(ngrid)) 21 28 allocate(zmax_th(ngrid)) 29 allocate(sensibFlux(ngrid)) 30 22 31 end subroutine ini_turb_mod 23 32 -
trunk/LMDZ.MARS/libf/phymars/vdif_cd.F
r1226 r1236 1 1 SUBROUTINE vdif_cd(ngrid,nlay,pz0, 2 & pg,pz,pu,pv,wstar,pts,ph,pcdv,pcdh 3 #ifdef MESOSCALE 4 & ,flag_LES 5 #endif 6 & ) 2 & pg,pz,pu,pv,wstar,pts,ph,pcdv,pcdh) 7 3 USE comcstfi_h 4 use turb_mod, only: turb_resolved 8 5 IMPLICIT NONE 9 6 c======================================================================= … … 52 49 REAL, INTENT(IN) :: wstar(ngrid) 53 50 REAL, INTENT(OUT) :: pcdv(ngrid),pcdh(ngrid) ! momentum and heat drag coefficient 54 55 #ifdef MESOSCALE56 LOGICAL, INTENT(IN) :: flag_LES !! pour LES avec isfflx!=057 #endif58 51 59 52 c Local: … … 160 153 zu2(ig)=pu(ig,1)*pu(ig,1) + pv(ig,1)*pv(ig,1) 161 154 & + (log(1.+0.7*wstar(ig) + 2.3*wstar(ig)**2))**2 162 #ifdef MESOSCALE 163 if(flag_LES) then 155 if(turb_resolved) then 164 156 zu2(ig)=MAX(zu2(ig),1.) 165 157 endif 166 #endif167 158 ! zu2(ig)=pu(ig,1)*pu(ig,1) + pv(ig,1)*pv(ig,1) + (0.5*wstar(ig))**2 168 159 -
trunk/LMDZ.MARS/libf/phymars/vdifc.F
r1226 r1236 6 6 $ pdudif,pdvdif,pdhdif,pdtsrf,pq2, 7 7 $ pdqdif,pdqsdif,wstar,zcdv_true,zcdh_true, 8 $ hfmax,sensibFlux 9 #ifdef MESOSCALE 10 & ,flag_LES 11 #endif 12 & ) 8 $ hfmax,sensibFlux) 9 13 10 use tracer_mod, only: noms, igcm_dust_mass, igcm_dust_number, 14 11 & igcm_dust_submicron, igcm_h2o_vap, … … 16 13 use surfdat_h, only: watercaptag, frost_albedo_threshold, dryness 17 14 USE comcstfi_h 15 use turb_mod, only: turb_resolved 18 16 IMPLICIT NONE 19 17 … … 156 154 REAL,INTENT(OUT) :: sensibFlux(ngrid) 157 155 158 #ifdef MESOSCALE159 LOGICAL flag_LES !! pour LES avec isfflx!=0160 #endif161 156 c ** un petit test de coherence 162 157 c -------------------------- … … 330 325 331 326 CALL vdif_cd(ngrid,nlay,pz0,g,pzlay,pu,pv,wstar,ptsrf,ph 332 & ,zcdv_true,zcdh_true 333 #ifdef MESOSCALE 334 & ,flag_LES 335 #endif 336 & ) 327 & ,zcdv_true,zcdh_true) 337 328 338 329 zu2(:)=pu(:,1)*pu(:,1)+pv(:,1)*pv(:,1) … … 554 545 555 546 llnt(:)=1 556 #ifdef MESOSCALE 557 IF (.not.flag_LES) THEN 558 #endif 547 IF (.not.turb_resolved) THEN 559 548 IF (callcond) THEN 560 549 DO ig=1,ngrid … … 570 559 ENDIF 571 560 572 #ifdef MESOSCALE573 561 ENDIF 574 #endif575 562 576 563 DO ig=1,ngrid … … 717 704 end do 718 705 else 706 #endif 719 707 call dustlift(ngrid,nlay,nq,rho,zcdh_true,zcdh,co2ice, 720 708 & pdqsdif) 709 #ifndef MESOSCALE 721 710 endif !doubleq.AND.submicron 722 #else723 call dustlift(ngrid,nlay,nq,rho,zcdh_true,zcdh,co2ice,724 & pdqsdif)725 711 #endif 726 712 else
Note: See TracChangeset
for help on using the changeset viewer.