source: CONFIG/publications/ICOLMDZORINCA_CO2_Transport_GMD_2023/INCA/build/ppsrc/INCA_SRC/photo_interp.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: 9.9 KB
Line 
1
2
3
4
5
6
7
8
9
10
11
12!$Id: photo_interp.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 PHOTO_INTERP( &
65   zin      ,&
66   sin      ,&
67   vin      ,&
68   albin    ,&
69   t500in   ,&
70   t200in   ,&
71   ajout )
72  !----------------------------------------------------------------------
73  !     ... Loglinear interpolation for the photodissociation rates
74  !         Note: this subroutine computes photorates for a vertical
75  !               column at a given longitude and latitude
76  !           This routine uses a six parameter table via a Taylor
77  !           series expansion.
78  !           Stacy Walters, Sep 30, 1996.  Changed code to strictly limit
79  !           the 200mb and 500mb temperature interpolation to the table
80  !           endpoints; i.e. no extrapolation beyond the table is allowed.
81  !----------------------------------------------------------------------
82 
83  USE PHT_TABLES
84  USE INCA_DIM
85 
86  IMPLICIT NONE
87 
88  !----------------------------------------------------------------------
89  !        ... Dummy arguments
90  !----------------------------------------------------------------------
91  REAL, INTENT(in)  ::  zin(PLEV)      ! pressure in millibars
92  REAL, INTENT(in)  ::  sin            ! secant solar zenith angle
93  REAL, INTENT(in)  ::  vin(PLEV)      ! o3 column density
94  REAL, INTENT(in)  ::  albin(PLEV)    ! surface albedo
95  REAL, INTENT(in)  ::  t500in         ! temp on 500mb surface
96  REAL, INTENT(in)  ::  t200in         ! temp on 200mb surface
97  REAL, INTENT(out) ::  ajout(jdim,PLEV)        ! photodissociation rates
98 
99  !----------------------------------------------------------------------
100  !        ... Local variables
101  !----------------------------------------------------------------------
102  INTEGER  ::  i, iz, is, iv, ial, nn, it500, it200
103  INTEGER  ::  i1, i2
104  INTEGER  ::  k
105  INTEGER  ::  izl
106  INTEGER  ::  index0
107  INTEGER  ::  base_ind
108  INTEGER  ::  indv0(7,PLEV)
109  INTEGER, DIMENSION(PLEV) :: altind, ratind, albind
110  REAL     ::  v3std
111  REAL     ::  psum
112  REAL     ::  dels(6)
113  REAL, DIMENSION(PLEV) :: v3rat, wght0, wght1, wght2, wght3, wght4
114  INTEGER :: first_level
115
116  !----------------------------------------------------------------------
117  !        ... Find the zenith angle index ( same for all levels )
118  !----------------------------------------------------------------------
119  DO is = 1,zangdim
120    IF( vsec(is) > sin ) THEN
121        EXIT
122    END IF
123  END DO
124  is = MAX( MIN( is,zangdim ) - 1,1 )
125  dels(2)  = (sin - vsec(is)) * delang(is)
126 
127  !----------------------------------------------------------------------
128  !        ... Find the 500mb temp index ( same for all levels )
129  !----------------------------------------------------------------------
130  DO it500 = 1,t500dim
131    IF( t500(it500) > t500in ) THEN
132        EXIT
133    END IF
134  END DO
135  it500 = MAX( MIN( it500,t500dim ) - 1,1 )
136  dels(5)  = (t500in - t500(it500)) * delt500(it500)
137  dels(5) = MAX( MIN( dels(5),1. ),0. )
138 
139  !----------------------------------------------------------------------
140  !        ... Find the 200mb temp index ( same for all levels )
141  !----------------------------------------------------------------------
142  it200 = 1
143  dels(6)  = (t200in - t200(it200)) * delt200(it200)
144  dels(6) = MAX( MIN( dels(6),1. ),0. )
145 
146  base_ind = is * offset(2) + it500 * offset(5) &
147     + it200 * offset(6) - offset(7)
148 
149  izl = 1
150  DO k = PLEV,1,-1
151    !----------------------------------------------------------------------
152    !        ... Find albedo indicies
153    !----------------------------------------------------------------------
154    DO ial = 1,albdim
155      IF( albev(ial) > albin(k) ) THEN
156          EXIT
157      END IF
158    END DO
159    albind(k) = MAX( MIN( ial,albdim ) - 1,1 )
160    !----------------------------------------------------------------------
161    !        ... Find level indicies
162    !----------------------------------------------------------------------
163    DO iz = izl,altdim
164      IF( zz(iz) > zin(k) ) THEN
165          izl = iz
166          EXIT
167      END IF
168    END DO
169    altind(k) = MAX( MIN( iz,altdim ) - 1,1 )
170    !----------------------------------------------------------------------
171    !        ... Find o3 ratio indicies
172    !----------------------------------------------------------------------
173    i = MAX( MIN( altmxdim-1,INT( zin(k) ) ),0 )
174    v3std = vo3(i) + (zin(k) - FLOAT(i)) * (vo3(i+1) - vo3(i))
175    v3rat(k) = vin(k) / v3std
176    DO iv = 1,o3ratdim
177      IF( xv3(iv) > v3rat(k) ) THEN
178          EXIT
179      END IF
180    END DO
181    ratind(k) = MAX( MIN( iv,o3ratdim ) - 1,1 )
182  END DO
183
184
185!!! patch pour le 79 niveau - Fixed a bug in the last level (at 80km)
186!!! we put the last 3 level to the value of the fourth one
187!!! Anne et Didier 24 mai 2017
188  IF (PLEV .EQ. 79) THEN
189     DO k = 1,3
190        iz  = altind(4)
191        iv  = ratind(4)
192        ial = albind(4)
193        index0 = base_ind + ial * offset(4)  &
194             + iv * offset(3) + iz * offset(1)
195       
196        dels(1)  = (zin(4) - zz(iz)) * delz(iz)
197        dels(3)  = (v3rat(4) - xv3(iv)) * delv(iv)
198        dels(4)  = (albin(4) - albev(ial)) * delalb(ial)
199       
200        !----------------------------------------------------------------------
201        !        ... Compute the weigths
202        !----------------------------------------------------------------------
203        wght0(k) = 1. - SUM( dels )
204        wght1(k) = dels(1)
205        wght3(k) = dels(3)
206        wght4(k) = dels(4)
207       
208        !----------------------------------------------------------------------
209        !        ... Compute the indicies into ajl
210        !----------------------------------------------------------------------
211        indv0(1,k) = index0
212        indv0(2,k) = index0 + offset(1)
213        indv0(3,k) = index0 + offset(2)
214        indv0(4,k) = index0 + offset(3)
215        indv0(5,k) = index0 + offset(4)
216        indv0(6,k) = index0 + offset(5)
217        indv0(7,k) = index0 + offset(6)
218     END DO
219     first_level=4
220  ELSE
221     first_level=1
222  ENDIF
223
224  DO k = first_level,PLEV
225    iz  = altind(k)
226    iv  = ratind(k)
227    ial = albind(k)
228    index0 = base_ind + ial * offset(4)  &
229       + iv * offset(3) + iz * offset(1)
230   
231    dels(1)  = (zin(k) - zz(iz)) * delz(iz)
232    dels(3)  = (v3rat(k) - xv3(iv)) * delv(iv)
233    dels(4)  = (albin(k) - albev(ial)) * delalb(ial)
234   
235    !----------------------------------------------------------------------
236    !        ... Compute the weigths
237    !----------------------------------------------------------------------
238    wght0(k) = 1. - SUM( dels )
239    wght1(k) = dels(1)
240    wght3(k) = dels(3)
241    wght4(k) = dels(4)
242   
243    !----------------------------------------------------------------------
244    !        ... Compute the indicies into ajl
245    !----------------------------------------------------------------------
246    indv0(1,k) = index0
247    indv0(2,k) = index0 + offset(1)
248    indv0(3,k) = index0 + offset(2)
249    indv0(4,k) = index0 + offset(3)
250    indv0(5,k) = index0 + offset(4)
251    indv0(6,k) = index0 + offset(5)
252    indv0(7,k) = index0 + offset(6)
253  END DO
254 
255  DO is = 1,jdim*PLEV
256    k = MOD( is-1,PLEV ) + 1
257    nn = (is - 1)/PLEV + 1
258    psum    = wght0(k) * ajl(indv0(1,k)+nn) &
259       + wght1(k) * ajl(indv0(2,k)+nn)  &
260       + dels(2)  * ajl(indv0(3,k)+nn)  &
261       + wght3(k) * ajl(indv0(4,k)+nn)  &
262       + wght4(k) * ajl(indv0(5,k)+nn)  &
263       + dels(5)  * ajl(indv0(6,k)+nn)  &
264       + dels(6)  * ajl(indv0(7,k)+nn) 
265    ajout(nn,k) = EXP( psum )
266
267
268  END DO
269
270
271END SUBROUTINE PHOTO_INTERP
Note: See TracBrowser for help on using the repository browser.