Ignore:
Timestamp:
Apr 26, 2019, 11:18:52 AM (6 years ago)
Author:
emillour
Message:

Common dynamics:
Some work to enforce total tracer mass conservation in the dynamics.
Still to be further studied and validated.
For now these changes are triggered by setting a "force_conserv_tracer"
flag to ".true." in run.def (default is ".false." to not change anything
with respect to previous versions).
When force_conserv_tracer=.true. then:

  1. Rescale tracer mass in caladvtrac after tracer advection computations
  2. Recompute q ratios once atmospheric mass has been updated in integrd

These steps technically ensure total tracer mass conservation but it
might be the tracer advection scheme and/or time-stepping updating
sequence of fields that should be rethought or fixed.
EM

Location:
trunk/LMDZ.COMMON/libf/dyn3d
Files:
1 added
3 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.COMMON/libf/dyn3d/caladvtrac.F

    r1508 r2126  
    99c
    1010      USE infotrac, ONLY : nqtot
    11       USE control_mod, ONLY : iapp_tracvl,planet_type
     11      USE control_mod, ONLY : iapp_tracvl,planet_type,
     12     &                        force_conserv_tracer
    1213      USE comconst_mod, ONLY: dtvr
    13  
     14      USE planetary_operations, ONLY: planetary_tracer_amount_from_mass
    1415      IMPLICIT NONE
    1516c
     
    4748      INTEGER ij,l, iq, iapptrac
    4849      REAL finmasse(ip1jmp1,llm), dtvrtrac
     50      REAL :: totaltracer_old(nqtot),totaltracer_new(nqtot)
     51      REAL :: ratio
    4952
     53! Ehouarn : try to fix tracer conservation issues:
     54      if (force_conserv_tracer) then
     55        do iq=1,nqtot
     56          call planetary_tracer_amount_from_mass(masse,q(:,:,iq),
     57     &                                totaltracer_old(iq))
     58        enddo
     59      endif
    5060cc
    5161c
     
    107117c
    108118        endif ! of if (planet_type.eq."earth")
    109       ELSE
     119       
     120        ! Ehouarn : try to fix tracer conservation after tracer advection
     121        if (force_conserv_tracer) then
     122          do iq=1,nqtot
     123            call planetary_tracer_amount_from_mass(masse,q(:,:,iq),
     124     &                                  totaltracer_new(iq))
     125            ratio=totaltracer_old(iq)/totaltracer_new(iq)
     126            q(:,:,iq)=q(:,:,iq)*ratio
     127          enddo
     128        endif !of if (force_conserv_tracer)
     129       
     130      ELSE ! i.e. iapptrac.NE.iapp_tracvl
    110131        if (planet_type.eq."earth") then
    111132! Earth-specific treatment for the first 2 tracers (water)
  • trunk/LMDZ.COMMON/libf/dyn3d/conf_gcm.F90

    r1824 r2126  
    1717                         output_grads_dyn, periodav, planet_type, &
    1818                         raz_date, resetvarc, starttime, timestart, &
    19                          ecritstart
     19                         ecritstart,force_conserv_tracer
    2020  USE infotrac, ONLY : type_trac
    2121  use assert_m, only: assert
     
    233233  iapp_tracvl = iperiod
    234234  CALL getin('iapp_tracvl',iapp_tracvl)
     235
     236! Enforce tracer conservation in integrd & caladvtrac ?
     237  force_conserv_tracer = .false.
     238  CALL getin('force_conserv_tracer',force_conserv_tracer)
    235239
    236240!Config  Key  = iconser
     
    949953 write(lunout,*)' iphysiq = ', iphysiq
    950954 write(lunout,*)' iflag_trac = ', iflag_trac
     955 write(lunout,*)' iapp_tracvl = ', iapp_tracvl
     956 write(lunout,*)' force_conserv_tracer = ', force_conserv_tracer
    951957 write(lunout,*)' clon = ', clon
    952958 write(lunout,*)' clat = ', clat
  • trunk/LMDZ.COMMON/libf/dyn3d/integrd.F

    r1422 r2126  
    77     &  )
    88
    9       use control_mod, only : planet_type
     9      use control_mod, only : planet_type,force_conserv_tracer
    1010      USE comvert_mod, ONLY: ap,bp
    1111      USE comconst_mod, ONLY: pi
     
    6666      REAL vscr( ip1jm ),uscr( ip1jmp1 ),hscr( ip1jmp1 ),pscr(ip1jmp1)
    6767      REAL massescr( ip1jmp1,llm )
     68      REAL :: massratio(ip1jmp1,llm)
    6869!      REAL finvmasse(ip1jmp1,llm)
    6970      REAL p(ip1jmp1,llmp1)
     
    242243
    243244      endif ! of if (planet_type.eq."earth")
     245
     246      if (force_conserv_tracer) then
     247        ! Ehouarn: try to keep total amont of tracers fixed
     248        ! by acounting for mass change in each cell
     249        massratio(1:ip1jmp1,1:llm)=massescr(1:ip1jmp1,1:llm)
     250     &                             /masse(1:ip1jmp1,1:llm)
     251        do iq=1,nq
     252        q(1:ip1jmp1,1:llm,iq)=q(1:ip1jmp1,1:llm,iq)
     253     &                        *massratio(1:ip1jmp1,1:llm)
     254        enddo
     255      endif ! of if (force_conserv_tracer)
    244256c
    245257c
Note: See TracChangeset for help on using the changeset viewer.