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

Last change on this file since 1047 was 1037, checked in by raasch, 11 years ago

last commit documented

  • Property svn:keywords set to Id
File size: 2.7 KB
Line 
1 SUBROUTINE local_tremain( remaining_time )
2
3!--------------------------------------------------------------------------------!
4! This file is part of PALM.
5!
6! PALM is free software: you can redistribute it and/or modify it under the terms
7! of the GNU General Public License as published by the Free Software Foundation,
8! either version 3 of the License, or (at your option) any later version.
9!
10! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
11! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
12! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
13!
14! You should have received a copy of the GNU General Public License along with
15! PALM. If not, see <http://www.gnu.org/licenses/>.
16!
17! Copyright 1997-2012  Leibniz University Hannover
18!--------------------------------------------------------------------------------!
19!
20! Current revisions:
21! -----------------
22!
23!
24! Former revisions:
25! -----------------
26! $Id: local_tremain.f90 1037 2012-10-22 14:10:22Z maronga $
27!
28! 1036 2012-10-22 13:43:42Z raasch
29! code put under GPL (PALM 3.9)
30!
31! 225 2009-01-26 14:44:20Z raasch
32! Type of count and count_rate changed to INTEGER(8) in order to avoid out of
33! range problems (which result in measured negative time intervals)
34!
35! 82 2007-04-16 15:40:52Z raasch
36! Preprocessor strings for different linux clusters changed to "lc",
37! preprocessor directives for old systems removed
38!
39! RCS Log replace by Id keyword, revision history cleaned up
40!
41! Revision 1.14  2006/06/02 15:20:33  raasch
42! Extended to TIT Sun Fire X4600 System (lctit)
43!
44! Revision 1.1  1998/03/18 20:14:47  raasch
45! Initial revision
46!
47!
48! Description:
49! ------------
50! For different operating systems get the remaining cpu-time of the job
51!------------------------------------------------------------------------------!
52
53    USE control_parameters
54    USE cpulog
55    USE pegrid
56
57    IMPLICIT NONE
58
59    REAL ::  remaining_time
60#if defined( __ibm )
61    INTEGER(8) ::  IRTC
62    REAL       ::  actual_wallclock_time
63#elif defined( __lc )
64    INTEGER(8) ::  count, count_rate
65    REAL       ::  actual_wallclock_time
66#endif
67
68#if defined( __ibm )
69
70    actual_wallclock_time = IRTC( ) * 1E-9
71    remaining_time = maximum_cpu_time_allowed - &
72                     ( actual_wallclock_time - initial_wallclock_time )
73
74#elif defined( __lc )
75
76    CALL SYSTEM_CLOCK( count, count_rate )
77    actual_wallclock_time = REAL( count ) / REAL( count_rate )
78    remaining_time = maximum_cpu_time_allowed - &
79                     ( actual_wallclock_time - initial_wallclock_time )
80
81#elif defined( __nec )
82   
83    CALL TREMAIN( remaining_time )
84    remaining_time = remaining_time / tasks_per_node
85
86#else
87
88!
89!-- No stop due to running out of cpu-time on other machines
90    remaining_time = 9999999.9
91
92#endif
93
94 END SUBROUTINE local_tremain
Note: See TracBrowser for help on using the repository browser.