source: CONFIG/publications/ICOLMDZORINCA_CO2_Transport_GMD_2023/INCA/build/ppsrc/INCA_SRC/ac_sulf.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.1 KB
Line 
1
2
3
4
5
6
7
8
9
10
11
12!$Id: ac_sulf.F90 10 2007-08-09 12:43:01Z 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 FINDPLB( x, nx, xval, index )
65  !-----------------------------------------------------------------------
66  !     ... "find periodic lower bound"
67  !     Search the input array for the lower bound of the interval that
68  !     contains the input value.  The returned index satifies:
69  !     x(index) .le. xval .lt. x(index+1)
70  !     Assume the array represents values in one cycle of a periodic coordinate.
71  !     So, if xval .lt. x(1), then index=nx.
72  ! Stacy Walters, NCAR, 1998.
73  !-----------------------------------------------------------------------
74  USE PRINT_INCA
75  IMPLICIT NONE
76
77  !-----------------------------------------------------------------------
78  !     ... Dummy args
79  !-----------------------------------------------------------------------
80  INTEGER, INTENT(in) ::  nx
81  INTEGER, INTENT(out) ::  index
82  REAL, INTENT(in) ::  x(nx)         ! strictly increasing array
83  REAL, INTENT(in) ::  xval
84
85  !-----------------------------------------------------------------------
86  !     ... Local variables
87  !-----------------------------------------------------------------------
88  INTEGER :: i
89
90  IF( xval < x(1) .OR. xval >= x(nx) ) THEN
91      index = nx
92      RETURN
93  END IF
94
95  DO i = 2,nx
96    IF( xval < x(i) ) THEN
97        index = i - 1
98        EXIT
99    END IF
100  END DO
101
102END SUBROUTINE FINDPLB
103
104subroutine LININTP( npts, t1, t2, tint, f1, f2, fint )
105!-----------------------------------------------------------------------
106!       ... Linearly interpolate between f1(t1) and f2(t2) to fint(tint)
107! Stacy Walters, NCAR, 1998.
108!-----------------------------------------------------------------------
109
110  implicit none
111
112!-----------------------------------------------------------------------
113!       ... Dummy args
114!-----------------------------------------------------------------------
115  integer, intent(in) ::  npts
116  real, intent(in) ::  t1               ! time level of f1
117  real, intent(in) :: t2               ! time level of f2
118  real, intent(in) :: tint             ! interpolant time
119  real, intent(in) :: f1(npts)         ! field at time t1
120  real, intent(in) :: f2(npts)         ! field at time t2
121  real, intent(out) :: fint(npts)       ! field at time tint
122 
123!-----------------------------------------------------------------------
124!       ... Local variables
125!-----------------------------------------------------------------------
126  integer :: i
127  real :: factor
128 
129  factor = (tint - t1) / (t2 - t1)
130
131  do i = 1, npts
132     fint(i) = f1(i) + ( f2(i) - f1(i) )*factor
133  end do
134 
135end subroutine LININTP
136
Note: See TracBrowser for help on using the repository browser.