Ignore:
Timestamp:
Jan 26, 2018, 3:02:55 PM (7 years ago)
Author:
jvatant
Message:

Fixing an incoherence - the upper chemistry fields
are in molar mixing ratio not mass mixing ratio
--JVO

Location:
trunk/LMDZ.TITAN/libf/dynphy_lonlat/phytitan
Files:
3 edited

Legend:

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

    r1894 r1899  
    1717 
    1818  ! Nouvelle grille physique, ancienne grille verticale
    19   REAL,ALLOCATABLE :: ykim_up_oldv(:,:,:)  
     19  REAL,ALLOCATABLE :: ykim_up_oldv(:,:,:) ! (mol/mol)
    2020
    2121  ! Nouvelle grille scalaire, ancienne grille verticale 
    22   REAL,ALLOCATABLE :: ykim_upS(:,:,:,:) 
     22  REAL,ALLOCATABLE :: ykim_upS(:,:,:,:)  ! (mol/mol)
    2323
    2424  ! Ancienne grille scalaire, ancienne grille verticale 
    25   REAL,ALLOCATABLE :: ykim_upoldS(:,:,:,:)
     25  REAL,ALLOCATABLE :: ykim_upoldS(:,:,:,:) ! (mol/mol)
    2626 
    2727END MODULE comchem_newstart_h
  • trunk/LMDZ.TITAN/libf/dynphy_lonlat/phytitan/start2archive.F

    r1895 r1899  
    531531          call write_archive(nid,ntime,trim(cnames(iq))//'_up',
    532532     .                trim(cnames(iq))//' in upper atmosphere',
    533      .                'kg/kg',4,ykim_upS(iq,:,:))
     533     .                'mol/mol',4,ykim_upS(iq,:,:))
    534534        ENDDO
    535535      ENDIF
  • trunk/LMDZ.TITAN/libf/dynphy_lonlat/phytitan/vert_regrid_kim.F90

    r1898 r1899  
    1616  ! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    1717
    18   USE comchem_h, ONLY: cnames, nlaykim_up, preskim, ykim_up
     18  USE comchem_h, ONLY: cnames, rat_mmol, nlaykim_up, preskim, ykim_up
    1919  USE comchem_newstart_h
    2020  USE tracer_h
     
    3434  REAL,DIMENSION(iim+1,jjm+1,llm,nq), INTENT(INOUT) :: q   ! Advected fields (kg/kg) on 3D dyn. grid
    3535
    36   REAL, DIMENSION(:,:), ALLOCATABLE   :: avg_qtop  ! Zonally averaged q on top layer
     36  REAL, DIMENSION(:,:), ALLOCATABLE   :: avg_qtop  ! Zonally averaged q (mol/mol) on top layer
    3737
    3838  REAL :: coef, ykimlon
     
    5252  ngridmx = size(ykim_up,DIM=2)
    5353
    54   ! -----------------------------------------------------------------------------------------
    55   ! 1. Compute zonal mean of last layer for every chem and lat and convert to physics grid
     54  ! ------------------------------------------------------------
     55  ! 1. Compute zonal mean of last layer for every chem and lat
     56  ! and convert it to molar mixing fraction and to physics grid
    5657  ! Preliminary, only in case ceiling has been lowered
    57   ! -----------------------------------------------------------------------------------------
     58  ! ------------------------------------------------------------
    5859
    5960  lowered = .FALSE.
     
    7576        ENDDO
    7677      ENDDO
     78      ! mass -> molar mixing ratio to be comparable to ykim_up later
     79      avg_qtop(ichem,:)=avg_qtop(ichem,:)*rat_mmol(chimi_indx(ichem))
    7780    ENDDO
    7881
     
    125128  ! 3. Correct the 3D advected chem. tracer fields if model ceiling is highered
    126129  ! In this case we interpolate between tracers below and upper_chemistry values
     130  ! Doing this we convert via rat_mmol ykim_up from molar to mass mixing ratio
    127131  ! ----------------------------------------------------------------------------
    128132 
     
    146150        ! so we deal with mono-gridpoints for North and South Poles   
    147151
    148         q(:,1,ilay,chimi_indx(ichem)) = (1.0-coef)*ykim_up(ichem,1,1) + coef*q(:,1,isup,chimi_indx(ichem))
    149         q(:,jjm+1,ilay,chimi_indx(ichem)) = (1.0-coef)*ykim_up(ichem,ngridmx,1) + coef*q(:,jjm+1,isup,chimi_indx(ichem))
     152        q(:,1,ilay,chimi_indx(ichem)) = (1.0-coef)*ykim_up(ichem,1,1)/rat_mmol(chimi_indx(ichem)) &
     153                                      + coef*q(:,1,isup,chimi_indx(ichem))
     154        q(:,jjm+1,ilay,chimi_indx(ichem)) = (1.0-coef)*ykim_up(ichem,ngridmx,1)/rat_mmol(chimi_indx(ichem)) &
     155                                          + coef*q(:,jjm+1,isup,chimi_indx(ichem))
    150156
    151157          DO ilat=2,jjm
     
    155161            DO ilon=2,iim
    156162              ! ykim_up and q are shifted one to the other on longitudinal grid
    157               ykimlon = 0.5*(ykim_up(ichem,ng0+ilon-1,1)+ykim_up(ichem,ng0+ilon,1))
     163              ykimlon = 0.5*(ykim_up(ichem,ng0+ilon-1,1)+ykim_up(ichem,ng0+ilon,1)) / rat_mmol(chimi_indx(ichem))
    158164
    159165              q(ilon,ilat,ilay,chimi_indx(ichem)) = (1.0-coef)*ykimlon + coef*q(ilon,ilat,isup,chimi_indx(ichem))
     
    162168            ! Periodicity on longitude at 180 and -180
    163169
    164             ykimlon = 0.5*(ykim_up(ichem,ng0+1,1)+ykim_up(ichem,ng0+iim,1))
     170            ykimlon = 0.5*(ykim_up(ichem,ng0+1,1)+ykim_up(ichem,ng0+iim,1)) / rat_mmol(chimi_indx(ichem))
    165171
    166172            q(1,ilat,ilay,chimi_indx(ichem)) = (1.0-coef)*ykimlon + coef*q(1,ilat,isup,chimi_indx(ichem))
Note: See TracChangeset for help on using the changeset viewer.