source: palm/trunk/SOURCE/local_tremain.f90 @ 484

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

typo in file headers removed

  • Property svn:keywords set to Id
File size: 1.9 KB
RevLine 
[1]1 SUBROUTINE local_tremain( remaining_time )
2
3!------------------------------------------------------------------------------!
[484]4! Current revisions:
[1]5! -----------------
[226]6!
[1]7!
8! Former revisions:
9! -----------------
[3]10! $Id: local_tremain.f90 484 2010-02-05 07:36:54Z raasch $
[83]11!
[226]12! 225 2009-01-26 14:44:20Z raasch
13! Type of count and count_rate changed to INTEGER(8) in order to avoid out of
14! range problems (which result in measured negative time intervals)
15!
[83]16! 82 2007-04-16 15:40:52Z raasch
17! Preprocessor strings for different linux clusters changed to "lc",
18! preprocessor directives for old systems removed
19!
[3]20! RCS Log replace by Id keyword, revision history cleaned up
21!
[1]22! Revision 1.14  2006/06/02 15:20:33  raasch
23! Extended to TIT Sun Fire X4600 System (lctit)
24!
25! Revision 1.1  1998/03/18 20:14:47  raasch
26! Initial revision
27!
28!
29! Description:
30! ------------
31! For different operating systems get the remaining cpu-time of the job
32!------------------------------------------------------------------------------!
33
34    USE control_parameters
35    USE cpulog
36    USE pegrid
37
38    IMPLICIT NONE
39
40    REAL ::  remaining_time
41#if defined( __ibm )
42    INTEGER(8) ::  IRTC
43    REAL       ::  actual_wallclock_time
[82]44#elif defined( __lc )
[225]45    INTEGER(8) ::  count, count_rate
[1]46    REAL       ::  actual_wallclock_time
47#endif
48
[82]49#if defined( __ibm )
[1]50
51    actual_wallclock_time = IRTC( ) * 1E-9
52    remaining_time = maximum_cpu_time_allowed - &
53                     ( actual_wallclock_time - initial_wallclock_time )
54
[82]55#elif defined( __lc )
[1]56
57    CALL SYSTEM_CLOCK( count, count_rate )
58    actual_wallclock_time = REAL( count ) / REAL( count_rate )
59    remaining_time = maximum_cpu_time_allowed - &
60                     ( actual_wallclock_time - initial_wallclock_time )
61
62#elif defined( __nec )
63   
64    CALL TREMAIN( remaining_time )
65    remaining_time = remaining_time / tasks_per_node
66
67#else
68
69!
70!-- No stop due to running out of cpu-time on other machines
71    remaining_time = 9999999.9
72
73#endif
74
75 END SUBROUTINE local_tremain
Note: See TracBrowser for help on using the repository browser.