ComparisonsModule Module

Defines procedures that test equality of different kinds of arguments. Procedures defined here are USEd by the FTAssertions Module.


Uses

  • module~~comparisonsmodule~~UsesGraph module~comparisonsmodule ComparisonsModule iso_fortran_env iso_fortran_env module~comparisonsmodule->iso_fortran_env module~ftolconstants FTOLConstants module~comparisonsmodule->module~ftolconstants

Used by

  • module~~comparisonsmodule~~UsedByGraph module~comparisonsmodule ComparisonsModule module~ftassertions FTAssertions module~ftassertions->module~comparisonsmodule module~ftobjectlibrary FTObjectLibrary module~ftobjectlibrary->module~comparisonsmodule module~ftobjectlibrary->module~ftassertions

Variables

Type Visibility Attributes Name Initial
integer, public, parameter :: ASSERT_SUCCESS = 0
integer, public, parameter :: ASSERT_SIZE_DIFFERS = 1
integer, public, parameter :: ASSERT_VALUES_DIFFER = 2
character(len=21), public, parameter :: compareCodeStrings(0:2) = [ASSERT_VALUES_OK_NAME, ASSERT_SIZE_DIFFERS_NAME, ASSERT_VALUES_DIFFERS_NAME]

Interfaces

public interface isEqual

  • private function isEqualTwoIntegers(i, j)

    Arguments

    Type IntentOptional Attributes Name
    integer, intent(in) :: i
    integer, intent(in) :: j

    Return Value logical

  • private function isEqualTwoIntegerArrays1D(a, b, info)

    Arguments

    Type IntentOptional Attributes Name
    integer, intent(in), DIMENSION(:) :: a
    integer, intent(in), DIMENSION(:) :: b
    type(assertInfoArray1D), intent(inout), optional :: info

    Return Value logical

  • private function isEqualTwoIntegerArrays2D(a, b, info)

    Arguments

    Type IntentOptional Attributes Name
    integer, intent(in), DIMENSION(:,:) :: a
    integer, intent(in), DIMENSION(:,:) :: b
    type(assertInfoArray2D), intent(inout), optional :: info

    Return Value logical

  • private function isWithinToleranceTwoReal(x, y, relTol, absTol)

    Arguments

    Type IntentOptional Attributes Name
    real, intent(in) :: x
    real, intent(in) :: y
    real, intent(in) :: relTol
    real, intent(in), optional :: absTol

    Return Value logical

  • private function isWithinToleranceTwoRealArrays1D(a, b, relTol, absTol, code)

    Arguments

    Type IntentOptional Attributes Name
    real, intent(in), DIMENSION(:) :: a
    real, intent(in), DIMENSION(:) :: b
    real, intent(in) :: relTol
    real, intent(in), optional :: absTol
    integer, intent(inout), optional :: code

    Return Value logical

  • private function isWithinToleranceTwoRealArrays2D(a, b, relTol, absTol, code)

    Arguments

    Type IntentOptional Attributes Name
    real, intent(in), DIMENSION(:,:) :: a
    real, intent(in), DIMENSION(:,:) :: b
    real, intent(in) :: relTol
    real, intent(in), optional :: absTol
    integer, intent(out), optional :: code

    Return Value logical

  • private function isWithinToleranceTwoDouble(x, y, relTol, absTol)

    Arguments

    Type IntentOptional Attributes Name
    double precision, intent(in) :: x
    double precision, intent(in) :: y
    double precision, intent(in) :: relTol
    double precision, intent(in), optional :: absTol

    Return Value logical

  • private function isWithinToleranceTwoDoubleArrays1D(a, b, relTol, absTol, code)

    Arguments

    Type IntentOptional Attributes Name
    double precision, intent(in), DIMENSION(:) :: a
    double precision, intent(in), DIMENSION(:) :: b
    double precision, intent(in) :: relTol
    double precision, intent(in), optional :: absTol
    integer, intent(out), optional :: code

    Return Value logical

  • private function isWithinToleranceTwoDoubleArrays2D(a, b, relTol, absTol, code)

    Arguments

    Type IntentOptional Attributes Name
    double precision, intent(in), DIMENSION(:,:) :: a
    double precision, intent(in), DIMENSION(:,:) :: b
    double precision, intent(in) :: relTol
    double precision, intent(in), optional :: absTol
    integer, intent(out), optional :: code

    Return Value logical

  • private function isEqualString(s1, s2)

    Arguments

    Type IntentOptional Attributes Name
    character(len=*) :: s1
    character(len=*) :: s2

    Return Value logical

  • private function isWithinToleranceTwoQuad(x, y, relTol, absTol)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=SELECTED_REAL_KIND(QUAD_DIGITS)), intent(in) :: x
    real(kind=SELECTED_REAL_KIND(QUAD_DIGITS)), intent(in) :: y
    real(kind=SELECTED_REAL_KIND(QUAD_DIGITS)), intent(in) :: relTol
    real(kind=SELECTED_REAL_KIND(QUAD_DIGITS)), intent(in), optional :: absTol

    Return Value logical


Derived Types

type, public ::  assertInfoArray1D

Components

Type Visibility Attributes Name Initial
character(len=128), public :: failureName
integer, public :: failureType
logical, public, DIMENSION(:), ALLOCATABLE :: locations

type, public ::  assertInfoArray2D

Components

Type Visibility Attributes Name Initial
character(len=128), public :: failureName
integer, public :: failureType
logical, public, DIMENSION(:,:), ALLOCATABLE :: locations

Functions

public function isTrue(condition)

Arguments

Type IntentOptional Attributes Name
logical :: condition

Return Value logical

public function isFalse(condition)

Arguments

Type IntentOptional Attributes Name
logical :: condition

Return Value logical