Skip to content
Snippets Groups Projects
messages.f90 3.3 KiB
Newer Older
  • Learn to ignore specific revisions
  • !=== COPYRIGHT AND LICENSE STATEMENT ===
    !
    !  This file is part of the TensorProductMultigrid code.
    !  
    !  (c) The copyright relating to this work is owned jointly by the
    !  Crown, Met Office and NERC [2014]. However, it has been created
    !  with the help of the GungHo Consortium, whose members are identified
    !  at https://puma.nerc.ac.uk/trac/GungHo/wiki .
    !  
    !  Main Developer: Eike Mueller
    !  
    !  TensorProductMultigrid is free software: you can redistribute it and/or
    !  modify it under the terms of the GNU Lesser General Public License as
    !  published by the Free Software Foundation, either version 3 of the
    !  License, or (at your option) any later version.
    !  
    !  TensorProductMultigrid is distributed in the hope that it will be useful,
    !  but WITHOUT ANY WARRANTY; without even the implied warranty of
    !  MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
    !  GNU Lesser General Public License for more details.
    !  
    !  You should have received a copy of the GNU Lesser General Public License
    !  along with TensorProductMultigrid (see files COPYING and COPYING.LESSER).
    !  If not, see <http://www.gnu.org/licenses/>.
    !
    !=== COPYRIGHT AND LICENSE STATEMENT ===
    
    
    !==================================================================
    !
    !  Module for error/warning/info messages
    !
    !    Eike Mueller, University of Bath, Feb 2012
    !
    !==================================================================
    module messages
    
      use parameters
    
    
      implicit none
    
    contains
    
    !==================================================================
    ! Print error message and exit
    !==================================================================
      subroutine fatalerror(message)
        implicit none
        character(len=*), intent(in) :: message
        integer :: ierr, rank
        integer, parameter :: errorcode = -1
        call mpi_comm_rank(MPI_COMM_WORLD,rank,ierr)
        if (rank == 0) then
          write(STDERR,'("FATAL ERROR: ",A)') message
        end if
        call mpi_finalize(ierr)
        STOP
      end subroutine fatalerror
    
    !==================================================================
    ! Print error message
    !==================================================================
      subroutine error(message)
        implicit none
        character(len=*), intent(in) :: message
        integer :: ierr, rank
        call mpi_comm_rank(MPI_COMM_WORLD,rank,ierr)
        if (rank == 0) then
          write(STDERR,'("ERROR: ",A)') message
        end if
      end subroutine error
    
    !==================================================================
    ! Print warning message
    !==================================================================
      subroutine warning(message)
        implicit none
        character(len=*), intent(in) :: message
        integer :: ierr, rank
        call mpi_comm_rank(MPI_COMM_WORLD,rank,ierr)
        if (rank == 0) then
          write(STDERR,'("WARNING: ",A)') message
        end if
      end subroutine warning
    
    !==================================================================
    ! Print info message
    !==================================================================
      subroutine information(message)
        implicit none
        character(len=*), intent(in) :: message
        integer :: ierr, rank
        call mpi_comm_rank(MPI_COMM_WORLD,rank,ierr)
        if (rank == 0) then
          write(STDERR,'("INFO: ",A)') message
        end if
      end subroutine information
    
    end module messages