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

Last change on this file since 723 was 674, checked in by suehring, 13 years ago

last commit documented

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