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

Last change on this file since 1002 was 1002, checked in by raasch, 12 years ago

last commit documented

  • Property svn:keywords set to Id
File size: 2.2 KB
Line 
1 SUBROUTINE swap_timelevel
2
3!------------------------------------------------------------------------------!
4! Current revisions:
5! -----------------
6!
7!
8! Former revisions:
9! -----------------
10! $Id: swap_timelevel.f90 1002 2012-09-13 15:12:24Z raasch $
11!
12! 1001 2012-09-13 14:08:46Z raasch
13! all actions concerning leapfrog scheme removed
14!
15! 102 2007-07-27 09:09:17Z raasch
16! swaping of uswst, vswst included
17!
18! 95 2007-06-02 16:48:38Z raasch
19! Swaping of salinity
20!
21! 75 2007-03-22 09:54:05Z raasch
22! moisture renamed humidity
23!
24! 19 2007-02-23 04:53:48Z raasch
25! Swaping of top fluxes
26!
27! RCS Log replace by Id keyword, revision history cleaned up
28!
29! Revision 1.8  2004/01/28 15:28:18  raasch
30! Swaping for Runge-Kutta schemes implemented
31!
32! Revision 1.1  2000/01/10  10:08:58  10:08:58  raasch (Siegfried Raasch)
33! Initial revision
34!
35!
36! Description:
37! ------------
38! Swap of timelevels of variables after each timestep
39!------------------------------------------------------------------------------!
40
41    USE arrays_3d
42    USE cpulog
43    USE interfaces
44    USE control_parameters
45
46    IMPLICIT NONE
47
48
49    CALL cpu_log( log_point(28), 'swap_timelevel', 'start' )
50
51!
52!-- Incrementing timestep counter
53    timestep_count = timestep_count + 1
54
55!
56!-- Swap of variables
57    SELECT CASE ( MOD( timestep_count, 2 ) )
58
59       CASE ( 0 )
60
61          u  => u_1;   u_p  => u_2
62          v  => v_1;   v_p  => v_2
63          w  => w_1;   w_p  => w_2
64          pt => pt_1;  pt_p => pt_2
65          IF ( .NOT. constant_diffusion )  THEN
66             e => e_1;    e_p => e_2
67          ENDIF
68          IF ( ocean )  THEN
69             sa => sa_1;  sa_p => sa_2
70          ENDIF
71          IF ( humidity  .OR.  passive_scalar )  THEN
72             q => q_1;    q_p => q_2
73          ENDIF
74
75
76       CASE ( 1 )
77
78          u  => u_2;   u_p  => u_1
79          v  => v_2;   v_p  => v_1
80          w  => w_2;   w_p  => w_1
81          pt => pt_2;  pt_p => pt_1
82          IF ( .NOT. constant_diffusion )  THEN
83             e => e_2;    e_p => e_1
84          ENDIF
85          IF ( ocean )  THEN
86             sa => sa_2;  sa_p => sa_1
87          ENDIF
88          IF ( humidity  .OR.  passive_scalar )  THEN
89             q => q_2;    q_p => q_1
90          ENDIF
91
92
93    END SELECT
94
95    CALL cpu_log( log_point(28), 'swap_timelevel', 'stop' )
96
97 END SUBROUTINE swap_timelevel
98
99
Note: See TracBrowser for help on using the repository browser.