Changeset 544 for trunk/LMDZ.MARS/libf


Ignore:
Timestamp:
Feb 27, 2012, 10:44:32 AM (13 years ago)
Author:
acolaitis
Message:

27/02/12 == AC

Continuation of thermals setting, comparisons with mesoscale results on Case C
Added possibility to call gcm (or 1d) with constant prescribed sensible heat flux, in the spirit of direct comparisons with LES

... This is directly comparable to the variable tke_heat_flux in namelist.input
... Requires the use of yamada4.F from terrestrial GCM (mixes more, seem more numerically stable)
... Usually requires high timesteps (>1000) to avoids crashes. Best approach is to compare
height of first model level z1 and teta_1 between LES and 1D, and increase the timesteps until results
between the two models are comparable (might require a slitghly different tke_heat_flux between the two models
due to difference in vertical diffusion schemes and subgrid effects)
... Syntax for use is to add "tke_heat_flux = ..." in callphys.def

Corrected some stuff with tke transport in thermals (which is anyway deactivated but one day maybe...)

Location:
trunk/LMDZ.MARS/libf/phymars
Files:
1 added
6 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.MARS/libf/phymars/callkeys.h

    r485 r544  
    1818     &   ,dustbin,nqchem_min,nltemodel,nircorr
    1919     
    20       COMMON/callkeys_r/topdustref,solarcondate,semi,alphan
     20      COMMON/callkeys_r/topdustref,solarcondate,semi,alphan,            &
     21     &   tke_heat_flux
    2122     
    2223      LOGICAL callrad,calldifv,calladj,callcond,callsoil,               &
     
    3637      real alphan
    3738      real solarcondate
     39      real tke_heat_flux
    3840
    3941      integer iddist
  • trunk/LMDZ.MARS/libf/phymars/calltherm_interface.F90

    r512 r544  
    158158       endif
    159159
    160 !       dtke_thermals=.false. !! default setting
    161 !       !call getin("dtke_thermals",dtke_thermals)
    162 !
    163 !       IF(dtke_thermals) THEN
    164 !          DO l=1,nlayermx
    165 !              q2_therm(:,l)=0.5*(q2(:,l)+q2(:,l+1))
    166 !          ENDDO
    167 !       ENDIF
     160       dtke_thermals=.false. !! default setting
     161       call getin("dtke_thermals",dtke_thermals)
     162       IF(dtke_thermals) THEN
     163          DO l=1,nlayermx
     164              q2_therm(:,l)=0.5*(q2(:,l)+q2(:,l+1))
     165          ENDDO
     166       ENDIF
    168167
    169168! **********************************************************************
     
    338337      endif
    339338
     339      if (dtke_thermals) then
     340      modname='tke'
     341      call thermcell_dqup(ngridmx,nlayermx,ptimestep     &
     342     &     ,fm_therm,entr_therm,detr_therm,  &
     343     &    masse,q2_therm,dq2_therm,modname,zdz)
     344      endif
     345
    340346      DO ig=1,ngridmx
    341347         hfmax(ig)=MAXVAL(heatFlux(ig,:)+heatFlux_down(ig,:))
     
    369375           endif
    370376
    371 !           IF(dtke_thermals) THEN
    372 !              DO l=2,nlayermx
    373 !                 pbl_dtke(:,l)=0.5*(dq2_therm(:,l-1)+dq2_therm(:,l))
    374 !              ENDDO
    375 ! 
    376 !              pbl_dtke(:,1)=0.5*dq2_therm(:,1)
    377 !              pbl_dtke(:,nlayermx+1)=0.
    378 !           ENDIF
     377           IF(dtke_thermals) THEN
     378              DO l=2,nlayermx
     379                 pbl_dtke(:,l)=0.5*(dq2_therm(:,l-1)+dq2_therm(:,l))
     380              ENDDO
     381 
     382              pbl_dtke(:,1)=0.5*dq2_therm(:,1)
     383              pbl_dtke(:,nlayermx+1)=0.
     384           ENDIF
    379385
    380386
  • trunk/LMDZ.MARS/libf/phymars/inifis.F

    r485 r544  
    203203         write(*,*) " topdustref = ",topdustref
    204204
     205         write(*,*) "Prescribed surface thermal flux (H/(rho*cp),K m/s)"
     206         tke_heat_flux=0. ! default value
     207         call getin("tke_heat_flux",tke_heat_flux)
     208         write(*,*) " tke_heat_flux = ",tke_heat_flux
     209         write(*,*) " 0 means the usual schemes are computing"
     210
    205211         write(*,*) "call radiative transfer ?"
    206212         callrad=.true. ! default value
  • trunk/LMDZ.MARS/libf/phymars/physiq.F

    r529 r544  
    1111#endif
    1212     $            )
     13
    1314
    1415      IMPLICIT NONE
     
    338339
    339340c Variables for PBL
    340 
     341      REAL zz1(ngridmx)
    341342      REAL lmax_th_out(ngridmx),zmax_th(ngridmx)
    342343      REAL, SAVE :: wstar(ngridmx)
     
    769770#endif
    770771
     772         IF (tke_heat_flux .ne. 0.) THEN
     773             zz1(:)=(pt(:,1)+pdt(:,1)*ptimestep)*(r/g)*
     774     &                 (-alog(pplay(:,1)/pplev(:,1)))
     775             pdt(:,1)=pdt(:,1) + (tke_heat_flux/zz1(:))*zpopsk(:,1)
     776         ENDIF
    771777
    772778c        Calling vdif (Martian version WITH CO2 condensation)
     
    19972003         call WRITEDIAGFI(ngrid,"pplev","Pressure","Pa",1,zplev)
    19982004         call WRITEDIAGFI(ngrid,"rho","rho","kg.m-3",1,rho)
     2005!         call WRITEDIAGFI(ngrid,"dtrad","rad. heat. rate",              &
     2006!     &              "K.s-1",1,dtrad/zpopsk)
     2007!        call WRITEDIAGFI(ngridmx,'sw_htrt','sw heat. rate',
     2008!     &                   'w.m-2',1,zdtsw/zpopsk)
     2009!        call WRITEDIAGFI(ngridmx,'lw_htrt','lw heat. rate',
     2010!     &                   'w.m-2',1,zdtlw/zpopsk)
     2011
    19992012! or output in diagfi.nc (for testphys1d)
    20002013         call WRITEDIAGFI(ngridmx,'ps','Surface pressure','Pa',0,ps)
  • trunk/LMDZ.MARS/libf/phymars/thermcell_main_mars.F90

    r532 r544  
    113113      REAL zdz,zbuoy(ngridmx,nlayermx),zw2m
    114114      LOGICAL activecell(ngridmx),activetmp(ngridmx)
    115       REAL a1,b1,ae,be,ad,bd,fdfu,b1inv,a1inv,omega
     115      REAL a1,b1,ae,be,ad,bd,fdfu,b1inv,a1inv,omega,adalim
    116116      INTEGER tic
    117117
     
    381381      b1inv=b1
    382382      omega=0.
     383      adalim=0.
    383384
    384385! One good config for 34/35 levels
     
    389390! Best configuration for 222 levels:
    390391
    391       omega=0.06
    392       b1=0.
    393       a1=1.
    394       a1inv=0.25*a1
    395       b1inv=0.0002
     392!      omega=0.06
     393!      b1=0.
     394!      a1=1.
     395!      a1inv=0.25*a1
     396!      b1inv=0.0002
     397!!
     398!!
     399!!      ae=0.9*ae
    396400
    397401! Best config for norad 222 levels:
    398 
    399 !       omega=0.06
    400 !       a1=1.
    401 !       b1=0.
    402 !       a1inv=a1
    403 !       be=1.1*be
    404 !       ad = 0.0004
    405 !       b1inv=0.00035
     402! with yamada4 and alim at sqrt(zlev)
     403
     404       omega=0.06
     405       a1=1.
     406       b1=0.
     407       a1inv=a1
     408       be=1.1*be
     409       ad = 0.0004
     410       b1inv=0.00035
     411       adalim=0.
     412
     413      b1inv=0.00025
    406414
    407415! Trying stuff :
     416
     417!      omega=0.04
     418!!      b1=0.
     419!      a1=1.
     420!      a1inv=a1
     421!      b1inv=0.0005689
     422!!      be=1.1*be
     423!!      ae=0.96*ae
     424
    408425
    409426!       omega=0.06
     
    431448            if (ztv(ig,1)>=(ztv(ig,2))) then
    432449               alim_star(ig,1)=MAX((ztv(ig,1)-ztv(ig,2)),0.)  &
    433      &                       *sqrt(zlev(ig,2))
     450!     &                       *sqrt(zlev(ig,2))
    434451!     &                       /sqrt(zlev(ig,2))
    435 !      &                       *zlev(ig,2)
     452      &                       *zlev(ig,2)
    436453               lalim(ig)=2
    437454               alim_star_tot(ig)=alim_star_tot(ig)+alim_star(ig,1)
     
    444461           if (ztv(ig,l)>(ztv(ig,l+1)+0.) .and. ztv(ig,1)>=ztv(ig,l) .and. (alim_star(ig,l-1) .ne. 0.)) then ! .and. (zlev(ig,l+1) .lt. 1000.)) then
    445462               alim_star(ig,l)=MAX((ztv(ig,l)-ztv(ig,l+1)),0.)  &
    446      &                       *sqrt(zlev(ig,l+1))
    447 !      &                       *zlev(ig,2)
     463!     &                       *sqrt(zlev(ig,l+1))
     464!     &                       /sqrt(zlev(ig,l+1))
     465      &                       *zlev(ig,l+1)
    448466                lalim(ig)=l+1
    449467               alim_star_tot(ig)=alim_star_tot(ig)+alim_star(ig,l)
     
    562580          if(zbuoy(ig,l) .gt. 0.) then
    563581             if(l .lt. lalim(ig)) then
    564                 detr_star(ig,l)=0.
     582
     583!                detr_star(ig,l)=0.
     584                 detr_star(ig,l) = f_star(ig,l)*zdz*              &
     585            &  adalim
    565586             else
    566587
     
    628649!---------------------------------------------------------------------------
    629650
    630       DO tic=0,0  ! internal convergence loop
     651      DO tic=0,5  ! internal convergence loop
    631652      activetmp(:)=activecell(:) .and. f_star(:,l+1)>1.e-10
    632653      do ig=1,ngridmx
     
    674695          if(zbuoy(ig,l) .gt. 0.) then
    675696             if(l .lt. lalim(ig)) then
    676                 detr_star(ig,l)=0.
     697
     698!                detr_star(ig,l)=0.
     699                 detr_star(ig,l) = f_star(ig,l)*zdz*              &
     700            &  adalim
     701
    677702             else
    678703                 detr_star(ig,l) = f_star(ig,l)*zdz*              &
  • trunk/LMDZ.MARS/libf/phymars/vdifc.F

    r529 r544  
    1010#endif
    1111     &                )
    12        USE ioipsl_getincom
    1312      IMPLICIT NONE
    1413
     
    369368c    ** schema de diffusion turbulente dans la couche limite
    370369c       ----------------------------------------------------
     370       IF (tke_heat_flux .eq. 0.) THEN
    371371
    372372       CALL vdif_kc(ptimestep,g,pzlev,pzlay
     
    374374     &              ,pq2,zkv,zkh,zq)
    375375
    376 !      pt(:,:)=ph(:,:)*ppopsk(:,:)
    377 !      CALL yamada4(ngrid,nlay,ptimestep,g,r,pplev,pt
    378 !     s   ,pzlev,pzlay,pu,pv,ph,zcdv_true,pq2,zkv,zkh,zkq,ust
    379 !     s   ,8)
     376      ELSE
     377
     378      pt(:,:)=zh(:,:)*ppopsk(:,:)
     379      CALL yamada4(ngrid,nlay,ptimestep,g,r,pplev,pt
     380     s   ,pzlev,pzlay,pu,pv,ph,zcdv_true,pq2,zkv,zkh,zkq,ust
     381     s   ,8)
     382
     383      ENDIF
    380384
    381385      if ((doubleq).and.(ngrid.eq.1)) then
     
    523527
    524528      z4st=4.*5.67e-8*ptimestep
     529      IF (tke_heat_flux .eq. 0.) THEN
    525530      DO ig=1,ngrid
    526531         zdplanck(ig)=z4st*pemis(ig)*ptsrf(ig)*ptsrf(ig)*ptsrf(ig)
    527532      ENDDO
     533      ELSE
     534         zdplanck(:)=0.
     535      ENDIF
    528536
    529537! calcul de zc et zd pour la couche top en prenant en compte le terme
Note: See TracChangeset for help on using the changeset viewer.