source: CONFIG/publications/ICOLMDZORINCA_CO2_Transport_GMD_2023/INCA/build/ppsrc/INCA_MOD/oxydant_com_mod.f90 @ 6610

Last change on this file since 6610 was 6610, checked in by acosce, 10 months ago

INCA used for ICOLMDZORINCA_CO2_Transport_GMD_2023

File size: 5.9 KB
Line 
1
2
3
4
5
6
7
8
9
10
11
12!$Id: oxydant_com_mod.F90 104 2008-12-23 10:28:51Z acosce $
13!! INCA - INteraction with Chemistry and Aerosols
14!!
15!! Copyright Laboratoire des Sciences du Climat et de l'Environnement (LSCE)
16!!           Unite mixte CEA-CNRS-UVSQ
17!!
18!! Contributors to this INCA subroutine:
19!!
20!! Didier Hauglustaine, LSCE, hauglustaine@cea.fr
21!! Stacy Walters, NCAR, stacy@ucar.edu
22!!
23!! Anne Cozic, LSCE, anne.cozic@cea.fr
24!! Yann Meurdesoif, LSCE, yann.meurdesoif@cea.fr
25!!
26!! This software is a computer program whose purpose is to simulate the
27!! atmospheric gas phase and aerosol composition. The model is designed to be
28!! used within a transport model or a general circulation model. This version
29!! of INCA was designed to be coupled to the LMDz GCM. LMDz-INCA accounts
30!! for emissions, transport (resolved and sub-grid scale), photochemical
31!! transformations, and scavenging (dry deposition and washout) of chemical
32!! species and aerosols interactively in the GCM. Several versions of the INCA
33!! model are currently used depending on the envisaged applications with the
34!! chemistry-climate model.
35!!
36!! This software is governed by the CeCILL  license under French law and
37!! abiding by the rules of distribution of free software.  You can  use,
38!! modify and/ or redistribute the software under the terms of the CeCILL
39!! license as circulated by CEA, CNRS and INRIA at the following URL
40!! "http://www.cecill.info".
41!!
42!! As a counterpart to the access to the source code and  rights to copy,
43!! modify and redistribute granted by the license, users are provided only
44!! with a limited warranty  and the software's author,  the holder of the
45!! economic rights,  and the successive licensors  have only  limited
46!! liability.
47!!
48!! In this respect, the user's attention is drawn to the risks associated
49!! with loading,  using,  modifying and/or developing or reproducing the
50!! software by the user in light of its specific status of free software,
51!! that may mean  that it is complicated to manipulate,  and  that  also
52!! therefore means  that it is reserved for developers  and  experienced
53!! professionals having in-depth computer knowledge. Users are therefore
54!! encouraged to load and test the software's suitability as regards their
55!! requirements in conditions enabling the security of their systems and/or
56!! data to be ensured and,  more generally, to use and operate it in the
57!! same conditions as regards security.
58!!
59!! The fact that you are presently reading this means that you have had
60!! knowledge of the CeCILL license and that you accept its terms.
61!! =========================================================================
62
63
64module OXYDANT_COM
65
66  implicit none
67
68  integer, save :: ncid
69  integer, save :: nlono, nlato, nlevo, ntimeo
70  integer, save :: lotime = 0, hitime = 0
71  integer, save :: loind  = 1, hiind  = 2
72  integer, save :: oh_id, o1d_id, o3_id, no3_id, h2o2_id, hno3_id, no2_id
73!$OMP THREADPRIVATE(ncid, nlono, nlato, nlevo, ntimeo)
74!$OMP THREADPRIVATE(lotime, hitime, loind, hiind)
75!$OMP THREADPRIVATE(oh_id, o1d_id, o3_id, no3_id, h2o2_id, hno3_id, no2_id)
76  REAL, SAVE :: time_oxyd_1, time_oxyd_2
77!$OMP THREADPRIVATE(time_oxyd_1, time_oxyd_2)
78  real, allocatable, save :: timeo(:)
79  real, allocatable, dimension(:,:,:,:), save :: ohoxydbd, o1doxydbd
80  real, allocatable, dimension(:,:,:,:), save :: o3oxydbd, no3oxydbd, h2o2oxydbd
81  real, allocatable, dimension(:,:,:,:), save :: hno3oxydbd, no2oxydbd
82  real, allocatable, dimension(:,:,:) , save :: ohoxyd_inter
83  real, allocatable, dimension(:,:,:) , save :: o1doxyd_inter
84  real, allocatable, dimension(:,:,:) , save :: o3oxyd_inter
85  real, allocatable, dimension(:,:,:) , save :: no3oxyd_inter
86  real, allocatable, dimension(:,:,:) , save :: h2o2oxyd_inter
87  real, allocatable, dimension(:,:,:) , save :: hno3oxyd_inter, no2oxyd_inter
88  real, allocatable, dimension(:,:,:) , save :: ohoxyd_phis
89  real, allocatable, dimension(:,:,:) , save :: o1doxyd_phis
90  real, allocatable, dimension(:,:,:) , save :: o3oxyd_phis
91  real, allocatable, dimension(:,:,:) , save :: no3oxyd_phis
92  real, allocatable, dimension(:,:,:) , save :: h2o2oxyd_phis
93  real, allocatable, dimension(:,:,:) , save :: hno3oxyd_phis, no2oxyd_phis
94!$OMP THREADPRIVATE(timeo)
95!$OMP THREADPRIVATE(ohoxydbd, o1doxydbd, o3oxydbd, no3oxydbd, h2o2oxydbd, hno3oxydbd, no2oxydbd)
96!$OMP THREADPRIVATE(ohoxyd_inter, o1doxyd_inter, o3oxyd_inter, no3oxyd_inter)
97!$OMP THREADPRIVATE(h2o2oxyd_inter, hno3oxyd_inter,no2oxyd_inter, ohoxyd_phis, o1doxyd_phis, o3oxyd_phis)
98!$OMP THREADPRIVATE(no3oxyd_phis, h2o2oxyd_phis, hno3oxyd_phis, no2oxyd_phis)
99  real, allocatable, dimension(:,:,:) , save :: ohoxyd_year
100  real, allocatable, dimension(:,:,:) , save :: o1doxyd_year
101  real, allocatable, dimension(:,:,:) , save :: o3oxyd_year
102  real, allocatable, dimension(:,:,:) , save :: no3oxyd_year
103  real, allocatable, dimension(:,:,:) , save :: h2o2oxyd_year
104  real, allocatable, dimension(:,:,:) , save :: hno3oxyd_year, no2oxyd_year
105
106!$OMP THREADPRIVATE(ohoxyd_year, o1doxyd_year, o3oxyd_year)
107!$OMP THREADPRIVATE(no3oxyd_year, h2o2oxyd_year, hno3oxyd_year, no2oxyd_year)                                                   
108
109
110
111  real, SAVE, ALLOCATABLE :: ohoxyd(:,:)
112  real, SAVE, ALLOCATABLE :: o1doxyd(:,:)
113  real, SAVE, ALLOCATABLE :: o3oxyd(:,:)
114  real, SAVE, ALLOCATABLE :: no3oxyd(:,:)
115  real, SAVE, ALLOCATABLE :: h2o2oxyd(:,:)
116  real, SAVE, ALLOCATABLE :: hno3oxyd(:,:)
117  real, SAVE, ALLOCATABLE :: no2oxyd(:,:)
118!$OMP THREADPRIVATE(ohoxyd,o1doxyd,o3oxyd,no3oxyd,h2o2oxyd,hno3oxyd, no2oxyd)
119  logical, save :: cyclical = .true.
120!$OMP THREADPRIVATE(cyclical)
121
122CONTAINS
123
124
125  SUBROUTINE init_oxydant_com
126    USE inca_dim
127    IMPLICIT NONE
128
129    ALLOCATE(ohoxyd(PLON,PLEV))
130    ALLOCATE(o1doxyd(PLON,PLEV))
131    ALLOCATE(o3oxyd(PLON,PLEV))
132    ALLOCATE(no3oxyd(PLON,PLEV))
133    ALLOCATE(h2o2oxyd(PLON,PLEV))
134    ALLOCATE(hno3oxyd(PLON,PLEV))
135    ALLOCATE(no2oxyd(PLON,PLEV))
136
137  END SUBROUTINE init_oxydant_com
138
139
140
141
142end module OXYDANT_COM
143
144
145
146
Note: See TracBrowser for help on using the repository browser.