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

Last change on this file since 4 was 4, checked in by raasch, 17 years ago

Id keyword set as property for all *.f90 files

  • Property svn:keywords set to Id
File size: 2.0 KB
Line 
1 SUBROUTINE local_tremain( remaining_time )
2
3!------------------------------------------------------------------------------!
4! Actual revisions:
5! -----------------
6!
7!
8! Former revisions:
9! -----------------
10! $Id: local_tremain.f90 4 2007-02-13 11:33:16Z raasch $
11! RCS Log replace by Id keyword, revision history cleaned up
12!
13! Revision 1.14  2006/06/02 15:20:33  raasch
14! Extended to TIT Sun Fire X4600 System (lctit)
15!
16! Revision 1.1  1998/03/18 20:14:47  raasch
17! Initial revision
18!
19!
20! Description:
21! ------------
22! For different operating systems get the remaining cpu-time of the job
23!------------------------------------------------------------------------------!
24
25    USE control_parameters
26    USE cpulog
27    USE pegrid
28
29    IMPLICIT NONE
30
31    REAL ::  remaining_time
32!#if defined( __vpp )
33!    REAL ::  cpu_time_used, rdum
34!#endif
35#if defined( __ibm )
36    INTEGER(8) ::  IRTC
37    REAL       ::  actual_wallclock_time
38#elif defined( __lctit )
39    INTEGER    ::  count, count_rate
40    REAL       ::  actual_wallclock_time
41#endif
42
43#if defined( __t3eh ) || defined( __t3eb ) || defined( __t3ej2 ) || defined( __t3ej5 )
44
45    CALL MPP_TREMAIN( remaining_time )
46
47!#elif defined( __vpp )
48!
49!    CALL CLOCKV( rdum, cpu_time_used, 0, 2 )
50!    remaining_time = maximum_cpu_time_allowed - cpu_time_used
51
52#elif defined( __ibm )
53
54!    CALL SYSTEM_CLOCK( count, count_rate )
55!    actual_wallclock_time = REAL( count ) / REAL( count_rate )
56    actual_wallclock_time = IRTC( ) * 1E-9
57    remaining_time = maximum_cpu_time_allowed - &
58                     ( actual_wallclock_time - initial_wallclock_time )
59
60#elif defined( __lctit )
61
62    CALL SYSTEM_CLOCK( count, count_rate )
63    actual_wallclock_time = REAL( count ) / REAL( count_rate )
64    remaining_time = maximum_cpu_time_allowed - &
65                     ( actual_wallclock_time - initial_wallclock_time )
66
67#elif defined( __nec )
68   
69    CALL TREMAIN( remaining_time )
70    remaining_time = remaining_time / tasks_per_node
71
72#else
73
74!
75!-- No stop due to running out of cpu-time on other machines
76    remaining_time = 9999999.9
77
78#endif
79
80 END SUBROUTINE local_tremain
Note: See TracBrowser for help on using the repository browser.