source: CONFIG/publications/ICOLMDZORINCA_CO2_Transport_GMD_2023/INCA/build/ppsrc/INCA_SRC/chem_inti.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: 4.7 KB
Line 
1
2
3
4
5
6
7
8
9
10
11
12!$Id: chem_inti.F90 104 2008-12-23 10:28:51Z acosce $
13!! =========================================================================
14!! INCA - INteraction with Chemistry and Aerosols
15!!
16!! Copyright Laboratoire des Sciences du Climat et de l'Environnement (LSCE)
17!!           Unite mixte CEA-CNRS-UVSQ
18!!
19!! Contributors to this INCA subroutine:
20!!
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
64SUBROUTINE CHEM_INTI( )
65
66  !--------------------------------------------------------
67  !     ... Initialize chemistry modules
68  ! Stacy Walters, NCAR, 2000.
69  !--------------------------------------------------------
70 
71  USE CHEM_TRACNM
72  USE CHEM_MODS
73  USE MOD_INCA_PARA
74  USE PRINT_INCA
75
76  IMPLICIT NONE
77 
78
79  !--------------------------------------------------------
80  !     ... Local variables
81  !--------------------------------------------------------
82  INTEGER  ::  i, k, ios
83  integer :: ierr
84  character(100) :: nbtrac
85  !________________________________________________________
86 
87  !--------------------------------------------------------
88  !     ... Open chem input unit
89  !--------------------------------------------------------
90!$OMP MASTER
91  IF (is_mpi_root) THEN
92      OPEN( unit = 20, file = 'inca.dat',status = 'old',iostat = ios )
93      IF( ios /= 0 ) THEN
94          CALL print_err(3, ' CHEM_INTI','Failed to open inca.dat file', '', '')
95      END IF
96  ENDIF
97!$OMP END MASTER
98
99  !--------------------------------------------------------
100  !        ... Read map info from data file
101  !--------------------------------------------------------
102!$OMP MASTER
103  IF (is_mpi_root) READ(20,*) nbtrac
104!$OMP END MASTER
105
106!$OMP MASTER
107  IF (is_mpi_root) READ(20,'(5i4)') clscnt
108!$OMP END MASTER
109  CALL bcast(clscnt)
110
111!$OMP MASTER
112  IF (is_mpi_root) READ(20,'(4i4)') cls_rxt_cnt
113!$OMP END MASTER
114  CALL bcast(cls_rxt_cnt)
115
116!$OMP MASTER
117  IF (is_mpi_root) THEN
118      DO k = 1,5
119        IF( clscnt(k) /= 0 ) THEN
120            READ(20,'(20i4)') clsmap(:clscnt(k),k)
121        END IF
122      END DO
123  ENDIF
124!$OMP END MASTER
125  CALL bcast(clsmap)
126
127!$OMP MASTER
128  IF (is_mpi_root) READ(20,*) adv_mass(:8)
129!$OMP END MASTER
130  CALL bcast(adv_mass)
131
132
133!$OMP MASTER
134  IF (is_mpi_root) READ(20,'(10a8)') solsym(:8)
135!$OMP END MASTER
136  CALL bcast(solsym)
137
138
139!$OMP MASTER
140  IF (is_mpi_root) THEN
141      DO i = 2,5
142        IF( clscnt(i) /= 0 ) THEN
143            READ(20,'(20i4)') permute(:clscnt(i),i)
144        END IF
145      END DO
146  ENDIF
147!$OMP END MASTER
148  CALL bcast(permute)
149
150!$OMP MASTER
151  IF (is_mpi_root) CLOSE( 20 )
152!$OMP END MASTER
153
154
155END SUBROUTINE CHEM_INTI
156
157
158
Note: See TracBrowser for help on using the repository browser.