source: CONFIG/publications/ICOLMDZORINCA_CO2_Transport_GMD_2023/INCA/build/ppsrc/INCA_SRC/ub_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: 11.5 KB
Line 
1
2
3
4
5
6
7
8
9
10
11
12!$Id: ub_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!! Didier Hauglustaine, LSCE, hauglustaine@cea.fr
22!! Stacy Walters, NCAR, stacy@ucar.edu
23!! 
24!! Anne Cozic, LSCE, anne.cozic@cea.fr
25!! Yann Meurdesoif, LSCE, yann.meurdesoif@cea.fr
26!!
27!! This software is a computer program whose purpose is to simulate the
28!! atmospheric gas phase and aerosol composition. The model is designed to be
29!! used within a transport model or a general circulation model. This version
30!! of INCA was designed to be coupled to the LMDz GCM. LMDz-INCA accounts
31!! for emissions, transport (resolved and sub-grid scale), photochemical
32!! transformations, and scavenging (dry deposition and washout) of chemical
33!! species and aerosols interactively in the GCM. Several versions of the INCA
34!! model are currently used depending on the envisaged applications with the
35!! chemistry-climate model.
36!!
37!! This software is governed by the CeCILL  license under French law and
38!! abiding by the rules of distribution of free software.  You can  use,
39!! modify and/ or redistribute the software under the terms of the CeCILL
40!! license as circulated by CEA, CNRS and INRIA at the following URL
41!! "http://www.cecill.info".
42!!
43!! As a counterpart to the access to the source code and  rights to copy,
44!! modify and redistribute granted by the license, users are provided only
45!! with a limited warranty  and the software's author,  the holder of the
46!! economic rights,  and the successive licensors  have only  limited
47!! liability.
48!!
49!! In this respect, the user's attention is drawn to the risks associated
50!! with loading,  using,  modifying and/or developing or reproducing the
51!! software by the user in light of its specific status of free software,
52!! that may mean  that it is complicated to manipulate,  and  that  also
53!! therefore means  that it is reserved for developers  and  experienced
54!! professionals having in-depth computer knowledge. Users are therefore
55!! encouraged to load and test the software's suitability as regards their
56!! requirements in conditions enabling the security of their systems and/or
57!! data to be ensured and,  more generally, to use and operate it in the
58!! same conditions as regards security.
59!!
60!! The fact that you are presently reading this means that you have had
61!! knowledge of the CeCILL license and that you accept its terms.
62!! =========================================================================
63
64
65SUBROUTINE OZCLIM_INTI (filename)
66  !----------------------------------------------------------------------
67  !       ... Ozone climatologies initialize
68  !----------------------------------------------------------------------
69 
70  USE O3CLIM_COM 
71  USE INCA_DIM
72  USE MOD_INCA_PARA
73  IMPLICIT NONE
74
75  INCLUDE 'netcdf.inc'
76
77  !----------------------------------------------------------------------
78  !       ... Dummy args
79  !----------------------------------------------------------------------
80  CHARACTER(len=*), INTENT(in) :: filename
81 
82  !----------------------------------------------------------------------
83  !       ... Local variables
84  !----------------------------------------------------------------------
85  INTEGER :: iret
86  INTEGER :: varid
87  INTEGER :: error
88 
89!$OMP MASTER
90  IF (is_mpi_root) THEN
91      ! ... Open the file
92      iret = nf_open(filename, 0, ncidc)
93      CALL check_err(iret, 'OZCLIM_INTI', 'problem to open file')
94     
95      ! ... Get lengths
96      iret = nf_inq_dimid(ncidc, 'time', varid)
97      CALL check_err(iret, 'OZCLIM_INTI', 'problem to check dimid time')
98      iret = nf_inq_dimlen(ncidc, varid, ntimec)
99      CALL check_err(iret, 'OZCLIM_INTI', 'problem to check dimlen time')
100      iret = nf_inq_dimid(ncidc, 'pressure', varid)
101      CALL check_err(iret, 'OZCLIM_INTI','problem to check dimid pressure')
102      iret = nf_inq_dimlen(ncidc, varid, nlevc)
103      CALL check_err(iret, 'OZCLIM_INTI', 'problem to check dimlen pressure')
104      iret = nf_inq_dimid(ncidc, 'vector', varid)
105      CALL check_err(iret, 'OZCLIM_INTI', 'problem to check dimid vector')
106      iret = nf_inq_dimlen(ncidc, varid, klonc)
107      CALL check_err(iret, 'OZCLIM_INTI', 'problem to check dimlen vector')
108  ENDIF
109!$OMP END MASTER     
110  CALL bcast(ntimec)
111  CALL bcast(nlevc)
112  CALL bcast(klonc)
113     
114  IF (klonc/=nbp_glo) THEN
115     write(lunout, *) '[klonc] [nbp_glo]', klonc, nbp_glo
116     call print_err(3, 'OZCLIM_INTI', 'check klonc and nbp_glo, they must to be equal', '', '')
117  ELSE
118      klonc=PLON
119  ENDIF
120         
121  ! ... Allocate variables
122  ALLOCATE(timec(ntimec), STAT=error)
123  IF (error /= 0) CALL print_err(3, 'OZCLIM_INTI', 'Space requested not possible for timec', '', '')
124  ALLOCATE(presc(nlevc), STAT=error)
125  IF (error /= 0) CALL print_err(3,  'OZCLIM_INTI', 'Space requested not possible for presc', '', '')
126  ALLOCATE(o3climbd(klonc,nlevc,2), STAT=error)
127  IF (error /= 0) CALL print_err(3,  'OZCLIM_INTI', 'Space requested not possible for o3climbd', '', '')
128  ALLOCATE(o3climcr(klonc,nlevc), STAT=error)
129  IF (error /= 0) CALL print_err(3,  'OZCLIM_INTI', 'Space requested not possible for o3climcr', '', '')
130 
131!$OMP MASTER
132  IF (is_mpi_root) THEN
133      ! ... Get the coordinates
134      iret = nf_inq_varid(ncidc, 'time', varid)
135      CALL check_err(iret, 'OZCLIM_INTI', 'problem to check varid time')
136      iret = nf_get_var_double(ncidc, varid, timec)
137      CALL check_err(iret, 'OZCLIM_INTI', 'problem to read time')
138
139      iret = nf_inq_varid(ncidc, 'pressure', varid)
140      CALL check_err(iret, 'OZCLIM_INTI', 'problem to check varid pressure')
141      iret = nf_get_var_double(ncidc, varid, presc)
142      CALL check_err(iret, 'OZCLIM_INTI', 'problem to read pressure')
143  ENDIF
144!$OMP END MASTER
145  CALL bcast(timec)
146  CALL bcast(presc)
147  ! ... Units (pressure from mbar to Pa)
148  presc = presc * 1.e2
149 
150END SUBROUTINE OZCLIM_INTI
151
152SUBROUTINE OZLIN_INTI (filename)
153  !----------------------------------------------------------------------
154  !       ... Ozone linear initialize
155  !----------------------------------------------------------------------
156 
157  USE O3LIN_COM 
158  USE INCA_DIM
159  USE MOD_INCA_PARA
160  IMPLICIT NONE
161
162  INCLUDE 'netcdf.inc'
163
164  !----------------------------------------------------------------------
165  !       ... Dummy args
166  !----------------------------------------------------------------------
167  CHARACTER(len=*), INTENT(in) :: filename
168 
169  !----------------------------------------------------------------------
170  !       ... Local variables
171  !----------------------------------------------------------------------
172  INTEGER :: iret
173  INTEGER :: varid
174  INTEGER :: error
175 
176!$OMP MASTER
177  IF (is_mpi_root) THEN
178      ! ... Open the file
179      iret = nf_open(filename, 0, ncidl)
180      CALL check_err(iret, 'OZLIN_INTI', 'problem to open file')
181     
182      ! ... Get lengths
183      iret = nf_inq_dimid(ncidl, 'time', varid)
184      CALL check_err(iret, 'OZLIN_INTI', 'problem to get id for dim time')
185      iret = nf_inq_dimlen(ncidl, varid, ntimel)
186      CALL check_err(iret, 'OZLIN_INTI', 'problem to get length time ')
187      iret = nf_inq_dimid(ncidl, 'pressure', varid)
188      CALL check_err(iret, 'OZLIN_INTI', 'problem to get id for dim pressure')
189      iret = nf_inq_dimlen(ncidl, varid, nlevl)
190      CALL check_err(iret, 'OZLIN_INTI', 'problem to get length pressure')
191      iret = nf_inq_dimid(ncidl, 'vector', varid)
192      CALL check_err(iret, 'OZLIN_INTI', 'problem to get id for dim vector')
193      iret = nf_inq_dimlen(ncidl, varid, klonl)
194      CALL check_err(iret, 'OZLIN_INTI', 'problem to get length vector')
195  ENDIF
196!$OMP END MASTER     
197  CALL bcast(ntimel)
198  CALL bcast(nlevl)
199  CALL bcast(klonl)
200     
201  IF (klonl/=nbp_glo) THEN
202     WRITE(lunout, *) '[klonl] [nbp_glo]', klonl, nbp_glo
203     CALL print_err(3, 'OZLIN_INTI', 'check klonl and nbp_glo, they must to be equal', '', '')
204  ELSE
205      klonl=PLON
206  ENDIF
207         
208  ! ... Allocate variables
209  ALLOCATE(timel(ntimel), STAT=error)
210  IF (error /= 0) CALL print_err(3, 'OZLIN_INTI', 'Space requested not possible for timel', '', '') 
211  ALLOCATE(presl(nlevl), STAT=error)
212  IF (error /= 0) CALL print_err(3, 'OZLIN_INTI', 'Space requested not possible for presl', '', '') 
213  ALLOCATE(A1bd(klonl,nlevl,2), STAT=error)
214  IF (error /= 0) CALL print_err(3, 'OZLIN_INTI', 'Space requested not possible for A1bd', '', '') 
215  ALLOCATE(A1cr(klonl,nlevl), STAT=error)
216  IF (error /= 0) CALL print_err(3, 'OZLIN_INTI', 'Space requested not possible for A1cr', '', '') 
217  ALLOCATE(A2bd(klonl,nlevl,2), STAT=error)
218  IF (error /= 0) CALL print_err(3, 'OZLIN_INTI', 'Space requested not possible for A2bd', '', '') 
219  ALLOCATE(A2cr(klonl,nlevl), STAT=error)
220  IF (error /= 0) CALL print_err(3, 'OZLIN_INTI', 'Space requested not possible for A2cr', '', '') 
221  ALLOCATE(A3bd(klonl,nlevl,2), STAT=error)
222  IF (error /= 0) CALL print_err(3, 'OZLIN_INTI', 'Space requested not possible for A3bd', '', '') 
223  ALLOCATE(A3cr(klonl,nlevl), STAT=error)
224  IF (error /= 0) CALL print_err(3, 'OZLIN_INTI', 'Space requested not possible for A3cr', '', '') 
225  ALLOCATE(A4bd(klonl,nlevl,2), STAT=error)
226  IF (error /= 0) CALL print_err(3, 'OZLIN_INTI', 'Space requested not possible for A4bd', '', '') 
227  ALLOCATE(A4cr(klonl,nlevl), STAT=error)
228  IF (error /= 0) CALL print_err(3, 'OZLIN_INTI', 'Space requested not possible for A4cr', '', '') 
229  ALLOCATE(A5bd(klonl,nlevl,2), STAT=error)
230  IF (error /= 0) CALL print_err(3, 'OZLIN_INTI', 'Space requested not possible for A5bd', '', '') 
231  ALLOCATE(A5cr(klonl,nlevl), STAT=error)
232  IF (error /= 0) CALL print_err(3, 'OZLIN_INTI', 'Space requested not possible for A5cr', '', '') 
233  ALLOCATE(A6bd(klonl,nlevl,2), STAT=error)
234  IF (error /= 0) CALL print_err(3, 'OZLIN_INTI', 'Space requested not possible for A6bd', '', '') 
235  ALLOCATE(A6cr(klonl,nlevl), STAT=error)
236  IF (error /= 0) CALL print_err(3, 'OZLIN_INTI', 'Space requested not possible for A6cr', '', '') 
237  ALLOCATE(A7bd(klonl,nlevl,2), STAT=error)
238  IF (error /= 0) CALL print_err(3, 'OZLIN_INTI', 'Space requested not possible for A7bd', '', '') 
239  ALLOCATE(A7cr(klonl,nlevl), STAT=error)
240  IF (error /= 0) CALL print_err(3, 'OZLIN_INTI', 'Space requested not possible for A7cr', '', '') 
241  ALLOCATE(A8bd(klonl,nlevl,2), STAT=error)
242  IF (error /= 0) CALL print_err(3, 'OZLIN_INTI', 'Space requested not possible for A8bd', '', '') 
243  ALLOCATE(A8cr(klonl,nlevl), STAT=error)
244  IF (error /= 0) CALL print_err(3, 'OZLIN_INTI', 'Space requested not possible for A8cr', '', '') 
245  ALLOCATE(A9bd(klonl,nlevl,2), STAT=error)
246  IF (error /= 0) CALL print_err(3, 'OZLIN_INTI', 'Space requested not possible for A9bd', '', '') 
247  ALLOCATE(A9cr(klonl,nlevl), STAT=error)
248  IF (error /= 0) CALL print_err(3, 'OZLIN_INTI', 'Space requested not possible for A9cr', '', '') 
249 
250!$OMP MASTER
251  IF (is_mpi_root) THEN
252      ! ... Get the coordinates
253      iret = nf_inq_varid(ncidl, 'time', varid)
254      CALL check_err(iret, 'OZLIN_INTI', 'problem to get id for var time')
255      iret = nf_get_var_double(ncidl, varid, timel)
256      CALL check_err(iret, 'OZLIN_INTI', 'problem to read var time')
257      iret = nf_inq_varid(ncidl, 'pressure', varid)
258      CALL check_err(iret, 'OZLIN_INTI', 'problem to get id for var pressure')
259      iret = nf_get_var_double(ncidl, varid, presl)
260      CALL check_err(iret, 'OZLIN_INTI', 'problem to read var pressure')
261  ENDIF
262!$OMP END MASTER
263
264  CALL bcast(timel)
265  CALL bcast(presl)
266
267  ! ... Units (pressure from hPa to Pa)
268  presl = presl * 1.e2
269 
270END SUBROUTINE OZLIN_INTI
271
272
Note: See TracBrowser for help on using the repository browser.