source: LMDZ6/trunk/libf/dyn3dmem/abort_gcm.f90 @ 5270

Last change on this file since 5270 was 5268, checked in by abarral, 2 days ago

.f90 <-> .F90 depending on cpp key use

  • 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
10  USE parallel_lmdz
11  INCLUDE "iniprint.h"
12
13  !
14  ! Stops the simulation cleanly, closing files and printing various
15  ! comments
16  !
17  !  Input: modname = name of calling program
18  !     message = stuff to print
19  !     ierr    = severity of situation ( = 0 normal )
20
21  character(len=*), intent(in):: modname
22  integer :: ierr, ierror_mpi
23  character(len=*), intent(in):: message
24
25  write(lunout,*) 'in abort_gcm'
26!$OMP MASTER
27  call histclo
28  call restclo
29  if (MPI_rank .eq. 0) then
30     call getin_dump
31  endif
32!$OMP END MASTER
33  ! call histclo(2)
34  ! call histclo(3)
35  ! call histclo(4)
36  ! call histclo(5)
37  write(lunout,*) 'Stopping in ', modname
38  write(lunout,*) 'Reason = ',message
39  if (ierr .eq. 0) then
40    write(lunout,*) 'Everything is cool'
41  else
42    write(lunout,*) 'Houston, we have a problem, ierr = ', ierr
43
44    if (using_mpi) THEN
45!$OMP CRITICAL (MPI_ABORT_GCM)
46      call MPI_ABORT(COMM_LMDZ, 1, ierror_mpi)
47!$OMP END CRITICAL (MPI_ABORT_GCM)
48    else
49     stop 1
50    endif
51
52  endif
53END SUBROUTINE abort_gcm
Note: See TracBrowser for help on using the repository browser.