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

Last change on this file since 225 was 225, checked in by raasch, 15 years ago

bugfixes concerning cpu time measurements and calculation of spectra in case of multigrid method switched on

  • Property svn:keywords set to Id
File size: 1.5 KB
RevLine 
[1]1 SUBROUTINE local_tremain_ini
2
3!------------------------------------------------------------------------------!
4! Actual revisions:
5! -----------------
[225]6! Type of count and count_rate changed to INTEGER(8) in order to avoid out of
7! range problems (which result in measured negative time intervals)
[1]8!
9! Former revisions:
10! -----------------
[3]11! $Id: local_tremain_ini.f90 225 2009-01-26 14:44:20Z raasch $
[83]12!
13! 82 2007-04-16 15:40:52Z raasch
14! Cpp-directive lctit renamed lc
15!
[3]16! RCS Log replace by Id keyword, revision history cleaned up
17!
[1]18! Revision 1.13  2007/02/11 13:07:03  raasch
19! Allowed cpu limit is now read from file instead of reading the value from
20! environment variable (see routine parin)
21!
22! Revision 1.1  1998/03/18 20:15:05  raasch
23! Initial revision
24!
25!
26! Description:
27! ------------
28! Initialization of CPU-time measurements for different operating systems
29!------------------------------------------------------------------------------!
30
31    USE control_parameters
32    USE cpulog
33
34    IMPLICIT NONE
35
36#if defined( __ibm )
37    CHARACTER (LEN=10) ::  value_chr
38    INTEGER            ::  idum
39    INTEGER(8)         ::  IRTC
[82]40#elif defined( __lc )
[1]41    CHARACTER (LEN=10) ::  value_chr
42    INTEGER            ::  idum
[225]43    INTEGER(8)         ::  count, count_rate
[1]44#endif
45
46
47!
48!-- Get initial wall clock time
49#if defined( __ibm )
50
51    initial_wallclock_time = IRTC( ) * 1E-9
52
[82]53#elif defined( __lc )
[1]54
55    CALL SYSTEM_CLOCK( count, count_rate )
56    initial_wallclock_time = REAL( count ) / REAL( count_rate )
57
58#else
59!
60!-- So far, nothing is done on these machines
61#endif
62
63
64 END SUBROUTINE local_tremain_ini
Note: See TracBrowser for help on using the repository browser.