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

Last change on this file since 1 was 1, checked in by raasch, 17 years ago

Initial repository layout and content

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