source: palm/tags/release-4.0/SOURCE/swap_timelevel.f90

Last change on this file was 1497, checked in by maronga, 9 years ago

last commit documented

  • Property svn:keywords set to Id
File size: 6.7 KB
Line 
1 SUBROUTINE swap_timelevel
2
3!--------------------------------------------------------------------------------!
4! This file is part of PALM.
5!
6! PALM is free software: you can redistribute it and/or modify it under the terms
7! of the GNU General Public License as published by the Free Software Foundation,
8! either version 3 of the License, or (at your option) any later 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-2014 Leibniz Universitaet Hannover
18!--------------------------------------------------------------------------------!
19!
20! Current revisions:
21! -----------------
22!
23!
24! Former revisions:
25! -----------------
26! $Id: swap_timelevel.f90 1497 2014-12-02 17:28:07Z banzhafs $
27!
28! 1496 2014-12-02 17:25:50Z maronga
29! Added swapping of land surface model quantities
30!
31! 1374 2014-04-25 12:55:07Z raasch
32! bugfix: use-statement for nopointer-case added
33!
34! 1320 2014-03-20 08:40:49Z raasch
35! ONLY-attribute added to USE-statements,
36! revision history before 2012 removed,
37! 1318 2014-03-17 13:35:16Z raasch
38! module interfaces removed
39!
40! 1115 2013-03-26 18:16:16Z hoffmann
41! calculation of qr and nr is restricted to precipitation
42!
43! 1111 2013-03-08 23:54:10Z raasch
44! openACC directives added
45!
46! 1053 2012-11-13 17:11:03Z hoffmann
47! swap of timelevels for nr, qr added
48!
49! 1036 2012-10-22 13:43:42Z raasch
50! code put under GPL (PALM 3.9)
51!
52! 1032 2012-10-21 13:03:21Z letzel
53! save memory by not allocating pt_2 in case of neutral = .T.
54!
55! 1010 2012-09-20 07:59:54Z raasch
56! cpp switch __nopointer added for pointer free version
57!
58! 1001 2012-09-13 14:08:46Z raasch
59! all actions concerning leapfrog scheme removed
60!
61! Revision 1.1  2000/01/10  10:08:58  10:08:58  raasch (Siegfried Raasch)
62! Initial revision
63!
64!
65! Description:
66! ------------
67! Swap of timelevels of variables after each timestep
68!------------------------------------------------------------------------------!
69
70#if defined( __nopointer )
71    USE arrays_3d,                                                             &
72        ONLY:  e, e_p, nr, nr_p, pt, pt_p, q, q_p, qr, qr_p, sa, sa_p, u, u_p, &
73               v, v_p, w, w_p
74
75    USE land_surface_model_mod,                                                &
76        ONLY: land_surface, m_liq, m_liq_p, m_soil, m_soil_p, T_0, T_0_p,      &
77              T_soil, T_soil_p
78#else
79    USE arrays_3d,                                                             &
80        ONLY:  e, e_1, e_2, e_p, nr, nr_1, nr_2, nr_p, pt, pt_1, pt_2, pt_p, q,&
81               q_1, q_2, q_p, qr, qr_1, qr_2, qr_p, sa, sa_1, sa_2, sa_p, u,   &
82               u_1, u_2, u_p, v, v_1, v_2, v_p, w, w_1, w_2, w_p
83
84    USE land_surface_model_mod,                                                &
85        ONLY: land_surface, m_liq, m_liq_1, m_liq_2, m_liq_p, m_soil,          &
86              m_soil_1, m_soil_2, m_soil_p, T_0, T_0_1, T_0_2, T_0_p, T_soil,  &
87              T_soil_1, T_soil_2, T_soil_p
88#endif
89
90    USE cpulog,                                                                &
91        ONLY: cpu_log, log_point
92
93    USE control_parameters,                                                    &
94        ONLY:  cloud_physics, constant_diffusion, humidity, icloud_scheme,     &
95               neutral, ocean, passive_scalar, precipitation, timestep_count
96
97    IMPLICIT NONE
98
99!
100!-- Incrementing timestep counter
101    timestep_count = timestep_count + 1
102
103!
104!-- Swap of variables
105#if defined( __nopointer )
106    CALL cpu_log( log_point(28), 'swap_timelevel (nop)', 'start' )
107
108    !$acc kernels present( pt, pt_p, u, u_p, v, v_p, w, w_p )
109    u  = u_p
110    v  = v_p
111    w  = w_p
112    pt = pt_p
113    !$acc end kernels
114    IF ( .NOT. constant_diffusion )  THEN
115       !$acc kernels present( e, e_p )
116       e = e_p
117       !$acc end kernels
118    ENDIF
119    IF ( ocean )  THEN
120       sa = sa_p
121    ENDIF
122    IF ( humidity  .OR.  passive_scalar )  THEN
123       q = q_p             
124       IF ( cloud_physics  .AND.  icloud_scheme == 0 )  THEN
125          qr = qr_p
126          nr = nr_p
127       ENDIF
128    ENDIF
129
130    IF ( land_surface )  THEN
131       T_0    = T_0_p
132       T_soil = T_soil_p
133       IF ( humidity )  THEN
134          m_soil = m_soil_p
135          m_liq  = m_liq_p
136       ENDIF
137    ENDIF
138
139
140    CALL cpu_log( log_point(28), 'swap_timelevel (nop)', 'stop' )
141#else
142    CALL cpu_log( log_point(28), 'swap_timelevel', 'start' )
143
144    SELECT CASE ( MOD( timestep_count, 2 ) )
145
146       CASE ( 0 )
147
148          u  => u_1;   u_p  => u_2
149          v  => v_1;   v_p  => v_2
150          w  => w_1;   w_p  => w_2
151          IF ( .NOT. neutral )  THEN
152             pt => pt_1;  pt_p => pt_2
153          ENDIF
154          IF ( .NOT. constant_diffusion )  THEN
155             e => e_1;    e_p => e_2
156          ENDIF
157          IF ( ocean )  THEN
158             sa => sa_1;  sa_p => sa_2
159          ENDIF
160          IF ( humidity  .OR.  passive_scalar )  THEN
161             q => q_1;    q_p => q_2
162             IF ( cloud_physics  .AND.  icloud_scheme == 0  .AND.  &
163                  precipitation )  THEN
164                qr => qr_1;    qr_p => qr_2
165                nr => nr_1;    nr_p => nr_2
166             ENDIF
167          ENDIF
168
169          IF ( land_surface )  THEN
170             T_0    => T_0_1;    T_0_p    => T_0_2
171             T_soil => T_soil_1; T_soil_p => T_soil_2
172             IF ( humidity )  THEN
173                m_soil => m_soil_1; m_soil_p  => m_soil_2
174                m_liq  => m_liq_1;  m_liq_p   => m_liq_2
175             ENDIF
176          ENDIF
177
178
179       CASE ( 1 )
180
181          u  => u_2;   u_p  => u_1
182          v  => v_2;   v_p  => v_1
183          w  => w_2;   w_p  => w_1
184          IF ( .NOT. neutral )  THEN
185             pt => pt_2;  pt_p => pt_1
186          ENDIF
187          IF ( .NOT. constant_diffusion )  THEN
188             e => e_2;    e_p => e_1
189          ENDIF
190          IF ( ocean )  THEN
191             sa => sa_2;  sa_p => sa_1
192          ENDIF
193          IF ( humidity  .OR.  passive_scalar )  THEN
194             q => q_2;    q_p => q_1
195             IF ( cloud_physics  .AND.  icloud_scheme == 0  .AND.  &
196                  precipitation)  THEN
197                qr => qr_2;    qr_p => qr_1
198                nr => nr_2;    nr_p => nr_1
199             ENDIF
200          ENDIF
201
202          IF ( land_surface )  THEN
203             T_0    => T_0_2;    T_0_p    => T_0_1
204             T_soil => T_soil_2; T_soil_p => T_soil_1
205             IF ( humidity )  THEN
206                m_soil => m_soil_2; m_soil_p  => m_soil_1
207                m_liq  => m_liq_2;  m_liq_p   => m_liq_1
208             ENDIF
209          ENDIF
210
211
212    END SELECT
213
214    CALL cpu_log( log_point(28), 'swap_timelevel', 'stop' )
215#endif
216
217 END SUBROUTINE swap_timelevel
218
219
Note: See TracBrowser for help on using the repository browser.