fsml_err.f90 Source File


This file depends on

sourcefile~~fsml_err.f90~~EfferentGraph sourcefile~fsml_err.f90 fsml_err.f90 sourcefile~fsml_con.f90 fsml_con.f90 sourcefile~fsml_err.f90->sourcefile~fsml_con.f90 sourcefile~fsml_ini.f90 fsml_ini.f90 sourcefile~fsml_err.f90->sourcefile~fsml_ini.f90 sourcefile~fsml_utl.f90 fsml_utl.f90 sourcefile~fsml_err.f90->sourcefile~fsml_utl.f90 sourcefile~fsml_con.f90->sourcefile~fsml_ini.f90 sourcefile~fsml_utl.f90->sourcefile~fsml_ini.f90

Files dependent on this one

sourcefile~~fsml_err.f90~~AfferentGraph sourcefile~fsml_err.f90 fsml_err.f90 sourcefile~fsml_dst.f90 fsml_dst.f90 sourcefile~fsml_dst.f90->sourcefile~fsml_err.f90 sourcefile~fsml_lin.f90 fsml_lin.f90 sourcefile~fsml_lin.f90->sourcefile~fsml_err.f90 sourcefile~fsml_sts.f90 fsml_sts.f90 sourcefile~fsml_lin.f90->sourcefile~fsml_sts.f90 sourcefile~fsml_sts.f90->sourcefile~fsml_err.f90 sourcefile~fsml_tst.f90 fsml_tst.f90 sourcefile~fsml_tst.f90->sourcefile~fsml_err.f90 sourcefile~fsml_tst.f90->sourcefile~fsml_dst.f90 sourcefile~fsml_tst.f90->sourcefile~fsml_sts.f90 sourcefile~fsml.f90 fsml.f90 sourcefile~fsml.f90->sourcefile~fsml_dst.f90 sourcefile~fsml.f90->sourcefile~fsml_lin.f90 sourcefile~fsml.f90->sourcefile~fsml_sts.f90 sourcefile~fsml.f90->sourcefile~fsml_tst.f90

Source Code

module fsml_err
!
! |--------------------------------------------------------------------|
! | fsml - fortran statistics and machine learning library             |
! |                                                                    |
! | about                                                              |
! | -----                                                              |
! | Errors handling.                                                   |
! |                                                                    |
! | license : MIT                                                      |
! | author  : Sebastian G. Mutz (sebastian@sebastianmutz.com)          |
! |--------------------------------------------------------------------|

! FORD
!! Module for everything related to error handling.

  ! load modules
  use :: fsml_ini
  use :: fsml_utl
  use :: fsml_con

  ! basic options
  implicit none
  private

  ! declare public
  public :: fsml_error, s_err_print
  public :: fsml_warning, s_err_warn

! ==== Declarations

  ! error messages
  character(len=128), parameter :: fsml_error(4) = [ character(len=128) ::   &
                                  & "[fsml error] Argument value out of valid&
                                  & range. Returning sentinel.          ",   &
                                  & "[fsml error] Argument value not in list &
                                  & of valid options. Returning sentinel.",  &
                                  & "[fsml error] Passed array has invalid   &
                                  & dimensions.                          ",  &
                                  & "[fsml error] Passed array has invalid   &
                                  & size.                                "   ]
  ! warning messages
  character(len=128), parameter :: fsml_warning(1) = [ character(len=128) :: &
                                  & "[fsml warning] Suspicious value returned.&
                                  & Convergence may not have been reached in&
                                  & bisection iterations." ]

contains

! ==================================================================== !
! -------------------------------------------------------------------- !
subroutine s_err_print(error)

! ==== Description
!! Prints error message in specific format.

! ==== Declarations
  character(len=*), intent(in) :: error
  character(len=128)           :: fstring

! ==== Instructions
  fstring = trim(error) // " (" // trim(f_utl_r2c(c_sentinel_r)) // ")"
!  fstring = txt_error // trim(error) // txt_info // &
!          & " (" // trim(f_utl_r2c(c_sentinel_r)) // ")" // txt_reset
  write(std_e, '(A)') fstring

end subroutine s_err_print

! ==================================================================== !
! -------------------------------------------------------------------- !
subroutine s_err_warn(warning)

! ==== Description
!! Prints warning message in specific format.

! ==== Declarations
  character(len=*), intent(in) :: warning
  character(len=128)           :: fstring

! ==== Instructions
  fstring = warning
!  fstring = txt_warn // trim(warning) // txt_reset
  write(std_e, '(A)') fstring

end subroutine s_err_warn

end module fsml_err