source: LMDZ6/trunk/libf/dyn3d_common/abort_gcm_NOMODULE.f90 @ 5319

Last change on this file since 5319 was 5310, checked in by abarral, 6 days ago

unify abort_gcm
rename wxios -> wxios_mod

  • Property copyright set to
    Name of program: LMDZ
    Creation date: 1984
    Version: LMDZ5
    License: CeCILL version 2
    Holder: Laboratoire de m\'et\'eorologie dynamique, CNRS, UMR 8539
    See the license file in the root directory
File size: 1.5 KB
Line 
1! /!\ 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
2
3SUBROUTINE abort_gcm(modname, message, ierr)
4  ! Stops the simulation cleanly, closing files and printing various
5  ! comments
6
7  !  Input: modname = name of calling program
8  !     message = stuff to print
9  !     ierr    = severity of situation ( = 0 normal )
10
11  USE IOIPSL, ONLY: histclo, restclo, getin_dump
12  USE wxios_mod, ONLY: using_xios, wxios_close
13  USE mod_phys_lmdz_mpi_data, ONLY: mpi_rank
14  USE lmdz_mpi, ONLY: using_mpi
15  USE mod_const_mpi, ONLY: comm_lmdz
16  USE iniprint_mod_h, ONLY: lunout, prt_level
17  IMPLICIT NONE
18
19  CHARACTER(LEN = *), INTENT(IN) :: modname
20  INTEGER, INTENT(IN) :: ierr
21  CHARACTER(LEN = *), INTENT(IN) :: message
22
23  INTEGER :: ierror_mpi
24
25  WRITE(lunout, *) 'in abort_gcm'
26
27  IF (using_xios) THEN !Fermeture propre de XIOS
28    CALL wxios_close()
29  ENDIF
30
31  !$OMP MASTER
32  CALL histclo
33  CALL restclo
34  IF (mpi_rank == 0) THEN
35    CALL getin_dump
36  ENDIF
37  !$OMP END MASTER
38  WRITE(lunout, *) 'Stopping in ', modname
39  WRITE(lunout, *) 'Reason = ', message
40  IF (ierr == 0) THEN
41    WRITE(lunout, *) 'Everything is cool'
42    IF (.NOT. using_mpi) THEN
43      STOP
44    END IF
45  ELSE
46    WRITE(lunout, *) 'Houston, we have a problem, ierr = ', ierr
47
48    IF (using_mpi) THEN
49      !$OMP CRITICAL (MPI_ABORT_GCM)
50      CALL MPI_ABORT(comm_lmdz, 1, ierror_mpi)
51      !$OMP END CRITICAL (MPI_ABORT_GCM)
52    ELSE
53      STOP 1
54    END IF
55  END IF
56END SUBROUTINE abort_gcm
Note: See TracBrowser for help on using the repository browser.