source: LMDZ6/trunk/libf/phydev/infotrac_phy.f90 @ 5481

Last change on this file since 5481 was 5481, checked in by dcugnet, 13 hours ago

Remove tracers attributes "isAdvected" and "isInPhysics" from infotrac (iadv is enough).
Remove tracers attribute "isAdvected" from infotrac_phy (isInPhysics is now equivalent
to former isInPhysics .AND. iadv > 0

File size: 3.3 KB
Line 
1
2! $Id: $
3
4MODULE infotrac_phy
5
6   USE strings_mod, ONLY: maxlen
7!   PUBLIC :: tracers, type_trac                            !--- Full tracers database, tracers type keyword
8!   PUBLIC :: nqtot,   nbtr,   nqo,   nqCO2,   nqtottr      !--- Main dimensions
9   INTEGER,SAVE :: nqtot,   nbtr,   nqo,   nqCO2,   nqtottr      !--- Main dimensions
10   INTEGER,SAVE :: niso,ntiso
11   CHARACTER(LEN=maxlen), SAVE :: type_trac                     !--- Keyword for tracers type(s)
12
13  TYPE :: keys_type                                        !=== TYPE FOR A SET OF KEYS ASSOCIATED TO AN ELEMENT
14    CHARACTER(LEN=maxlen)              :: name             !--- Tracer name
15    CHARACTER(LEN=maxlen), ALLOCATABLE :: key(:)           !--- Keys string list
16    CHARACTER(LEN=maxlen), ALLOCATABLE :: val(:)           !--- Corresponding values string list
17  END TYPE keys_type
18
19  TYPE :: trac_type                                        !=== TYPE FOR A SINGLE TRACER NAMED "name"
20    CHARACTER(LEN=maxlen) :: name        = ''              !--- Name of the tracer
21    CHARACTER(LEN=maxlen) :: gen0Name    = ''              !--- First generation ancestor name
22    CHARACTER(LEN=maxlen) :: parent      = ''              !--- Parent name
23    CHARACTER(LEN=maxlen) :: longName    = ''              !--- Long name (with advection scheme suffix)
24    CHARACTER(LEN=maxlen) :: type        = 'tracer'        !--- Type  (so far: 'tracer' / 'tag')
25    CHARACTER(LEN=maxlen) :: phase       = 'g'             !--- Phase ('g'as / 'l'iquid / 's'olid)
26    CHARACTER(LEN=maxlen) :: component   = ''              !--- Coma-separated list of components (Ex: lmdz,inca)
27    INTEGER               :: iGeneration = -1              !--- Generation number (>=0)
28    INTEGER               :: iqParent    = 0               !--- Parent index
29    INTEGER,  ALLOCATABLE :: iqDescen(:)                   !--- Descendants index (in growing generation order)
30    INTEGER               :: nqDescen    = 0               !--- Number of descendants (all generations)
31    INTEGER               :: nqChildren  = 0               !--- Number of children  (first generation)
32    TYPE(keys_type)       :: keys                          !--- <key>=<val> pairs vector
33    INTEGER               :: iadv        = 10              !--- Advection scheme used
34    LOGICAL               :: isInPhysics = .TRUE.          !--- "true" tracers: in tr_seri. COUNT(isInPhysics)=nqtottr
35    INTEGER               :: iso_iGroup  = 0               !--- Isotopes group index in isotopes(:)
36    INTEGER               :: iso_iName   = 0               !--- Isotope  name  index in isotopes(iso_iGroup)%trac(:)
37    INTEGER               :: iso_iZone   = 0               !--- Isotope  zone  index in isotopes(iso_iGroup)%zone(:)
38    INTEGER               :: iso_iPhase  = 0               !--- Isotope  phase index in isotopes(iso_iGroup)%phase
39  END TYPE trac_type
40
41   TYPE(trac_type), ALLOCATABLE, TARGET, SAVE ::  tracers(:)
42
43
44!$OMP THREADPRIVATE(nqtot, nbtr, nqo, nqtottr, nqCO2, type_trac)
45!$OMP THREADPRIVATE(niso,ntiso)
46!$OMP THREADPRIVATE(trac_type,tracers)
47
48
49
50
51CONTAINS
52
53SUBROUTINE init_infotrac_phy(nqtot_, type_trac_)
54   IMPLICIT NONE
55   INTEGER,          INTENT(IN) :: nqtot_
56   CHARACTER(LEN=*), INTENT(IN) :: type_trac_
57   CHARACTER(LEN=maxlen) :: modname='init_infotrac_phy'
58
59   nqtot = nqtot_
60   type_trac = type_trac_
61
62  END SUBROUTINE init_infotrac_phy
63
64END MODULE infotrac_phy
Note: See TracBrowser for help on using the repository browser.