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

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

last commit documented

  • Property svn:keywords set to Id
File size: 1.8 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 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! 673 2011-01-18 16:19:48Z suehring
16! No pressure term during time integration (tsc(4)=0.0).
17!
18! RCS Log replace by Id keyword, revision history cleaned up
19!
20! Revision 1.2  2005/03/26 21:17:06  raasch
21! No pressure term for Runge-Kutta-schemes (tsc(4)=0.0)
22!
23! Revision 1.1  2004/01/28 15:34:47  raasch
24! Initial revision
25!
26!
27! Description:
28! ------------
29! Depending on the timestep scheme set the steering factors for the prognostic
30! equations.
31!------------------------------------------------------------------------------!
32
33    USE control_parameters
34
35    IMPLICIT NONE
36
37
38    IF ( timestep_scheme(1:5) == 'runge' )  THEN
39!
40!--    Runge-Kutta schemes (here the factors depend on the respective
41!--    intermediate step)
42       IF ( timestep_scheme == 'runge-kutta-2' )  THEN
43          IF ( intermediate_timestep_count == 1 )  THEN
44             tsc(1:5) = (/ 1.0, 1.0,  0.0, 0.0, 0.0 /)
45          ELSE
46             tsc(1:5) = (/ 1.0, 0.5, -0.5, 0.0, 1.0 /)
47          ENDIF
48       ELSE
49          IF ( intermediate_timestep_count == 1 )  THEN
50             tsc(1:5) = (/ 1.0,   1.0/3.0,        0.0, 0.0, 0.0 /)
51          ELSEIF ( intermediate_timestep_count == 2 )  THEN
52             tsc(1:5) = (/ 1.0, 15.0/16.0, -25.0/48.0, 0.0, 0.0 /)
53          ELSE
54             tsc(1:5) = (/ 1.0,  8.0/15.0,   1.0/15.0, 0.0, 1.0 /)
55          ENDIF         
56       ENDIF
57
58    ELSEIF ( timestep_scheme == 'euler' )  THEN
59!
60!--    Euler scheme
61       tsc(1:5) = (/ 1.0, 1.0, 0.0, 0.0, 1.0 /)
62
63    ENDIF
64
65
66 END SUBROUTINE timestep_scheme_steering
Note: See TracBrowser for help on using the repository browser.