source: CONFIG/publications/ICOLMDZORINCA_CO2_Transport_GMD_2023/INCA/build/ppsrc/INCA_MOD/chem_controls_mod.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.4 KB
Line 
1
2
3
4
5
6
7
8
9
10
11
12!$Id: chem_controls_mod.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
64module CHEM_CONTROLS
65  !-------------------------------------------------------------------
66  !     ... Control variables
67  !     Stacy Walters, NCAR, 1998.
68  !-------------------------------------------------------------------
69
70  implicit none
71
72  real, parameter :: secpday = 86400.
73  integer, save :: nspday                    ! number of steps per day
74  integer, save :: delt                      ! delt in seconds
75  integer, save :: step_cnt = 0              ! time step counter
76  integer, save :: time_step                 ! time step index
77  integer, save :: total_steps
78  logical, save :: first_step
79  logical, save :: last_step
80  logical, save :: diurnal_step = .false.
81!$OMP THREADPRIVATE(nspday,delt,step_cnt,time_step,total_steps)
82!$OMP THREADPRIVATE(first_step,last_step,diurnal_step)
83
84  type DATE_TIME
85     integer :: date
86     integer :: secs
87  end type DATE_TIME
88  type(DATE_TIME), SAVE :: time_t
89!$OMP THREADPRIVATE(time_t)
90
91  !ym     
92  logical, SAVE :: lafin=.FALSE.
93!$OMP THREADPRIVATE(lafin)
94
95CONTAINS
96
97  subroutine INI_DATE( ncdate, ncsec, mdelt, begstep, endstep )
98    !-------------------------------------------------------------------
99    !   ... Initialize the time_t structure to next time
100    !-------------------------------------------------------------------
101
102    implicit none
103
104    !-------------------------------------------------------------------
105    !   ... Dummy args
106    !-------------------------------------------------------------------
107    integer, intent(in) :: ncdate, ncsec, begstep, mdelt, endstep
108
109    time_step = begstep
110    time_t%date = ncdate
111    time_t%secs = ncsec
112    delt = mdelt
113    total_steps = endstep - begstep
114    nspday = NINT( secpday/REAL(mdelt) )
115
116  end subroutine INI_DATE
117
118  subroutine UPDATE_TIME( )
119    !-------------------------------------------------------------------
120    !   ... Update the time_t structure to next time
121    !-------------------------------------------------------------------
122
123    implicit none
124
125    !-------------------------------------------------------------------
126    !   ... Local variables
127    !-------------------------------------------------------------------
128    integer :: iday
129
130    !-------------------------------------------------------------------
131    !   ... Function declarations
132    !-------------------------------------------------------------------
133    integer :: NEWDATE
134
135    step_cnt = step_cnt + 1
136    time_step = time_step + 1
137    time_t%secs = time_t%secs + delt
138    if( time_t%secs >= secpday ) then
139       iday = INT(time_t%secs/secpday)
140       time_t%secs = MOD( time_t%secs,INT(secpday) )
141       time_t%date = NEWDATE( time_t%date, iday )
142    end if
143    first_step = step_cnt == 1
144    last_step  = step_cnt == total_steps
145    diurnal_step = MOD( step_cnt,nspday ) == 0
146
147  end subroutine UPDATE_TIME
148
149end module CHEM_CONTROLS
Note: See TracBrowser for help on using the repository browser.