SUBROUTINE local_stop !------------------------------------------------------------------------------! ! Actual revisions: ! ----------------- ! ! ! ! Former revisions: ! ----------------- ! $Id: local_stop.f90 110 2007-10-05 05:13:14Z knoop $ ! ! 108 2007-08-24 15:10:38Z letzel ! modifications to terminate coupled runs ! ! RCS Log replace by Id keyword, revision history cleaned up ! ! Revision 1.2 2003/03/16 09:40:28 raasch ! Two underscores (_) are placed in front of all define-strings ! ! Revision 1.1 2002/12/19 15:46:23 raasch ! Initial revision ! ! ! Description: ! ------------ ! Stop program execution !------------------------------------------------------------------------------! USE pegrid USE control_parameters #if defined( __parallel ) IF ( coupling_mode == 'uncoupled' ) THEN CALL MPI_FINALIZE( ierr ) ELSE SELECT CASE ( terminate_coupled_remote ) CASE ( 0 ) IF ( myid == 0 ) THEN PRINT*, '+++ local_stop:' PRINT*, ' local model "', TRIM( coupling_mode ), & '" stops now' ENDIF ! !-- Inform the remote model of the termination and its reason, provided !-- the remote model has not already been informed of another !-- termination reason (terminate_coupled > 0) before. IF ( terminate_coupled == 0 ) THEN terminate_coupled = 1 CALL MPI_SENDRECV( & terminate_coupled, 1, MPI_INTEGER, myid, 0, & terminate_coupled_remote, 1, MPI_INTEGER, myid, 0, & comm_inter, status, ierr ) ENDIF CALL MPI_FINALIZE( ierr ) CASE ( 1 ) IF ( myid == 0 ) THEN PRINT*, '+++ local_stop:' PRINT*, ' remote model "', TRIM( coupling_mode_remote ), & '" stopped' ENDIF CALL MPI_FINALIZE( ierr ) CASE ( 2 ) IF ( myid == 0 ) THEN PRINT*, '+++ local_stop:' PRINT*, ' remote model "', TRIM( coupling_mode_remote ), & '" terminated' PRINT*, ' with stop_dt = .T.' ENDIF stop_dt = .TRUE. CASE ( 3 ) IF ( myid == 0 ) THEN PRINT*, '+++ local_stop:' PRINT*, ' remote model "', TRIM( coupling_mode_remote ), & '" terminated' PRINT*, ' with terminate_run = .T. (CPU-time limit)' ENDIF terminate_run = .TRUE. CASE ( 4 ) IF ( myid == 0 ) THEN PRINT*, '+++ local_stop:' PRINT*, ' remote model "', TRIM( coupling_mode_remote ), & '" terminated' PRINT*, ' with terminate_run = .T. (restart)' ENDIF terminate_run = .TRUE. time_restart = time_restart + dt_restart CASE ( 5 ) IF ( myid == 0 ) THEN PRINT*, '+++ local_stop:' PRINT*, ' remote model "', TRIM( coupling_mode_remote ), & '" terminated' PRINT*, ' with terminate_run = .T. (single restart)' ENDIF terminate_run = .TRUE. time_restart = 9999999.9 END SELECT ENDIF #else STOP #endif END SUBROUTINE local_stop