! $Id: abort_gcm.F 1747 2013-04-23 14:06:30Z lguez $ ! ! SUBROUTINE abort_gcm(modname, message, ierr) USE IOIPSL USE parallel_lmdz INCLUDE "iniprint.h" ! ! Stops the simulation cleanly, closing files and printing various ! comments ! ! Input: modname = name of calling program ! message = stuff to print ! ierr = severity of situation ( = 0 normal ) CHARACTER(LEN=*), INTENT(IN):: modname INTEGER :: ierr, ierror_mpi CHARACTER(LEN=*), INTENT(IN):: message WRITE(lunout,*) 'in abort_gcm' !$OMP MASTER CALL histclo CALL restclo IF (MPI_rank == 0) THEN CALL getin_dump ENDIF !$OMP END MASTER ! CALL histclo(2) ! CALL histclo(3) ! CALL histclo(4) ! CALL histclo(5) WRITE(lunout,*) 'Stopping in ', modname WRITE(lunout,*) 'Reason = ',message IF (ierr == 0) THEN WRITE(lunout,*) 'Everything is cool' else WRITE(lunout,*) 'Houston, we have a problem, ierr = ', ierr IF (using_mpi) THEN !$OMP CRITICAL (MPI_ABORT_GCM) CALL MPI_ABORT(COMM_LMDZ, 1, ierror_mpi) !$OMP END CRITICAL (MPI_ABORT_GCM) else stop 1 endif ENDIF END SUBROUTINE abort_gcm