Ignore:
Timestamp:
Jul 1, 2018, 5:07:48 PM (6 years ago)
Author:
jvatant
Message:

+ Add surface methane CH4 flux pseudo-evap diagnostic and include it in bottom layer zdqcond as >0.
+ minor cosmetic changes in gptitan.c
--JVO

Location:
trunk/LMDZ.TITAN/libf/phytitan
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.TITAN/libf/phytitan/calchim.F90

    r1950 r1956  
    11SUBROUTINE calchim(ngrid,qy_c,declin,dtchim,            &
    2      ctemp,cpphi,cplay,cplev,czlay,czlev,dqyc)
     2     ctemp,cpphi,cplay,cplev,czlay,czlev,dqyc,zdyevapCH4)
    33
    44  !---------------------------------------------------------------------------------------------------------
     
    5656  ! -----------------------------------------------------------------
    5757
     58  USE, INTRINSIC :: iso_c_binding
    5859  USE comchem_h
    5960  USE dimphy
     
    8586
    8687  REAL*8, DIMENSION(ngrid,klev,nkim), INTENT(OUT)  :: dqyc        ! Chemical species tendencies on GCM layers (mol/mol/s).
     88  REAL*8, DIMENSION(ngrid),           INTENT(OUT)  :: zdyevapCH4  ! Diagnostic surface methane pseudo-evaporation flux (mol/mol/s).
    8789
    8890  ! Local variables :
     
    115117  REAL*8, DIMENSION(nlaykim_tot) :: rinter ! Inter-layer distance (km) to planetographic center (RA grid in chem. module).
    116118  ! NB : rinter is on nlaykim_tot too, we don't care of the uppermost layer upper boundary altitude.
     119
     120  REAL(c_double) :: fluxCH4 ! Surface "evaporation" flux (mol/mol)
    117121
    118122  ! Saved variables initialized at firstcall
     
    465469             nomqy_c,cqy,                               &
    466470             dtchim,latitude(ig)*180./pi,mass,md,       &
    467              kedd,botCH4,krate,reactif,                 &
     471             kedd,botCH4,fluxCH4,krate,reactif,         &
    468472             nom_prod,nom_perte,prod,perte,             &
    469473             aerprod,utilaer,cmaer,cprodaer,ccsn,ccsh,  &
    470474             htoh2,surfhaze)
     475
     476        zdyevapCH4(ig) = fluxCH4 / dtchim ! Diagnostic pseudo-evaporation ( due to readjustement to botCH4 value ) (mol/mol/s)
    471477
    472478        ! 5. Calculates tendencies on composition for advected tracers
     
    488494
    489495
    490      ELSE ! In 2D chemistry, if following grid point at same latitude, same zonal mean so don't do calculations again !
     496     ELSE ! In 2D chemistry, if following grid point at same latitude, same zonal mean so don't do calculations again !
     497        zdyevapCH4(ig)  = zdyevapCH4(igm1)
    491498        dqyc(ig,:,:)    = dqyc(igm1,:,:) ! will be put back in 3D with longitudinal variations assuming same relative tendencies within a lat band
    492499        ykim_up(:,ig,:) = ykim_up(:,igm1,:) ! no horizontal mixing in upper layers -> no longitudinal variations
  • trunk/LMDZ.TITAN/libf/phytitan/physiq_mod.F90

    r1947 r1956  
    387387      real temp_eq(nlayer), press_eq(nlayer) ! Planetary averages for the init. of saturation profiles (K,mbar)
    388388
    389       ! Surface methane tank
    390       real,dimension(:),allocatable,save :: tankCH4 ! Depth of surface methane tank (m)
    391 !$OMP THREADPRIVATE(tankCH4)
     389      ! Surface methane
     390      real, dimension(:), allocatable, save :: tankCH4    ! Depth of surface methane tank (m)
     391      real, dimension(:), allocatable, save :: zdyevapCH4 ! Surface pseudo-evaporation flux (chemistry keeping constant surface humidity) (mol/mol/s).
     392!$OMP THREADPRIVATE(tankCH4,zdyevapCH4)
    392393
    393394      ! -----******----- FOR MUPHYS OPTICS -----******-----
     
    522523            allocate(dycchi(ngrid,nlayer,nkim)) ! only for chemical tracers
    523524            allocate(qysat(nlayer,nkim))
     525            allocate(zdyevapCH4(ngrid))
    524526           
    525527            ! Chemistry timestep
     
    11991201                 ! Here we send zonal average fields ( corrected with cond ) from dynamics to chem. module
    12001202                 call calchim(ngrid,ychimbar,declin,ctimestep,ztfibar,zphibar,  &
    1201                               zplaybar,zplevbar,zzlaybar,zzlevbar,dycchi)
     1203                              zplaybar,zplevbar,zzlaybar,zzlevbar,dycchi,zdyevapCH4)
    12021204               else ! 3D chemistry (or 1D run)
    12031205                 call calchim(ngrid,ychim,declin,ctimestep,pt,pphi,  &
    1204                               pplay,pplev,zzlay,zzlev,dycchi)
     1206                              pplay,pplev,zzlay,zzlev,dycchi,zdyevapCH4)
    12051207               endif ! if moyzon
    12061208
    12071209            endif
     1210           
     1211            ! Add diagnostic-only surface pseudo-evapoaration in condensation tendency for bottom layer
     1212            zdqcond(:,1,chimi_indx(7)) = zdyevapCH4(:)*rat_mmol(chimi_indx(7))
    12081213           
    12091214            do iq=1,nkim
     
    15591564             call writediagfi(ngrid,cnames(iq),cnames(iq),'mol/mol',3,zq(:,:,iq+nmicro)/rat_mmol(iq+nmicro))
    15601565           enddo
     1566           call writediagfi(ngrid,"fluxCH4","Surface CH4 pseudo-evaporation",'mol/mol/s',2,zdyevapCH4)
    15611567         endif
    15621568
Note: See TracChangeset for help on using the changeset viewer.