--- trunk/libf/dyn3d/abort_gcm.f90 2008/02/27 13:16:39 3 +++ trunk/Sources/dyn3d/abort_gcm.f 2015/04/29 15:47:56 134 @@ -7,35 +7,22 @@ SUBROUTINE abort_gcm(modname, message, ierr) ! From abort_gcm.F, version 1.1.1.1 2004/05/19 12:53:05 + ! Stops the simulation, closing files and printing comments. - ! Stops the simulation cleanly, closing files and printing various - ! comments + USE histclo_m, only: histclo - ! Input: modname = name of calling program - ! message = stuff to print - ! ierr = severity of situation ( = 0 normal ) - - USE IOIPSL, only: histclo - use iniprint, only: lunout - - character(len=*), intent(in):: modname - integer, intent(in):: ierr - character(len=*), intent(in):: message + character(len=*), intent(in):: modname ! name of calling program + integer, intent(in):: ierr ! severity of situation (= 0 normal) + character(len=*), intent(in):: message ! to print !------------------- print *, 'abort_gcm' - call histclo - write(lunout,*) 'Stopping in ', modname - write(lunout,*) 'Reason = ', trim(message) - if (ierr == 0) then - write(lunout,*) 'Everything is cool' - STOP - else - write(lunout,*) 'Houston, we have a problem ', ierr - STOP 1 - endif + print *, 'Stopping in ', modname + print *, 'Reason: ', trim(message) + print *, 'Houston, we have a problem ', ierr + STOP 1 END SUBROUTINE abort_gcm