Ignore:
Timestamp:
Nov 1, 2024, 1:05:47 PM (3 months ago)
Author:
abarral
Message:

unify abort_gcm
rename wxios -> wxios_mod

File:
1 moved

Legend:

Unmodified
Added
Removed
  • LMDZ6/trunk/libf/dyn3d_common/abort_gcm_NOMODULE.f90

    r5309 r5310  
    1 !
    2 ! $Id: abort_gcm.F 1747 2013-04-23 14:06:30Z lguez $
    3 !
    4 !
    5 !
     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
    63SUBROUTINE abort_gcm(modname, message, ierr)
    7 
    8   USE iniprint_mod_h
    9   USE IOIPSL
    10 
    11   USE parallel_lmdz
    12 
    13   !
    144  ! Stops the simulation cleanly, closing files and printing various
    155  ! comments
    16   !
     6
    177  !  Input: modname = name of calling program
    188  !     message = stuff to print
    199  !     ierr    = severity of situation ( = 0 normal )
    2010
    21   character(len=*), intent(in):: modname
    22   integer :: ierr, ierror_mpi
    23   character(len=*), intent(in):: message
     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
    2418
    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
     19  CHARACTER(LEN = *), INTENT(IN) :: modname
     20  INTEGER, INTENT(IN) :: ierr
     21  CHARACTER(LEN = *), INTENT(IN) :: message
    4322
    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
     23  INTEGER :: ierror_mpi
    5124
    52   endif
     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
    5356END SUBROUTINE abort_gcm
Note: See TracChangeset for help on using the changeset viewer.