Changeset 1808


Ignore:
Timestamp:
Apr 5, 2016 7:44:00 PM (8 years ago)
Author:
raasch
Message:

preprocessor directives using machine dependent flags (lc, ibm, etc.) mostly removed from the code

Location:
palm/trunk
Files:
2 deleted
26 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/SOURCE/Makefile

    r1798 r1808  
    2020# Current revisions:
    2121# ------------------
    22 #
     22# -local_flush, -local_getenv
    2323#
    2424# Former revisions:
     
    256256        init_grid.f90 init_masks.f90 init_ocean.f90 \
    257257        init_pegrid.f90 init_pt_anomaly.f90 init_rankine.f90 init_slope.f90 \
    258         interaction_droplets_ptq.f90 land_surface_model.f90 local_flush.f90 \
    259         local_getenv.f90 local_stop.f90 local_system.f90 local_tremain.f90 \
     258        interaction_droplets_ptq.f90 land_surface_model.f90 \
     259        local_stop.f90 local_system.f90 local_tremain.f90 \
    260260        local_tremain_ini.f90 lpm.f90 lpm_advec.f90 lpm_boundary_conds.f90 \
    261261        lpm_calc_liquid_water_content.f90 lpm_collision_kernels.f90 \
     
    409409interaction_droplets_ptq.o: modules.o mod_kinds.o
    410410land_surface_model.o: modules.o mod_kinds.o radiation_model.o
    411 local_flush.o: mod_kinds.o
    412 local_getenv.o: modules.o mod_kinds.o
    413411local_stop.o: modules.o mod_kinds.o pmc_interface.o
    414412local_tremain.o: modules.o cpulog.o mod_kinds.o
  • palm/trunk/SOURCE/cpulog.f90

    r1683 r1808  
    1919! Current revisions:
    2020! -----------------
    21 !
     21! cpu measurements are done with standard FORTRAN routine on every machine
    2222!
    2323! Former revisions:
     
    182182       TYPE(logpoint)    ::  log_event          !<
    183183
    184 #if defined( __lc ) || defined( __decalpha )
    185184       INTEGER(idp)     ::  count        !<
    186185       INTEGER(idp)     ::  count_rate   !<
    187 #elif defined( __nec )
    188        INTEGER(iwp)      ::  count       !<
    189        INTEGER(iwp)      ::  count_rate  !<
    190 #elif defined( __ibm )
    191        INTEGER(idp)     ::  IRTC         !<
    192 #endif
    193186
    194187
     
    224217!
    225218!--    Take current time
    226 #if defined( __lc ) || defined( __decalpha ) || defined( __nec )
    227219       CALL SYSTEM_CLOCK( count, count_rate )
    228220       mtime = REAL( count, KIND=wp ) / REAL( count_rate, KIND=wp )
    229 #elif defined( __ibm )
    230        mtime = IRTC( ) * 1E-9_wp
    231 #else
    232        message_string = 'no time measurement defined on this host'
    233        CALL message( 'cpu_log', 'PA0175', 1, 2, 0, 6, 0 )
    234 #endif
    235221
    236222!
  • palm/trunk/SOURCE/data_output_3d.f90

    r1784 r1808  
    1919! Current revisions:
    2020! ------------------
    21 !
     21! test output removed
    2222!
    2323! Former revisions:
     
    223223       ENDIF
    224224    ENDIF
    225     WRITE(9,*) '___hier4'
    226     CALL local_flush(9)
    227225
    228226!
  • palm/trunk/SOURCE/header.f90

    r1798 r1808  
    1919! Current revisions:
    2020! -----------------
    21 !
     21! routine local_flush replaced by FORTRAN statement
    2222!
    2323! Former revisions:
     
    19761976!
    19771977!-- Write buffer contents to disc immediately
    1978     CALL local_flush( io )
     1978    FLUSH( io )
    19791979
    19801980!
  • palm/trunk/SOURCE/init_1d_model.f90

    r1710 r1808  
    1919! Current revisions:
    2020! -----------------
    21 !
     21! routine local_flush replaced by FORTRAN statement
    2222!
    2323! Former revisions:
     
    830830!
    831831!--    Write buffer contents to disc immediately
    832        CALL local_flush( 15 )
     832       FLUSH( 15 )
    833833
    834834    ENDIF
     
    977977!
    978978!--    Write buffer contents to disc immediately
    979        CALL local_flush( 17 )
     979       FLUSH( 17 )
    980980
    981981    ENDIF
  • palm/trunk/SOURCE/init_coupling.f90

    r1683 r1808  
    1919! Current revisions:
    2020! -----------------
    21 !
     21! routine local_getenv replaced by standard FORTRAN routine
    2222!
    2323! Former revisions:
     
    7171!-- This method is currently not used because the mpiexec command is not
    7272!-- available on some machines
    73 !    CALL local_getenv( 'coupling_mode', 13, coupling_mode, i )
     73!    CALL GET_ENVIRONMENT_VARIABLE( 'coupling_mode', coupling_mode, i )
    7474!    IF ( i == 0 )  coupling_mode = 'uncoupled'
    7575!    IF ( coupling_mode == 'ocean_to_atmosphere' )  coupling_char = '_O'
  • palm/trunk/SOURCE/init_dvrp.f90

    r1683 r1808  
    1919! Current revisions:
    2020! -----------------
    21 !
     21! routine local_getenv replaced by standard FORTRAN routine
    2222!
    2323! Former revisions:
     
    783783!
    784784!-- Find out, if dvrp output shall be done by a dedicated PE
    785     CALL local_getenv( 'use_seperate_pe_for_dvrp_output', 31, chr, idummy )
     785    CALL GET_ENVIRONMENT_VARIABLE( 'use_seperate_pe_for_dvrp_output', chr,     &
     786                                   idummy )
    786787    IF ( chr == 'true' )  THEN
    787788
  • palm/trunk/SOURCE/local_tremain.f90

    r1683 r1808  
    1919! Current revisions:
    2020! -----------------
    21 !
     21! cpu measurements are done with standard FORTRAN routine on every machine
    2222!
    2323! Former revisions:
     
    6868    IMPLICIT NONE
    6969
    70     REAL(wp)     ::  remaining_time        !<
    71 #if defined( __ibm )
    72     INTEGER(idp) ::  IRTC                  !<
    73     REAL(wp)     ::  actual_wallclock_time !<
    74 #elif defined( __lc )
    7570    INTEGER(idp) ::  count                 !<
    7671    INTEGER(idp) ::  count_rate            !<
     72
    7773    REAL(wp)     ::  actual_wallclock_time !<
    78 #endif
    79 
    80 #if defined( __ibm )
    81 
    82     actual_wallclock_time = IRTC( ) * 1E-9_wp
    83     remaining_time = maximum_cpu_time_allowed - &
    84                      ( actual_wallclock_time - initial_wallclock_time )
    85 
    86 #elif defined( __lc )
     74    REAL(wp)     ::  remaining_time        !<
    8775
    8876    CALL SYSTEM_CLOCK( count, count_rate )
     
    9179                     ( actual_wallclock_time - initial_wallclock_time )
    9280
    93 #elif defined( __nec )
    94    
    95     CALL TREMAIN( remaining_time )
    96     remaining_time = remaining_time / tasks_per_node
    97 
    98 #else
    99 
    100 !
    101 !-- No stop due to running out of cpu-time on other machines
    102     remaining_time = 9999999.9_wp
    103 
    104 #endif
    105 
    10681 END SUBROUTINE local_tremain
  • palm/trunk/SOURCE/local_tremain_ini.f90

    r1683 r1808  
    1919! Current revisions:
    2020! -----------------
    21 !
     21! cpu measurements are done with standard FORTRAN routine on every machine
    2222!
    2323! Former revisions:
     
    6363    IMPLICIT NONE
    6464
    65 #if defined( __ibm )
    66     INTEGER(idp)     ::  IRTC       !<
    67 #elif defined( __lc )
    6865    INTEGER(idp)     ::  count      !<
    6966    INTEGER(idp)     ::  count_rate !<
    70 #endif
    71 
    7267
    7368!
    7469!-- Get initial wall clock time
    75 #if defined( __ibm )
    76 
    77     initial_wallclock_time = IRTC( ) * 1E-9_wp
    78 
    79 #elif defined( __lc )
    80 
    8170    CALL SYSTEM_CLOCK( count, count_rate )
    8271    initial_wallclock_time = REAL( count, KIND=wp ) / REAL( count_rate, KIND=wp )
    8372
    84 #else
    85 !
    86 !-- So far, nothing is done on these machines
    87 #endif
    88 
    89 
    9073 END SUBROUTINE local_tremain_ini
  • palm/trunk/SOURCE/message.f90

    r1765 r1808  
    1919! Current revisions:
    2020! -----------------
    21 !
     21! routine local_flush replaced by FORTRAN statement
    2222!
    2323! Former revisions:
     
    6464!> output_on_pe: -1 - all, else - output on specified PE
    6565!> file_id: 6 - stdout (*)
    66 !> flush: 0 - no action, 1 - flush the respective output buffer
     66!> flush_file: 0 - no action, 1 - flush the respective output buffer
    6767!------------------------------------------------------------------------------!
    6868 SUBROUTINE message( routine_name, message_identifier, requested_action, &
    69                      message_level, output_on_pe, file_id, flush )
     69                     message_level, output_on_pe, file_id, flush_file )
    7070 
    7171    USE control_parameters,                                                    &
     
    8989
    9090    INTEGER(iwp) ::  file_id                             !<
    91     INTEGER(iwp) ::  flush                               !<
     91    INTEGER(iwp) ::  flush_file                          !<
    9292    INTEGER(iwp) ::  i                                   !<
    9393    INTEGER(iwp) ::  message_level                       !<
     
    203203!
    204204!--       Flush buffer, if requested
    205           IF ( flush == 1 )  CALL local_flush( file_id )
     205          IF ( flush_file == 1 )  FLUSH( file_id )
    206206       ENDIF
    207207
     
    261261                TRIM( location )
    262262       ENDIF
    263        CALL local_flush( OUTPUT_UNIT )
     263       FLUSH( OUTPUT_UNIT )
    264264    ENDIF
    265265
  • palm/trunk/SOURCE/modules.f90

    r1805 r1808  
    1919! Current revisions:
    2020! ------------------
    21 !
     21! MPI module used by default on all machines
    2222!
    2323! Former revisions:
     
    11771177
    11781178#if defined( __parallel )
    1179 #if defined( __lc )
     1179#if defined( __mpifh )
     1180    INCLUDE "mpif.h"
     1181#else
    11801182    USE MPI
    1181 #else
    1182     INCLUDE "mpif.h"
    11831183#endif
    11841184#endif
  • palm/trunk/SOURCE/palm.f90

    r1784 r1808  
    1919! Current revisions:
    2020! -----------------
    21 !
     21! routine local_flush replaced by FORTRAN statement
    2222!
    2323! Former revisions:
     
    278278!-- TEST OUTPUT (TO BE REMOVED)
    279279    WRITE(9,*) '*** coupling_mode = "', TRIM( coupling_mode ), '"'
    280     CALL LOCAL_FLUSH( 9 )
     280    FLUSH( 9 )
    281281    IF ( TRIM( coupling_mode ) /= 'uncoupled' )  THEN
    282282       PRINT*, '*** PE', myid, ' Global target PE:', target_id, &
  • palm/trunk/SOURCE/pmc_client.f90

    r1798 r1808  
    2020! Current revisions:
    2121! ------------------
    22 !
     22! MPI module used by default on all machines
    2323!
    2424! Former revisions:
     
    6060    use, intrinsic :: iso_c_binding
    6161
    62 #if defined( __lc )
     62#if defined( __mpifh )
     63    INCLUDE "mpif.h"
     64#else
    6365    USE MPI
    64 #else
    65     INCLUDE "mpif.h"
    6666#endif
    6767    USE  kinds
  • palm/trunk/SOURCE/pmc_general.f90

    r1787 r1808  
    2020! Current revisions:
    2121! ------------------
    22 !
     22! MPI module used by default on all machines
    2323!
    2424! Former revisions:
     
    5555   USE kinds
    5656
    57 #if defined( __lc )
     57#if defined( __mpifh )
     58    INCLUDE "mpif.h"
     59#else
    5860    USE MPI
    59 #else
    60     INCLUDE "mpif.h"
    6161#endif
    6262
  • palm/trunk/SOURCE/pmc_handle_communicator.f90

    r1798 r1808  
    2020! Current revisions:
    2121! ------------------
    22 !
     22! MPI module used by default on all machines
    2323!
    2424! Former revisions:
     
    6262    USE kinds
    6363
    64 #if defined( __lc )
     64#if defined( __mpifh )
     65    INCLUDE "mpif.h"
     66#else
    6567    USE MPI
    66 #else
    67     INCLUDE "mpif.h"
    6868#endif
    6969
  • palm/trunk/SOURCE/pmc_interface.f90

    r1802 r1808  
    2020! Current revisions:
    2121! ------------------
    22 !
     22! MPI module used by default on all machines
    2323!
    2424! Former revisions:
     
    110110
    111111#if defined( __parallel )
    112 #if defined( __lc )
     112#if defined( __mpifh )
     113    INCLUDE "mpif.h"
     114#else
    113115    USE MPI
    114 #else
    115     INCLUDE "mpif.h"
    116116#endif
    117117
  • palm/trunk/SOURCE/pmc_mpi_wrapper.f90

    r1780 r1808  
    2020! Current revisions:
    2121! ------------------
    22 !
     22! MPI module used by default on all machines
    2323!
    2424! Former revisions:
     
    4545   use, intrinsic :: iso_c_binding
    4646
    47 #if defined( __lc )
     47#if defined( __mpifh )
     48    INCLUDE "mpif.h"
     49#else
    4850    USE MPI
    49 #else
    50     INCLUDE "mpif.h"
    5151#endif
    5252   USE  kinds
  • palm/trunk/SOURCE/pmc_server.f90

    r1798 r1808  
    2020! Current revisions:
    2121! ------------------
    22 !
     22! MPI module used by default on all machines
    2323!
    2424! Former revisions:
     
    6060   use, intrinsic :: iso_c_binding
    6161
    62 #if defined( __lc )
     62#if defined( __mpifh )
     63    INCLUDE "mpif.h"
     64#else
    6365    USE MPI
    64 #else
    65     INCLUDE "mpif.h"
    6666#endif
    6767   USE  kinds
  • palm/trunk/SOURCE/progress_bar.f90

    r1683 r1808  
    1919! Current revisions:
    2020! -----------------
    21 !
     21! routine local_flush replaced by FORTRAN statement
    2222!
    2323! Former revisions:
     
    148148          WRITE ( 117, FMT='(F5.2,1X,F5.2)' ) remaining_time_in_percent,       &
    149149                                              remaining_time_in_percent_total
    150           CALL local_flush( 117 )
     150          FLUSH( 117 )
    151151
    152152       ELSE
     
    170170                                  100.0_wp )
    171171#endif
    172           CALL local_flush( OUTPUT_UNIT )
     172          FLUSH( OUTPUT_UNIT )
    173173
    174174       ENDIF
  • palm/trunk/SOURCE/read_3d_binary.f90

    r1789 r1808  
    1919! Current revisions:
    2020! -----------------
    21 !
     21! test output removed
    2222!
    2323! Former revisions:
     
    288288         
    289289       IF ( j > 0 )  overlap_count(files_to_be_opened) = j
    290 
    291 !
    292 !--    Test output, to be removed later
    293        IF ( j > 0 )  THEN
    294           WRITE (9,*) '*** reading from file: ', i, j, ' times'
    295           WRITE (9,*) '    nxl = ', nxl, ' nxr = ', nxr, ' nys = ', &
    296                                     nys, ' nyn = ', nyn
    297           WRITE (9,*) ' '
    298           DO  k = 1, j
    299              WRITE (9,*) 'k = ', k
    300              WRITE (9,'(6(A,I4))') 'nxlfa = ', nxlfa(files_to_be_opened,k),&
    301                      ' nxrfa = ', nxrfa(files_to_be_opened,k), &
    302                      ' offset_xa = ', offset_xa(files_to_be_opened,k), &
    303                      ' nysfa = ', nysfa(files_to_be_opened,k), &
    304                      ' nynfa = ', nynfa(files_to_be_opened,k), &
    305                      ' offset_ya = ', offset_ya(files_to_be_opened,k)
    306           ENDDO
    307           CALL local_flush( 9 )
    308        ENDIF
    309 
    310290         
    311291    ENDDO
     
    314294!-- Save the id-string of the current process, since myid_char may now be used
    315295!-- to open files created by PEs with other id.
    316           myid_char_save = myid_char
    317 
    318 !
    319 !-- Test output (remove later)
    320          
    321     DO i = 1, numprocs_previous_run
    322        WRITE (9,*) 'i=',i-1, ' ibs= ',hor_index_bounds_previous_run(1:4,i-1)
    323     ENDDO
    324     CALL local_flush( 9 )
     296    myid_char_save = myid_char
    325297
    326298    IF ( files_to_be_opened /= 1  .OR.  numprocs /= numprocs_previous_run ) &
     
    340312!--    Set the filename (underscore followed by four digit processor id)
    341313       WRITE (myid_char,'(''_'',I6.6)')  j
    342        WRITE (9,*) 'myid=',myid,' opening file "',myid_char,'"'
    343        CALL local_flush( 9 )
    344314
    345315!
     
    348318!--    first.
    349319       CALL check_open( 13 )
    350        WRITE (9,*) 'before skipping'
    351        CALL local_flush( 9 )
    352320       IF ( j == 0 )  CALL skip_var_list
    353        WRITE (9,*) 'skipping done'
    354        CALL local_flush( 9 )
    355321
    356322!
     
    468434             nync = nynfa(i,k) + offset_ya(i,k)
    469435
    470 
    471              WRITE (9,*) 'var = ', field_chr
    472              CALL local_flush( 9 )
    473436
    474437             SELECT CASE ( TRIM( field_chr ) )
  • palm/trunk/SOURCE/read_var_list.f90

    r1784 r1808  
    1919! Current revisions:
    2020! ------------------
    21 !
     21! test output removed
    2222!
    2323! Former revisions:
     
    739739!
    740740!--    Read next string
    741        WRITE(9,*) 'var1 ', variable_chr
    742        CALL local_flush(9)
    743741       READ ( 13 )  variable_chr
    744        WRITE(9,*) 'var2 ', variable_chr
    745        CALL local_flush(9)
    746742
    747743    ENDDO
     
    800796    CALL check_open( 13 )
    801797
    802     WRITE (9,*) 'rpovl: after check open 13'
    803     CALL local_flush( 9 )
    804798    READ ( 13 )  version_on_file
    805799
     
    887881!
    888882!-- Now read and check some control parameters and skip the rest
    889     WRITE (9,*) 'wpovl: begin reading variables'
    890     CALL local_flush( 9 )
    891883    READ ( 13 )  variable_chr
    892884
     
    988980
    989981
    990     WRITE (9,*) 'skipvl #1'
    991     CALL local_flush( 9 )
    992982    READ ( 13 )  version_on_file
    993983
    994     WRITE (9,*) 'skipvl before variable_chr'
    995     CALL local_flush( 9 )
    996     READ ( 13 )  variable_chr
    997     WRITE (9,*) 'skipvl after variable_chr'
    998     CALL local_flush( 9 )
     984    READ ( 13 )  variable_chr
    999985
    1000986    DO  WHILE ( TRIM( variable_chr ) /= '*** end ***' )
    1001987
    1002     WRITE (9,*) 'skipvl chr = ', variable_chr
    1003     CALL local_flush( 9 )
    1004988       READ ( 13 )  cdum
    1005989       READ ( 13 )  variable_chr
    1006990
    1007991    ENDDO
    1008     WRITE (9,*) 'skipvl last'
    1009     CALL local_flush( 9 )
    1010992
    1011993
  • palm/trunk/SOURCE/run_control.f90

    r1698 r1808  
    1919! Current revisions:
    2020! -----------------
    21 !
     21! routine local_flush replaced by FORTRAN statement
    2222!
    2323! Former revisions:
     
    135135!
    136136!--    Write buffer contents to disc immediately
    137        CALL local_flush( 15 )
     137       FLUSH( 15 )
    138138
    139139    ENDIF
  • palm/trunk/SOURCE/spectrum.f90

    r1787 r1808  
    1919! Current revisions:
    2020! -----------------
    21 !
     21! MPI module used by default on all machines
    2222!
    2323! Former revisions:
     
    291291       USE kinds
    292292
    293 #if defined( __lc )
     293#if defined( __mpifh )
     294       INCLUDE "mpif.h"
     295#else
    294296       USE MPI
    295 #else
    296        INCLUDE "mpif.h"
    297297#endif
    298298       USE pegrid,                                                             &
     
    393393       USE kinds
    394394
    395 #if defined( __lc )
     395#if defined( __mpifh )
     396       INCLUDE "mpif.h"
     397#else
    396398       USE MPI
    397 #else
    398        INCLUDE "mpif.h"
    399399#endif
    400400       USE pegrid,                                                             &
     
    534534       USE kinds
    535535
    536 #if defined( __lc )
     536#if defined( __mpifh )
     537       INCLUDE "mpif.h"
     538#else
    537539       USE MPI
    538 #else
    539        INCLUDE "mpif.h"
    540540#endif
    541541       USE pegrid,                                                             &
  • palm/trunk/SOURCE/time_integration.f90

    r1798 r1808  
    1919! Current revisions:
    2020! ------------------
    21 !
     21! output message in case unscheduled radiation calls removed
    2222!
    2323! Former revisions:
     
    839839                IF ( .NOT. force_radiation_call )  THEN
    840840                   time_radiation = time_radiation - dt_radiation
    841                 ELSE
    842                    WRITE(9,*) "Unscheduled radiation call at ", simulated_time
    843                    CALL LOCAL_FLUSH ( 9 )
    844841                ENDIF
    845842
  • palm/trunk/SOURCE/tridia_solver.f90

    r1805 r1808  
    1919! Current revisions:
    2020! ------------------
    21 !
     21! test output removed
    2222!
    2323! Former revisions:
     
    509509!--    the exchanged loops create bank conflicts. The following directive
    510510!--    prohibits loop exchange and the loops perform much better.
    511 !       tn = omp_get_thread_num()
    512 !       WRITE( 120+tn, * ) '+++ id=',myid,' nx=',nx,' thread=', omp_get_thread_num()
    513 !       CALL local_flush( 120+tn )
    514511!CDIR NOLOOPCHG
    515512       DO  k = 0, nz-1
     
    519516          ENDDO
    520517       ENDDO
    521 !       WRITE( 120+tn, * ) '+++ id=',myid,' end of first tridia loop   thread=', omp_get_thread_num()
    522 !       CALL local_flush( 120+tn )
    523518
    524519       IF ( j <= nnyh )  THEN
  • palm/trunk/UTIL/combine_plot_fields.f90

    r1552 r1808  
    2020! Current revisions:
    2121! -----------------
    22 !
     22! cpu measurements are done with standard FORTRAN routine on every machine
    2323!
    2424! Former revisions:
     
    107107                     ze, zza, zze
    108108
    109 #if defined( __lc ) || defined( __decalpha )
    110     INTEGER(8)                  ::  count, count_rate
    111 #elif defined( __nec )
    112     INTEGER(iwp)                ::  count, count_rate
    113 #elif defined( __ibm )
    114     INTEGER(8)                  ::  IRTC
    115 #endif
     109    INTEGER(8)                        ::  count, count_rate
    116110
    117111    INTEGER(iwp), DIMENSION(0:1)      ::  current_level, current_var,          &
     
    180174!
    181175!--       Take current time
    182 #if defined( __lc ) || defined( __decalpha ) || defined( __nec )
    183176          CALL SYSTEM_CLOCK( count, count_rate )
    184177          cpu_start_time = REAL( count ) / REAL( count_rate )
    185 #elif defined( __ibm )
    186           cpu_start_time = IRTC( ) * 1E-9
    187 #else
    188           PRINT*,  '+++ INFORMATIVE: no time measurement defined on this host'
    189 #endif
    190178
    191179          netcdf_parallel = .FALSE.
     
    553541!--       Output required cpu time
    554542          IF ( danz /= 0  .AND.  .NOT. netcdf_parallel )  THEN
    555 #if defined( __lc ) || defined( __decalpha ) || defined( __nec )
    556543             CALL SYSTEM_CLOCK( count, count_rate )
    557544             cpu_end_time = REAL( count ) / REAL( count_rate )
    558545             WRITE (*,'(5X,A,F9.3,A)')  'Required cpu-time: ', &
    559546                                        cpu_end_time-cpu_start_time, ' sec'
    560 #elif defined( __ibm )
    561              cpu_end_time = IRTC( ) * 1E-9
    562              WRITE (*,'(5X,A,F9.3,A)')  'Required cpu-time: ', &
    563                                         cpu_end_time-cpu_start_time, ' sec'
    564 #else
    565              CONTINUE
    566 #endif
    567547          ENDIF
    568548
     
    592572!
    593573!--    Take current time
    594 #if defined( __lc ) || defined( __decalpha ) || defined( __nec )
    595574       CALL SYSTEM_CLOCK( count, count_rate )
    596575       cpu_start_time = REAL( count ) / REAL( count_rate )
    597 #elif defined( __ibm )
    598        cpu_start_time = IRTC( ) * 1E-9
    599 #else
    600        PRINT*,  '+++ INFORMATIVE: no time measurement defined on this host'
    601 #endif
    602576
    603577!
     
    885859!
    886860!--       Output required cpu time
    887 #if defined( __lc ) || defined( __decalpha ) || defined( __nec )
    888861          CALL SYSTEM_CLOCK( count, count_rate )
    889862          cpu_end_time = REAL( count ) / REAL( count_rate )
    890863          WRITE (*,'(5X,A,F9.3,A)')  'Required cpu-time: ', &
    891864                                     cpu_end_time-cpu_start_time, ' sec'
    892 #elif defined( __ibm )
    893           cpu_end_time = IRTC( ) * 1E-9
    894           WRITE (*,'(5X,A,F9.3,A)')  'Required cpu-time: ', &
    895                                      cpu_end_time-cpu_start_time, ' sec'
    896 #endif
    897865
    898866       ENDIF
Note: See TracChangeset for help on using the changeset viewer.