Ignore:
Timestamp:
May 28, 2018, 11:47:03 PM (7 years ago)
Author:
jvatant
Message:

1) Microphysics diags / outputs :


+ Add supplementary diagnostics outputs for microphysics ( precip, flux, rc ... ) ( new muphy_diag.F90 module )
+ Correct the outputs of microphys tracers to be in X/m-3 to be comparable to "standard values"

+ Also update the deftank callphys.def with latest revs modifs for microphysics

2) Condensation / chemistry updates :


+ Moved chemistry AFTER microphysics

  • To have mufi condensation before photochem
  • Chemistry called last coherent with the fact that it brings back fields to equilibrium

+ If 2D chemistry, make zonally averaged fields go through mufi and chem condensation

to have non saturated profiles in input of photochemistry
( other 'short' processes neglected as 2D -> no diurnal cycle, just seasonal evolution )

+ Also corrected the positivity check ( took Mars GCM syntax ) after chemistry ( could previously lead to negs )

3) Noticed a weird behaviour ( bug? ) :


+ If generalize the use of arrays *_indx for tracers, to get rid of ugly "iq+nmicro",

it ends up with weird results / crash in optim mode ( ok in debug ) but didn't find out why ...

--JVO

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.TITAN/libf/muphytitan/mmp_gcm.f90

    r1897 r1926  
    9393    INTEGER                                           :: i
    9494    TYPE(cfgparser)                                   :: cparser
    95     CHARACTER(len=st_slen)                            :: spcpath,pssfile,mqfile
     95    CHARACTER(len=st_slen)                            :: spcpath,pssfile,mqfile,opt_file
    9696    CHARACTER(len=st_slen), DIMENSION(:), ALLOCATABLE :: species
    9797    REAL(kind=mm_wp), DIMENSION(:), ALLOCATABLE       :: tmp
     
    138138    err = mm_check_opt(cfg_get_value(cparser,"haze_coag_interactions",coag_choice),coag_choice,7,mm_log)
    139139
     140    ! optic look-up table file path.
     141    mmp_optic_file = ''
     142    opt_file = ''
     143    err = mm_check_opt(cfg_get_value(cparser,"optics/optic_file",opt_file),opt_file,'',mm_log)
     144    IF (err /= 0) THEN
     145      WRITE(*,'(a)') "Warning: I was unable to retrieve the path of the optic look-up table file:"
     146      WRITE(*,'(a)') "  The GCM may abort if it uses YAMMS optical properties calculation module !"
     147    ELSE
     148      mmp_optic_file = TRIM(opt_file)
     149    ENDIF
     150
    140151    ! Retrieve clouds species configuration file
    141152    spcpath = ''
Note: See TracChangeset for help on using the changeset viewer.