source: LMDZ6/trunk/libf/phy_common/abort_physic.f90 @ 5268

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

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

File size: 1.4 KB
RevLine 
[2311]1! $Id: $
2      SUBROUTINE abort_physic(modname, message, ierr)
3     
4      USE IOIPSL
[5267]5
[2311]6      USE mod_phys_lmdz_para
7      USE print_control_mod, ONLY: lunout
8      IMPLICIT NONE
9!
10! Stops the simulation cleanly, closing files and printing various
11! comments
12!
13!  Input: modname = name of calling program
14!         message = stuff to print
15!         ierr    = severity of situation ( = 0 normal )
16
17      character(len=*), intent(in):: modname
18      integer ierr, ierror_mpi
19      character(len=*), intent(in):: message
20
21      write(lunout,*) 'in abort_physic'
22!$OMP MASTER
23      call histclo
24      call restclo
25      if (mpi_rank .eq. 0) then
26         call getin_dump
27      endif
28!$OMP END MASTER
29
30      write(lunout,*) 'Stopping in ', modname
31      write(lunout,*) 'Reason = ',message
32      if (ierr .eq. 0) then
33        write(lunout,*) 'Everything is cool'
[4600]34        if (using_mpi) then
35          !$OMP CRITICAL (MPI_ABORT_PHYSIC)
36          call MPI_ABORT(COMM_LMDZ_PHY, 0, ierror_mpi)
37          !$OMP END CRITICAL (MPI_ABORT_PHYSIC)
38        else
39          stop 0
40        endif         
[2311]41      else
42        write(lunout,*) 'Houston, we have a problem, ierr = ', ierr
[4600]43        if (using_mpi) then
44          !$OMP CRITICAL (MPI_ABORT_PHYSIC)
45          call MPI_ABORT(COMM_LMDZ_PHY, 1, ierror_mpi)
46          !$OMP END CRITICAL (MPI_ABORT_PHYSIC)
47        else
48          stop 1
49        endif         
[2311]50      endif
51      END
Note: See TracBrowser for help on using the repository browser.