source: palm/trunk/SOURCE/timestep_scheme_steering.f90 @ 550

Last change on this file since 550 was 484, checked in by raasch, 14 years ago

typo in file headers removed

  • Property svn:keywords set to Id
File size: 3.0 KB
Line 
1 SUBROUTINE timestep_scheme_steering
2
3!------------------------------------------------------------------------------!
4! Current revisions:
5! -----------------
6!
7!
8! Former revisions:
9! -----------------
10! $Id: timestep_scheme_steering.f90 484 2010-02-05 07:36:54Z maronga $
11! RCS Log replace by Id keyword, revision history cleaned up
12!
13! Revision 1.2  2005/03/26 21:17:06  raasch
14! No pressure term for Runge-Kutta-schemes (tsc(4)=0.0)
15!
16! Revision 1.1  2004/01/28 15:34:47  raasch
17! Initial revision
18!
19!
20! Description:
21! ------------
22! Depending on the timestep scheme set the steering factors for the prognostic
23! equations.
24!------------------------------------------------------------------------------!
25
26    USE control_parameters
27
28    IMPLICIT NONE
29
30
31    IF ( timestep_scheme(1:5) == 'runge' )  THEN
32!
33!--    Runge-Kutta schemes (here the factors depend on the respective
34!--    intermediate step)
35       IF ( timestep_scheme == 'runge-kutta-2' )  THEN
36          IF ( intermediate_timestep_count == 1 )  THEN
37             tsc(1:5) = (/ 1.0, 1.0,  0.0, 0.0, 0.0 /)
38          ELSE
39             tsc(1:5) = (/ 1.0, 0.5, -0.5, 0.0, 1.0 /)
40          ENDIF
41       ELSE
42          IF ( intermediate_timestep_count == 1 )  THEN
43             tsc(1:5) = (/ 1.0,   1.0/3.0,        0.0, 0.0, 0.0 /)
44          ELSEIF ( intermediate_timestep_count == 2 )  THEN
45             tsc(1:5) = (/ 1.0, 15.0/16.0, -25.0/48.0, 0.0, 0.0 /)
46          ELSE
47             tsc(1:5) = (/ 1.0,  8.0/15.0,   1.0/15.0, 0.0, 1.0 /)
48          ENDIF         
49       ENDIF
50
51    ELSE
52
53       IF ( .NOT. dt_fixed )  THEN
54!
55!--       Leapfrog and Euler schemes
56!--       Determine whether after the time step adjustment the Euler- or the
57!--       leapfrog scheme will be applied. The very first time step must always
58!--       be an Euler step.
59          IF ( dt_changed )  THEN
60             IF ( timestep_scheme == 'leapfrog+euler'  .OR. &
61                  timestep_scheme == 'euler' .OR. simulated_time == 0.0 )  THEN
62                tsc(1:5) = (/ 1.0, 1.0, 0.0, 1.0, 1.0 /)
63             ELSE
64                tsc(1:5) = (/ 0.0, 2.0, 0.0, 1.0, 2.0 /)
65             ENDIF
66          ELSE
67!
68!--          No time step change, hence continue with the scheme set by the
69!--          user.
70             IF ( timestep_scheme == 'euler' )  THEN
71                tsc(1:5) = (/ 1.0, 1.0, 0.0, 1.0, 1.0 /)
72             ELSE
73                tsc(1:5) = (/ 0.0, 2.0, 0.0, 1.0, 2.0 /)
74             ENDIF
75          ENDIF
76
77       ELSE
78
79!
80!--       Fixed time step:
81!
82!--       In any case, the very first time step must always be an Euler step.
83          timestep_reason = 'F'
84          IF ( simulated_time == 0.0 )  THEN
85             dt_changed = .TRUE.
86             tsc(1:5) = (/ 1.0, 1.0, 0.0, 1.0, 1.0 /)
87          ELSE
88             dt_changed = .FALSE.
89             IF ( timestep_scheme == 'euler' )  THEN
90                tsc(1:5) = (/ 1.0, 1.0, 0.0, 1.0, 1.0 /)
91             ELSE
92                tsc(1:5) = (/ 0.0, 2.0, 0.0, 1.0, 2.0 /)
93             ENDIF
94          ENDIF
95
96       ENDIF
97
98    ENDIF
99
100
101 END SUBROUTINE timestep_scheme_steering
Note: See TracBrowser for help on using the repository browser.