! /!\ We can't put this in a module right away with FCM1, as this creates a circular dependency e.g. with wxios through iniprint_mod SUBROUTINE abort_gcm(modname, message, ierr) ! 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 ) USE IOIPSL, ONLY: histclo, restclo, getin_dump USE wxios_mod, ONLY: using_xios, wxios_close USE mod_phys_lmdz_mpi_data, ONLY: mpi_rank USE lmdz_mpi, ONLY: using_mpi USE mod_const_mpi, ONLY: comm_lmdz USE iniprint_mod_h, ONLY: lunout, prt_level IMPLICIT NONE CHARACTER(LEN = *), INTENT(IN) :: modname INTEGER, INTENT(IN) :: ierr CHARACTER(LEN = *), INTENT(IN) :: message INTEGER :: ierror_mpi WRITE(lunout, *) 'in abort_gcm' IF (using_xios) THEN !Fermeture propre de XIOS CALL wxios_close() ENDIF !$OMP MASTER CALL histclo CALL restclo IF (mpi_rank == 0) THEN CALL getin_dump ENDIF !$OMP END MASTER WRITE(lunout, *) 'Stopping in ', modname WRITE(lunout, *) 'Reason = ', message IF (ierr == 0) THEN WRITE(lunout, *) 'Everything is cool' IF (.NOT. using_mpi) THEN STOP END IF 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 END IF END IF END SUBROUTINE abort_gcm