SUBROUTINE local_stop !--------------------------------------------------------------------------------! ! This file is part of PALM. ! ! PALM is free software: you can redistribute it and/or modify it under the terms ! of the GNU General Public License as published by the Free Software Foundation, ! either version 3 of the License, or (at your option) any later version. ! ! PALM is distributed in the hope that it will be useful, but WITHOUT ANY ! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR ! A PARTICULAR PURPOSE. See the GNU General Public License for more details. ! ! You should have received a copy of the GNU General Public License along with ! PALM. If not, see . ! ! Copyright 1997-2012 Leibniz University Hannover !--------------------------------------------------------------------------------! ! ! Current revisions: ! ----------------- ! ! ! Former revisions: ! ----------------- ! $Id: local_stop.f90 1037 2012-10-22 14:10:22Z raasch $ ! ! 1036 2012-10-22 13:43:42Z raasch ! code put under GPL (PALM 3.9) ! ! 809 2012-01-30 13:32:58Z maronga ! Bugfix: replaced .AND. and .NOT. with && and ! in the preprocessor directives ! ! 807 2012-01-25 11:53:51Z maronga ! New cpp directive "__check" implemented which is used by check_namelist_files ! ! 667 2010-12-23 12:06:00Z suehring/gryschka ! Exchange of terminate_coupled between ocean and atmosphere via PE0 ! ! 213 2008-11-13 10:26:18Z raasch ! Implementation of a MPI-1 coupling: replaced myid with target_id. ! The uncoupled case allows stop or mpi_abort depending on new steering ! parameter abort_mode, which is set in routine message. ! ! 147 2008-02-01 12:41:46Z raasch ! Bugfix: a stop command was missing in some cases of the parallel branch ! ! 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 ) && ! defined ( __check ) IF ( coupling_mode == 'uncoupled' ) THEN IF ( abort_mode == 1 ) THEN CALL MPI_FINALIZE( ierr ) STOP ELSEIF ( abort_mode == 2 ) THEN CALL MPI_ABORT( comm2d, 9999, ierr ) ENDIF 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 IF ( myid == 0 ) THEN CALL MPI_SENDRECV( & terminate_coupled, 1, MPI_INTEGER, target_id, 0, & terminate_coupled_remote, 1, MPI_INTEGER, target_id, 0, & comm_inter, status, ierr ) ENDIF CALL MPI_BCAST( terminate_coupled_remote, 1, MPI_REAL, 0, comm2d, ierr) ENDIF CALL MPI_FINALIZE( ierr ) STOP CASE ( 1 ) IF ( myid == 0 ) THEN PRINT*, '+++ local_stop:' PRINT*, ' remote model "', TRIM( coupling_mode_remote ), & '" stopped' ENDIF CALL MPI_FINALIZE( ierr ) STOP 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