Changeset 1943 for trunk/LMDZ.TITAN/libf


Ignore:
Timestamp:
Jun 4, 2018, 11:59:42 AM (7 years ago)
Author:
jvatant
Message:

Add XIOS outputs for chemistry including "*_tot" fields (concat GCM+upper atm : 0->1300km )
Only in pseudo-pressure axis for now, pseudo-altitude TBD.
--JVO

Location:
trunk/LMDZ.TITAN/libf/phytitan
Files:
5 edited

Legend:

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

    r1903 r1943  
    1 SUBROUTINE chem_settings(nid,ngrid,indextime)
     1SUBROUTINE chem_settings(nid,ngrid,nlayer,indextime)
    22
    33! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     
    1818
    1919USE comchem_h
    20 
    2120USE iostart, only: get_field, get_var, inquire_dimension_length
    2221USE callkeys_mod, only : callchim
     22
     23USE vertical_layers_mod, only: presnivs, pseudoalt
    2324
    2425IMPLICIT NONE
     
    2930  INTEGER,INTENT(IN)  :: nid            ! Input Netcdf file ID
    3031  INTEGER,INTENT(IN)  :: ngrid          ! # of horizontal grid points
     32  INTEGER,INTENT(IN)  :: nlayer         ! # of vertical layers
    3133  INTEGER,INTENT(IN)  :: indextime      ! position on time axis
    3234!======================================================================
    3335! local variables:
     36  REAL :: phi0, phi
     37
    3438  INTEGER :: ierr       ! status (returned by NetCDF functions)
    3539  INTEGER :: nvarid     ! ID of NetCDF variable
    3640  INTEGER :: dimid      ! ID of NetCDF dimension
    3741 
    38   INTEGER :: iq
     42  INTEGER :: ilay, iq
    3943 
    4044  LOGICAL ::  found
     
    5963  WRITE(*,*) "chem_settings: Upper chemistry pressure grid <preskim> range:", &
    6064               maxval(preskim), minval(preskim)
     65               
     66  ! 3. Compute others chemistry grid
     67 
     68  ! a. Total pressure grid (0->1300km)
     69  DO ilay=1,nlayer ! GCM levels
     70    preskim_tot(ilay) = presnivs(ilay)
     71  ENDDO
     72  DO ilay=1,nlaykim_up ! Upper chemistry
     73    preskim_tot(ilay+nlayer) = preskim(ilay)
     74  ENDDO
     75 
     76  ! b. Pseudo-altitudes ( TBD - hydrostatic equilibrium or read somewhere ?)         
    6177 
    62   ! 3. Inquire ( and load ) upper chemistry composition fields
     78  ! 4. Inquire ( and load ) upper chemistry composition fields
    6379 
    6480  CALL get_field("H_up",ykim_up(1,:,:),found,indextime)
     
    7389   
    7490    DEALLOCATE(ykim_up) ! it will be useless
     91    DEALLOCATE(ykim_tot) ! it will be useless
    7592   
    7693  ELSE
  • trunk/LMDZ.TITAN/libf/phytitan/comchem_h.F90

    r1908 r1943  
    7878
    7979   REAL,SAVE,ALLOCATABLE,DIMENSION(:)     :: preskim  ! Pressure (Pa) of upper chemistry (mid)-layers
    80    REAL,SAVE,ALLOCATABLE,DIMENSION(:,:)   :: zlay_kim ! Altitude (km) of all chemistry (mid)-layers
     80   REAL,SAVE,ALLOCATABLE,DIMENSION(:,:)   :: zlaykim  ! Pseudo-altitude (km) of upper chemistry (mid)-layers
    8181   REAL,SAVE,ALLOCATABLE,DIMENSION(:,:,:) :: ykim_up  ! Upper chemistry fields (mol/mol)
    82 !$OMP_THREADPRIVATE(preskim,zlay_kim,ykim_up)
    83 
    84 
     82   
     83   ! These "_tot" fields are for output only
     84   REAL,SAVE,ALLOCATABLE,DIMENSION(:)     :: preskim_tot  ! Pressure (Pa) of total chemistry (mid)-layers
     85   REAL,SAVE,ALLOCATABLE,DIMENSION(:,:)   :: zlaykim_tot  ! Pseudo-altitude (km) of total chemistry (mid)-layers
     86   REAL,SAVE,ALLOCATABLE,DIMENSION(:,:,:) :: ykim_tot     ! Total chemistry fields (mol/mol)
     87   
     88!$OMP_THREADPRIVATE(preskim,zlaykim,ykim_up)
     89!$OMP_THREADPRIVATE(preskim_tot,zlaykim_tot,ykim_tot)
    8590
    8691   ! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
     
    116121 
    117122    IF (.NOT.allocated(preskim)) ALLOCATE(preskim(nlaykim_up))
    118     IF (.NOT.allocated(zlay_kim)) ALLOCATE(zlay_kim(ngrid,nlaykim_tot))
     123    IF (.NOT.allocated(zlaykim)) ALLOCATE(zlaykim(ngrid,nlaykim_up))
    119124    IF (.NOT.allocated(ykim_up)) ALLOCATE(ykim_up(nkim,ngrid,nlaykim_up))
     125   
     126    IF (.NOT.allocated(preskim_tot)) ALLOCATE(preskim_tot(nlaykim_tot))
     127    IF (.NOT.allocated(zlaykim_tot)) ALLOCATE(zlaykim_tot(ngrid,nlaykim_tot))
     128    IF (.NOT.allocated(ykim_tot)) ALLOCATE(ykim_tot(nkim,ngrid,nlaykim_tot))
    120129 
    121130  END SUBROUTINE ini_comchem_h
  • trunk/LMDZ.TITAN/libf/phytitan/phyetat0_mod.F90

    r1894 r1943  
    274274  ! Call to soil_settings, in order to read upper chemistry
    275275  ! pressure grid as well as composition fields
    276   call chem_settings(nid_start,ngrid,indextime)
     276  call chem_settings(nid_start,ngrid,nlayer,indextime)
    277277endif ! of if (startphy_file)
    278278
  • trunk/LMDZ.TITAN/libf/phytitan/physiq_mod.F90

    r1927 r1943  
    1717      use radcommon_h, only: sigma, glat, grav, BWNV
    1818      use surfdat_h, only: phisfi, zmea, zstd, zsig, zgam, zthe
    19       use comchem_h, only: nkim, cnames
     19      use comchem_h, only: nkim, cnames, nlaykim_up, ykim_up, ykim_tot
    2020      use comdiurn_h, only: coslat, sinlat, coslon, sinlon
    2121      use comsaison_h, only: mu0, fract, dist_star, declin, right_ascen
     
    15931593      ! Chemical tracers
    15941594      if (callchim) then
     1595     
     1596        ! Advected fields
    15951597        do iq=1,nkim
    1596           CALL send_xios_field(cnames(iq),zq(:,:,iq+nmicro)/rat_mmol(iq+nmicro)) ! mol/mol
     1598          CALL send_xios_field(trim(cnames(iq)),zq(:,:,iq+nmicro)/rat_mmol(iq+nmicro)) ! kg/kg -> mol/mol
    15971599        enddo
    1598       endif
     1600       
     1601        ! Upper chemistry fields
     1602        do iq=1,nkim
     1603          CALL send_xios_field(trim(cnames(iq))//"_up",ykim_up(iq,:,:)) ! mol/mol
     1604        enddo
     1605       
     1606        ! Append fields in ykim_tot for output on the total vertical grid (0->1300km)
     1607        do iq=1,nkim
     1608         
     1609          ! GCM levels
     1610          do l=1,nlayer
     1611            ykim_tot(iq,:,l) = zq(:,l,iq+nmicro)/rat_mmol(iq+nmicro)
     1612          enddo
     1613          ! Upper levels
     1614          do l=1,nlaykim_up
     1615            ykim_tot(iq,:,nlayer+l) = ykim_up(iq,:,l)
     1616          enddo
     1617         
     1618          CALL send_xios_field(trim(cnames(iq))//"_tot",ykim_tot(iq,:,:)) ! mol/mol
     1619         
     1620        enddo
     1621       
     1622      endif ! of 'if callchim'
    15991623
    16001624      ! Microphysical tracers
  • trunk/LMDZ.TITAN/libf/phytitan/xios_output_mod.F90

    r1896 r1943  
    3535#endif
    3636  USE wxios, ONLY: wxios_domain_param, wxios_domain_param_unstructured, wxios_closedef
     37 
     38  USE comchem_h, ONLY: preskim, preskim_tot, zlaykim, zlaykim_tot
     39 
    3740  IMPLICIT NONE
    3841 
     
    4548 
    4649 
     50  INTEGER :: i
    4751  INTEGER :: data_ibegin, data_iend
    4852  TYPE(xios_duration) :: timestep
     
    6064    CALL xios_set_axis_attr("altitude", n_glo=size(pseudoalt), value=pseudoalt,&
    6165                            unit="km",positive="up")
     66   
     67    IF (prt_level>=10) WRITE(lunout,*) "initialize_xios_output: call xios_set_axis_attr for preskim"
     68    CALL xios_set_axis_attr("preskim", n_glo=size(preskim), value=preskim,&
     69                            unit="Pa",positive="down")
     70                         
     71    IF (prt_level>=10) WRITE(lunout,*) "initialize_xios_output: call xios_set_axis_attr for preskim_tot"
     72    CALL xios_set_axis_attr("preskim_tot", n_glo=size(preskim_tot), value=preskim_tot,&
     73                            unit="Pa",positive="down")
     74                           
     75    ! Calculation of pseudo-altitudes is still to be done
     76    !IF (prt_level>=10) WRITE(lunout,*) "initialize_xios_output: call xios_set_axis_attr for zlaykim"
     77    !CALL xios_set_axis_attr("zlaykim", n_glo=size(preskim), value=preskim,&
     78    !                        unit="km",positive="up")
     79    !                     
     80    !IF (prt_level>=10) WRITE(lunout,*) "initialize_xios_output: call xios_set_axis_attr for zlaykim_tot"
     81    !CALL xios_set_axis_attr("zlaykim_tot", n_glo=size(zlaykim_tot), value=zlaykim_tot,&
     82    !                        unit="km",positive="up")
     83   
    6284   
    6385    ! 2. Declare horizontal domain
Note: See TracChangeset for help on using the changeset viewer.