source: CONFIG_DEVT/IPSLCM6.5_work_ENSEMBLES/oasis3-mct/examples/toy_configuration_components_C/routine_model_abort.f90 @ 5725

Last change on this file since 5725 was 5725, checked in by aclsce, 3 years ago

Added new oasis3-MCT version to be used to handle ensembles simulations with XIOS.

File size: 960 bytes
Line 
1!*********************************************************************************
2SUBROUTINE routine_model_abort(w_unit,file,line,subn)
3  !*********************************************************************************
4  !
5  implicit none
6  !
7  INCLUDE 'mpif.h'
8  !
9  ! Call abort in a toy model
10  !
11  integer, intent(in)                    :: w_unit, line
12  character(len=*), intent(in), optional :: subn
13  character(len=*), intent(in)           :: file
14  integer                                :: ierror
15  character(len=*),parameter             :: subname = '(oasis_abort)'
16  !
17  !
18  WRITE (w_unit,*) subname,' Aborting at line = ',line
19  call flush(w_unit)
20  !
21  if (present(subn)) then
22       WRITE (w_unit,*) subname,' Aborting in = ',trim(subn)
23       call flush(w_unit)
24  endif
25
26  WRITE (w_unit,*) subname,' Aborting in file : ',file
27  call flush(w_unit)
28
29  call MPI_Abort ( MPI_COMM_WORLD, 1, ierror )
30  !
31  RETURN
32END SUBROUTINE routine_model_abort
Note: See TracBrowser for help on using the repository browser.