MFIX  2016-1
check_bqend.f
Go to the documentation of this file.
1 !----------------------------------------------------------------------!
2 ! !
3 ! Subroutine: CHECK_BATCH_QUEUE_END !
4 ! Author: A.Gel Date: !
5 ! !
6 ! Purpose: !
7 ! !
8 !----------------------------------------------------------------------!
9  SUBROUTINE check_batch_queue_end(pEXIT_SIGNAL)
10 
11  use compar, only: pe_io
12  use error_manager
13  use machine, only: wall_time
14  use run, only: get_tunit
15  use mpi_utility, only: bcast
16  use run, only: batch_wallclock
17  use run, only: term_buffer
18  use time_cpu, only: wall_start
19 
20  IMPLICIT NONE
21 
22  LOGICAL, INTENT(INOUT) :: pEXIT_SIGNAL
23 
24 ! Logical flags for hault cases.
25  LOGICAL :: USER_HAULT, WALL_HAULT
26 ! Elapsed wall time, and fancy formatted buffer/batch queue times.
27  DOUBLE PRECISION :: WALL_STOP, FANCY_BUFF, FANCY_BATCH
28 ! Time units for formatted output.
29  CHARACTER(LEN=4) :: WT_UNIT, BF_UNIT, BC_UNIT
30 
31 ! Calculate the current elapsed wall time.
32  wall_stop = wall_time()
33  wall_stop = wall_stop - wall_start
34 
35 ! Set flags for wall time exceeded or user specified hault.
36  wall_hault = ((wall_stop+term_buffer) >= batch_wallclock)
37  INQUIRE(file="MFIX.STOP", exist=user_hault)
38 
39 ! Report that the max user wall time was reached and exit.
40  IF(wall_hault) THEN
41  CALL get_tunit(wall_stop,wt_unit)
42  fancy_buff = term_buffer
43  CALL get_tunit(fancy_buff, bf_unit)
44  fancy_batch = batch_wallclock
45  CALL get_tunit(fancy_batch, bc_unit)
46  WRITE(err_msg, 1100) wall_stop, wt_unit, fancy_buff, bf_unit, &
47  fancy_batch, bc_unit
48  CALL flush_err_msg(header=.false., footer=.false.)
49  ENDIF
50 
51  1100 FORMAT(2/,15('='),' REQUESTED CPU TIME LIMIT REACHED ',('='),/ &
52  'Batch Wall Time:',3x,f9.2,1x,a,/'Elapsed Wall Time: ',f9.2, &
53  1x,a,/'Term Buffer:',7x,f9.2,a,/15('='),' REQUESTED CPU ', &
54  'TIME LIMIT REACHED ',('='))
55 
56 ! Report that the hault signal was detected.
57  IF(user_hault) THEN
58  WRITE(err_msg, 1200)
59  CALL flush_err_msg(header=.false., footer=.false.)
60  ENDIF
61 
62  1200 FORMAT(2/,19('='),' MFIX STOP SIGNAL DETECTED ',19('='),/'MFIX.',&
63  'STOP file detected in run directory. Terminating MFIX.',/ &
64  'Please DO NOT FORGET to erase the MFIX.STOP file before ', &
65  'restarting',/19('='),'MFIX STOP SIGNAL DETECTED ',19('='))
66 
67 ! This routine was restructured so all MPI ranks to the same action. As
68 ! a result, broadcasting the BATCHQ flag may not be needed.
69  pexit_signal = (wall_hault .OR. user_hault) .OR. pexit_signal
70  call bcast (pexit_signal,pe_io)
71 
72  END SUBROUTINE check_batch_queue_end
subroutine check_batch_queue_end(pEXIT_SIGNAL)
Definition: check_bqend.f:10
double precision function wall_time()
Definition: machine_mod.f:135
double precision wall_start
Definition: time_cpu_mod.f:19
double precision term_buffer
Definition: run_mod.f:202
integer pe_io
Definition: compar_mod.f:30
Definition: run_mod.f:13
double precision batch_wallclock
Definition: run_mod.f:195
character(len=line_length), dimension(line_count) err_msg
subroutine get_tunit(TLEFT, TUNIT)
Definition: run_mod.f:277
subroutine flush_err_msg(DEBUG, HEADER, FOOTER, ABORT, LOG, CALL_TREE)