source: CONFIG/publications/ICOLMDZORINCA_CO2_Transport_GMD_2023/INCA/build/ppsrc/INCA_SRC/prate_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: 6.1 KB
Line 
1
2
3
4
5
6
7
8
9
10
11
12!$Id: prate_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
63SUBROUTINE PRATE_INTI( unit )
64  !----------------------------------------------------------------------
65  !     ... Read in the photorate tables and arrays
66  !         Results are "returned" via the module PHT_TABLES
67  ! Stacy Walters, NCAR, 1998.
68  !----------------------------------------------------------------------
69
70  USE PHT_TABLES
71  USE MOD_INCA_PARA
72  USE PRINT_INCA
73  USE CHEM_CONS
74
75  IMPLICIT NONE
76 
77  !----------------------------------------------------------------------
78  !        ... Dummy args
79  !----------------------------------------------------------------------
80  INTEGER, INTENT(in) :: unit
81
82  !----------------------------------------------------------------------
83  !        ... Local variables
84  !----------------------------------------------------------------------
85  INTEGER    :: it500, it200, izen, ialb, idob
86  INTEGER    :: ios, is
87  REAL       :: jinput(jdim,altdim,zangdim,o3ratdim, &
88     albdim,t500dim,t200dim)
89 
90!$OMP MASTER
91  IF (is_mpi_root) THEN
92     
93      OPEN( unit   = unit              ,&
94         file   = 'phototable.dat'  ,&
95         status = 'old'             ,&
96         form   = 'formatted'       ,&
97         iostat = ios )
98      IF( ios /= 0 ) THEN
99          !----------------------------------------------------------------------
100          !     ... Open error exit
101          !----------------------------------------------------------------------
102          call print_err(3, "PRATE_INTI", 'Error opening phototable.dat', '', '')
103      END IF
104     
105!----------------------------------------------------------------------
106!        ... Readin the reference o3 column and photorate table
107!----------------------------------------------------------------------
108      READ(unit,*,iostat=ios) vo3
109      IF( ios /= 0 ) THEN
110          CALL print_err(3, ' PRATE_INTI','Failed to read o3 column', '', '')
111      END IF
112
113      DO it500 = 1,t500dim
114        DO it200 = 1,t200dim
115          DO izen = 1,zangdim
116            DO ialb = 1,albdim
117              DO idob = 1,o3ratdim
118                READ(unit,*,iostat=ios)        & 
119                   jinput(:,:,izen,idob,ialb,it500,it200)
120                IF( ios /= 0 ) THEN
121                    CALL print_err(3, ' PRATE_INTI', ' Failed to read phototable', '', '')
122                END IF
123              END DO
124            END DO
125          END DO
126        END DO
127      END DO
128      ajl = RESHAPE( jinput, (/tabdim/) )
129      CLOSE( unit )
130     
131  ENDIF ! is_root_prc
132!$OMP END MASTER
133     
134  CALL bcast(vo3)
135  CALL bcast(ajl)
136 
137  !----------------------------------------------------------------------
138  ! ... Calculates secant based on input zenith angle
139  !----------------------------------------------------------------------
140  DO is = 1, zangdim
141    vsec(is) = 1. / COS(dsza(is)*d2r)
142  END DO
143
144  !----------------------------------------------------------------------
145  !     ... Set module variables
146  !----------------------------------------------------------------------
147  delz(:altdim-1) = 1. / (zz(2:altdim) - zz(:altdim-1))
148  delang(:zangdim-1) = 1. / (vsec(2:zangdim) - vsec(:zangdim-1))
149  delv(:o3ratdim-1) = 1. / (xv3(2:o3ratdim) - xv3(:o3ratdim-1))
150  delalb(:albdim-1)  = 1. / (albev(2:albdim) - albev(:albdim-1))
151  delt500(:t500dim-1) = 1. / (t500(2:t500dim) - t500(:t500dim-1))
152  delt200(:t200dim-1) = 1. / (t200(2:t200dim) - t200(:t200dim-1))
153 
154  offset(1) = jdim
155  offset(2) = offset(1)*altdim
156  offset(3) = offset(2)*zangdim
157  offset(4) = offset(3)*o3ratdim
158  offset(5) = offset(4)*albdim
159  offset(6) = offset(5)*t500dim
160  offset(7) = SUM( offset(1:6) )
161 
162END SUBROUTINE PRATE_INTI
163
Note: See TracBrowser for help on using the repository browser.