source: palm/trunk/SOURCE/swap_timelevel.f90 @ 4002

Last change on this file since 4002 was 3761, checked in by raasch, 5 years ago

unused variables removed, OpenACC directives re-formatted, statements added to avoid compiler warnings

  • Property svn:keywords set to Id
File size: 7.1 KB
Line 
1!> @file swap_timelevel.f90
2!------------------------------------------------------------------------------!
3! This file is part of the PALM model system.
4!
5! PALM is free software: you can redistribute it and/or modify it under the
6! terms of the GNU General Public License as published by the Free Software
7! Foundation, either version 3 of the License, or (at your option) any later
8! version.
9!
10! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
11! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
12! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
13!
14! You should have received a copy of the GNU General Public License along with
15! PALM. If not, see <http://www.gnu.org/licenses/>.
16!
17! Copyright 1997-2019 Leibniz Universitaet Hannover
18!------------------------------------------------------------------------------!
19!
20! Current revisions:
21! -----------------
22!
23!
24! Former revisions:
25! -----------------
26! $Id: swap_timelevel.f90 3761 2019-02-25 15:31:42Z Giersch $
27! unused variables removed
28!
29! 3655 2019-01-07 16:51:22Z knoop
30! Implementation of the PALM module interface
31!
32! 3636 2018-12-19 13:48:34Z raasch
33! nopointer option removed
34!
35! 3589 2018-11-30 15:09:51Z suehring
36! Move the control parameter "salsa" from salsa_mod to control_parameters
37! (M. Kurppa)
38!
39! 3582 2018-11-29 19:16:36Z suehring
40! Implementation of a new aerosol module salsa.
41!
42! 3303 2018-10-03 12:04:15Z raasch
43! bugfix for swapping in case of ocean mode
44!
45! 3294 2018-10-01 02:37:10Z raasch
46! changes concerning modularization of ocean option
47!
48! 3274 2018-09-24 15:42:55Z knoop
49! Modularization of all bulk cloud physics code components
50!
51! 3241 2018-09-12 15:02:00Z raasch
52! unused variables removed
53!
54! 2817 2018-02-19 16:32:21Z knoop
55! Preliminary gust module interface implemented
56!
57! 2766 2018-01-22 17:17:47Z kanani
58! Removed preprocessor directive __chem
59!
60! 2718 2018-01-02 08:49:38Z maronga
61! Corrected "Former revisions" section
62!
63! 2696 2017-12-14 17:12:51Z kanani
64! Change in file header (GPL part)
65! Moved TKE to turbulence_closure_mod (TG)
66! Implementation of chemistry module (FK)
67!
68! 2350 2017-08-15 11:48:26Z kanani
69! Bugfix in nopointer version
70!
71! 2292 2017-06-20 09:51:42Z schwenkel
72! Implementation of new microphysic scheme: cloud_scheme = 'morrison'
73! includes two more prognostic equations for cloud drop concentration (nc) 
74! and cloud water content (qc).
75!
76! 2233 2017-05-30 18:08:54Z suehring
77!
78! 2232 2017-05-30 17:47:52Z suehring
79! Adjustments to new surface concept
80!
81! 2118 2017-01-17 16:38:49Z raasch
82! OpenACC directives removed
83!
84! 2011 2016-09-19 17:29:57Z kanani
85! Flag urban_surface is now defined in module control_parameters.
86!
87! 2007 2016-08-24 15:47:17Z kanani
88! Added swapping of urban surface model quantities,
89! removed redundance for land surface model
90!
91! 2000 2016-08-20 18:09:15Z knoop
92! Forced header and separation lines into 80 columns
93!
94! 1960 2016-07-12 16:34:24Z suehring
95! Separate humidity and passive scalar
96!
97! 1822 2016-04-07 07:49:42Z hoffmann
98! icloud_scheme replaced by microphysics_*
99!
100! swap_timelevel.f90 1766 2016-02-29 08:37:15Z raasch
101! setting the swap level for pmc data transfer
102!
103! 1747 2016-02-08 12:25:53Z raasch
104! explicit loops in nopointer case to omit craypointer option of pgi compiler
105!
106! 1682 2015-10-07 23:56:08Z knoop
107! Code annotations made doxygen readable
108!
109! 1496 2014-12-02 17:25:50Z maronga
110! Added swapping of land surface model quantities
111!
112! 1374 2014-04-25 12:55:07Z raasch
113! bugfix: use-statement for nopointer-case added
114!
115! 1320 2014-03-20 08:40:49Z raasch
116! ONLY-attribute added to USE-statements,
117! revision history before 2012 removed,
118! 1318 2014-03-17 13:35:16Z raasch
119! module interfaces removed
120!
121! 1115 2013-03-26 18:16:16Z hoffmann
122! calculation of qr and nr is restricted to precipitation
123!
124! 1111 2013-03-08 23:54:10Z raasch
125! openACC directives added
126!
127! 1053 2012-11-13 17:11:03Z hoffmann
128! swap of timelevels for nr, qr added
129!
130! 1036 2012-10-22 13:43:42Z raasch
131! code put under GPL (PALM 3.9)
132!
133! 1032 2012-10-21 13:03:21Z letzel
134! save memory by not allocating pt_2 in case of neutral = .T.
135!
136! 1010 2012-09-20 07:59:54Z raasch
137! cpp switch __nopointer added for pointer free version
138!
139! 1001 2012-09-13 14:08:46Z raasch
140! all actions concerning leapfrog scheme removed
141!
142! Revision 1.1  2000/01/10  10:08:58  10:08:58  raasch (Siegfried Raasch)
143! Initial revision
144!
145!
146! Description:
147! ------------
148!> Swap of timelevels of variables after each timestep
149!------------------------------------------------------------------------------!
150 SUBROUTINE swap_timelevel
151 
152
153    USE arrays_3d,                                                                                 &
154        ONLY:  pt, pt_1, pt_2, pt_p, q, q_1, q_2, q_p, s, s_1, s_2, s_p, u, u_1, u_2, u_p, v, v_1, &
155               v_2, v_p, w, w_1, w_2, w_p
156
157    USE cpulog,                                                                                    &
158        ONLY: cpu_log, log_point
159
160    USE control_parameters,                                                                        &
161        ONLY:  humidity, neutral, passive_scalar, timestep_count
162
163    USE kinds
164
165    USE module_interface,                                                                          &
166        ONLY:  module_interface_swap_timelevel
167
168    USE pmc_interface,                                                                             &
169        ONLY: nested_run, pmci_set_swaplevel
170
171    USE turbulence_closure_mod,                                                                    &
172        ONLY:  tcm_swap_timelevel
173
174
175    IMPLICIT NONE
176
177    INTEGER(iwp) ::  swap_level  !> swap_level for steering the pmc data transfer
178
179!
180!-- Incrementing timestep counter
181    timestep_count = timestep_count + 1
182
183!
184!-- Swap of variables
185    CALL cpu_log( log_point(28), 'swap_timelevel', 'start' )
186
187    SELECT CASE ( MOD( timestep_count, 2 ) )
188
189       CASE ( 0 )
190
191          u  => u_1;   u_p  => u_2
192          v  => v_1;   v_p  => v_2
193          w  => w_1;   w_p  => w_2
194          IF ( .NOT. neutral )  THEN
195             pt => pt_1;  pt_p => pt_2
196          ENDIF
197          IF ( humidity )  THEN
198             q => q_1;    q_p => q_2
199          ENDIF
200          IF ( passive_scalar )  THEN
201             s => s_1;    s_p => s_2
202          ENDIF
203
204          swap_level = 1
205
206       CASE ( 1 )
207
208          u  => u_2;   u_p  => u_1
209          v  => v_2;   v_p  => v_1
210          w  => w_2;   w_p  => w_1
211          IF ( .NOT. neutral )  THEN
212             pt => pt_2;  pt_p => pt_1
213          ENDIF
214          IF ( humidity )  THEN
215             q => q_2;    q_p => q_1
216          ENDIF
217          IF ( passive_scalar )  THEN
218             s => s_2;    s_p => s_1
219          ENDIF
220
221          swap_level = 2
222
223    END SELECT
224
225!
226!-- Set the swap level the turbulence closure module
227    CALL tcm_swap_timelevel( MOD( timestep_count, 2) )
228
229!
230!-- Set the swap level for all other modules
231    CALL module_interface_swap_timelevel( MOD( timestep_count, 2) )
232
233!
234!-- Set the swap level for steering the pmc data transfer
235    IF ( nested_run )  CALL pmci_set_swaplevel( swap_level )
236
237    CALL cpu_log( log_point(28), 'swap_timelevel', 'stop' )
238
239 END SUBROUTINE swap_timelevel
240
241
Note: See TracBrowser for help on using the repository browser.