source: palm/trunk/SOURCE/timestep_scheme_steering.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: 1.8 KB
RevLine 
[1]1 SUBROUTINE timestep_scheme_steering
2
3!------------------------------------------------------------------------------!
[484]4! Current revisions:
[1001]5! ------------------
6! all actions concerning leapfrog scheme removed
[1]7!
8! Former revisions:
9! -----------------
[3]10! $Id: timestep_scheme_steering.f90 1001 2012-09-13 14:08:46Z raasch $
[674]11!
12! 673 2011-01-18 16:19:48Z suehring
13! No pressure term during time integration (tsc(4)=0.0).
14!
[3]15! RCS Log replace by Id keyword, revision history cleaned up
16!
[1]17! Revision 1.2  2005/03/26 21:17:06  raasch
18! No pressure term for Runge-Kutta-schemes (tsc(4)=0.0)
19!
20! Revision 1.1  2004/01/28 15:34:47  raasch
21! Initial revision
22!
23!
24! Description:
25! ------------
26! Depending on the timestep scheme set the steering factors for the prognostic
27! equations.
28!------------------------------------------------------------------------------!
29
30    USE control_parameters
31
32    IMPLICIT NONE
33
34
35    IF ( timestep_scheme(1:5) == 'runge' )  THEN
36!
37!--    Runge-Kutta schemes (here the factors depend on the respective
38!--    intermediate step)
39       IF ( timestep_scheme == 'runge-kutta-2' )  THEN
40          IF ( intermediate_timestep_count == 1 )  THEN
41             tsc(1:5) = (/ 1.0, 1.0,  0.0, 0.0, 0.0 /)
42          ELSE
43             tsc(1:5) = (/ 1.0, 0.5, -0.5, 0.0, 1.0 /)
44          ENDIF
45       ELSE
46          IF ( intermediate_timestep_count == 1 )  THEN
47             tsc(1:5) = (/ 1.0,   1.0/3.0,        0.0, 0.0, 0.0 /)
48          ELSEIF ( intermediate_timestep_count == 2 )  THEN
49             tsc(1:5) = (/ 1.0, 15.0/16.0, -25.0/48.0, 0.0, 0.0 /)
50          ELSE
51             tsc(1:5) = (/ 1.0,  8.0/15.0,   1.0/15.0, 0.0, 1.0 /)
52          ENDIF         
53       ENDIF
54
[1001]55    ELSEIF ( timestep_scheme == 'euler' )  THEN
[1]56!
[1001]57!--    Euler scheme
58       tsc(1:5) = (/ 1.0, 1.0, 0.0, 0.0, 1.0 /)
[1]59
60    ENDIF
61
62
63 END SUBROUTINE timestep_scheme_steering
Note: See TracBrowser for help on using the repository browser.