Ignore:
Timestamp:
May 6, 2020, 4:46:33 PM (5 years ago)
Author:
lrossi
Message:

MARS GCM:
Implementation of HDO in the physics
New tracers hdo_vap and hdo_ice are added. Cf. traceur.def.isotopes in deftank for exemple of traceur.def.
All HDO related computations are activated by flag hdo=.true. in callphys.def. (see callphys.def.hdo in deftank for an example)
Additional option hdofrac (true by default) allows for turning on/off fractionation (for tests).
For now, only functional with simplified cloud scheme (so microphys=.false. and activice=.false. also recommended).
Initialisation of start files can be done with option 'inihdo' in newstart.
LR

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.MARS/libf/phymars/vdifc_mod.F

    r2274 r2312  
    1818     &                      igcm_dust_submicron, igcm_h2o_vap,
    1919     &                      igcm_h2o_ice, alpha_lift,
     20     &                      igcm_hdo_vap, igcm_hdo_ice,
    2021     &                      igcm_stormdust_mass, igcm_stormdust_number
    2122      use surfdat_h, only: watercaptag, frost_albedo_threshold, dryness
     
    2425      use turb_mod, only: turb_resolved, ustar, tstar
    2526      use compute_dtau_mod, only: ti_injection_sol,tf_injection_sol
     27      use hdo_surfex_mod, only: hdo_surfex
     28
    2629      IMPLICIT NONE
    2730
     
    140143      REAL qsat(ngrid)
    141144
     145      REAL hdoflux(ngrid)       ! value of vapour flux of HDO
     146      REAL h2oflux(ngrid)       ! value of vapour flux of H2O
     147      REAL old_h2o_vap(ngrid)   ! traceur d'eau avant traitement
     148
    142149      REAL kmixmin
    143150
     
    167174
    168175      REAL,INTENT(OUT) :: sensibFlux(ngrid)
     176
     177!!MARGAUX
     178      REAL DoH_vap(ngrid,nlay)
    169179
    170180c    ** un petit test de coherence
     
    443453c       donc les entrees sont /zcdv/ pour la condition a la limite sol
    444454c       et /zkv/ = Ku
    445  
     455
    446456      zb(1:ngrid,2:nlay)=zkv(1:ngrid,2:nlay)*zb0(1:ngrid,2:nlay)
    447457      zb(1:ngrid,1)=zcdv(1:ngrid)*zb0(1:ngrid,1)
     
    786796          zb(1:ngrid,2:nlay)=zkh(1:ngrid,2:nlay)*zb0(1:ngrid,2:nlay)
    787797
    788           if ((water).and.(iq.eq.igcm_h2o_vap)) then 
     798          if ((water).and.(iq.eq.igcm_h2o_vap)) then
    789799c            This line is required to account for turbulent transport
    790800c            from surface (e.g. ice) to mid-layer of atmosphere:
     
    811821          ENDDO
    812822
    813           if (water.and.(iq.eq.igcm_h2o_ice)) then
     823          if ( (water.and.(iq.eq.igcm_h2o_ice))
     824     $      .or. (hdo.and.(iq.eq.igcm_hdo_ice)) ) then
    814825            ! special case for water ice tracer: do not include
    815826            ! h2o ice tracer from surface (which is set when handling
     
    821832     $         zb(ig,2)*zc(ig,2)) *z1(ig)
    822833            ENDDO
     834         else if (hdo.and.(iq.eq.igcm_hdo_vap)) then
     835            CALL hdo_surfex(ngrid,nlay,nq,ptimestep,
     836     &                      zt,zq,pqsurf,
     837     &                      old_h2o_vap,pdqsdif,h2oflux,
     838     &                      hdoflux)
     839            DO ig=1,ngrid
     840                z1(ig)=1./(za(ig,1)+zb(ig,1)+
     841     $           zb(ig,2)*(1.-zd(ig,2)))
     842                zc(ig,1)=(za(ig,1)*zq(ig,1,iq)+
     843     $         zb(ig,2)*zc(ig,2) +
     844     $        (-hdoflux(ig)) *ptimestep) *z1(ig)  !tracer flux from surface
     845            ENDDO
     846
    823847          else ! general case
    824848            DO ig=1,ngrid
     
    829853     $        (-pdqsdif(ig,iq)) *ptimestep) *z1(ig)  !tracer flux from surface
    830854            ENDDO
     855
    831856          endif ! of if (water.and.(iq.eq.igcm_h2o_ice))
    832857 
     
    834859c           Calculation for turbulent exchange with the surface (for ice)
    835860            DO ig=1,ngrid
     861              old_h2o_vap(ig)=zq(ig,1,igcm_h2o_vap)
    836862              zd(ig,1)=zb(ig,1)*z1(ig)
    837863              zq1temp(ig)=zc(ig,1)+ zd(ig,1)*qsat(ig)
     
    843869
    844870            DO ig=1,ngrid
     871            IF (hdo) then !if hdo, need to treat polar caps differently
     872              h2oflux(ig) = pdqsdif(ig,igcm_h2o_ice) ! h2oflux is
     873                                                     ! uncorrected waterflux
     874            ENDIF !hdo
     875
    845876              if ((-pdqsdif(ig,igcm_h2o_ice)*ptimestep)
    846877     &             .gt.(pqsurf(ig,igcm_h2o_ice))) then
     
    857888     &                         -pqsurf(ig,igcm_h2o_ice)/ptimestep
    858889                   dwatercap_dif(ig) = 0.0
     890                   if (hdo) then
     891                     h2oflux(ig) = pdqsdif(ig,igcm_h2o_ice)
     892                   endif
    859893
    860894                endif   
     
    910944        enddo ! of do iq=1,nq
    911945      end if ! of if(tracer)
    912      
     946
     947C       Diagnostic output for HDO
     948        if (hdo) then
     949            CALL WRITEDIAGFI(ngrid,'hdoflux',
     950     &                       'hdoflux',
     951     &                       ' ',2,hdoflux) 
     952            CALL WRITEDIAGFI(ngrid,'h2oflux',
     953     &                       'h2oflux',
     954     &                       ' ',2,h2oflux)
     955        endif
    913956
    914957c-----------------------------------------------------------------------
     
    9581001      END SUBROUTINE vdifc
    9591002
     1003c====================================
     1004
     1005
    9601006      END MODULE vdifc_mod
Note: See TracChangeset for help on using the changeset viewer.