Changeset 1889


Ignore:
Timestamp:
Jan 9, 2018, 12:26:53 PM (7 years ago)
Author:
jvatant
Message:

Making chemistry handling more flexible - Step 2
+ Added the calculation of the pressure grid in newstart
using Vervack profile in gr_kim_vervack routine
+ Next step : regridding !
--JVO

Location:
trunk/LMDZ.TITAN
Files:
1 added
7 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.TITAN/README

    r1871 r1889  
    13431343Big modifs of the tracer gestion/init in the physiq with a new query by names (see tracer_h )
    13441344
    1345 == 20/12/2017 - ... : r1871- ... == JVO
     1345== 20/12/2017 - ... : r1871-1886-1888 ... == JVO
    13461346Management of the chemistry within startfi. Open the way to :
    13471347 1) run with chemistry in another resolution than 32x48 !
     
    13521352rather than read in the middle of calchim as before from compo files
    13531353+ An "upper_chemistry_layers" dimension is now handled in startfi files
    1354 + This dimension is also stored in tabfi
    13551354+ Added a comchem_h.F90 module for all the stuff related to chemistry
     1355+ In newstart we calculates the pressure grid above GCM top using Vervack profile
    13561356+ ...
  • trunk/LMDZ.TITAN/libf/dynphy_lonlat/phytitan/lect_start_archive.F

    r1647 r1889  
    55
    66!      USE surfdat_h
     7      USE comchem_h, ONLY: nlaykimold, preskimold
    78      USE comsoil_h, ONLY: nsoilmx, layer, mlayer, volcapa, inertiedat
    89      USE infotrac, ONLY: tname, nqtot
     
    4647c------------------------------------
    4748      INTEGER   imold,jmold,lmold,nsoilold,nqold
    48 
    4949
    5050c Variables pour les lectures des fichiers "ini"
     
    147147      real, dimension(:,:), allocatable :: emisold
    148148      real, dimension(:,:,:,:), allocatable :: qold
    149 
     149     
    150150      real tab_cntrl(100)
    151151
     
    158158      logical :: therminertia_3D=.true. ! flag
    159159! therminertia_3D=.true. if thermal inertia is 3D and read from datafile
     160
    160161c Variable intermediaires iutilise pour l'extrapolation verticale
    161162c----------------------------------------------------------------
     
    247248      endif
    248249
    249 
    250250      if (nsoilold.ne.nsoilmx) then ! interpolation will be required
    251251        depthinterpol=.true.
    252252      endif
     253
     254! 1.2.2 find out the # of upper chemistry layers
     255
     256      ierr= NF_INQ_DIMID(nid,"upper_chemistry_layers",dimid)
     257      ierr= NF_INQ_DIMLEN(nid,dimid,nlaykimold)
     258
     259      ! NB : The regriding, if needed cannot be done here since the new
     260      ! pressure grid is only computed at the end of newstart
    253261
    254262! 1.3 Report dimensions
     
    266274      write(*,*) '  Otherwise, set nsoilmx -in dimphys.h- to: ',nsoilold
    267275      endif
     276      write(*,*) "upper_chemistry_layers: ",nlaykimold
    268277      write(*,*) "time lenght: ",timelen
    269278      write(*,*)
     
    295304      allocate(mlayerold(nsoilold))
    296305      allocate(qsurfold(imold+1,jmold+1,nqtot))
     306     
     307      allocate(preskimold(nlaykimold))
    297308
    298309      allocate(var (imold+1,jmold+1,llm))
     
    512523       endif
    513524      endif
    514 
    515 c-----------------------------------------------------------------------
    516 c 3.6 Lecture geopotentiel au sol
     525     
     526c-----------------------------------------------------------------------
     527c 3.6 Read upper chemistry mid-layer pressure
     528c----------------------------------------------------------------------- 
     529   
     530      ierr=NF_INQ_VARID(nid,"preskim",nvarid)
     531      IF (ierr .NE. NF_NOERR) THEN
     532         PRINT*, "lect_start_archive: Le champ <preskim> est absent"
     533         CALL abort
     534      ENDIF
     535#ifdef NC_DOUBLE
     536      ierr = NF_GET_VAR_DOUBLE(nid, nvarid, preskimold)
     537#else
     538      ierr = NF_GET_VAR_REAL(nid, nvarid, preskimold)
     539#endif
     540      IF (ierr .NE. NF_NOERR) THEN
     541         PRINT*, "lect_start_archive: Lecture echouee pour <preskim>"
     542         CALL abort
     543      ENDIF
     544
     545c-----------------------------------------------------------------------
     546c 3.7 Lecture geopotentiel au sol
    517547c-----------------------------------------------------------------------
    518548c
  • trunk/LMDZ.TITAN/libf/dynphy_lonlat/phytitan/newstart.F

    r1871 r1889  
    1717     &                              is_master
    1818      use infotrac, only: infotrac_init, nqtot, tname
     19      USE comchem_h, ONLY: nlaykim_up, nlaykimold
    1920      USE comsoil_h, ONLY: nsoilmx, layer, mlayer, inertiedat
    2021      USE surfdat_h, ONLY: phisfi, albedodat,
     
    130131      real tab_cntrl(100)
    131132      real tab_cntrl_bis(100)
    132 
     133     
    133134c variables diverses
    134135c-------------------
     
    258259
    259260      endif
    260 
    261261
    262262c=======================================================================
     
    536536        CALL lect_start_archive(ngridmx,llm,
    537537     &   date,tsurf,tsoil,emis,q2,
    538      &   t,ucov,vcov,ps,teta,phisold_newgrid,q,qsurf,
    539      &   surfith,nid)
     538     &   t,ucov,vcov,ps,teta,phisold_newgrid,
     539     &   q,qsurf,surfith,nid)
    540540        write(*,*) "OK, read start_archive file"
    541541        ! copy soil thermal inertia
     
    572572      write(*,*) 'q=x : give a specific uniform value to one tracer'
    573573      write(*,*) 'q=profile    : specify a profile for a tracer'
    574 !      write(*,*) 'ini_q : tracers initialisation for chemistry, water an
    575 !     $d ice   '
    576 !      write(*,*) 'ini_q-H2O : tracers initialisation for chemistry and
    577 !     $ice '
    578 !      write(*,*) 'ini_q-iceH2O : tracers initialisation for chemistry on
    579 !     $ly '
    580574      write(*,*) 'isotherm  : Isothermal Temperatures, wind set to zero'
    581575      write(*,*) 'radequi   : Earth-like radiative equilibrium temperature
     
    10711065      CALL inifilr
    10721066      CALL pression(ip1jmp1, ap, bp, ps, p3d)
     1067     
     1068
     1069c=========================================================================
     1070c  Calcul de la dimension verticale pour la chimie  - JVO 2017
     1071c  start_archive seulement, la grille verticale pouvant avoir ete modifiee
     1072c==========================================================================
     1073
     1074      IF (choix_1.eq.0) THEN
     1075
     1076        ! Calculate the # of upper chemistry layers with the "new" pressure grid
     1077        ! For this we use Vervack profile for upper atmosphere with dz=10km
     1078
     1079        CALL gr_kim_vervack
     1080
     1081        WRITE(*,*)
     1082        WRITE(*,*) " With the compiled vertical grid we found :"
     1083        WRITE(*,*) " Number of upper chemistry layers =", nlaykim_up
     1084       
     1085        ! Regriding is then done, if needed
     1086       
     1087        IF (nlaykimold.ne.nlaykim_up) THEN
     1088
     1089          WRITE(*,*) " Warning, nlaykimold=", nlaykimold
     1090          WRITE(*,*) ' which implies that a regriding on upper chemistry
     1091     & will be performed.'
     1092          WRITE(*,*)
     1093         
     1094!          CALL  regrid_kim
     1095         
     1096        ENDIF
     1097 
     1098      endif ! of if (choix_1.eq.0)     
     1099 
    10731100
    10741101c-----------------------------------------------------------------------
     
    11251152         day_ini=int(date)
    11261153      endif
     1154
    11271155c
    11281156      CALL geopot  ( ip1jmp1, teta  , pk , pks,  phis  , phi   )
  • trunk/LMDZ.TITAN/libf/phytitan/comchem_h.F90

    r1887 r1889  
    1919!$OMP_THREADPRIVATE(zlay_kim)
    2020
     21
     22  ! Variable and allocatables for regriding chemistry newstart
     23  ! ----------------------------------------------------------
     24   
     25  INTEGER :: nlaykimold ! Number of upper atm. layers for chemistry in the start_archive file
     26  REAL, ALLOCATABLE, DIMENSION(:) :: preskimold ! Pressure grid of upper chemistry in the start_archive file
    2127
    2228  ! Allocatable arrays for start2archive
  • trunk/LMDZ.TITAN/libf/phytitan/iostart.F90

    r1871 r1889  
    944944                    NF90_PUT_ATT, NF90_NOERR, nf90_strerror, &
    945945                    nf90_inq_dimid, nf90_inquire_dimension, NF90_INQ_VARID
     946  USE comchem_h, only: nlaykim_up
    946947  USE comsoil_h, only: nsoilmx
    947948  USE mod_phys_lmdz_para, only: is_master
     
    997998        ! We know it is an  "mlayer" kind of 1D array
    998999        idim1d=idim3
     1000      ELSEIF (var_size==nlaykim_up) THEN
     1001        ! We know it is an  "preskim" kind of 1D array
     1002        idim1d=idim8
    9991003      ELSE
    10001004        PRINT *, "put_var_rgen error : wrong dimension"
  • trunk/LMDZ.TITAN/libf/phytitan/phyredem.F90

    r1789 r1889  
    99                         alb,ith,pzmea,pzstd,pzsig,pzgam,pzthe)
    1010! create physics restart file and write time-independent variables
     11  use comchem_h, only: preskim
    1112  use comsoil_h, only: volcapa, mlayer
    1213  use geometry_mod, only: cell_area
     
    104105  call put_var("soildepth","Soil mid-layer depth",mlayer)
    105106 
     107  ! Write the mid-layer upper chemistry pressure
     108  call put_var("preskim","Upper chemistry mid-layer pressure",preskim)
     109 
    106110  ! Write longitudes
    107111  call put_field("longitude","Longitudes of physics grid",lonfi)
  • trunk/LMDZ.TITAN/libf/phytitan/tabfi_mod.F90

    r1871 r1889  
    5555                           emissiv
    5656      use comsoil_h, only: volcapa
    57       use comchem_h, only: nlaykim_up
    5857      use iostart, only: get_var
    5958      use mod_phys_lmdz_para, only: is_parallel
     
    150149        dtemisice(:)=0 !time scale for snow metamorphism
    151150        volcapa=1000000 ! volumetric heat capacity of subsurface
    152 ! chemistry
    153         nlaykim_up=70 ! size of vertical grid for upper chemistry
    154151       
    155152      ELSE
     
    207204! soil properties
    208205      volcapa = tab_cntrl(tab0+35) ! volumetric heat capacity
    209 ! chemistry
    210       nlaykim_up = nint(tab_cntrl(tab0+40)) ! size of vertical grid for upper chemistry
    211206!-----------------------------------------------------------------------
    212207!       Save some constants for later use (as routine arguments)
     
    261256
    262257      write(*,5) '(35)        volcapa',tab_cntrl(tab0+35),volcapa
    263 
    264       write(*,5) '(40)     nlaykim_up',tab_cntrl(tab0+40),float(nlaykim_up)
    265258
    266259      write(*,*)
     
    571564 
    572565      write(*,5) '(35)        volcapa',tab_cntrl(tab0+35),volcapa
    573      
    574       write(*,5) '(40)     nlaykim_up',tab_cntrl(tab0+40),float(nlaykim_up)
    575566
    576567      write(*,*) 
Note: See TracChangeset for help on using the changeset viewer.