Ignore:
Timestamp:
Sep 24, 2014 2:06:57 PM (10 years ago)
Author:
maronga
Message:

New flag files allow to force unscheduled termination/restarts of batch jobs, progress output is made for batch runs, small adjustments for lxce6 and lccrayh/lccrayb

File:
1 edited

Legend:

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

    r1402 r1468  
    2020! Current revisions:
    2121! -----------------
    22 !
     22! Added support for progress file PROGRESS which is used in case of batch jobs
    2323!
    2424! Former revisions:
     
    2828! Description:
    2929! ------------
    30 ! CPU-time measurements for any program part whatever. Results of the
     30! This routine prints either a progress bar on the standard output in case of
     31! interactive runs, or it prints the progress in a separate file called
     32! PROGRESS.
    3133!------------------------------------------------------------------------------!
    3234
    3335    USE control_parameters,                                                    &
    34         ONLY : end_time, simulated_time, simulated_time_at_begin, time_restart
     36        ONLY : end_time, run_identifier, simulated_time,                       &
     37               simulated_time_at_begin, time_restart
    3538
    36     USE, INTRINSIC ::  ISO_FORTRAN_ENV,                                     &
     39    USE, INTRINSIC ::  ISO_FORTRAN_ENV,                                        &
    3740        ONLY :  OUTPUT_UNIT
    3841
     
    6063
    6164    SUBROUTINE init_progress_bar
     65!------------------------------------------------------------------------------!
     66! Description:
     67! ------------
     68! Initialize the progress bar/file
     69!------------------------------------------------------------------------------!
    6270
    6371       IMPLICIT NONE
     
    7482       ENDIF
    7583
    76        bar = '____________________________________________________________'
    77        crosses = 'XXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXX'
     84       IF ( batch_job )  THEN
     85
     86          CALL check_open ( 117 )
     87          WRITE ( 117, FMT='(A20,/)' ) run_identifier
     88
     89       ELSE
     90          bar = '____________________________________________________________'
     91          crosses = 'XXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXX'
    7892!
    79 !--    Line feed on stdout to seperate the progress bar from previous messages
    80        WRITE ( OUTPUT_UNIT, '(1X)' )
     93!--       Line feed on stdout to seperate the progress bar from previous messages
     94          WRITE ( OUTPUT_UNIT, '(1X)' )
    8195#if defined( __intel_compiler )
    8296!
    83 !--    The Intel compiler does not allow to immediately flush the output buffer
    84 !--    in case that option ADVANCE='NO' is used in the write statement.
    85 !--    A workaround is to set a special carriage control feature and use "+" as
    86 !--    first output character, but this non-standard and only available with the
    87 !--    Intel compiler
    88        OPEN ( OUTPUT_UNIT, CARRIAGECONTROL='FORTRAN' )
     97!--       The Intel compiler does not allow to immediately flush the output buffer
     98!--       in case that option ADVANCE='NO' is used in the write statement.
     99!--       A workaround is to set a special carriage control feature and use "+" as
     100!--       first output character, but this non-standard and only available with the
     101!--       Intel compiler
     102          OPEN ( OUTPUT_UNIT, CARRIAGECONTROL='FORTRAN' )
    89103#endif
     104
     105       ENDIF
     106
    90107       initialized = .TRUE.
    91108
     
    97114! Description:
    98115! ------------
    99 !
     116! Print progress data to standard output (interactive) or to file (batch jobs)
    100117!------------------------------------------------------------------------------!
    101118
     
    104121       REAL(wp) ::  remaining_time_in_percent  !: remaining time to be simulated
    105122                                               !: in the job
     123       REAL(wp) ::  remaining_time_in_percent_total !: total remaining time of
     124                                                    !: the job chain
     125
     126       IF ( .NOT. initialized )  CALL init_progress_bar
     127
     128
     129       remaining_time_in_percent =                                             &
     130          ( simulated_time - simulated_time_at_begin ) / time_to_be_simulated
     131
     132       remaining_time_in_percent_total = ( simulated_time / end_time )
    106133
    107134!
    108 !--    Porgress bar does not make sense in batch mode (and also ADVANCE=no does
    109 !--    not properly work in batch mode on Cray XC30)
    110        IF ( batch_job )  RETURN
     135!--    In batch mode, use a file (PROGRESS), otherwise use progress bar
     136       IF ( batch_job )  THEN
    111137
    112        IF ( .NOT. initialized )  CALL init_progress_bar
     138          BACKSPACE ( 117 )
     139          WRITE ( 117, FMT='(F5.2,1X,F5.2)' ) remaining_time_in_percent,       &
     140                                              remaining_time_in_percent_total
     141          CALL local_flush( 117 )
     142
     143       ELSE
     144
    113145!
    114 !--    Calculate length of progress bar
    115        remaining_time_in_percent =                                             &
    116              ( simulated_time - simulated_time_at_begin ) / time_to_be_simulated
     146!--       Calculate length of progress bar
     147          ilength = remaining_time_in_percent * 60.0_wp
     148          ilength = MIN( ilength, 60 )
    117149
    118        ilength = remaining_time_in_percent * 60.0_wp
    119        ilength = MIN( ilength, 60 )
    120 
    121        bar(1:ilength) = crosses(1:ilength)
     150          bar(1:ilength) = crosses(1:ilength)
    122151
    123152#if defined( __intel_compiler )
    124        WRITE ( OUTPUT_UNIT, '(A,6X,''['',A,''] '',F5.1,'' left'')' )           &
    125                '+', bar,                                                       &
    126                 MAX( 0.0_wp, ( 1.0_wp - remaining_time_in_percent ) * 100.0_wp )
     153          WRITE ( OUTPUT_UNIT, '(A,6X,''['',A,''] '',F5.1,'' left'')' )        &
     154                  '+', bar,                                                    &
     155                   MAX( 0.0_wp, ( 1.0_wp - remaining_time_in_percent ) *       &
     156                                  100.0_wp )
    127157#else
    128        WRITE ( OUTPUT_UNIT, '(A,6X,''['',A,''] '',F5.1,'' left'')',            &
    129                ADVANCE='NO' )  CHAR( 13 ), bar,                                &
    130                 MAX( 0.0_wp, ( 1.0_wp - remaining_time_in_percent ) * 100.0_wp )
     158          WRITE ( OUTPUT_UNIT, '(A,6X,''['',A,''] '',F5.1,'' left'')',         &
     159                  ADVANCE='NO' )  CHAR( 13 ), bar,                             &
     160                   MAX( 0.0_wp, ( 1.0_wp - remaining_time_in_percent ) *       &
     161                                  100.0_wp )
    131162#endif
    132        CALL local_flush( OUTPUT_UNIT )
     163          CALL local_flush( OUTPUT_UNIT )
     164
     165       ENDIF
    133166
    134167    END SUBROUTINE output_progress_bar
    135168
    136169    SUBROUTINE finish_progress_bar
     170!------------------------------------------------------------------------------!
     171! Description:
     172! ------------
     173! Finalization of the progress bar/file
     174!------------------------------------------------------------------------------!
    137175
    138176       IMPLICIT NONE
    139177
    140        IF ( batch_job )  RETURN
     178       IF ( batch_job )  THEN
    141179
     180          CALL close_file ( 117 )
     181
     182       ELSE
     183       
    142184#if defined( __intel_compiler )
    143185!
    144 !--    Reset to the default carriage control
    145        OPEN ( OUTPUT_UNIT, CARRIAGECONTROL='LIST' )
     186!--       Reset to the default carriage control
     187          OPEN ( OUTPUT_UNIT, CARRIAGECONTROL='LIST' )
    146188#endif
    147189!
    148 !--    Line feed when simulation has finished
    149        WRITE ( OUTPUT_UNIT, '(1X)' )
     190!--       Line feed when simulation has finished
     191          WRITE ( OUTPUT_UNIT, '(1X)' )
     192
     193       ENDIF
    150194
    151195    END SUBROUTINE finish_progress_bar
    152196
     197
    153198 END MODULE progress_bar
Note: See TracChangeset for help on using the changeset viewer.