Changeset 284 for trunk/LMDZ.MARS/libf


Ignore:
Timestamp:
Sep 7, 2011, 3:20:37 PM (13 years ago)
Author:
acolaitis
Message:

--- AC 07/09/2011 ---

  • Added new flag for the Richardson-based surface layer :

callrichsl, can be changed in callphys.def

One should always use the thermals model when using this surface layer model.
Somes cases (weakly unstable with low winds), when not using thermals, won't be well represented by the
Richardson surface layer. This stands for Mesoscale and Gcm but not for LES model.

Correct configs :

callrichsl = .true.
calltherm = .true.

callrichsl = .false.
calltherm = .false.

callrichsl = .false.
calltherm = .true.

Previously unstable config :

callrichsl = .true.
calltherm = .false.

  • To be able to run without thermals and with the new surface layer, a modification has been made to

physiq.F to account for gustiness in GCM and MESOSCALE for negative Richardson, so that :

callrichsl = .true.
calltherm = .false.

can now be used without problems, but is not recommended.

  • Consequently, callrichsl = .false. is now the default configuration for thermals.

We recall the available options in callphys.def for thermals :

outptherm = BOOLEAN (.false. by default) : outputs thermals related quantities (lots of diagfi)
nsplit_thermals = INTEGER (50 by default in gcm, 2 in mesoscale) : subtimestep for thermals model.

It is recommended to use at least 40 in the gcm, and at least 2 in the mesoscale.
The user can lower these values but should check it's log for anomalies or errors regarding
tracer transport in the thermals, or "granulosity" in the outputs for wmax, lmax and hfmax.


Location:
trunk/LMDZ.MARS/libf/phymars
Files:
8 edited

