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

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

leapfrog timestep scheme and upstream-spline advection scheme completely removed from the code,
reading of dt_fixed from restart file removed

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