source: palm/trunk/SOURCE/local_tremain_ini.f90 @ 2

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

Initial repository layout and content

File size: 2.3 KB
Line 
1 SUBROUTINE local_tremain_ini
2
3!------------------------------------------------------------------------------!
4! Actual revisions:
5! -----------------
6!
7!
8! Former revisions:
9! -----------------
10! $Log: local_tremain_ini.f90,v $
11! Revision 1.13  2007/02/11 13:07:03  raasch
12! Allowed cpu limit is now read from file instead of reading the value from
13! environment variable (see routine parin)
14!
15! Revision 1.12  2006/06/02 15:21:09  raasch
16! Extended to TIT Sun Fire X4600 System (lctit)
17!
18! Revision 1.11  2003/05/09 14:40:20  raasch
19! Time measurement on IBM is now done using function irtc, which allows correct
20! measurements for jobs running over the 24:00 timeline
21!
22! Revision 1.10  2003/03/16 09:42:01  raasch
23! Two underscores (_) are placed in front of all define-strings
24!
25! Revision 1.9  2002/12/19 15:50:31  raasch
26! Measurements extended for IBM
27!
28! Revision 1.8  2001/03/30 07:35:16  raasch
29! Translation of remaining German identifiers (variables, subroutines, etc.)
30!
31! Revision 1.7  2001/01/22 08:35:38  raasch
32! Module test_variables removed
33!
34! Revision 1.5  1998/07/16 06:52:11  raasch
35! cpp-Direktiven fuer t3ej2 und t3ej5 erweitert
36!
37! Revision 1.4  1998/07/06 12:19:21  raasch
38! + USE test_variables
39!
40! Revision 1.3  1998/03/24 15:27:38  raasch
41! Initialisierung auf t3eh ergaenzt
42!
43! Revision 1.2  1998/03/23 08:40:23  raasch
44! Initialisierung auf vpp ergaenzt
45!
46! Revision 1.1  1998/03/18 20:15:05  raasch
47! Initial revision
48!
49!
50! Description:
51! ------------
52! Initialization of CPU-time measurements for different operating systems
53!------------------------------------------------------------------------------!
54
55    USE control_parameters
56    USE cpulog
57
58    IMPLICIT NONE
59
60#if defined( __ibm )
61    CHARACTER (LEN=10) ::  value_chr
62    INTEGER            ::  idum
63    INTEGER(8)         ::  IRTC
64#elif defined( __lctit )
65    CHARACTER (LEN=10) ::  value_chr
66    INTEGER            ::  idum
67    INTEGER            ::  count, count_rate
68#endif
69
70
71!
72!-- Get initial wall clock time
73#if defined( __ibm )
74
75    initial_wallclock_time = IRTC( ) * 1E-9
76
77#elif defined( __lctit )
78
79    CALL SYSTEM_CLOCK( count, count_rate )
80    initial_wallclock_time = REAL( count ) / REAL( count_rate )
81
82#else
83!
84!-- So far, nothing is done on these machines
85#endif
86
87
88 END SUBROUTINE local_tremain_ini
Note: See TracBrowser for help on using the repository browser.