Legend:

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

    r234 r284  
    1212     &   ,callg2d,linear,rayleigh,tracer,active,doubleq,submicron       &
    1313     &   ,lifting,callddevil,scavenging,sedimentation,activice,water    &
    14      &   ,caps,photochem,calltherm,outptherm,callslope
     14     &   ,caps,photochem,calltherm,outptherm,callrichsl,callslope
    1515     
    1616      COMMON/callkeys_i/iradia,iaervar,iddist,ilwd,ilwb,ilwn,ncouche    &
     
    2424     &   ,callnirco2,callnlte,callthermos,callconduct,                  &
    2525     &    calleuv,callmolvis,callmoldiff,thermochem,thermoswater        &
    26      &   ,calltherm,outptherm,callslope
     26     &   ,calltherm,outptherm,callrichsl,callslope
    2727
    2828
  • trunk/LMDZ.MARS/libf/phymars/calltherm_interface.F90

    r185 r284  
    7171      REAL buoyancyEst(ngridmx,nlayermx)
    7272      REAL hfmax(ngridmx),wmax(ngridmx)
    73 
    74       REAL tstart,tstop
    7573
    7674!---------------------------------------------------------
     
    135133         endif
    136134
    137          call cpu_time(tstart)
    138 
    139135         CALL calltherm_mars(ptimestep,zzlev,zzlay &
    140136     &      ,pplay,pplev,pphi &
     
    146142     &      ,zpopsk,ztla,heatFlux,heatFlux_down &
    147143     &      ,buoyancyOut,buoyancyEst,hfmax,wmax)
    148           call cpu_time(tstop)
    149          print*,'TOTAL elapsed time in thermals : ',tstop-tstart
    150 
    151144
    152145! Accumulation des  tendances. On n'accumule pas les quantités de traceurs car celle ci n'a pas du changer
  • trunk/LMDZ.MARS/libf/phymars/calltherm_mars.F90

    r277 r284  
    9999         r_aspect_thermals=0.7
    100100#else
    101          nsplit_thermals=40
     101         nsplit_thermals=50
    102102         r_aspect_thermals=2.
    103103#endif
  • trunk/LMDZ.MARS/libf/phymars/inifis.F

    r283 r284  
    252252          stop
    253253         endif
     254
     255         write(*,*) "call Richardson-based surface layer ?"
     256         callrichsl=.false. ! default value
     257         call getin("callrichsl",callrichsl)
     258         write(*,*) " callrichsl = ",callrichsl
    254259
    255260         write(*,*) "call CO2 condensation ?"
  • trunk/LMDZ.MARS/libf/phymars/meso_inc/meso_inc_les.F

    r268 r284  
    1          DO ig=1,ngrid
    2           !! sensible heat flux in W/m2
    3 !          hfx(ig) = zflubid(ig)-capcal(ig)*zdtsdif(ig)
     1         if (callrichsl .eq. .false.) then
     2       
     3             DO ig=1,ngrid
     4!! sensible heat flux in W/m2
     5
     6             hfx(ig) = zflubid(ig)-capcal(ig)*zdtsdif(ig)
     7
     8!! u star in similarity theory in m/s
     9             ust(ig) = 0.4
     10     .               * sqrt( pu(ig,1)*pu(ig,1) + pv(ig,1)*pv(ig,1) )
     11     .               / log( 1.E+0 + zzlay(ig,1)/z0_default )
     12             ENDDO
     13
     14         else
     15
     16            DO ig=1,ngrid
    417
    518! New SL parametrization, correct formulation for hfx :
    619
    7           hfx(ig) = (pplay(ig,1)/(r*pt(ig,1)))*cpp
    8      &    *sqrt((pu(ig,1)*pu(ig,1) + pv(ig,1)*pv(ig,1)))
    9      &    *zcdh(ig)*(tsurf(ig)-zh(ig,1))
     20            hfx(ig) = (pplay(ig,1)/(r*pt(ig,1)))*cpp
     21     &        *sqrt(pu(ig,1)*pu(ig,1) + pv(ig,1)*pv(ig,1)
     22     &        + (1.0*wmax_th(ig))**2)
     23     &        *zcdh(ig)*(tsurf(ig)-zh(ig,1))
    1024
    11           !! u star in similarity theory in m/s
    12 !          ust(ig) = 0.4
    13 !     .               * sqrt( pu(ig,1)*pu(ig,1) + pv(ig,1)*pv(ig,1) )
    14 !     .               / log( 1.E+0 + zzlay(ig,1)/z0_default )
    1525
    1626! New SL parametrization, ust is more accurately computed in vdif_cd :
    17         ust(ig) = sqrt(zcdv(ig)*(pu(ig,1)*pu(ig,1) + pv(ig,1)*pv(ig,1)))
     27            ust(ig) = sqrt(zcdv(ig)*
     28     &   (pu(ig,1)*pu(ig,1) + pv(ig,1)*pv(ig,1) + (1.0*wmax_th(ig))**2)
     29     &                     )
    1830
    19          ENDDO   
     31            ENDDO   
     32
     33         endif  !of if callrichsl
     34
    2035!         write (*,*) 'PHYS HFX cp zdts', hfx(100), zflubid(100),
    2136!     .       capcal(100),
  • trunk/LMDZ.MARS/libf/phymars/physiq.F

    r283 r284  
    694694         enddo
    695695
     696c Treatment of a special case : using new surface layer (Richardson based)
     697c without using the thermals in gcm and mesoscale can yield problems in
     698c weakly unstable situations when winds are near to 0. For those cases, we add
     699c a unit subgrid gustiness. Remember that thermals should be used we using the
     700c Richardson based surface layer model.
     701
     702#ifdef MESOSCALE
     703      IF (flag_LES .eq. .false.) THEN
     704        IF ((calltherm .eq. .false.) .and. (callrichsl .eq. .true.)) THEN
     705          DO ig=1, ngridmx
     706             IF (zh(ig,1) .lt. tsurf(ig)) THEN
     707               wmax_th(ig)=1.
     708             ENDIF       
     709          ENDDO
     710        ENDIF
     711      ENDIF
     712#else
     713      IF ((calltherm .eq. .false.) .and. (callrichsl .eq. .true.)) THEN
     714        DO ig=1, ngridmx
     715          IF (zh(ig,1) .lt. tsurf(ig)) THEN
     716            wmax_th(ig)=1.
     717          ENDIF
     718        ENDDO
     719      ENDIF   
     720#endif
     721
    696722c        Calling vdif (Martian version WITH CO2 condensation)
    697723         CALL vdifc(ngrid,nlayer,nq,co2ice,zpopsk,
     
    14331459        call WRITEDIAGFI(ngrid,"co2ice","co2 ice thickness","kg.m-2",2,
    14341460     &                  co2ice)
     1461
    14351462c         call WRITEDIAGFI(ngrid,"temp7","temperature in layer 7",
    14361463c     &                  "K",2,zt(1,7))
    1437          call WRITEDIAGFI(ngrid,"fluxsurf_lw","fluxsurf_lw","W.m-2",2,
    1438      &                  fluxsurf_lw)
    1439          call WRITEDIAGFI(ngrid,"fluxsurf_sw","fluxsurf_sw","W.m-2",2,
    1440      &                  fluxsurf_sw_tot)
    1441          call WRITEDIAGFI(ngrid,"fluxtop_lw","fluxtop_lw","W.m-2",2,
    1442      &                  fluxtop_lw)
    1443          call WRITEDIAGFI(ngrid,"fluxtop_sw","fluxtop_sw","W.m-2",2,
    1444      &                  fluxtop_sw_tot)
     1464c         call WRITEDIAGFI(ngrid,"fluxsurf_lw","fluxsurf_lw","W.m-2",2,
     1465c     &                  fluxsurf_lw)
     1466c         call WRITEDIAGFI(ngrid,"fluxsurf_sw","fluxsurf_sw","W.m-2",2,
     1467c     &                  fluxsurf_sw_tot)
     1468c         call WRITEDIAGFI(ngrid,"fluxtop_lw","fluxtop_lw","W.m-2",2,
     1469c     &                  fluxtop_lw)
     1470c         call WRITEDIAGFI(ngrid,"fluxtop_sw","fluxtop_sw","W.m-2",2,
     1471c     &                  fluxtop_sw_tot)
    14451472         call WRITEDIAGFI(ngrid,"temp","temperature","K",3,zt)
    14461473        call WRITEDIAGFI(ngrid,"u","Zonal wind","m.s-1",3,zu)
     
    17341761         endif
    17351762
    1736 ! ---
    1737 
    1738 
    1739 
    17401763         if(calltherm) then
    17411764
  • trunk/LMDZ.MARS/libf/phymars/vdif_cd.F

    r276 r284  
    3636
    3737#include "comcstfi.h"
     38#include "callkeys.h"
    3839
    3940c   Arguments:
     
    8788c   ------------------
    8889
    89       reynolds(:)=0.
    90 
    9190c Original formulation :
    9291
    93 c      DO ig=1,ngrid
    94 c         z1=1.E+0 + pz(ig,1)/pz0(ig)
    95 c         zcd0=karman/log(z1)
    96 c         zcd0=zcd0*zcd0
    97 c         pcdv(ig)=zcd0
    98 c         pcdh(ig)=zcd0
    99 c      ENDDO
     92      if(callrichsl .eq. .false.) then
     93
     94      DO ig=1,ngrid
     95         z1=1.E+0 + pz(ig,1)/pz0(ig)
     96         zcd0=karman/log(z1)
     97         zcd0=zcd0*zcd0
     98         pcdv(ig)=zcd0
     99         pcdh(ig)=zcd0
     100      ENDDO
    100101     
    101102!      print*,'old : cd,ch; ',pcdv,pcdh
     103      else
     104
     105      reynolds(:)=0.
    102106
    103107c New formulation (AC) :
     
    224228! Some useful diagnostics :
    225229
    226 !        call WRITEDIAGFI(ngrid,'RiB',
     230!       call WRITEDIAGFI(ngrid,'RiB',
    227231!     &              'Bulk Richardson nb','no units',
    228232!     &                         2,rib)
     
    241245
    242246
     247      endif !of if call richardson surface layer
     248
    243249      RETURN
    244250      END
  • trunk/LMDZ.MARS/libf/phymars/vdifc.F

    r283 r284  
    8686      REAL zc(ngridmx,nlayermx),zd(ngridmx,nlayermx)
    8787      REAL zcst1
    88       REAL zu2
     88      REAL zu2(ngridmx)
    8989
    9090      EXTERNAL SSUM,SCOPY
     
    234234     &             ,zcdv_true,zcdh_true)
    235235
    236       DO ig=1,ngrid
    237 
    238         zu2=pu(ig,1)*pu(ig,1)+pv(ig,1)*pv(ig,1)
    239      &             +(1.*wmax(ig))**2        ! subgrid gustiness added by quadratic interpolation with a coeff beta, here beta=1. (tuned from
     236
     237        IF (callrichsl .eq. .true.) then
     238           zu2(:)=pu(:,1)*pu(:,1)+pv(:,1)*pv(:,1)
     239     &             +(1.*wmax(:))**2        ! subgrid gustiness added by quadratic interpolation with a coeff beta, here beta=1. (tuned from
    240240                                            ! LES comparisons. This parameter is linked to the thermals settings)
    241        
    242         zcdv(ig)=zcdv_true(ig)*sqrt(zu2)     ! 1 / bulk aerodynamic momentum conductance
    243         zcdh(ig)=zcdh_true(ig)*sqrt(zu2)     ! 1 / bulk aerodynamic heat conductance
     241        ELSE
     242           zu2(:)=pu(:,1)*pu(:,1)+pv(:,1)*pv(:,1)
     243        ENDIF       
     244
     245        zcdv(:)=zcdv_true(:)*sqrt(zu2(:))     ! 1 / bulk aerodynamic momentum conductance
     246        zcdh(:)=zcdh_true(:)*sqrt(zu2(:))     ! 1 / bulk aerodynamic heat conductance
    244247                                             ! these are the quantities to be looked at when comparing surface layers of different models
    245       ENDDO
    246248
    247249! Some usefull diagnostics for the new surface layer parametrization :
     
    254256!     &                         2,zcdh_true)
    255257!        call WRITEDIAGFI(ngridmx,'u*',
    256 !    &              'friction velocity','m/s',
    257 !     &                         2,sqrt(zcdv_true(:))*sqrt(zu2))
     258!     &              'friction velocity','m/s',
     259!     &                         2,sqrt(zcdv_true(:))*sqrt(zu2(:)))
    258260!        call WRITEDIAGFI(ngridmx,'T*',
    259261!     &              'friction temperature','K',
     
    479481c     ----------------------------------------------------------------
    480482        DO ig=1,ngrid
    481           zu2=zu(ig,1)*zu(ig,1)+zv(ig,1)*zv(ig,1)
    482           zcdv(ig)=zcdv_true(ig)*sqrt(zu2)
    483           zcdh(ig)=zcdh_true(ig)*sqrt(zu2)
     483          zu2(ig)=zu(ig,1)*zu(ig,1)+zv(ig,1)*zv(ig,1)
     484          zcdv(ig)=zcdv_true(ig)*sqrt(zu2(ig))
     485          zcdh(ig)=zcdh_true(ig)*sqrt(zu2(ig))
    484486        ENDDO
    485487
Note: See TracChangeset for help on using the changeset viewer.