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

Last change on this file since 1032 was 1032, checked in by letzel, 12 years ago
  • mask locations determined based on scalar positions (init_masks)
  • save memory by not allocating pt_2 in case of neutral = .T. (init_3d_model, swap_timelevel)
  • minor reformatting (check_for_restart)
  • Property svn:keywords set to Id
File size: 2.9 KB
Line 
1 SUBROUTINE swap_timelevel
2
3!------------------------------------------------------------------------------!
4! Current revisions:
5! -----------------
6! save memory by not allocating pt_2 in case of neutral = .T.
7!
8! Former revisions:
9! -----------------
10! $Id: swap_timelevel.f90 1032 2012-10-21 13:03:21Z letzel $
11!
12! 1010 2012-09-20 07:59:54Z raasch
13! cpp switch __nopointer added for pointer free version
14!
15! 1001 2012-09-13 14:08:46Z raasch
16! all actions concerning leapfrog scheme removed
17!
18! 102 2007-07-27 09:09:17Z raasch
19! swaping of uswst, vswst included
20!
21! 95 2007-06-02 16:48:38Z raasch
22! Swaping of salinity
23!
24! 75 2007-03-22 09:54:05Z raasch
25! moisture renamed humidity
26!
27! 19 2007-02-23 04:53:48Z raasch
28! Swaping of top fluxes
29!
30! RCS Log replace by Id keyword, revision history cleaned up
31!
32! Revision 1.8  2004/01/28 15:28:18  raasch
33! Swaping for Runge-Kutta schemes implemented
34!
35! Revision 1.1  2000/01/10  10:08:58  10:08:58  raasch (Siegfried Raasch)
36! Initial revision
37!
38!
39! Description:
40! ------------
41! Swap of timelevels of variables after each timestep
42!------------------------------------------------------------------------------!
43
44    USE arrays_3d
45    USE cpulog
46    USE interfaces
47    USE control_parameters
48
49    IMPLICIT NONE
50
51!
52!-- Incrementing timestep counter
53    timestep_count = timestep_count + 1
54
55!
56!-- Swap of variables
57#if defined( __nopointer )
58    CALL cpu_log( log_point(28), 'swap_timelevel (nop)', 'start' )
59
60    u  = u_p
61    v  = v_p
62    w  = w_p
63    pt = pt_p
64    IF ( .NOT. constant_diffusion )  THEN
65       e = e_p
66    ENDIF
67    IF ( ocean )  THEN
68       sa = sa_p
69    ENDIF
70    IF ( humidity  .OR.  passive_scalar )  THEN
71       q = q_p
72    ENDIF
73
74    CALL cpu_log( log_point(28), 'swap_timelevel (nop)', 'stop' )
75#else
76    CALL cpu_log( log_point(28), 'swap_timelevel', 'start' )
77
78    SELECT CASE ( MOD( timestep_count, 2 ) )
79
80       CASE ( 0 )
81
82          u  => u_1;   u_p  => u_2
83          v  => v_1;   v_p  => v_2
84          w  => w_1;   w_p  => w_2
85          IF ( .NOT. neutral )  THEN
86             pt => pt_1;  pt_p => pt_2
87          ENDIF
88          IF ( .NOT. constant_diffusion )  THEN
89             e => e_1;    e_p => e_2
90          ENDIF
91          IF ( ocean )  THEN
92             sa => sa_1;  sa_p => sa_2
93          ENDIF
94          IF ( humidity  .OR.  passive_scalar )  THEN
95             q => q_1;    q_p => q_2
96          ENDIF
97
98
99       CASE ( 1 )
100
101          u  => u_2;   u_p  => u_1
102          v  => v_2;   v_p  => v_1
103          w  => w_2;   w_p  => w_1
104          IF ( .NOT. neutral )  THEN
105             pt => pt_2;  pt_p => pt_1
106          ENDIF
107          IF ( .NOT. constant_diffusion )  THEN
108             e => e_2;    e_p => e_1
109          ENDIF
110          IF ( ocean )  THEN
111             sa => sa_2;  sa_p => sa_1
112          ENDIF
113          IF ( humidity  .OR.  passive_scalar )  THEN
114             q => q_2;    q_p => q_1
115          ENDIF
116
117
118    END SELECT
119
120    CALL cpu_log( log_point(28), 'swap_timelevel', 'stop' )
121#endif
122
123 END SUBROUTINE swap_timelevel
124
125
Note: See TracBrowser for help on using the repository browser.