source: LMDZ6/branches/Amaury_dev/libf/dyn3dmem/abort_gcm.f90 @ 5119

Last change on this file since 5119 was 5118, checked in by abarral, 2 months ago

Replace iniprint.h by lmdz_iniprint.f90
(lint) along the way

  • 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.1 KB
Line 
1
2! $Id: abort_gcm.F 1747 2013-04-23 14:06:30Z lguez $
3
4!
5!
6SUBROUTINE abort_gcm(modname, message, ierr)
7
8  USE IOIPSL
9  USE parallel_lmdz
10  USE lmdz_iniprint, ONLY: lunout, prt_level
11
12  !
13  ! Stops the simulation cleanly, closing files and printing various
14  ! comments
15  !
16  !  Input: modname = name of calling program
17  !     message = stuff to print
18  !     ierr    = severity of situation ( = 0 normal )
19
20  CHARACTER(LEN=*), INTENT(IN):: modname
21  INTEGER :: ierr, ierror_mpi
22  CHARACTER(LEN=*), INTENT(IN):: message
23
24  WRITE(lunout,*) 'in abort_gcm'
25!$OMP MASTER
26  CALL histclo
27  CALL restclo
28  IF (MPI_rank == 0) THEN
29     CALL getin_dump
30  ENDIF
31!$OMP END MASTER
32  ! CALL histclo(2)
33  ! CALL histclo(3)
34  ! CALL histclo(4)
35  ! CALL histclo(5)
36  WRITE(lunout,*) 'Stopping in ', modname
37  WRITE(lunout,*) 'Reason = ',message
38  IF (ierr == 0) THEN
39    WRITE(lunout,*) 'Everything is cool'
40  else
41    WRITE(lunout,*) 'Houston, we have a problem, ierr = ', ierr
42
43    IF (using_mpi) THEN
44!$OMP CRITICAL (MPI_ABORT_GCM)
45      CALL MPI_ABORT(COMM_LMDZ, 1, ierror_mpi)
46!$OMP END CRITICAL (MPI_ABORT_GCM)
47    else
48     stop 1
49    endif
50
51  ENDIF
52END SUBROUTINE abort_gcm
Note: See TracBrowser for help on using the repository browser.