source: trunk/LMDZ.TITAN/libf/phytitan/chem_settings.F90 @ 3567

Last change on this file since 3567 was 2326, checked in by jvatant, 5 years ago

Update Titan reference photochemistry (reaction constants,branching ratios, condensation rates) according to Vuitton et al 2019.
--JVO

File size: 3.8 KB
RevLine 
[1943]1SUBROUTINE chem_settings(nid,ngrid,nlayer,indextime)
[1894]2
3! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
4!
5! Author : Jan Vatant d'Ollone (2018)
6! ------
7!
8! Purpose : + Intialise upper atmosphere chemistry pressure grid
9! -------   and composition fields.
10!           + This subroutine is called in phyetat0 and reads
11!           from a NetCDF "startfi.nc" file.
12!           + The presence of pressure grid is compulsory in the
13!           file but not composition fields. The presence of the
14!           1st field is tested and then we assume there's either
[2326]15!           no one or all of the nkim chemistry scheme species.
[1894]16!
17! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
18
19USE comchem_h
[1895]20USE iostart, only: get_field, get_var, inquire_dimension_length
21USE callkeys_mod, only : callchim
[1894]22
[1943]23USE vertical_layers_mod, only: presnivs, pseudoalt
24
[1894]25IMPLICIT NONE
26
27!======================================================================
28!  INPUTS :
29!  --------
30  INTEGER,INTENT(IN)  :: nid            ! Input Netcdf file ID
31  INTEGER,INTENT(IN)  :: ngrid          ! # of horizontal grid points
[1943]32  INTEGER,INTENT(IN)  :: nlayer         ! # of vertical layers
[1894]33  INTEGER,INTENT(IN)  :: indextime      ! position on time axis
34!======================================================================
35! local variables:
[1943]36  REAL :: phi0, phi
37
[1894]38  INTEGER :: ierr       ! status (returned by NetCDF functions)
39  INTEGER :: nvarid     ! ID of NetCDF variable
40  INTEGER :: dimid      ! ID of NetCDF dimension
41 
[1943]42  INTEGER :: ilay, iq
[1894]43 
44  LOGICAL ::  found
45 
46  CHARACTER(LEN=13) :: modname
47!======================================================================
48
[1895]49  ! 0. Start by reading how many layers of upper chemistry there are
50 
51  nlaykim_up=inquire_dimension_length("upper_chemistry_layers")
52 
53  ! 1. Allocates arrays in comchem_h
54 
[1894]55  CALL ini_comchem_h(ngrid)
56
[1895]57  ! 2. Load upper chemistry pressure grid
[1894]58 
59  CALL get_var("preskim",preskim,found)
60  IF (.NOT.found) THEN
61    CALL abort_physic(modname,"Failed loading <preskim>",1)
62  ENDIF
63  WRITE(*,*) "chem_settings: Upper chemistry pressure grid <preskim> range:", &
64               maxval(preskim), minval(preskim)
[1943]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 ?)         
[1894]77 
[1943]78  ! 4. Inquire ( and load ) upper chemistry composition fields
[1894]79 
80  CALL get_field("H_up",ykim_up(1,:,:),found,indextime)
81  IF (.NOT.found) THEN
[1895]82 
[1894]83    ! We assume we can't do uncomplete chemistry
84    WRITE(*,*) "chem_settings: No upper chemistry fields."
[1895]85   
86    IF ( callchim ) THEN ! if chemistry we must have the upper fields !
87      CALL abort_physic(modname,"Failed loading uppper chemistry fields, whereas callchim set to true !",1)
88    ENDIF
89   
90    DEALLOCATE(ykim_up) ! it will be useless
[1943]91    DEALLOCATE(ykim_tot) ! it will be useless
[1895]92   
[1894]93  ELSE
94 
95    WRITE(*,*) "chem_settings: H in upper atmosphere <H_up> range:", &
96               minval(ykim_up(1,:,:)), maxval(ykim_up(1,:,:))
97               
98    ! Load others fields if first one found only as we assume we can't do uncomplete chemistry
[2326]99    ! NB : We assume a given order of the chemistry species !!
100    ! ( H=1, H2=2 ...,) -> cf comchem_h
[1894]101   
[1903]102    DO iq=2,nkim
[1894]103      CALL get_field(trim(cnames(iq))//"_up",ykim_up(iq,:,:),found,indextime)
104      IF (.NOT.found) THEN
105        CALL abort_physic(modname,"Failed loading <"//trim(cnames(iq))//"_up>",1)
106      ENDIF
107      WRITE(*,*) "chem_settings: "//trim(cnames(iq))//" in upper atmosphere <"//trim(cnames(iq))//"_up> range:", &
108                 minval(ykim_up(iq,:,:)), maxval(ykim_up(iq,:,:))
109    ENDDO
110     
111  ENDIF ! of if H_up found
112 
113END SUBROUTINE chem_settings
Note: See TracBrowser for help on using the repository browser.