Ignore:
Timestamp:
Mar 17, 2014 1:35:16 PM (10 years ago)
Author:
raasch
Message:

former files/routines cpu_log and cpu_statistics combined to one module,
which also includes the former data module cpulog from the modules-file,
module interfaces removed

File:
1 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/SOURCE/modules.f90

    r1315 r1318  
    2020! Current revisions:
    2121! ------------------
    22 !
     22! module cpulog moved to new separate module-file
     23! interface for cpu_log removed
    2324! Former revisions:
    2425! -----------------
     
    942943
    943944
    944 
    945  MODULE cpulog
    946 
    947 !------------------------------------------------------------------------------!
    948 ! Description:
    949 ! ------------
    950 ! Definition of variables for cpu-time measurements
    951 !------------------------------------------------------------------------------!
    952 
    953     REAL ::  initial_wallclock_time
    954 
    955     TYPE logpoint
    956        REAL               ::  isum, ivect, mean, mtime, mtimevec, sum, vector
    957        INTEGER            ::  counts
    958        CHARACTER (LEN=20) ::  place
    959     END TYPE logpoint
    960 
    961     TYPE(logpoint), DIMENSION(100) ::  log_point = logpoint( 0.0, 0.0, 0.0,   &
    962                                        0.0, 0.0, 0.0, 0.0, 0, ' ' ),          &
    963                                        log_point_s = logpoint( 0.0, 0.0, 0.0, &
    964                                        0.0, 0.0, 0.0, 0.0, 0, ' ' )
    965 
    966     SAVE
    967 
    968  END MODULE cpulog
    969 
    970 
    971 
    972 
    973945 MODULE dvrp_variables
    974946
     
    11661138! Interfaces for special subroutines which use optional parameters
    11671139!------------------------------------------------------------------------------!
    1168 
    1169     INTERFACE
    1170 
    1171        SUBROUTINE cpu_log( log_event, place, modus, barrierwait )
    1172 
    1173           USE cpulog
    1174 
    1175           CHARACTER (LEN=*)           ::  modus, place
    1176           CHARACTER (LEN=*), OPTIONAL ::  barrierwait
    1177           TYPE(logpoint)              ::  log_event
    1178 
    1179        END SUBROUTINE cpu_log
    1180 
    1181     END INTERFACE
    1182 
    1183 
    11841140
    11851141    INTERFACE
Note: See TracChangeset for help on using the changeset viewer.