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/dyn3dpar
Files:
1 added
3 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.COMMON/libf/dyn3dpar/advtrac_p.F90

    r1959 r2126  
    1818  USE times
    1919  USE infotrac, ONLY: nqtot, iadv
    20   USE control_mod, ONLY: iapp_tracvl, day_step, planet_type
     20  USE control_mod, ONLY: iapp_tracvl, day_step, planet_type, &
     21                         force_conserv_tracer
    2122  USE comconst_mod, ONLY: dtvr
     23  USE planetary_operations_p, ONLY: planetary_tracer_amount_from_mass_p
    2224  IMPLICIT NONE
    2325  !
     
    7779  REAL,SAVE :: teta_tmp(ip1jmp1,llm)
    7880  REAL,SAVE :: pk_tmp(ip1jmp1,llm)
     81  REAL :: totaltracer_old(nqtot),totaltracer_new(nqtot)
     82  REAL :: ratio
     83
     84! Ehouarn : try to fix tracer conservation issues:
     85  if (force_conserv_tracer) then
     86    do iq=1,nqtot
     87       call planetary_tracer_amount_from_mass_p(masse,q(:,:,iq), &
     88                                          totaltracer_old(iq))
     89    enddo
     90  endif
    7991
    8092  ijb_u=ij_begin
     
    467479     endif ! of if (planet_type=="earth")
    468480
     481     ! Ehouarn : try to fix tracer conservation after tracer advection
     482     if (force_conserv_tracer) then
     483       ijb=ij_begin
     484       ije=ij_end
     485       do iq=1,nqtot
     486         call planetary_tracer_amount_from_mass_p(masse,q(:,:,iq), &
     487                                     totaltracer_new(iq))
     488         ratio=totaltracer_old(iq)/totaltracer_new(iq)
     489         q(ijb:ije,1:llm,iq)=q(ijb:ije,1:llm,iq)*ratio
     490       enddo
     491     endif !of if (force_conserv_tracer)
     492
    469493        !------------------------------------------------------------------
    470494        !   on reinitialise a zero les flux de masse cumules
  • trunk/LMDZ.COMMON/libf/dyn3dpar/conf_gcm.F90

    r1824 r2126  
    255255  iapp_tracvl = iperiod
    256256  CALL getin('iapp_tracvl',iapp_tracvl)
     257
     258! Enforce tracer conservation in integrd & caladvtrac ?
     259  force_conserv_tracer = .false.
     260  CALL getin('force_conserv_tracer',force_conserv_tracer)
    257261
    258262!Config  Key  = iconser
     
    987991      write(lunout,*)' iphysiq = ', iphysiq
    988992      write(lunout,*)' iflag_trac = ', iflag_trac
     993      write(lunout,*)' iapp_tracvl = ', iapp_tracvl
     994      write(lunout,*)' force_conserv_tracer = ', force_conserv_tracer
    989995      write(lunout,*)' clon = ', clon
    990996      write(lunout,*)' clat = ', clat
  • trunk/LMDZ.COMMON/libf/dyn3dpar/integrd_p.F

    r1959 r2126  
    77      USE parallel_lmdz, ONLY: ij_begin, ij_end, pole_nord, pole_sud,
    88     &                         omp_chunk
    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
     
    6565      REAL vscr( ip1jm ),uscr( ip1jmp1 ),hscr( ip1jmp1 ),pscr(ip1jmp1)
    6666      REAL massescr( ip1jmp1,llm )
     67      REAL :: massratio(ip1jmp1,llm)
    6768!      REAL finvmasse(ip1jmp1,llm)
    6869      REAL,SAVE :: p(ip1jmp1,llmp1)
     
    361362      endif ! of if (planet_type.eq."earth")
    362363
     364
     365      if (force_conserv_tracer) then
     366        ! Ehouarn: try to keep total amont of tracers fixed
     367        ! by acounting for mass change in each cell
     368        massratio(ijb:ije,1:llm)=massescr(ijb:ije,1:llm)
     369     &                             /masse(ijb:ije,1:llm)
     370        do iq=1,nq
     371        q(ijb:ije,1:llm,iq)=q(ijb:ije,1:llm,iq)
     372     &                        *massratio(ijb:ije,1:llm)
     373        enddo
     374      endif ! of if (force_conserv_tracer)
    363375c
    364376c
Note: See TracChangeset for help on using the changeset viewer.