Changeset 2482 for trunk


Ignore:
Timestamp:
Mar 18, 2021, 6:18:21 PM (4 years ago)
Author:
yjaziri
Message:

Generic GCM:
Clean convadj.F90 specific CO2 Mars convection
Add alb_ocean used in hydrol.F90 as option in .def files
Add kmixmin 1D minimum eddy mix coeff for turbdiff as rcm1d.def option
and comment lines to help coding specific eddy mix coeff in turbdiff with Earth example

YJ

Location:
trunk/LMDZ.GENERIC
Files:
7 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.GENERIC/README

    r2480 r2482  
    16201620          if they are provided (i.e. if flag diagdtau is .true.)
    16211621
    1622 == 06/03/2020 == YJ
     1622== 06/03/2021 == YJ
    16231623ModernTrac bug fix in infotrac from commit r2436 24/11/2020
    16241624Missing log message, see previous commit r2468
    16251625
    1626 == 08/03/2020 == YJ
     1626== 08/03/2021 == YJ
    16271627global1d and szangle for 1D simulation moved from callcorrk to callkeys
    16281628to defined a consistent 1D sza in physiq_mod used also in chemistry
     
    16311631== 16/03/2021 == AB
    16321632Commit the last changes in the thermal plume model which was waiting for one year.
     1633
     1634== 18/03/2021 == YJ
     1635Clean convadj.F90 specific CO2 Mars convection
     1636Add alb_ocean used in hydrol.F90 as option in .def files
     1637Add kmixmin 1D minimum eddy mix coeff for turbdiff as rcm1d.def option
     1638and comment lines to help coding specific eddy mix coeff in turbdiff with Earth example
  • trunk/LMDZ.GENERIC/libf/phystd/callkeys_mod.F90

    r2470 r2482  
    125125      real,save :: pceil
    126126      real,save :: albedosnow
     127      real,save :: alb_ocean
    127128      real,save :: albedoco2ice
    128129      real,save :: maxicethick
    129 !$OMP THREADPRIVATE(co2supsat,pceil,albedosnow,albedoco2ice,maxicethick)
     130!$OMP THREADPRIVATE(co2supsat,pceil,albedosnow,alb_ocean,albedoco2ice,maxicethick)
    130131      real,save :: Tsaldiff
    131132      real,save :: tau_relax
     
    146147      real,save :: noseason_day
    147148!$OMP THREADPRIVATE(noseason_day)
     149      real,save :: kmixmin
     150!$OMP THREADPRIVATE(kmixmin)
    148151     
    149152      logical,save :: iscallphys=.false.!existence of callphys.def
  • trunk/LMDZ.GENERIC/libf/phystd/convadj.F

    r2232 r2482  
    6161
    6262!     Tracers
    63       INTEGER iq,ico2
    64       save ico2
    65 !$OMP THREADPRIVATE(ico2)
     63      INTEGER iq
    6664      REAL zq(ngrid,nlay,nq), zq2(ngrid,nlay,nq)
    6765      REAL zqm(nq),zqco2m
    68       real m_co2, m_noco2, A , B
    69       save A, B
    70 !$OMP THREADPRIVATE(A,B)
    71 
    72       real mtot1, mtot2 , mm1, mm2
    73        integer l1ref, l2ref
    74       LOGICAL vtest(ngrid),down,firstcall
    75       save firstcall
    76       data firstcall/.true./
    77 !$OMP THREADPRIVATE(firstcall)
     66
     67      LOGICAL vtest(ngrid),down
    7868
    7969!     for conservation test
     
    8575!     Initialisation
    8676!     --------------
    87 
    88       IF (firstcall) THEN
    89         ico2=0
    90         if (tracer) then
    91 !     Prepare Special treatment if one of the tracers is CO2 gas
    92            do iq=1,nq
    93              if (noms(iq).eq."co2") then
    94                 print*,'dont go there'
    95 !                stop
    96                 ico2=iq
    97                 m_co2 = 44.01E-3  ! CO2 molecular mass (kg/mol)   
    98                 m_noco2 = 33.37E-3  ! Non condensible mol mass (kg/mol)   
    99 !               Compute A and B coefficient use to compute
    100 !               mean molecular mass Mair defined by
    101 !               1/Mair = q(ico2)/m_co2 + (1-q(ico2))/m_noco2
    102 !               1/Mair = A*q(ico2) + B
    103                 A =(1/m_co2 - 1/m_noco2)
    104                 B=1/m_noco2
    105              end if
    106            enddo
    107         endif
    108         firstcall=.false.
    109       ENDIF ! of IF (firstcall)
    11077
    11178      DO l=1,nlay
     
    141108      ENDDO
    142109
    143       if (ico2.ne.0) then
    144 !     Special case if one of the tracers is CO2 gas
    145          DO l=1,nlay
    146            DO ig=1,ngrid
    147              zhc(ig,l) = zh2(ig,l)*(A*zq2(ig,l,ico2)+B)
    148            ENDDO
    149          ENDDO
    150        else
    151           CALL scopy(ngrid*nlay,zh2,1,zhc,1)
    152        end if
     110      CALL scopy(ngrid*nlay,zh2,1,zhc,1)
    153111
    154112!     Find out which grid points are convectively unstable
     
    204162              zdsm = dsig(l2)
    205163              zhm = zh2(i, l2)
    206               if(ico2.ne.0) zqco2m = zq2(i,l2,ico2)
    207164
    208165!     Test loop downwards
     
    212169                zdsm = zdsm + dsig(l)
    213170                zhm = zhm + sdsig(l) * (zh2(i, l) - zhm) / zsm
    214                 if(ico2.ne.0) then
    215                   zqco2m =
    216      &            zqco2m + dsig(l) * (zq2(i,l,ico2) - zqco2m) / zdsm
    217                   zhmc = zhm*(A*zqco2m+B)
    218                 else
    219                   zhmc = zhm
    220                 end if
     171                zhmc = zhm
    221172 
    222173!     do we have to extend the column downwards?
     
    261212              end do
    262213              DO l = l1, l2
    263                 if(ico2.ne.0) then
    264                   zalpha=zalpha+
    265      &            ABS(zhc(i,l)/(A+B*zqco2m) -zhm)*dsig(l)
    266                 else
    267                   zalpha=zalpha+ABS(zh2(i,l)-zhm)*dsig(l)
    268                 endif
     214                zalpha=zalpha+ABS(zh2(i,l)-zhm)*dsig(l)
    269215                zh2(i, l) = zhm
    270216!     modifs by RDW !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     
    307253                 end do
    308254              ENDDO
    309               if (ico2.ne.0) then
    310                 DO l=l1, l2
    311                   zhc(i,l) = zh2(i,l)*(A*zq2(i,l,ico2)+B)
    312                 ENDDO
    313               end if
    314255
    315256
  • trunk/LMDZ.GENERIC/libf/phystd/hydrol.F90

    r1543 r2482  
    1313  USE tracer_h
    1414  use slab_ice_h
    15   use callkeys_mod, only: albedosnow,albedoco2ice,ok_slab_ocean,Tsaldiff,maxicethick,co2cond
     15  use callkeys_mod, only: albedosnow,alb_ocean,albedoco2ice,ok_slab_ocean,Tsaldiff,maxicethick,co2cond
    1616  use radinc_h, only : L_NSPECTV
    1717
     
    190190!            else
    191191               do nw=1,L_NSPECTV
    192                   albedo(ig,nw) = alb_ocean ! For now, alb_ocean is defined in slab_ice_h.F90. Later we could introduce spectral dependency for alb_ocean.
     192                  albedo(ig,nw) = alb_ocean ! For now, alb_ocean is defined in inifis_mod.F90. Later we could introduce spectral dependency for alb_ocean.
    193193               enddo
    194194!            end if
  • trunk/LMDZ.GENERIC/libf/phystd/inifis_mod.F90

    r2470 r2482  
    874874     write(*,*) " albedosnow = ",albedosnow
    875875         
     876     write(*,*) "Ocean albedo ?"
     877     alb_ocean=0.07         ! default value
     878     call getin_p("alb_ocean",alb_ocean)
     879     write(*,*) " alb_ocean = ",alb_ocean
     880         
    876881     write(*,*) "CO2 ice albedo ?"
    877882     albedoco2ice=0.5       ! default value
     
    888893     call getin_p("Tsaldiff",Tsaldiff)
    889894     write(*,*) " Tsaldiff = ",Tsaldiff
     895
     896     write(*,*) "Minimum eddy mix coeff in 1D ?"
     897     kmixmin=1.0e-2         ! default value
     898     call getin_p("kmixmin",kmixmin)
     899     write(*,*) " kmixmin = ",kmixmin
    890900
    891901     write(*,*) "Does user want to force cpp and mugaz?"
  • trunk/LMDZ.GENERIC/libf/phystd/slab_ice_h.F90

    r1298 r2482  
    1212      real, parameter :: alb_ice_min=0.2       
    1313      real, parameter :: alb_ice_max=0.65
    14       real, parameter :: alb_ocean=0.07
    1514      real, parameter :: ice_frac_min=0.0001
    1615      real, parameter :: ice_frac_max=1.!0.9999
  • trunk/LMDZ.GENERIC/libf/phystd/turbdiff_mod.F90

    r2427 r2482  
    1818      use tracer_h, only: igcm_h2o_vap, igcm_h2o_ice
    1919      use comcstfi_mod, only: rcp, g, r, cpp
    20       use callkeys_mod, only: water,tracer,nosurf
     20      use callkeys_mod, only: water,tracer,nosurf,kmixmin
    2121      use turb_mod, only : ustar
    2222#ifdef MESOSCALE
     
    107107      REAL zcq0(ngrid),zdq0(ngrid)
    108108      REAL zx_alf1(ngrid),zx_alf2(ngrid)
     109      ! 1D eddy diffusion coefficient
     110      REAL kzz_eddy(nlay)
     111      REAL pmin_kzz
    109112
    110113      LOGICAL,SAVE :: firstcall=.true.
     
    119122      REAL zdmassevap(ngrid)
    120123      REAL rho(ngrid)         ! near-surface air density
    121       REAL kmixmin
    122124
    123125!     Variables added for implicit latent heat inclusion
     
    250252!     R. Wordsworth & F. Forget (2010)
    251253      if ((ngrid.eq.1)) then
    252          kmixmin = 1.0e-2       ! minimum eddy mix coeff in 1D
     254         ! kmixmin minimum eddy mix coeff in 1D
     255         ! set up in inifis_mod.F90 - default value 1.0e-2
    253256         do ilev=1,nlay
     257
     258!            Here to code your specific eddy mix coeff in 1D
     259!            Earth example that can be uncommented below
     260!            -------------------------------------------------
     261!            *====== Earth kzz from Zahnle et al. 2006 ======*
     262!            -------------------------------------------------
     263!            if(pzlev(1,ilev).le.11.0e3) then
     264!               kzz_eddy(ilev)=10.0
     265!               pmin_kzz=pplev(1,ilev)*exp((pzlev(1,ilev)-11.0e3)*g/(r*zt(1,ilev)))
     266!            else
     267!               kzz_eddy(ilev)=0.1*(pplev(1,ilev)/pmin_kzz)**(-0.5)
     268!               kzz_eddy(ilev)=min(kzz_eddy(ilev),100.0)
     269!            endif
     270!            do ig=1,ngrid
     271!               zkh(ig,ilev) = max(kzz_eddy(ilev),zkh(ig,ilev))
     272!               zkv(ig,ilev) = max(kzz_eddy(ilev),zkv(ig,ilev))
     273!            end do
     274
    254275            do ig=1,ngrid
    255276               zkh(ig,ilev) = max(kmixmin,zkh(ig,ilev))
Note: See TracChangeset for help on using the changeset viewer.