Skip to content
Snippets Groups Projects

Compare revisions

Changes are shown as if the source revision was being merged into the target revision. Learn more about comparing revisions.

Source

Select target project
No results found

Target

Select target project
  • liangb30/cas-741-boliang
  • pignierb/cas741
  • jimoha1/cas741
  • huoy8/cas741
  • grandhia/cas741
  • chenq84/cas741
  • yex33/cas741
  • xuey45/cas741
  • garcilau/cas-741-uriel-garcilazo-msa
  • schankuc2/cas741
  • ahmady3/cas741
  • saadh/cas741
  • singhk56/cas741
  • lin523/cas741
  • fangz58/cas741
  • tranp30/cas741
  • ceranich/cas741
  • norouf1/cas741
  • mirzam48/cas741
  • djavahet/cas741
  • hossaa27/cas741
  • yiding_el/cas-741-upate-name
  • sayadia/cas741
  • elmasn2/cas741
  • cheemf8/cas741
  • cheny997/cas741
  • ma209/cas741
  • mousas26/cas741
  • liuy363/cas741
  • wongk124/cas741
  • dua11/cas741
  • zhoug28/cas741
  • courses/cas-741-tst
  • liy443/cas-741-fork-csv
  • sochania/cas741
  • liy443/cas-741-update-csv-old
  • mahdipoa/cas741
  • wangz892/cas741
  • wangn14/cas741
  • defourej/cas741
  • zhaox183/cas741
  • smiths/cas741
42 results
Show changes
Showing
with 9601 additions and 0 deletions
! ------------------------------------------------------------------------
!> \brief Module for Material Property Data
! ------------------------------------------------------------------------
MODULE material_data
USE system_constants !> Global system constants (for min/max prop values)
USE log_message_control !> Print log/error messages
USE log_messages !> Log/error codes and messages
IMPLICIT NONE
PRIVATE
! ************************************************************************
! EXPORTS
! ************************************************************************
!> Exported interfaces
PUBLIC :: mtl_init, mtl_clean, &
mtl_numMtl, &
mtl_getEmod, mtl_setEmod, &
mtl_getPois, mtl_setPois, &
mtl_getDens, mtl_setDens
! ************************************************************************
! LOCAL CONSTANTS
! ************************************************************************
!> sender code for this module
INTEGER, PARAMETER :: sdr = MTLDAT
! ************************************************************************
! DATA TYPES
! ************************************************************************
!> enumerated type indicating material model
ENUM, BIND(C)
ENUMERATOR :: linear_elastic
END ENUM
! ------------------------------------------------------------------------
!> \brief Material Type
!!
!! \param num Hash value indicating material number
!! \param typ Material model type (from enumerated type in this module)
!! \param emod Elastic modulus
!! \param nu Poisson's ratio
!! \param rho Density
! ------------------------------------------------------------------------
TYPE materialT
INTEGER :: num
INTEGER :: typ
DOUBLE PRECISION :: emod, nu, rho
END TYPE materialT
! ************************************************************************
! STATE VARIABLES
! ************************************************************************
TYPE(materialT), ALLOCATABLE :: materials(:)
! ************************************************************************
! INTERFACES
! ************************************************************************
!> \brief Interface to constructor for module state variables
INTERFACE mtl_init
MODULE PROCEDURE mtl_init_
MODULE PROCEDURE mtl_init_exc_
END INTERFACE mtl_init
!> \brief Interface to destructor for module state variables
INTERFACE mtl_clean
MODULE PROCEDURE mtl_clean_
END INTERFACE mtl_clean
!> \brief Interface for number of materials
INTERFACE mtl_numMtl
MODULE PROCEDURE mtl_num_mtl_
END INTERFACE mtl_numMtl
!> \brief Interface for getter for elastic modulus
INTERFACE mtl_getEmod
MODULE PROCEDURE mtl_get_emod_
MODULE PROCEDURE mtl_get_emod_exc_
END INTERFACE mtl_getEmod
!> \brief Interface for setter for elastic modulus
INTERFACE mtl_setEmod
MODULE PROCEDURE mtl_set_emod_
MODULE PROCEDURE mtl_set_emod_exc_
END INTERFACE mtl_setEmod
!> \brief Interface for getter for Poisson's ratio
INTERFACE mtl_getPois
MODULE PROCEDURE mtl_get_pois_
MODULE PROCEDURE mtl_get_pois_exc_
END INTERFACE mtl_getPois
!> \brief Interface for setter for Poisson's ratio
INTERFACE mtl_setPois
MODULE PROCEDURE mtl_set_pois_
MODULE PROCEDURE mtl_set_pois_exc_
END INTERFACE mtl_setPois
!> \brief Interface for getter for density
INTERFACE mtl_getDens
MODULE PROCEDURE mtl_get_dens_
MODULE PROCEDURE mtl_get_dens_exc_
END INTERFACE mtl_getDens
!> \brief Interface for setter for density
INTERFACE mtl_setDens
MODULE PROCEDURE mtl_set_dens_
MODULE PROCEDURE mtl_set_dens_exc_
END INTERFACE mtl_setDens
CONTAINS
! ************************************************************************
! ACCESS PROGRAMS
! ************************************************************************
! ------------------------------------------------------------------------
!> \brief Constructor for Material Data state variables (non-exception checking)
!!
!! \param nmtl Number of materials
!!
!! This routine allocates memory and initializes the state variable that
!! contains the set of material property information for the problem.
! ------------------------------------------------------------------------
SUBROUTINE mtl_init_ (nmtl)
INTEGER, INTENT(IN) :: nmtl
INTEGER :: imtl !> loop variable
!> only reallocate if new dimension does not match existing dimension
IF (mtl_numMtl().NE.nmtl) THEN
!> ensure state variable is clear
CALL mtl_clean()
!> allocate memory for material data state variable
ALLOCATE(materials(nmtl))
END IF
!> initialize state variable
DO imtl = 1,nmtl
materials(imtl)%num = imtl
materials(imtl)%typ = linear_elastic
materials(imtl)%emod = 0.d0
materials(imtl)%nu = 0.d0
materials(imtl)%rho = 0.d0
END DO
END SUBROUTINE mtl_init_
! ------------------------------------------------------------------------
!> \brief Constructor for Material Data state variables (exception checking)
!!
!! \param nmtl Number of materials
!! \param exc Error code
!!
!! \exception ALLOC Memory allocation for state variable failed
!! \exception SZE Specified number of materials is invalid
!!
!! This routine allocates memory and initializes the state variable that
!! contains the set of material property information for the problem.
! ------------------------------------------------------------------------
SUBROUTINE mtl_init_exc_ (nmtl, exc)
INTEGER, INTENT(IN) :: nmtl
INTEGER, INTENT(OUT) :: exc
INTEGER :: e !> error code for allocation
INTEGER :: imtl !> loop variable
!> ensure that specified number of materials is valid
IF (nmtl.LT.1 .OR. nmtl.GT.MAX_MATERIALS) THEN
exc=SZE
CALL log_printLogMsg(exc,sdr)
RETURN
ELSE
exc=OK
END IF
!> only reallocate if new dimension does not match existing dimension
IF (mtl_numMtl().NE.nmtl) THEN
!> ensure state variable is clear
CALL mtl_clean()
!> allocate memory for material data state variable
ALLOCATE(materials(nmtl), STAT=e)
!> ensure that memory allocation was successful
IF (e.NE.0) THEN
exc=ALLOC
CALL log_printLogMsg(exc,sdr)
RETURN
ELSE
exc=OK
END IF
END IF
!> initialize state variable
DO imtl = 1,nmtl
materials(imtl)%num = imtl
materials(imtl)%typ = linear_elastic
materials(imtl)%emod = 0.d0
materials(imtl)%nu = 0.d0
materials(imtl)%rho = 0.d0
END DO
END SUBROUTINE mtl_init_exc_
! ------------------------------------------------------------------------
!> \brief Destructor for Material Data state variables
!!
!! This routine clears the memory allocated to the state variable that
!! contains the set of material property information for the problem.
! ------------------------------------------------------------------------
SUBROUTINE mtl_clean_ ()
IF (ALLOCATED(materials)) DEALLOCATE(materials)
END SUBROUTINE mtl_clean_
! ------------------------------------------------------------------------
!> \brief Getter for number of materials
!!
!! \return nmtl Number of materials
!!
!! This routine determines the number of data entries that have been
!! allocated for material data. It does not check that the material data
!! has been populated (i.e. changed from initial zero values).
! ------------------------------------------------------------------------
FUNCTION mtl_num_mtl_ () RESULT(nmtl)
INTEGER :: nmtl
!> if data is initialized, return number of materials
IF (ALLOCATED(materials)) THEN
nmtl = SIZE(materials)
ELSE
nmtl = 0 !> if not initialized, there are no materials
END IF
END FUNCTION mtl_num_mtl_
! ------------------------------------------------------------------------
!> \brief Getter for elastic modulus (non-exception checking)
!!
!! \param i Material number
!! \return emod Elastic modulus
!!
!! This routine determines the value of the elastic modulus for material
!! number i.
! ------------------------------------------------------------------------
FUNCTION mtl_get_emod_ (i) RESULT(emod)
INTEGER, INTENT(IN) :: i
DOUBLE PRECISION :: emod
emod = materials(i)%emod
END FUNCTION mtl_get_emod_
! ------------------------------------------------------------------------
!> \brief Getter for elastic modulus (exception checking)
!!
!! \param i Material number
!! \param exc Error code
!!
!! \return emod Elastic modulus
!!
!! \exception POSIT The material number is not in [1..mtl_numMtls()]
!! \exception TYP The material type is not 'linear_elastic'
!!
!! This routine determines the value of the elastic modulus for material
!! number i.
! ------------------------------------------------------------------------
FUNCTION mtl_get_emod_exc_ (i, exc) RESULT(emod)
INTEGER, INTENT(IN) :: i
INTEGER, INTENT(OUT) :: exc
DOUBLE PRECISION :: emod
!> check that the index is within the bounds of the material list
IF ( i.LT.1 .OR. i.GT.mtl_numMtl() ) THEN
exc=POSIT
CALL log_printLogMsg(exc,sdr)
emod = 0.d0
RETURN
!> check that the material type is linear elastic
!! (otherwise, elastic modulus may not be appropriate)
ELSE IF ( materials(i)%typ .NE. linear_elastic ) THEN
exc=TYP
CALL log_printLogMsg(exc,sdr)
emod = 0.d0
RETURN
ELSE
exc=OK
END IF
!> call non-exception version
emod = mtl_getEmod(i)
END FUNCTION mtl_get_emod_exc_
! ------------------------------------------------------------------------
!> \brief Setter for elastic modulus (non-exception checking)
!!
!! \param i Material number
!! \param emod Elastic modulus
!!
!! This routine sets the value of the elastic modulus for material
!! number i.
! ------------------------------------------------------------------------
SUBROUTINE mtl_set_emod_ (i,emod)
INTEGER, INTENT(IN) :: i
DOUBLE PRECISION, INTENT(IN) :: emod
materials(i)%emod = emod
END SUBROUTINE mtl_set_emod_
! ------------------------------------------------------------------------
!> \brief Setter for elastic modulus (exception checking)
!!
!! \param i Material number
!! \param emod Elastic modulus
!! \param exc Error code
!!
!! \exception EXCEED The value of elastic modulus exceeds defined limits
!! \exception POSIT The material number is not in [1..mtl_numMtls()]
!! \exception TYP The material type is not 'linear_elastic'
!!
!! This routine sets the value of the elastic modulus for material
!! number i.
! ------------------------------------------------------------------------
SUBROUTINE mtl_set_emod_exc_ (i,emod, exc)
INTEGER, INTENT(IN) :: i
DOUBLE PRECISION, INTENT(IN) :: emod
INTEGER, INTENT(OUT) :: exc
!> check that the index is within the bounds of the material list
IF ( i.LT.1 .OR. i.GT.mtl_numMtl() ) THEN
exc=POSIT
CALL log_printLogMsg(exc,sdr)
RETURN
!> check that the material type is linear elastic
!! (otherwise, elastic modulus may not be appropriate)
ELSE IF ( materials(i)%typ .NE. linear_elastic ) THEN
exc=TYP
CALL log_printLogMsg(exc,sdr)
RETURN
!> check that the value of elastic modulus is within prescribed limits
ELSE IF (emod.LT.E_MIN .OR. emod.GT.E_MAX) THEN
exc=EXCEED
CALL log_printLogMsg(exc,sdr)
RETURN
ELSE
exc=OK
END IF
!> call non-exception version
CALL mtl_setEmod(i,emod)
END SUBROUTINE mtl_set_emod_exc_
! ------------------------------------------------------------------------
!> \brief Getter for Poisson's ratio (non-exception checking)
!!
!! \param i Material number
!! \return nu Poisson's ratio
!!
!! This routine determines the value of Poisson's ratio for material
!! number i.
! ------------------------------------------------------------------------
FUNCTION mtl_get_pois_ (i) RESULT(nu)
INTEGER, INTENT(IN) :: i
DOUBLE PRECISION :: nu
nu = materials(i)%nu
END FUNCTION mtl_get_pois_
! ------------------------------------------------------------------------
!> \brief Getter for Poisson's ratio (exception checking)
!!
!! \param i Material number
!! \param exc Error code
!!
!! \return nu Poisson's ratio
!!
!! \exception POSIT The material number is not in [1..mtl_numMtls()]
!! \exception TYP The material type is not 'linear_elastic'
!!
!! This routine determines the value of Poisson's ratio for material
!! number i.
! ------------------------------------------------------------------------
FUNCTION mtl_get_pois_exc_ (i, exc) RESULT(nu)
INTEGER, INTENT(IN) :: i
INTEGER, INTENT(OUT) :: exc
DOUBLE PRECISION :: nu
!> check that the index is within the bounds of the material list
IF ( i.LT.1 .OR. i.GT.mtl_numMtl() ) THEN
exc=POSIT
CALL log_printLogMsg(exc,sdr)
nu = 0.d0
RETURN
!> check that the material type is linear elastic
!! (otherwise, Poisson's ratio may not be appropriate)
ELSE IF ( materials(i)%typ .NE. linear_elastic ) THEN
exc=TYP
CALL log_printLogMsg(exc,sdr)
nu = 0.d0
RETURN
ELSE
exc=OK
END IF
!> call non-exception version
nu = mtl_getPois(i)
END FUNCTION mtl_get_pois_exc_
! ------------------------------------------------------------------------
!> \brief Setter for Poisson's ratio (non-exception checking)
!!
!! \param i Material number
!! \param nu Poisson's ratio
!!
!! This routine sets the value of Poisson's ratio for material
!! number i.
! ------------------------------------------------------------------------
SUBROUTINE mtl_set_pois_ (i,nu)
INTEGER, INTENT(IN) :: i
DOUBLE PRECISION, INTENT(IN) :: nu
materials(i)%nu = nu
END SUBROUTINE mtl_set_pois_
! ------------------------------------------------------------------------
!> \brief Setter for Poisson's ratio (exception checking)
!!
!! \param i Material number
!! \param nu Poisson's ratio
!! \param exc Error code
!!
!! \exception EXCEED The value of Poisson's ratio exceeds defined limits
!! \exception POSIT The material number is not in [1..mtl_numMtls()]
!! \exception TYP The material type is not 'linear_elastic'
!!
!! This routine sets the value of Poisson's ratio for material
!! number i.
! ------------------------------------------------------------------------
SUBROUTINE mtl_set_pois_exc_ (i,nu, exc)
INTEGER, INTENT(IN) :: i
DOUBLE PRECISION, INTENT(IN) :: nu
INTEGER, INTENT(OUT) :: exc
!> check that the index is within the bounds of the material list
IF ( i.LT.1 .OR. i.GT.mtl_numMtl() ) THEN
exc=POSIT
CALL log_printLogMsg(exc,sdr)
RETURN
!> check that the material type is linear elastic
!! (otherwise, elastic modulus may not be appropriate)
ELSE IF ( materials(i)%typ .NE. linear_elastic ) THEN
exc=TYP
CALL log_printLogMsg(exc,sdr)
RETURN
!> check that the value of elastic modulus is within prescribed limits
ELSE IF (nu.LT.NU_MIN .OR. nu.GT.NU_MAX) THEN
exc=EXCEED
CALL log_printLogMsg(exc,sdr)
RETURN
ELSE
exc=OK
END IF
!> call non-exception version
CALL mtl_setPois(i,nu)
END SUBROUTINE mtl_set_pois_exc_
! ------------------------------------------------------------------------
!> \brief Getter for density (non-exception checking)
!!
!! \param i Material number
!! \return rho Density
!!
!! This routine determines the value of the density of material
!! number i.
! ------------------------------------------------------------------------
FUNCTION mtl_get_dens_ (i) RESULT(rho)
INTEGER, INTENT(IN) :: i
DOUBLE PRECISION :: rho
rho = materials(i)%rho
END FUNCTION mtl_get_dens_
! ------------------------------------------------------------------------
!> \brief Getter for density (exception checking)
!!
!! \param i Material number
!! \param exc Error code
!!
!! \return rho Density
!!
!! \exception POSIT The material number is not in [1..mtl_numMtls()]
!!
!! This routine determines the value of the density of material
!! number i.
! ------------------------------------------------------------------------
FUNCTION mtl_get_dens_exc_ (i, exc) RESULT(rho)
INTEGER, INTENT(IN) :: i
INTEGER, INTENT(OUT) :: exc
DOUBLE PRECISION :: rho
!> check that the index is within the bounds of the material list
IF ( i.LT.1 .OR. i.GT.mtl_numMtl() ) THEN
exc=POSIT
CALL log_printLogMsg(exc,sdr)
rho = 0.d0
RETURN
ELSE
exc=OK
END IF
!> call non-exception version
rho = mtl_getDens(i)
END FUNCTION mtl_get_dens_exc_
! ------------------------------------------------------------------------
!> \brief Setter for density (non-exception checking)
!!
!! \param i Material number
!! \param rho Density
!!
!! This routine sets the value of the density of material number i.
! ------------------------------------------------------------------------
SUBROUTINE mtl_set_dens_ (i,rho)
INTEGER, INTENT(IN) :: i
DOUBLE PRECISION, INTENT(IN) :: rho
materials(i)%rho = rho
END SUBROUTINE mtl_set_dens_
! ------------------------------------------------------------------------
!> \brief Setter for density (exception checking)
!!
!! \param i Material number
!! \param rho Density
!! \param exc Error code
!!
!! \exception EXCEED The value of the density exceeds defined limits
!! \exception POSIT The material number is not in [1..mtl_numMtls()]
!!
!! This routine sets the value of the density of material number i.
! ------------------------------------------------------------------------
SUBROUTINE mtl_set_dens_exc_ (i,rho, exc)
INTEGER, INTENT(IN) :: i
DOUBLE PRECISION, INTENT(IN) :: rho
INTEGER, INTENT(OUT) :: exc
!> check that the index is within the bounds of the material list
IF ( i.LT.1 .OR. i.GT.mtl_numMtl() ) THEN
exc=POSIT
CALL log_printLogMsg(exc,sdr)
RETURN
!> check that the value of density is within prescribed limits
ELSE IF (rho.LT.RHO_MIN .OR. rho.GT.RHO_MAX) THEN
exc=EXCEED
CALL log_printLogMsg(exc,sdr)
RETURN
ELSE
exc=OK
END IF
!> call non-exception version
CALL mtl_setDens(i,rho)
END SUBROUTINE mtl_set_dens_exc_
! ************************************************************************
! LOCAL FUNCTIONS
! ************************************************************************
! none
END MODULE material_data
! ------------------------------------------------------------------------
!> \brief Module for testing Material Property Data module
! ------------------------------------------------------------------------
MODULE material_data_test
USE fruit !> Unit testing framework
USE system_constants !> Global constants
USE log_message_control !> Printing log/error messages
USE log_messages !> Log/error codes
USE material_data !> Material Property Data module
IMPLICIT NONE
CONTAINS
! ------------------------------------------------------------------------
!> \test Test for OK exception message on allocation
!!
!! \param unit_name Name of unit test (for FRUIT)
!! \param testName Filename for log file (required for exceptions)
!! \param nmtl Number of materials
!! \param expMsg Expected log message
!! \param actMsg Actual log message
!!
!! This test initializes the material_data module and makes sure that the
!! exception message is OK (i.e. allocation did not fail).
! ------------------------------------------------------------------------
SUBROUTINE test_mtl_allocation_MSG
CHARACTER (LEN=*), PARAMETER :: unit_name = 'test_mtl_allocation_MSG'
CHARACTER (LEN=*), PARAMETER :: testName = 'testName'
INTEGER, PARAMETER :: nmtl=10
INTEGER, PARAMETER :: expMsg=OK
INTEGER :: actMsg
!> initialize unit test
CALL set_unit_name(unit_name)
!> initialize log message file
CALL log_setFileName(testName)
CALL log_initLogFile()
!> initialize module and check the exception
CALL mtl_init(nmtl, actMsg)
CALL assertEquals(expMsg,actMsg)
!> finalize log file and deallocate module
CALL log_closeLogFile()
CALL mtl_clean()
END SUBROUTINE test_mtl_allocation_MSG
! ------------------------------------------------------------------------
!> \test Test for SZE exception message on allocation
!!
!! \param unit_name Name of unit test (for FRUIT)
!! \param testName Filename for log file (required for exceptions)
!! \param expMsg Expected log message
!! \param actMsg Actual log message
!!
!! This test attempts to initialize the material data module with invalid
!! size parameters and verifies that the correct exception is returned.
! ------------------------------------------------------------------------
SUBROUTINE test_mtl_allocation_SZE
CHARACTER (LEN=*), PARAMETER :: unit_name = 'test_mtl_allocation_SZE'
CHARACTER (LEN=*), PARAMETER :: testName = 'testName'
INTEGER, PARAMETER :: expMsg=SZE
INTEGER :: actMsg
!> initialize unit test
CALL set_unit_name(unit_name)
!> initialize log file
CALL log_setFileName(testName)
CALL log_initLogFile()
!> try to initialize with nmtl=0
CALL mtl_init(0, actMsg)
CALL assertEquals(expMsg,actMsg)
!> ensure module is reset
CALL mtl_clean()
!> try to initialize with nmtl=MAX_MATERIALS+1
CALL mtl_init(MAX_MATERIALS+1, actMsg)
CALL assertEquals(expMsg,actMsg)
!> finalize log file and deallocate module
CALL log_closeLogFile()
CALL mtl_clean()
END SUBROUTINE test_mtl_allocation_SZE
! ------------------------------------------------------------------------
!> \test Test for number of materials when module is not initialized
!!
!! \param unit_name Name of unit test (for FRUIT)
!! \param expected Expected number of materials
!! \param actual Actual number of materials
!!
!! This test makes sure that the number of materials is returned as 0
!! when the module is not initialized
! ------------------------------------------------------------------------
SUBROUTINE test_mtl_num_mtl_not_allocated
CHARACTER (LEN=*), PARAMETER :: unit_name = 'test_mtl_num_mtl_not_allocated'
INTEGER, PARAMETER :: expected = 0
INTEGER :: actual
!> initialize unit test
CALL set_unit_name(unit_name)
!> check number of materials
actual = mtl_numMtl()
CALL assertEquals(expected, actual)
END SUBROUTINE test_mtl_num_mtl_not_allocated
! ------------------------------------------------------------------------
!> \test Test for number of materials when module is initialized
!!
!! \param unit_name Name of unit test (for FRUIT)
!! \param expected Expected number of materials
!! \param actual Actual number of materials
!!
!! This test makes sure that the correct number of materials is returned.
! ------------------------------------------------------------------------
SUBROUTINE test_mtl_num_mtl_allocated
CHARACTER (LEN=*), PARAMETER :: unit_name = 'test_mtl_num_mtl_allocated'
INTEGER, PARAMETER :: expected = 10
INTEGER :: actual
!> initialize unit test
CALL set_unit_name(unit_name)
!> initialize the module
CALL mtl_init(expected)
!> check number of materials
actual = mtl_numMtl()
CALL assertEquals(expected, actual)
!> deallocate the module
CALL mtl_clean()
END SUBROUTINE test_mtl_num_mtl_allocated
! ------------------------------------------------------------------------
!> \test Test for POSIT exception from mtl_getEmod
!!
!! \param unit_name Name of unit test (for FRUIT)
!! \param testName Filename for log file (required for exceptions)
!! \param nmtl Number of materials
!! \param expMsg Expected log message
!! \param actMsg Actual log message
!! \param emod Dummy variable for get function return
!!
!! This test checks that a POSIT exception is returned when the requested
!! location is not inside the material list.
! ------------------------------------------------------------------------
SUBROUTINE test_mtl_get_emod_POSIT
CHARACTER (LEN=*), PARAMETER :: unit_name = 'test_mtl_get_emod_POSIT'
CHARACTER (LEN=*), PARAMETER :: testName = 'testName'
INTEGER, PARAMETER :: nmtl=10
INTEGER, PARAMETER :: expMsg = POSIT
INTEGER :: actMsg
DOUBLE PRECISION :: emod
!> initialize unit test
CALL set_unit_name(unit_name)
!> initialize log file
CALL log_setFileName(testName)
CALL log_initLogFile()
!> initialize materials
CALL mtl_init(nmtl)
!> try to get beyond last material
emod = mtl_getEmod(nmtl+1, actMsg)
CALL assertEquals(expMsg,actMsg)
!> try to get before first material
emod = mtl_getEmod(0, actMsg)
CALL assertEquals(expMsg,actMsg)
!> finalize the log file and deallocate the material list
CALL log_closeLogFile()
CALL mtl_clean()
END SUBROUTINE test_mtl_get_emod_POSIT
! ------------------------------------------------------------------------
!> \test Test for POSIT exception from mtl_setEmod
!!
!! \param unit_name Name of unit test (for FRUIT)
!! \param testName Filename for log file (required for exceptions)
!! \param nmtl Number of materials
!! \param expMsg Expected log message
!! \param actMsg Actual log message
!! \param emod Dummy variable for set routine input
!!
!! This test checks that a POSIT exception is returned when the requested
!! location is not inside the material list.
! ------------------------------------------------------------------------
SUBROUTINE test_mtl_set_emod_POSIT
CHARACTER (LEN=*), PARAMETER :: unit_name = 'test_mtl_set_emod_POSIT'
CHARACTER (LEN=*), PARAMETER :: testName = 'testName'
INTEGER, PARAMETER :: nmtl=10
INTEGER, PARAMETER :: expMsg = POSIT
INTEGER :: actMsg
DOUBLE PRECISION, PARAMETER :: emod = 3.d0
!> initialize unit test
CALL set_unit_name(unit_name)
!> initialize log file
CALL log_setFileName(testName)
CALL log_initLogFile()
!> initialize materials
CALL mtl_init(nmtl)
!> try to set beyond last material
CALL mtl_setEmod(nmtl+1,emod, actMsg)
CALL assertEquals(expMsg,actMsg)
!> try to set before first material
CALL mtl_setEmod(0,emod, actMsg)
CALL assertEquals(expMsg,actMsg)
!> finalize the log file and deallocate the material list
CALL log_closeLogFile()
CALL mtl_clean()
END SUBROUTINE test_mtl_set_emod_POSIT
! ------------------------------------------------------------------------
!> \test Test for EXCEED exception from mtl_setEmod
!!
!! \param unit_name Name of unit test (for FRUIT)
!! \param testName Filename for log file (required for exceptions)
!! \param nmtl Number of materials
!! \param i Material number for test location
!! \param expMsg Expected log message
!! \param actMsg Actual log message
!!
!! This test checks that an EXCEED exception is returned when the
!! specified input is not within the range defined in the System
!! Constants module.
! ------------------------------------------------------------------------
SUBROUTINE test_mtl_set_emod_EXCEED
CHARACTER (LEN=*), PARAMETER :: unit_name = 'test_mtl_set_emod_EXCEED'
CHARACTER (LEN=*), PARAMETER :: testName = 'testName'
INTEGER, PARAMETER :: nmtl=10
INTEGER, PARAMETER :: i=3
INTEGER, PARAMETER :: expMsg = EXCEED
INTEGER :: actMsg
!> initialize unit test
CALL set_unit_name(unit_name)
!> initialize log file
CALL log_setFileName(testName)
CALL log_initLogFile()
!> initialize materials
CALL mtl_init(nmtl)
!> try to set below min value
CALL mtl_setEmod(i,E_MIN-1.d0, actMsg)
CALL assertEquals(expMsg,actMsg)
!> try to set above max value
CALL mtl_setEmod(i,E_MAX+1.d0, actMsg)
CALL assertEquals(expMsg,actMsg)
!> finalize the log file and deallocate the material list
CALL log_closeLogFile()
CALL mtl_clean()
END SUBROUTINE test_mtl_set_emod_EXCEED
! ------------------------------------------------------------------------
!> \test Test for correct value getting and setting in mtl_getEmod and mtl_setEmod
!!
!! \param unit_name Name of unit test (for FRUIT)
!! \param nmtl Number of materials
!! \param i Material number for test location
!! \param expVal Expected data value
!! \param actVal Actual data value
!!
!! This test checks that the correct value is set using the mtl_setEmod
!! access program and returned from the mtl_getEmod access program.
! ------------------------------------------------------------------------
SUBROUTINE test_mtl_get_set_emod_VAL
CHARACTER (LEN=*), PARAMETER :: unit_name = 'test_mtl_get_set_emod_VAL'
INTEGER, PARAMETER :: nmtl=10
INTEGER, PARAMETER :: i=3
DOUBLE PRECISION, PARAMETER :: expVal = 3.d0
DOUBLE PRECISION :: actVal
!> initialize unit test
CALL set_unit_name(unit_name)
!> initialize materials
CALL mtl_init(nmtl)
!> set the value of the material
CALL mtl_setEmod(i,expVal)
!> get the value using the access program
actVal = mtl_getEmod(i)
CALL assertEquals(expVal,actVal)
!> deallocate the materials
CALL mtl_clean()
END SUBROUTINE test_mtl_get_set_emod_VAL
! ------------------------------------------------------------------------
!> \test Test for POSIT exception from mtl_getPois
!!
!! \param unit_name Name of unit test (for FRUIT)
!! \param testName Filename for log file (required for exceptions)
!! \param nmtl Number of materials
!! \param expMsg Expected log message
!! \param actMsg Actual log message
!! \param nu Dummy variable for get function return
!!
!! This test checks that a POSIT exception is returned when the requested
!! location is not inside the material list.
! ------------------------------------------------------------------------
SUBROUTINE test_mtl_get_pois_POSIT
CHARACTER (LEN=*), PARAMETER :: unit_name = 'test_mtl_get_pois_POSIT'
CHARACTER (LEN=*), PARAMETER :: testName = 'testName'
INTEGER, PARAMETER :: nmtl=10
INTEGER, PARAMETER :: expMsg = POSIT
INTEGER :: actMsg
DOUBLE PRECISION :: nu
!> initialize unit test
CALL set_unit_name(unit_name)
!> initialize log file
CALL log_setFileName(testName)
CALL log_initLogFile()
!> initialize materials
CALL mtl_init(nmtl)
!> try to get beyond last material
nu = mtl_getPois(nmtl+1, actMsg)
CALL assertEquals(expMsg,actMsg)
!> try to get before first material
nu = mtl_getPois(0, actMsg)
CALL assertEquals(expMsg,actMsg)
!> finalize the log file and deallocate the material list
CALL log_closeLogFile()
CALL mtl_clean()
END SUBROUTINE test_mtl_get_pois_POSIT
! ------------------------------------------------------------------------
!> \test Test for POSIT exception from mtl_setPois
!!
!! \param unit_name Name of unit test (for FRUIT)
!! \param testName Filename for log file (required for exceptions)
!! \param nmtl Number of materials
!! \param expMsg Expected log message
!! \param actMsg Actual log message
!! \param nu Dummy variable for set routine input
!!
!! This test checks that a POSIT exception is returned when the requested
!! location is not inside the material list.
! ------------------------------------------------------------------------
SUBROUTINE test_mtl_set_pois_POSIT
CHARACTER (LEN=*), PARAMETER :: unit_name = 'test_mtl_set_pois_POSIT'
CHARACTER (LEN=*), PARAMETER :: testName = 'testName'
INTEGER, PARAMETER :: nmtl=10
INTEGER, PARAMETER :: expMsg = POSIT
INTEGER :: actMsg
DOUBLE PRECISION, PARAMETER :: nu = 0.25d0
!> initialize unit test
CALL set_unit_name(unit_name)
!> initialize log file
CALL log_setFileName(testName)
CALL log_initLogFile()
!> initialize materials
CALL mtl_init(nmtl)
!> try to set beyond last material
CALL mtl_setPois(nmtl+1,nu, actMsg)
CALL assertEquals(expMsg,actMsg)
!> try to set before first material
CALL mtl_setPois(0,nu, actMsg)
CALL assertEquals(expMsg,actMsg)
!> finalize the log file and deallocate the material list
CALL log_closeLogFile()
CALL mtl_clean()
END SUBROUTINE test_mtl_set_pois_POSIT
! ------------------------------------------------------------------------
!> \test Test for EXCEED exception from mtl_setPois
!!
!! \param unit_name Name of unit test (for FRUIT)
!! \param testName Filename for log file (required for exceptions)
!! \param nmtl Number of materials
!! \param i Material number for test location
!! \param expMsg Expected log message
!! \param actMsg Actual log message
!!
!! This test checks that an EXCEED exception is returned when the
!! specified input is not within the range defined in the System
!! Constants module.
! ------------------------------------------------------------------------
SUBROUTINE test_mtl_set_pois_EXCEED
CHARACTER (LEN=*), PARAMETER :: unit_name = 'test_mtl_set_pois_EXCEED'
CHARACTER (LEN=*), PARAMETER :: testName = 'testName'
INTEGER, PARAMETER :: nmtl=10
INTEGER, PARAMETER :: i=3
INTEGER, PARAMETER :: expMsg = EXCEED
INTEGER :: actMsg
!> initialize unit test
CALL set_unit_name(unit_name)
!> initialize log file
CALL log_setFileName(testName)
CALL log_initLogFile()
!> initialize materials
CALL mtl_init(nmtl)
!> try to set below min value
CALL mtl_setPois(i,NU_MIN-0.1d0, actMsg)
CALL assertEquals(expMsg,actMsg)
!> try to set above max value
CALL mtl_setPois(i,NU_MAX+0.1d0, actMsg)
CALL assertEquals(expMsg,actMsg)
!> finalize the log file and deallocate the material list
CALL log_closeLogFile()
CALL mtl_clean()
END SUBROUTINE test_mtl_set_pois_EXCEED
! ------------------------------------------------------------------------
!> \test Test for correct value getting and setting in mtl_getPois and mtl_setPois
!!
!! \param unit_name Name of unit test (for FRUIT)
!! \param nmtl Number of materials
!! \param i Material number for test location
!! \param expVal Expected data value
!! \param actVal Actual data value
!!
!! This test checks that the correct value is set using the mtl_setPois
!! access program and returned from the mtl_getPois access program.
! ------------------------------------------------------------------------
SUBROUTINE test_mtl_get_set_pois_VAL
CHARACTER (LEN=*), PARAMETER :: unit_name = 'test_mtl_get_set_pois_VAL'
INTEGER, PARAMETER :: nmtl=10
INTEGER, PARAMETER :: i=3
DOUBLE PRECISION, PARAMETER :: expVal = 0.25d0
DOUBLE PRECISION :: actVal
!> initialize unit test
CALL set_unit_name(unit_name)
!> initialize materials
CALL mtl_init(nmtl)
!> set the value of the material
CALL mtl_setPois(i,expVal)
!> get the value using the access program
actVal = mtl_getPois(i)
CALL assertEquals(expVal,actVal)
!> deallocate the materials
CALL mtl_clean()
END SUBROUTINE test_mtl_get_set_pois_VAL
! ------------------------------------------------------------------------
!> \test Test for POSIT exception from mtl_getDens
!!
!! \param unit_name Name of unit test (for FRUIT)
!! \param testName Filename for log file (required for exceptions)
!! \param nmtl Number of materials
!! \param expMsg Expected log message
!! \param actMsg Actual log message
!! \param rho Dummy variable for get function return
!!
!! This test checks that a POSIT exception is returned when the requested
!! location is not inside the material list.
! ------------------------------------------------------------------------
SUBROUTINE test_mtl_get_dens_POSIT
CHARACTER (LEN=*), PARAMETER :: unit_name = 'test_mtl_get_dens_POSIT'
CHARACTER (LEN=*), PARAMETER :: testName = 'testName'
INTEGER, PARAMETER :: nmtl=10
INTEGER, PARAMETER :: expMsg = POSIT
INTEGER :: actMsg
DOUBLE PRECISION :: rho
!> initialize unit test
CALL set_unit_name(unit_name)
!> initialize log file
CALL log_setFileName(testName)
CALL log_initLogFile()
!> initialize materials
CALL mtl_init(nmtl)
!> try to get beyond last material
rho = mtl_getDens(nmtl+1, actMsg)
CALL assertEquals(expMsg,actMsg)
!> try to get before first material
rho = mtl_getDens(0, actMsg)
CALL assertEquals(expMsg,actMsg)
!> finalize the log file and deallocate the material list
CALL log_closeLogFile()
CALL mtl_clean()
END SUBROUTINE test_mtl_get_dens_POSIT
! ------------------------------------------------------------------------
!> \test Test for POSIT exception from mtl_setDens
!!
!! \param unit_name Name of unit test (for FRUIT)
!! \param testName Filename for log file (required for exceptions)
!! \param nmtl Number of materials
!! \param expMsg Expected log message
!! \param actMsg Actual log message
!! \param rho Dummy variable for set routine input
!!
!! This test checks that a POSIT exception is returned when the requested
!! location is not inside the material list.
! ------------------------------------------------------------------------
SUBROUTINE test_mtl_set_dens_POSIT
CHARACTER (LEN=*), PARAMETER :: unit_name = 'test_mtl_set_dens_POSIT'
CHARACTER (LEN=*), PARAMETER :: testName = 'testName'
INTEGER, PARAMETER :: nmtl=10
INTEGER, PARAMETER :: expMsg = POSIT
INTEGER :: actMsg
DOUBLE PRECISION, PARAMETER :: rho = 2.d3
!> initialize unit test
CALL set_unit_name(unit_name)
!> initialize log file
CALL log_setFileName(testName)
CALL log_initLogFile()
!> initialize materials
CALL mtl_init(nmtl)
!> try to set beyond last material
CALL mtl_setDens(nmtl+1,rho, actMsg)
CALL assertEquals(expMsg,actMsg)
!> try to set before first material
CALL mtl_setDens(0,rho, actMsg)
CALL assertEquals(expMsg,actMsg)
!> finalize the log file and deallocate the material list
CALL log_closeLogFile()
CALL mtl_clean()
END SUBROUTINE test_mtl_set_dens_POSIT
! ------------------------------------------------------------------------
!> \test Test for EXCEED exception from mtl_setDens
!!
!! \param unit_name Name of unit test (for FRUIT)
!! \param testName Filename for log file (required for exceptions)
!! \param nmtl Number of materials
!! \param i Material number for test location
!! \param expMsg Expected log message
!! \param actMsg Actual log message
!!
!! This test checks that an EXCEED exception is returned when the
!! specified input is not within the range defined in the System
!! Constants module.
! ------------------------------------------------------------------------
SUBROUTINE test_mtl_set_dens_EXCEED
CHARACTER (LEN=*), PARAMETER :: unit_name = 'test_mtl_set_dens_EXCEED'
CHARACTER (LEN=*), PARAMETER :: testName = 'testName'
INTEGER, PARAMETER :: nmtl=10
INTEGER, PARAMETER :: i=3
INTEGER, PARAMETER :: expMsg = EXCEED
INTEGER :: actMsg
!> initialize unit test
CALL set_unit_name(unit_name)
!> initialize log file
CALL log_setFileName(testName)
CALL log_initLogFile()
!> initialize materials
CALL mtl_init(nmtl)
!> try to set below min value
CALL mtl_setDens(i,RHO_MIN-1.d0, actMsg)
CALL assertEquals(expMsg,actMsg)
!> try to set above max value
CALL mtl_setDens(i,RHO_MAX+1.d0, actMsg)
CALL assertEquals(expMsg,actMsg)
!> finalize the log file and deallocate the material list
CALL log_closeLogFile()
CALL mtl_clean()
END SUBROUTINE test_mtl_set_dens_EXCEED
! ------------------------------------------------------------------------
!> \test Test for correct value getting and setting in mtl_getDens and mtl_setDens
!!
!! \param unit_name Name of unit test (for FRUIT)
!! \param nmtl Number of materials
!! \param i Material number for test location
!! \param expVal Expected data value
!! \param actVal Actual data value
!!
!! This test checks that the correct value is set using the mtl_setDens
!! access program and returned from the mtl_getDens access program.
! ------------------------------------------------------------------------
SUBROUTINE test_mtl_get_set_dens_VAL
CHARACTER (LEN=*), PARAMETER :: unit_name = 'test_mtl_get_set_dens_VAL'
INTEGER, PARAMETER :: nmtl=10
INTEGER, PARAMETER :: i=3
DOUBLE PRECISION, PARAMETER :: expVal = 2.d3
DOUBLE PRECISION :: actVal
!> initialize unit test
CALL set_unit_name(unit_name)
!> initialize materials
CALL mtl_init(nmtl)
!> set the value of the material
CALL mtl_setDens(i,expVal)
!> get the value using the access program
actVal = mtl_getDens(i)
CALL assertEquals(expVal,actVal)
!> deallocate material data
CALL mtl_clean()
END SUBROUTINE test_mtl_get_set_dens_VAL
END MODULE material_data_test
! ------------------------------------------------------------------------
!> \brief Module for Material Models
! ------------------------------------------------------------------------
MODULE material_model
USE dense_matrix_def !> Dense Matrix data type
USE vector_def !> Vector data type
USE constitutive !> Constitutive Matrix module
IMPLICIT NONE
PRIVATE
! ************************************************************************
! EXPORTS
! ************************************************************************
!> Exported interfaces
PUBLIC :: linearElastic
! ************************************************************************
! LOCAL CONSTANTS
! ************************************************************************
! none
! ************************************************************************
! DATA TYPES
! ************************************************************************
! none
! ************************************************************************
! INTERFACES
! ************************************************************************
!> \brief Interface to linear elastic material model
INTERFACE linearElastic
MODULE PROCEDURE linear_elastic_2d_plane_strain_
END INTERFACE linearElastic
CONTAINS
! ************************************************************************
! ACCESS PROGRAMS
! ************************************************************************
! ------------------------------------------------------------------------
!> \brief Linear elastic material model (2-d, plane strain)
!!
!! \param emod Elastic modulus
!! \param nu Poisson's ratio
!! \param deps Strain increment
!! \param dsig Stress increment
!!
!! This routine computes the incremental stress given the incremental
!! strain for a linear elastic material.
! ------------------------------------------------------------------------
SUBROUTINE linear_elastic_2d_plane_strain_ (emod,nu, deps, dsig)
DOUBLE PRECISION, INTENT(IN) :: emod,nu
TYPE(vectorT), INTENT(IN) :: deps
TYPE(vectorT), INTENT(INOUT) :: dsig
TYPE(matrixT) :: Dmat !> constitutive matrix
!> get constitutive matrix
CALL dmatrix(emod,nu, Dmat)
CALL vec_clean(dsig) !> ensure dsig is deallocated (avoid memory leak)
dsig = Dmat*deps !> compute stress increment
!> deallocate constitutive matrix
CALL dm_clean(Dmat)
END SUBROUTINE linear_elastic_2d_plane_strain_
! ************************************************************************
! LOCAL FUNCTIONS
! ************************************************************************
! none
END MODULE material_model
! ------------------------------------------------------------------------
!> \brief Module defining PDE Solver Constants
! ------------------------------------------------------------------------
MODULE pde_solver_constants
USE system_constants !> Global system constants
IMPLICIT NONE
INTEGER, PARAMETER :: NGAUSS_ELEM = 1 !> number of Gaussian integration points per body element
INTEGER, PARAMETER :: NGAUSS_BOUND = 1 !> number of Gaussian integration points per traction element
!> Gaussian integration data for body elements
DOUBLE PRECISION, PARAMETER, DIMENSION(NGAUSS_ELEM,2) :: GAUSS_PT_ELEM = RESHAPE( (/ ONE_THIRD, ONE_THIRD /), SHAPE(GAUSS_PT_ELEM) )
DOUBLE PRECISION, PARAMETER, DIMENSION(NGAUSS_ELEM) :: GAUSS_WT_ELEM = (/ 1.d0 /)
!> Gaussian integration data for traction elements
DOUBLE PRECISION, PARAMETER, DIMENSION(NGAUSS_BOUND) :: GAUSS_PT_BOUND = (/ 0.5d0 /)
DOUBLE PRECISION, PARAMETER, DIMENSION(NGAUSS_BOUND) :: GAUSS_WT_BOUND = (/ 1.d0 /)
!> parameters for Newmark time-stepping
DOUBLE PRECISION, PARAMETER :: GAMA = 0.5d0
DOUBLE PRECISION, PARAMETER :: BETA = 0.25d0
END MODULE pde_solver_constants
! ------------------------------------------------------------------------
!> \brief Module for PDE Solver Control
! ------------------------------------------------------------------------
MODULE pde_solver_control
USE system_constants !> global system constants
USE pde_solver_constants !> constants for PDE solver
USE log_message_control !> print log/error messages
USE log_messages !> log/error message and sender codes
USE band_sym_matrix_def !> banded symmetric matrix ADT
USE dense_matrix_def !> dense matrix ADT
USE vector_def !> vector ADT
USE field_data !> field data module
USE boundary_data !> boundary data module
USE material_data !> material property data module
USE body_element_integration !> body element integration (mass and stiff)
USE traction_element_integration !> traction element load vectors
IMPLICIT NONE
PRIVATE
! ************************************************************************
! EXPORTS
! ************************************************************************
!> Exported state variables
PUBLIC :: hbw, nnod, nel, nelb, ndof, &
mass, modMass, damp, stiff, &
initStress, initStrain, body, trac, load, &
prevDisp, incDisp, newDisp, &
prevVel, incVel, newVel, &
prevAcc, newAcc, &
prevStress, incStress, newStress, &
prevStrain, incStrain, newStrain
!> Exported interfaces
PUBLIC :: pde_init, pde_clean, &
pde_buildMassMatrix, &
pde_buildStiffMatrix!, &
! pde_buildDampMatrix, &
! pde_buildModMassMatrix, &
! pde_buildLoadVector, &
! pde_initAcc, &
! pde_incAcc, pde_incVel, pde_incDisp, &
! pde_incStress, pde_incStrain, &
! pde_updateAcc, pde_updateVel, pde_updateDisp, &
! pde_updateStress, pde_updateStrain
! ************************************************************************
! LOCAL CONSTANTS
! ************************************************************************
! none
! ************************************************************************
! DATA TYPES
! ************************************************************************
! none
! ************************************************************************
! STATE VARIABLES
! ************************************************************************
INTEGER, SAVE :: hbw !> half bandwidth of system matrices
INTEGER, SAVE :: nnod !> total number of nodes
INTEGER, SAVE :: nel !> total number of body elements
INTEGER, SAVE :: nelb !> total number of traction elements
INTEGER, SAVE :: ndof !> total number of system degrees of freedom
TYPE(bandSymMatrixT), SAVE :: mass !> mass matrix
TYPE(bandSymMatrixT), SAVE :: modMass !> modified mass matrix (for time-stepping)
TYPE(bandSymMatrixT), SAVE :: stiff !> stiffness matrix
TYPE(bandSymMatrixT), SAVE :: damp !> damping matrix
TYPE(vectorT), SAVE :: initStress !> load vector due to initial stress
TYPE(vectorT), SAVE :: initStrain !> load vector due to initial strain
TYPE(vectorT), SAVE :: body !> load vector due to body forces
TYPE(vectorT), SAVE :: trac !> load vector due to surface tractions
TYPE(vectorT), SAVE :: load !> total load vector
TYPE(vectorT), SAVE :: prevDisp !> displacement vector on previous time step
TYPE(vectorT), SAVE :: incDisp !> change in displacement on current time step
TYPE(vectorT), SAVE :: newDisp !> displacement vector on current time step
TYPE(vectorT), SAVE :: prevVel !> velocity vector on previous time step
TYPE(vectorT), SAVE :: incVel !> change in velocity on current time step
TYPE(vectorT), SAVE :: newVel !> velocity vector on current time step
TYPE(vectorT), SAVE :: prevAcc !> acceleration vector on previous time step
TYPE(vectorT), SAVE :: newAcc !> acceleration vector on current time step
TYPE(vectorT), SAVE :: prevStress !> element stresses on previous time step
TYPE(vectorT), SAVE :: incStress !> change in element stresses on current time step
TYPE(vectorT), SAVE :: newStress !> element stresses on current time step
TYPE(vectorT), SAVE :: prevStrain !> element strains on previous time step
TYPE(vectorT), SAVE :: incStrain !> change in element strains on current time step
TYPE(vectorT), SAVE :: newStrain !> element strains on current time step
! ************************************************************************
! INTERFACES
! ************************************************************************
!> \brief Interface to PDE solver initializer
INTERFACE pde_init
MODULE PROCEDURE pde_init_
END INTERFACE pde_init
!> \brief Interface to PDE solver destructor
INTERFACE pde_clean
MODULE PROCEDURE pde_clean_
END INTERFACE pde_clean
!> \brief Interface to mass matrix constructor
INTERFACE pde_buildMassMatrix
MODULE PROCEDURE pde_build_mass_matrix_
END INTERFACE pde_buildMassMatrix
!> \brief Interface to stiffness matrix constructor
INTERFACE pde_buildStiffMatrix
MODULE PROCEDURE pde_build_stiff_matrix_
END INTERFACE pde_buildStiffMatrix
!> \brief Interface to damping matrix constructor
!INTERFACE pde_buildDampMatrix
! MODULE PROCEDURE pde_build_damp_matrix_
!END INTERFACE pde_buildDampMatrix
!> \brief Interface to modified mass matrix constructor
!INTERFACE pde_buildModMassMatrix
! MODULE PROCEDURE pde_build_mod_mass_matrix_
!END INTERFACE pde_buildModMassMatrix
!> \brief Interface to load vector constructor
!INTERFACE pde_buildLoadVector
! MODULE PROCEDURE pde_build_load_vector_
!END INTERFACE pde_buildLoadVector
!> \brief Interface to acceleration vector initializer
!INTERFACE pde_initAcc
! MODULE PROCEDURE pde_init_acc_
!END INTERFACE pde_initAcc
!> \brief Interface to acceleration vector incrementer
!INTERFACE pde_incAcc
! MODULE PROCEDURE pde_inc_acc_
!END INTERFACE pde_incAcc
!> \brief Interface to velocity vector incrementer
!INTERFACE pde_incVel
! MODULE PROCEDURE pde_inc_vel_
!END INTERFACE pde_incVel
!> \brief Interface to displacement vector incrementer
!INTERFACE pde_incDisp
! MODULE PROCEDURE pde_inc_disp_
!END INTERFACE pde_incDisp
!> \brief Interface to stress incrementer
!INTERFACE pde_incStress
! MODULE PROCEDURE pde_inc_stress_
!END INTERFACE pde_incStress
!> \brief Interface to strain incrementer
!INTERFACE pde_incStrain
! MODULE PROCEDURE pde_inc_strain_
!END INTERFACE pde_incStrain
!> \brief Interface to acceleration vector updater
!INTERFACE pde_updateAcc
! MODULE PROCEDURE pde_update_acc_
!END INTERFACE pde_updateAcc
!> \brief Interface to velocity vector updater
!INTERFACE pde_updateVel
! MODULE PROCEDURE pde_update_vel_
!END INTERFACE pde_updateVel
!> \brief Interface to displacement vector updater
!INTERFACE pde_updateDisp
! MODULE PROCEDURE pde_update_disp_
!END INTERFACE pde_updateDisp
!> \brief Interface to stress updater
!INTERFACE pde_updateStress
! MODULE PROCEDURE pde_update_stress_
!END INTERFACE pde_updateStress
!> \brief Interface to strain updater
!INTERFACE pde_updateStrain
! MODULE PROCEDURE pde_update_strain_
!END INTERFACE pde_updateStrain
CONTAINS
! ************************************************************************
! ACCESS PROGRAMS
! ************************************************************************
! ------------------------------------------------------------------------
!> \brief Initializer for PDE solver
!!
!! \param exc For returning exception codes. (Optional).
!!
!! This routine sets up the solution space for the problem by allocating
!! memory for the following state variables:
!!
!! mass, stiff, initStress, initStrain, body, trac, load,
!! prevDisp, incDisp, newDisp,
!! prevVel, incVel, newVel,
!! prevAcc, newAcc,
!! prevStress, incStress, newStress,
!! prevStrain, incStrain, newStrain
!!
!! Note that modMass and damp are not allocated here since
!! they will be computed by combining other matrices later.
!!
!! This routine also initializes the values stored in:
!!
!! prevDisp, prevVel, prevStress, prevStrain
!!
!! These represent the initial conditions of the system.
! ------------------------------------------------------------------------
SUBROUTINE pde_init_ (exc)
INTEGER, INTENT(OUT), OPTIONAL :: exc
INTEGER :: exc_tmp !> for storing exceptions
INTEGER :: nstress !> total number of stress/strain entries
INTEGER :: i,j !> loop variables
INTEGER :: dof !> degree of freedom number
!> determine system size properties
nnod = fld_numNode()
nel = fld_numElem()
nelb = bnd_numBoundElem()
ndof = fld_numDof()
hbw = compute_hbw()
! ----------------------------
!> allocate system matrices
! ----------------------------
!> mass matrix
CALL bsm_init(mass, hbw,ndof, exc_tmp)
IF (exc_tmp.NE.OK) THEN
IF (PRESENT(exc)) exc=exc_tmp
RETURN
END IF
!> stiffness matrix
CALL bsm_init(stiff, hbw,ndof, exc_tmp)
IF (exc_tmp.NE.OK) THEN
IF (PRESENT(exc)) exc=exc_tmp
RETURN
END IF
! ----------------------------
!> allocate system vectors
! ----------------------------
!> initial stress load vector
CALL vec_init(initStress, ndof, exc_tmp)
IF (exc_tmp.NE.OK) THEN
IF (PRESENT(exc)) exc=exc_tmp
RETURN
END IF
!> initial strain load vector
CALL vec_init(initStrain, ndof, exc_tmp)
IF (exc_tmp.NE.OK) THEN
IF (PRESENT(exc)) exc=exc_tmp
RETURN
END IF
!> body force load vector
CALL vec_init(body, ndof, exc_tmp)
IF (exc_tmp.NE.OK) THEN
IF (PRESENT(exc)) exc=exc_tmp
RETURN
END IF
!> traction load vector
CALL vec_init(trac, ndof, exc_tmp)
IF (exc_tmp.NE.OK) THEN
IF (PRESENT(exc)) exc=exc_tmp
RETURN
END IF
!> total load vector
CALL vec_init(load, ndof, exc_tmp)
IF (exc_tmp.NE.OK) THEN
IF (PRESENT(exc)) exc=exc_tmp
RETURN
END IF
!> previous displacement
CALL vec_init(prevDisp, ndof, exc_tmp)
IF (exc_tmp.NE.OK) THEN
IF (PRESENT(exc)) exc=exc_tmp
RETURN
END IF
!> incremental displacement
CALL vec_init(incDisp, ndof, exc_tmp)
IF (exc_tmp.NE.OK) THEN
IF (PRESENT(exc)) exc=exc_tmp
RETURN
END IF
!> current displacement
CALL vec_init(newDisp, ndof, exc_tmp)
IF (exc_tmp.NE.OK) THEN
IF (PRESENT(exc)) exc=exc_tmp
RETURN
END IF
!> previous velocity
CALL vec_init(prevVel, ndof, exc_tmp)
IF (exc_tmp.NE.OK) THEN
IF (PRESENT(exc)) exc=exc_tmp
RETURN
END IF
!> incremental velocity
CALL vec_init(incVel, ndof, exc_tmp)
IF (exc_tmp.NE.OK) THEN
IF (PRESENT(exc)) exc=exc_tmp
RETURN
END IF
!> current velocity
CALL vec_init(newVel, ndof, exc_tmp)
IF (exc_tmp.NE.OK) THEN
IF (PRESENT(exc)) exc=exc_tmp
RETURN
END IF
!> previous acceleration
CALL vec_init(prevAcc, ndof, exc_tmp)
IF (exc_tmp.NE.OK) THEN
IF (PRESENT(exc)) exc=exc_tmp
RETURN
END IF
!> current acceleration
CALL vec_init(newAcc, ndof, exc_tmp)
IF (exc_tmp.NE.OK) THEN
IF (PRESENT(exc)) exc=exc_tmp
RETURN
END IF
! ----------------------------------
!> allocate stress/strain vectors
! ----------------------------------
nstress = nel*NTNS
!> previous stress
CALL vec_init(prevStress, nstress, exc_tmp)
IF (exc_tmp.NE.OK) THEN
IF (PRESENT(exc)) exc=exc_tmp
RETURN
END IF
!> incremental stress
CALL vec_init(incStress, nstress, exc_tmp)
IF (exc_tmp.NE.OK) THEN
IF (PRESENT(exc)) exc=exc_tmp
RETURN
END IF
!> current stress
CALL vec_init(newStress, nstress, exc_tmp)
IF (exc_tmp.NE.OK) THEN
IF (PRESENT(exc)) exc=exc_tmp
RETURN
END IF
!> previous strain
CALL vec_init(prevStrain, nstress, exc_tmp)
IF (exc_tmp.NE.OK) THEN
IF (PRESENT(exc)) exc=exc_tmp
RETURN
END IF
!> incremental strain
CALL vec_init(incStrain, nstress, exc_tmp)
IF (exc_tmp.NE.OK) THEN
IF (PRESENT(exc)) exc=exc_tmp
RETURN
END IF
!> current strain
CALL vec_init(newStrain, nstress, exc_tmp)
IF (exc_tmp.NE.OK) THEN
IF (PRESENT(exc)) exc=exc_tmp
RETURN
END IF
! ----------------------------
!> set up initial conditions
! ----------------------------
!> displacement and velocity
DO i = 1,nnod
DO j = 1,NDIM
dof = fld_getDof(i,j, exc_tmp)
IF (exc_tmp.NE.OK) THEN
IF (PRESENT(exc)) exc=exc_tmp
RETURN
END IF
IF (dof.NE.0) THEN
CALL vec_set(prevDisp, dof, fld_getDisp(i,j), exc_tmp)
IF (exc_tmp.NE.OK) THEN
IF (PRESENT(exc)) exc=exc_tmp
RETURN
END IF
CALL vec_set(prevVel, dof, fld_getVel(i,j), exc_tmp)
IF (exc_tmp.NE.OK) THEN
IF (PRESENT(exc)) exc=exc_tmp
RETURN
END IF
END IF
END DO
END DO
!> stress and strain
DO i = 1,nel
dof = (i-1)*NTNS
DO j = 1,NTNS
CALL vec_set(prevStress, dof+j, fld_getStressElem(i,j), exc_tmp)
IF (exc_tmp.NE.OK) THEN
IF (PRESENT(exc)) exc=exc_tmp
RETURN
END IF
CALL vec_set(prevStrain, dof+j, fld_getStrainElem(i,j), exc_tmp)
IF (exc_tmp.NE.OK) THEN
IF (PRESENT(exc)) exc=exc_tmp
RETURN
END IF
END DO
END DO
!> if no exceptions were raised, everything is A-OK
IF (PRESENT(exc)) exc=OK
END SUBROUTINE pde_init_
! ------------------------------------------------------------------------
!> \brief Destructor for PDE solver
!!
!! This routine ensures that all state variables that have been
!! dynamically allocated are deallocated. It also resets system size
!! parameters.
! ------------------------------------------------------------------------
SUBROUTINE pde_clean_ ()
!> size parameters
nnod = 0
nel = 0
nelb = 0
ndof = 0
hbw = 0
!> matrices
CALL bsm_clean(mass)
CALL bsm_clean(modMass)
CALL bsm_clean(stiff)
CALL bsm_clean(damp)
!> vectors
CALL vec_clean(initStress)
CALL vec_clean(initStrain)
CALL vec_clean(body)
CALL vec_clean(trac)
CALL vec_clean(load)
CALL vec_clean(prevDisp)
CALL vec_clean(incDisp)
CALL vec_clean(newDisp)
CALL vec_clean(prevVel)
CALL vec_clean(incVel)
CALL vec_clean(newVel)
CALL vec_clean(prevAcc)
CALL vec_clean(newAcc)
CALL vec_clean(prevStress)
CALL vec_clean(incStress)
CALL vec_clean(newStress)
CALL vec_clean(prevStrain)
CALL vec_clean(incStrain)
CALL vec_clean(newStrain)
END SUBROUTINE pde_clean_
! ------------------------------------------------------------------------
!> \brief Build the global mass matrix
!!
!! \param exc Error code
!!
!! This routine constructs the global (consistent) mass matrix by
!! summing element mass matrices taking connectivity into account. This
!! routine assumes that pde_init() has already been called.
! ------------------------------------------------------------------------
SUBROUTINE pde_build_mass_matrix_ (exc)
INTEGER, INTENT(OUT), OPTIONAL :: exc
TYPE(matrixT) :: emass !> element mass matrix
INTEGER :: ind(NNODEL*NDIM) !> mapping indices
INTEGER :: i !> loop variable
INTEGER :: exc_tmp !> for getting exception code
!> loop through elements, adding element mass matrices
DO i = 1,nel
!> get element mass matrix and add it to the global mass matrix
CALL bint_emass(i,emass)
ind = get_index(i)
CALL bsm_mappedAdd(mass, emass,ind, exc_tmp)
!> check that mapped add was successful
IF (exc_tmp.NE.OK) THEN
IF (PRESENT(exc)) exc=exc_tmp
RETURN
END IF
END DO
!> if loop completed, everything is OK
IF (PRESENT(exc)) exc=OK
END SUBROUTINE pde_build_mass_matrix_
! ------------------------------------------------------------------------
!> \brief Build the global stiffness matrix
!!
!! \param exc Error code
!!
!! This routine constructs the global stiffness matrix by summing element
!! stiffness matrices taking connectivity into account. This
!! routine assumes that pde_init() has already been called.
! ------------------------------------------------------------------------
SUBROUTINE pde_build_stiff_matrix_ (exc)
INTEGER, INTENT(OUT), OPTIONAL :: exc
TYPE(matrixT) :: estiff !> element stiffness matrix
INTEGER :: ind(NNODEL*NDIM) !> mapping indices
INTEGER :: i !> loop variable
INTEGER :: exc_tmp !> for getting exception code
!> loop through elements, adding element stiffness matrices
DO i = 1,nel
!> get element stiffness matrix and add it to the global stiffness matrix
CALL bint_estiff(i,estiff)
ind = get_index(i)
CALL bsm_mappedAdd(stiff, estiff,ind, exc_tmp)
!> check that mapped add was successful
IF (exc_tmp.NE.OK) THEN
IF (PRESENT(exc)) exc=exc_tmp
RETURN
END IF
END DO
!> if loop completed, everything is OK
IF (PRESENT(exc)) exc=OK
END SUBROUTINE pde_build_stiff_matrix_
! ************************************************************************
! LOCAL FUNCTIONS
! ************************************************************************
! ------------------------------------------------------------------------
!> \brief Compute the half bandwidth of the system matrices
!!
!! \return hbw Half bandwidth
! ------------------------------------------------------------------------
FUNCTION compute_hbw () RESULT(hbw)
INTEGER :: hbw
INTEGER :: i,j,k,l,m !> loop variables
INTEGER :: lmin, mmin !> loop limits
INTEGER :: nel !> number of elements
INTEGER :: dof1,dof2 !> for calculating diff between dofs
!> initialize half bandwidth
hbw = 0
!> get number of elements
nel = fld_numElem()
!> loop through elements
!! (the goal is to find the maximum absolute difference between
!! non-zero degree of freedom numbers within a single element)
DO i = 1,nel
DO j = 1,NNODEL !> loop through nodes in current element
DO k = 1,NDIM !> loop through coordinate (dof) directions
!> get current dof
dof1 = fld_getDof(fld_getConnect(i,j),k)
!> if current dof=0, no need to compare
IF (dof1.EQ.0) CYCLE
!> get minimum loop indices for next dof
IF (k.LT.NDIM) THEN
lmin = j !> start from current node
mmin = k+1 !> start from next dof of current node
ELSE
lmin = j+1 !> start from next node
mmin = 1 !> start from first dof of next node
END IF
DO l = lmin,NNODEL
DO m = mmin,NDIM
!> get next dof
dof2 = fld_getDof(fld_getConnect(i,l),m)
!> if next dof is non-zero, update hbw
IF (dof2.NE.0) THEN
hbw = MAX(hbw, ABS(dof2-dof1))
END IF
END DO ! m = mmin,NDIM
END DO ! l = lmin,NNODEL
END DO ! k = 1,NDIM
END DO ! j = 1,NNODEL
END DO ! i = 1,nel
!> add one to include diagonal
hbw = hbw+1
END FUNCTION compute_hbw
! ------------------------------------------------------------------------
!> \brief Determine the mapping indices for a body element
!!
!! \param i Element number
!!
!! \return ind Mapping indices
!!
!! Note that this function assumes that the element index is valid. It
!! does not catch POSIT exceptions
! ------------------------------------------------------------------------
FUNCTION get_index (i) RESULT(ind)
INTEGER, INTENT(IN) :: i
INTEGER :: ind(NNODEL*NDIM)
INTEGER :: j,k !> loop variables
DO j = 1,NNODEL
DO k = 1,NDIM
ind( (j-1)*NDIM+k ) = fld_getDof(fld_getConnect(i,j),k)
END DO
END DO
END FUNCTION
! ------------------------------------------------------------------------
!> \brief Determine the mapping indices for a traction element
!!
!! \param i Element number
!!
!! \return ind Mapping indices
!!
!! Note that this function assumes that the element index is valid. It
!! does not catch POSIT exceptions
! ------------------------------------------------------------------------
FUNCTION get_index_trac (i) RESULT(ind)
INTEGER, INTENT(IN) :: i
INTEGER :: ind(NNODELB*NDIM)
INTEGER :: j,k !> loop variables
DO j = 1,NNODELB
DO k = 1,NDIM
ind( (j-1)*NDIM+k ) = fld_getDof(bnd_getConnect(i,j),k)
END DO
END DO
END FUNCTION
END MODULE pde_solver_control
! ------------------------------------------------------------------------
!> \brief Module for testing PDE Solver Control module
! ------------------------------------------------------------------------
MODULE pde_solver_control_test
USE fruit !> FRUIT unit testing framework for Fortran
USE system_constants !> global system constants
USE pde_solver_constants !> constants for PDE solver
USE log_message_control !> print log/error messages
USE log_messages !> log/error message and sender codes
USE band_sym_matrix_def !> banded symmetric matrix ADT
USE dense_matrix_def !> dense matrix ADT
USE vector_def !> vector ADT
USE field_data !> field data module
USE boundary_data !> boundary data module
USE material_data !> material property data module
USE pde_solver_control !> PDE solver contorl module
IMPLICIT NONE
CONTAINS
! ------------------------------------------------------------------------
!> \brief Initialization test for PDE Solver Control
!!
!! \param unit_name_size Name of unit test (for FRUIT)
!! \param unit_name_area Name of unit test (for FRUIT)
!! \param unit_name_mass Name of unit test (for FRUIT)
!! \param unit_name_stiff Name of unit test (for FRUIT)
!! \param unit_name_clean Name of unit test (for FRUIT)
!! \param testName Filename for log file (required for exceptions)
!! \param nnodExp Expected number of nodes (15)
!! \param nelExp Expected number of elements (16)
!! \param ndofExp Expected number of degrees of freedom (24)
!! \param hbwExp Expected half bandwidth (10)
!! \param ntnsExp Expected number of tensor variables (48)
!! \param nmtl Number of material types (1)
!! \param rho Density of material 1 (2200 kg/m^3)
!! \param emod Elastic modulus of material 1 (26000 MPa)
!! \param nu Poisson's ratio of material 1 (0.25)
!! \param expArea Expected total area (5.0 x 8.0 = 40.0)
!! \param totalArea Actual total area (from summing element areas)
!! \param expMass For checking mass matrix (see test_straight.xlsx)
!! \param expStiff For checking stiffness matrix (see test_straight.xlsx)
!! \param toler Tolerance for floating point error
!! \param expMsg Expected exception message
!! \param actMsg Actual exception message
!!
!! This routine tests tests correct allocation and initialization of
!! state variables for a simple system. The system is a straight column
!! with a fixed base. It has a width of 5 m and a height of 8 m. The
!! mesh of the system has the following properties:
!!
!! nnod = 15
!! nel = 16
!! ndof = 24
!! hbw = 10
!!
!! These parameters are verified after the initialization. The test also
!! verifies the size of all system matrices and vectors. The test also
!! deallocates the system and verifies that everything is set back to
!! zero post-deallocation.
! ------------------------------------------------------------------------
SUBROUTINE test_pde_solver_initialization
CHARACTER (LEN=*), PARAMETER :: unit_name_size = 'test_pde_solver_initialization_size'
CHARACTER (LEN=*), PARAMETER :: unit_name_area = 'test_pde_solver_initialization_area'
CHARACTER (LEN=*), PARAMETER :: unit_name_mass = 'test_pde_solver_initialization_mass'
CHARACTER (LEN=*), PARAMETER :: unit_name_stiff = 'test_pde_solver_initialization_stiff'
CHARACTER (LEN=*), PARAMETER :: unit_name_clean = 'test_pde_solver_initialization_clean'
CHARACTER (LEN=*), PARAMETER :: testName = 'test_straight_coarse'
INTEGER, PARAMETER :: nnodExp = 15
INTEGER, PARAMETER :: nelExp = 16
INTEGER, PARAMETER :: ndofExp = 24
INTEGER, PARAMETER :: hbwExp = 10
INTEGER, PARAMETER :: ntnsExp = nelExp*NTNS
INTEGER, PARAMETER :: nmtl = 1
DOUBLE PRECISION, PARAMETER :: rho = 2200.d0
DOUBLE PRECISION, PARAMETER :: emod = 26.d9
DOUBLE PRECISION, PARAMETER :: nu = 0.25d0
DOUBLE PRECISION, PARAMETER :: expArea = 40.d0
DOUBLE PRECISION :: totalArea
DOUBLE PRECISION, PARAMETER :: toler = 1.d-12
DOUBLE PRECISION :: expMass(hbwExp,ndofExp)
DOUBLE PRECISION :: expStiff(hbwExp,ndofExp)
INTEGER, PARAMETER :: expMsg=OK
INTEGER :: actMsg
INTEGER :: i,j !> loop variables
DOUBLE PRECISION :: ycoord !> for setting up coordinates
!> initialize log message file
CALL log_setFileName(testName)
CALL log_initLogFile()
!> initialize material data
CALL mtl_init(nmtl)
CALL mtl_setDens(1,rho)
CALL mtl_setEmod(1,emod)
CALL mtl_setPois(1,nu)
!> initialize node data
CALL fld_initNode(nnodExp)
!> x-coords of left column of nodes = 0
!> x-coords of middle column of nodes = 2.5
DO i = 2,nnodExp,3
CALL fld_setCoord(i,1,2.5d0)
END DO
!> x-coords of right column of nodes = 5
DO i = 3,nnodExp,3
CALL fld_setCoord(i,1,5.d0)
END DO
!> y-coords, steps of 2
DO i = 1,nnodExp,3
ycoord = ONE_THIRD*DBLE(i-1)*2.d0
CALL fld_setCoord(i,2,ycoord)
CALL fld_setCoord(i+1,2,ycoord)
CALL fld_setCoord(i+2,2,ycoord)
END DO
!> fix base
CALL fld_setFix(1,1,.TRUE.)
CALL fld_setFix(1,2,.TRUE.)
CALL fld_setFix(2,1,.TRUE.)
CALL fld_setFix(2,2,.TRUE.)
CALL fld_setFix(3,1,.TRUE.)
CALL fld_setFix(3,2,.TRUE.)
!> initialize system degrees of freedom
CALL fld_initDof()
!> initialize element data
CALL fld_initElem(nelExp)
!> element 1
CALL fld_setConnect(1,1,1)
CALL fld_setConnect(1,2,2)
CALL fld_setConnect(1,3,4)
!> element 2
CALL fld_setConnect(2,1,2)
CALL fld_setConnect(2,2,5)
CALL fld_setConnect(2,3,4)
!> element 3
CALL fld_setConnect(3,1,2)
CALL fld_setConnect(3,2,6)
CALL fld_setConnect(3,3,5)
!> element 4
CALL fld_setConnect(4,1,2)
CALL fld_setConnect(4,2,3)
CALL fld_setConnect(4,3,6)
!> element 5
CALL fld_setConnect(5,1,4)
CALL fld_setConnect(5,2,5)
CALL fld_setConnect(5,3,7)
!> element 6
CALL fld_setConnect(6,1,5)
CALL fld_setConnect(6,2,8)
CALL fld_setConnect(6,3,7)
!> element 7
CALL fld_setConnect(7,1,5)
CALL fld_setConnect(7,2,9)
CALL fld_setConnect(7,3,8)
!> element 8
CALL fld_setConnect(8,1,5)
CALL fld_setConnect(8,2,6)
CALL fld_setConnect(8,3,9)
!> element 9
CALL fld_setConnect(9,1,7)
CALL fld_setConnect(9,2,8)
CALL fld_setConnect(9,3,10)
!> element 10
CALL fld_setConnect(10,1,8)
CALL fld_setConnect(10,2,11)
CALL fld_setConnect(10,3,10)
!> element 11
CALL fld_setConnect(11,1,8)
CALL fld_setConnect(11,2,12)
CALL fld_setConnect(11,3,11)
!> element 12
CALL fld_setConnect(12,1,8)
CALL fld_setConnect(12,2,9)
CALL fld_setConnect(12,3,12)
!> element 13
CALL fld_setConnect(13,1,10)
CALL fld_setConnect(13,2,11)
CALL fld_setConnect(13,3,13)
!> element 14
CALL fld_setConnect(14,1,11)
CALL fld_setConnect(14,2,14)
CALL fld_setConnect(14,3,13)
!> element 15
CALL fld_setConnect(15,1,11)
CALL fld_setConnect(15,2,15)
CALL fld_setConnect(15,3,14)
!> element 16
CALL fld_setConnect(16,1,11)
CALL fld_setConnect(16,2,12)
CALL fld_setConnect(16,3,15)
!> set element materials
DO i = 1,nelExp
CALL fld_setMaterial(i,1)
END DO
!> initialize unit test
CALL set_unit_name(unit_name_size)
!> initialize pde solver
CALL pde_init(actMsg)
CALL assertEquals(expMsg,actMsg)
!> check system parameters
CALL assertEquals(nnodExp,nnod)
CALL assertEquals(nelExp,nel)
CALL assertEquals(ndofExp,ndof)
CALL assertEquals(hbwExp,hbw)
!> check state variables (matrices and vectors)
CALL assertEquals(hbwExp,bsm_halfBW(mass))
CALL assertEquals(ndofExp,bsm_numRows(mass))
CALL assertEquals(hbwExp,bsm_halfBW(stiff))
CALL assertEquals(ndofExp,bsm_numRows(stiff))
CALL assertEquals(ndofExp,vec_length(initStress))
CALL assertEquals(ndofExp,vec_length(initStrain))
CALL assertEquals(ndofExp,vec_length(body))
CALL assertEquals(ndofExp,vec_length(trac))
CALL assertEquals(ndofExp,vec_length(load))
CALL assertEquals(ndofExp,vec_length(prevDisp))
CALL assertEquals(ndofExp,vec_length(incDisp))
CALL assertEquals(ndofExp,vec_length(newDisp))
CALL assertEquals(ndofExp,vec_length(prevVel))
CALL assertEquals(ndofExp,vec_length(incVel))
CALL assertEquals(ndofExp,vec_length(newVel))
CALL assertEquals(ndofExp,vec_length(prevAcc))
CALL assertEquals(ndofExp,vec_length(newAcc))
CALL assertEquals(ntnsExp,vec_length(prevStress))
CALL assertEquals(ntnsExp,vec_length(incStress))
CALL assertEquals(ntnsExp,vec_length(newStress))
CALL assertEquals(ntnsExp,vec_length(prevStrain))
CALL assertEquals(ntnsExp,vec_length(incStrain))
CALL assertEquals(ntnsExp,vec_length(newStrain))
!> initialize unit test
CALL set_unit_name(unit_name_area)
!> check total area
totalArea = 0.d0
DO i = 1,nel
totalArea = totalArea + fld_volElem(i)
END DO
CALL assertEquals(expArea,totalArea,toler)
!> initialize unit test
CALL set_unit_name(unit_name_mass)
!> set up expected mass matrix data
expMass = RESHAPE( (/ &
0.d0, 0.d0, 0.d0, 0.d0, 0.d0, 0.d0, 0.d0, 0.d0, &
0.d0, 1833.33333333333333d0, 0.d0, 0.d0, 0.d0, &
0.d0, 0.d0, 0.d0, 0.d0, 0.d0, 0.d0, &
1833.33333333333333d0, 0.d0, 0.d0, 0.d0, 0.d0, &
0.d0, 0.d0, 0.d0, 1222.22222222222222d0, 0.d0, &
3666.66666666666667d0, 0.d0, 0.d0, 0.d0, 0.d0, &
0.d0, 0.d0, 0.d0, 1222.22222222222222d0, 0.d0, &
3666.66666666666667d0, 0.d0, 0.d0, 0.d0, 0.d0, &
0.d0, 0.d0, 0.d0, 1222.22222222222222d0, 0.d0, &
1833.33333333333333d0, 0.d0, 0.d0, 0.d0, 0.d0, &
0.d0, 0.d0, 0.d0, 1222.22222222222222d0, 0.d0, &
1833.33333333333333d0, 0.d0, 0.d0, 0.d0, &
611.111111111111111d0, 0.d0, &
1222.22222222222222d0, 0.d0, 0.d0, 0.d0, &
1833.33333333333333d0, 0.d0, 0.d0, 0.d0, &
611.111111111111111d0, 0.d0, &
1222.22222222222222d0, 0.d0, 0.d0, 0.d0, &
1833.33333333333333d0, 0.d0, 0.d0, 0.d0, &
1222.22222222222222d0, 0.d0, 0.d0, 0.d0, &
1222.22222222222222d0, 0.d0, &
3666.66666666666667d0, 0.d0, 0.d0, 0.d0, &
1222.22222222222222d0, 0.d0, 0.d0, 0.d0, &
1222.22222222222222d0, 0.d0, &
3666.66666666666667d0, 0.d0, &
1222.22222222222222d0, 0.d0, &
611.111111111111111d0, 0.d0, 0.d0, 0.d0, &
1222.22222222222222d0, 0.d0, &
1833.33333333333333d0, 0.d0, &
1222.22222222222222d0, 0.d0, &
611.111111111111111d0, 0.d0, 0.d0, 0.d0, &
1222.22222222222222d0, 0.d0, &
1833.33333333333333d0, 0.d0, 0.d0, 0.d0, &
611.111111111111111d0, 0.d0, &
1222.22222222222222d0, 0.d0, 0.d0, 0.d0, &
1833.33333333333333d0, 0.d0, 0.d0, 0.d0, &
611.111111111111111d0, 0.d0, &
1222.22222222222222d0, 0.d0, 0.d0, 0.d0, &
1833.33333333333333d0, 0.d0, 0.d0, 0.d0, &
1222.22222222222222d0, 0.d0, 0.d0, 0.d0, &
1222.22222222222222d0, 0.d0, &
3666.66666666666667d0, 0.d0, 0.d0, 0.d0, &
1222.22222222222222d0, 0.d0, 0.d0, 0.d0, &
1222.22222222222222d0, 0.d0, &
3666.66666666666667d0, 0.d0, &
1222.22222222222222d0, 0.d0, &
611.111111111111111d0, 0.d0, 0.d0, 0.d0, &
1222.22222222222222d0, 0.d0, &
1833.33333333333333d0, 0.d0, &
1222.22222222222222d0, 0.d0, &
611.111111111111111d0, 0.d0, 0.d0, 0.d0, &
1222.22222222222222d0, 0.d0, &
1833.33333333333333d0, 0.d0, 0.d0, 0.d0, &
611.111111111111111d0, 0.d0, &
1222.22222222222222d0, 0.d0, 0.d0, 0.d0, &
1222.22222222222222d0, 0.d0, 0.d0, 0.d0, &
611.111111111111111d0, 0.d0, &
1222.22222222222222d0, 0.d0, 0.d0, 0.d0, &
1222.22222222222222d0, 0.d0, 0.d0, 0.d0, &
1222.22222222222222d0, 0.d0, 0.d0, 0.d0, &
611.111111111111111d0, 0.d0, &
1222.22222222222222d0, 0.d0, 0.d0, 0.d0, &
1222.22222222222222d0, 0.d0, 0.d0, 0.d0, &
611.111111111111111d0, 0.d0, &
1222.22222222222222d0, 0.d0, &
1222.22222222222222d0, 0.d0, &
611.111111111111111d0, 0.d0, 0.d0, 0.d0, &
611.111111111111111d0, 0.d0, &
1222.22222222222222d0, 0.d0, &
1222.22222222222222d0, 0.d0, &
611.111111111111111d0, 0.d0, 0.d0, 0.d0, &
611.111111111111111d0, 0.d0, &
1222.22222222222222d0 &
/), SHAPE(expMass) )
!> set actual mass matrix
CALL pde_buildMassMatrix(actMsg)
CALL assertEquals(expMsg,actMsg)
!> check mass matrix
CALL assertEquals(expMass,mass%dat, hbwExp,ndofExp, toler)
!> initialize unit test
CALL set_unit_name(unit_name_stiff)
!> set up expected stiffness matrix data
expStiff = RESHAPE( (/ &
0.d0, 0.d0, 0.d0, 0.d0, 0.d0, 0.d0, 0.d0, 0.d0, &
0.d0, 37960000000.d0, 0.d0, 0.d0, 0.d0, 0.d0, &
0.d0, 0.d0, 0.d0, 0.d0, 10400000000.d0, &
47320000000.d0, 0.d0, 0.d0, 0.d0, 0.d0, 0.d0, &
0.d0, 0.d0, -24960000000.d0, -10400000000.d0, &
75920000000.d0, 0.d0, 0.d0, 0.d0, 0.d0, 0.d0, &
0.d0, -10400000000.d0, -8320000000.d0, 0.d0, &
94640000000.d0, 0.d0, 0.d0, 0.d0, 0.d0, 0.d0, &
0.d0, 0.d0, -24960000000.d0, 10400000000.d0, &
37960000000.d0, 0.d0, 0.d0, 0.d0, 0.d0, 0.d0, &
0.d0, 10400000000.d0, -8320000000.d0, &
-10400000000.d0, 47320000000.d0, 0.d0, 0.d0, &
0.d0, -6500000000.d0, -5200000000.d0, 0.d0, &
10400000000.d0, 0.d0, 0.d0, 37960000000.d0, &
0.d0, 0.d0, -5200000000.d0, -19500000000.d0, &
10400000000.d0, 0.d0, 0.d0, 0.d0, 10400000000.d0, &
47320000000.d0, 0.d0, 0.d0, 0.d0, -13000000000.d0, &
0.d0, 0.d0, 0.d0, -24960000000.d0, &
-10400000000.d0, 75920000000.d0, 0.d0, 0.d0, 0.d0, &
-39000000000.d0, 0.d0, 0.d0, -10400000000.d0, &
-8320000000.d0, 0.d0, 94640000000.d0, 0.d0, 0.d0, &
-10400000000.d0, -6500000000.d0, 5200000000.d0, &
0.d0, 0.d0, -24960000000.d0, 10400000000.d0, &
37960000000.d0, -10400000000.d0, 0.d0, &
5200000000.d0, -19500000000.d0, 0.d0, 0.d0, &
10400000000.d0, -8320000000.d0, -10400000000.d0, &
47320000000.d0, 0.d0, 0.d0, 0.d0, -6500000000.d0, &
-5200000000.d0, 0.d0, 10400000000.d0, 0.d0, 0.d0, &
37960000000.d0, 0.d0, 0.d0, -5200000000.d0, &
-19500000000.d0, 10400000000.d0, 0.d0, 0.d0, 0.d0, &
10400000000.d0, 47320000000.d0, 0.d0, 0.d0, 0.d0, &
-13000000000.d0, 0.d0, 0.d0, 0.d0, &
-24960000000.d0, -10400000000.d0, 75920000000.d0, &
0.d0, 0.d0, 0.d0, -39000000000.d0, 0.d0, 0.d0, &
-10400000000.d0, -8320000000.d0, 0.d0, &
94640000000.d0, 0.d0, 0.d0, -10400000000.d0, &
-6500000000.d0, 5200000000.d0, 0.d0, 0.d0, &
-24960000000.d0, 10400000000.d0, 37960000000.d0, &
-10400000000.d0, 0.d0, 5200000000.d0, &
-19500000000.d0, 0.d0, 0.d0, 10400000000.d0, &
-8320000000.d0, -10400000000.d0, 47320000000.d0, &
0.d0, 0.d0, 0.d0, -6500000000.d0, -5200000000.d0, &
0.d0, 10400000000.d0, 0.d0, 0.d0, 18980000000.d0, &
0.d0, 0.d0, -5200000000.d0, -19500000000.d0, &
10400000000.d0, 0.d0, 0.d0, 0.d0, 0.d0, &
23660000000.d0, 0.d0, 0.d0, 0.d0, -13000000000.d0, &
0.d0, 0.d0, 0.d0, -12480000000.d0, -5200000000.d0, &
37960000000.d0, 0.d0, 0.d0, 0.d0, -39000000000.d0, &
0.d0, 0.d0, -5200000000.d0, -4160000000.d0, 0.d0, &
47320000000.d0, 0.d0, 0.d0, -10400000000.d0, &
-6500000000.d0, 5200000000.d0, 0.d0, 0.d0, &
-12480000000.d0, 5200000000.d0, 18980000000.d0, &
-10400000000.d0, 0.d0, 5200000000.d0, &
-19500000000.d0, 0.d0, 0.d0, 5200000000.d0, &
-4160000000.d0, 0.d0, 23660000000.d0 &
/), SHAPE(expStiff) )
!> set actual stiffness matrix
CALL pde_buildStiffMatrix(actMsg)
CALL assertEquals(expMsg,actMsg)
!> check stiffness matrix
CALL assertEquals(expStiff,stiff%dat, hbwExp,ndofExp, toler)
!> initialize unit test
CALL set_unit_name(unit_name_clean)
!> finalize pde solver
CALL pde_clean()
!> check system parameters
CALL assertEquals(0,nnod)
CALL assertEquals(0,nel)
CALL assertEquals(0,ndof)
CALL assertEquals(0,hbw)
!> check state variables (matrices and vectors)
CALL assertEquals(0,bsm_halfBW(mass))
CALL assertEquals(0,bsm_numRows(mass))
CALL assertEquals(0,bsm_halfBW(stiff))
CALL assertEquals(0,bsm_numRows(stiff))
CALL assertEquals(0,vec_length(initStress))
CALL assertEquals(0,vec_length(initStrain))
CALL assertEquals(0,vec_length(body))
CALL assertEquals(0,vec_length(trac))
CALL assertEquals(0,vec_length(load))
CALL assertEquals(0,vec_length(prevDisp))
CALL assertEquals(0,vec_length(incDisp))
CALL assertEquals(0,vec_length(newDisp))
CALL assertEquals(0,vec_length(prevVel))
CALL assertEquals(0,vec_length(incVel))
CALL assertEquals(0,vec_length(newVel))
CALL assertEquals(0,vec_length(prevAcc))
CALL assertEquals(0,vec_length(newAcc))
CALL assertEquals(0,vec_length(prevStress))
CALL assertEquals(0,vec_length(incStress))
CALL assertEquals(0,vec_length(newStress))
CALL assertEquals(0,vec_length(prevStrain))
CALL assertEquals(0,vec_length(incStrain))
CALL assertEquals(0,vec_length(newStrain))
!> finalize log file and deallocate objects
CALL log_closeLogFile()
CALL fld_cleanNode()
CALL fld_cleanElem()
END SUBROUTINE test_pde_solver_initialization
END MODULE pde_solver_control_test
! ------------------------------------------------------------------------
!> \brief Module defining System Constants
! ------------------------------------------------------------------------
MODULE system_constants
IMPLICIT NONE
INTEGER, PARAMETER :: MAXLEN = 200 !> maximum string length
DOUBLE PRECISION, PARAMETER :: ONE_THIRD = 0.33333333333333333d0 !> avoid computing 1/3
INTEGER, PARAMETER :: NDIM = 2 !> number of coordinate dims
INTEGER, PARAMETER :: NTNS = 3 !> number of tensor components
INTEGER, PARAMETER :: NNODEL = 3 !> number of nodes per body element
INTEGER, PARAMETER :: NNODELB = 2 !> number of nodes per traction element
INTEGER, PARAMETER :: MAX_NODES = 2000 !> maximum number of nodes
INTEGER, PARAMETER :: MAX_DOFS = 3990 !> maximum number of degrees of freedom
INTEGER, PARAMETER :: MAX_ELEMENTS = 5000 !> maximum number of elements
INTEGER, PARAMETER :: MAX_BOUNDELS = 2000 !> maximum number of traction elements
INTEGER, PARAMETER :: MAX_MATERIALS = 30 !> maximum number of materials
INTEGER, PARAMETER :: MAX_TIMESTEPS = 10000 !> maximum number of time steps
DOUBLE PRECISION, PARAMETER :: E_MIN = 0.d0 !> minimum value of elastic modulus
DOUBLE PRECISION, PARAMETER :: E_MAX = 1.d11 !> maximum value of elastic modulus
DOUBLE PRECISION, PARAMETER :: NU_MIN = 0.d0 !> minimum value of Poisson's ratio
DOUBLE PRECISION, PARAMETER :: NU_MAX = 0.499d0 !> maximum value of Poisson's ratio
DOUBLE PRECISION, PARAMETER :: RHO_MIN = 0.d0 !> minimum value of density
DOUBLE PRECISION, PARAMETER :: RHO_MAX = 1.d11 !> maximum value of density
DOUBLE PRECISION, PARAMETER :: COORD_MIN = -1.d11 !> minimum value of coordinates
DOUBLE PRECISION, PARAMETER :: COORD_MAX = 1.d11 !> maximum value of coordinates
DOUBLE PRECISION, PARAMETER :: DISP_MIN = -1.d11 !> minimum value of displacement
DOUBLE PRECISION, PARAMETER :: DISP_MAX = 1.d11 !> maximum value of displacement
DOUBLE PRECISION, PARAMETER :: VEL_MIN = -1.d11 !> minimum value of velocity
DOUBLE PRECISION, PARAMETER :: VEL_MAX = 1.d11 !> maximum value of velocity
DOUBLE PRECISION, PARAMETER :: ACC_MIN = -1.d11 !> minimum value of acceleration
DOUBLE PRECISION, PARAMETER :: ACC_MAX = 1.d11 !> maximum value of acceleration
DOUBLE PRECISION, PARAMETER :: SIG_MIN = -1.d11 !> minimum value of stress
DOUBLE PRECISION, PARAMETER :: SIG_MAX = 1.d11 !> maximum value of stress
DOUBLE PRECISION, PARAMETER :: STR_SMALL = 1.d-2 !> threshold for small strains
DOUBLE PRECISION, PARAMETER :: STR_MIN = -STR_SMALL !> minimum value of strain
DOUBLE PRECISION, PARAMETER :: STR_MAX = STR_SMALL !> maximum value of strain
DOUBLE PRECISION, PARAMETER :: DTIME_MIN = 1.d-11 !> minimum value of time step
DOUBLE PRECISION, PARAMETER :: DTIME_MAX = 1.d4 !> maximum value of time step
END MODULE system_constants
PROGRAM test_driver
USE fruit
USE log_messages_test
USE log_message_control_test
USE dense_matrix_test
USE vector_test
USE band_sym_matrix_test
USE linear_solver_test
USE material_data_test
USE field_data_test
USE boundary_data_test
USE constitutive_test
USE pde_solver_control_test
CALL init_fruit
! log_messages message code tests
CALL test_ALLOC_message_code
CALL test_DIMEN_message_code
CALL test_EXCEED_message_code
CALL test_EXISTS_message_code
CALL test_FORMT_message_code
CALL test_POSDEF_message_code
CALL test_POSIT_message_code
CALL test_SZE_message_code
CALL test_TYP_message_code
CALL test_unexpected_message_code
! log_messages sender code tests
CALL test_BFCRDR_sender_code
CALL test_BNDDAT_sender_code
CALL test_BNDRDR_sender_code
CALL test_BSYMAT_sender_code
CALL test_CNSMAT_sender_code
CALL test_DMNRDR_sender_code
CALL test_DNSMAT_sender_code
CALL test_FLDDAT_sender_code
CALL test_ICTRDR_sender_code
CALL test_ICVRDR_sender_code
CALL test_KBCRDR_sender_code
CALL test_LINSLV_sender_code
CALL test_MTLDAT_sender_code
CALL test_MTLRDR_sender_code
CALL test_NBCRDR_sender_code
CALL test_TNSWTR_sender_code
CALL test_VECTOR_sender_code
CALL test_VECWTR_sender_code
CALL test_unexpected_sender_code
! log_message_control tests
CALL test_log_setFileName
CALL test_log_initLogFile
CALL test_log_closeLogFile
CALL test_log_printLogMsg
! dense_matrix_def tests
CALL test_dm_allocation_MSG
CALL test_dm_allocation_SZE
CALL test_dm_allocation_DAT
CALL test_dm_deallocation
CALL test_dm_num_rows_not_allocated
CALL test_dm_num_rows_allocated
CALL test_dm_num_cols_not_allocated
CALL test_dm_num_cols_allocated
CALL test_dm_get_POSIT
CALL test_dm_get_VAL
CALL test_dm_set_POSIT
CALL test_dm_set_VAL
CALL test_dm_add_DIMEN
CALL test_dm_add_VAL
CALL test_dm_add_OP
CALL test_dm_scal_mul_VAL
CALL test_dm_scal_mul_ZERO
CALL test_dm_scal_mul_OP
CALL test_dm_vec_mul_DIMEN
CALL test_dm_vec_mul_VAL
CALL test_dm_vec_mul_ZERO
CALL test_dm_vec_mul_IDENT
CALL test_dm_vec_mul_OP
CALL test_dm_mat_mul_DIMEN
CALL test_dm_mat_mul_VAL
CALL test_dm_mat_mul_ZERO
CALL test_dm_mat_mul_IDENT
CALL test_dm_mat_mul_OP
CALL test_dm_transpose
! vector_def tests
CALL test_vec_allocation_MSG
CALL test_vec_allocation_SZE
CALL test_vec_allocation_DAT
CALL test_vec_deallocation
CALL test_vec_length_not_allocated
CALL test_vec_length_allocated
CALL test_vec_get_POSIT
CALL test_vec_get_VAL
CALL test_vec_set_POSIT
CALL test_vec_set_VAL
CALL test_vec_add_DIMEN
CALL test_vec_add_VAL
CALL test_vec_add_OP
CALL test_vec_mapped_add_DIMEN
CALL test_vec_mapped_add_POSIT
CALL test_vec_mapped_add_VAL1
CALL test_vec_mapped_add_VAL2
CALL test_vec_mapped_add_VAL3
CALL test_vec_scal_mul_VAL
CALL test_vec_scal_mul_ZERO
CALL test_vec_scal_mul_OP
CALL test_vec_dot_prod_DIMEN
CALL test_vec_dot_prod_ZERO
CALL test_vec_dot_prod_VAL
! band_sym_matrix_def tests
CALL test_bsm_allocation_MSG
CALL test_bsm_allocation_SZE
CALL test_bsm_allocation_DAT
CALL test_bsm_deallocation
CALL test_bsm_num_rows_not_allocated
CALL test_bsm_num_rows_allocated
CALL test_bsm_half_bw_not_allocated
CALL test_bsm_half_bw_allocated
CALL test_bsm_get_POSIT
CALL test_bsm_get_VAL
CALL test_bsm_set_POSIT
CALL test_bsm_set_VAL
CALL test_bsm_set_decomp_DIMEN
CALL test_bsm_set_decomp_VAL
CALL test_bsm_is_decomposed
CALL test_bsm_add_DIMEN
CALL test_bsm_add_VAL
CALL test_bsm_add_OP
CALL test_bsm_mapped_add_DIMEN1
CALL test_bsm_mapped_add_DIMEN2
CALL test_bsm_mapped_add_DIMEN3
CALL test_bsm_mapped_add_POSIT1
CALL test_bsm_mapped_add_POSIT2
CALL test_bsm_mapped_add_VAL1
CALL test_bsm_mapped_add_VAL2
CALL test_bsm_mapped_add_VAL3
CALL test_bsm_scal_mul_VAL
CALL test_bsm_scal_mul_ZERO
CALL test_bsm_scal_mul_OP
CALL test_bsm_vec_mul_DIMEN
CALL test_bsm_vec_mul_VAL
CALL test_bsm_vec_mul_ZERO
CALL test_bsm_vec_mul_IDENT
CALL test_bsm_vec_mul_OP
! linear_solver tests
CALL test_linear_solver_DIMEN
CALL test_linear_solver_POSDEF
CALL test_linear_solver_VAL
CALL test_linear_solver_IDENT
CALL test_linear_solver_ZERO
CALL test_linear_solver_DECOMP
! material property data tests
CALL test_mtl_allocation_MSG
CALL test_mtl_allocation_SZE
CALL test_mtl_num_mtl_not_allocated
CALL test_mtl_num_mtl_allocated
CALL test_mtl_get_emod_POSIT
CALL test_mtl_set_emod_POSIT
CALL test_mtl_set_emod_EXCEED
CALL test_mtl_get_set_emod_VAL
CALL test_mtl_get_pois_POSIT
CALL test_mtl_set_pois_POSIT
CALL test_mtl_set_pois_EXCEED
CALL test_mtl_get_set_pois_VAL
CALL test_mtl_get_dens_POSIT
CALL test_mtl_set_dens_POSIT
CALL test_mtl_set_dens_EXCEED
CALL test_mtl_get_set_dens_VAL
! field data tests
CALL test_fld_init_time_EXCEED
CALL test_fld_time_step_not_initialized
CALL test_fld_time_step_initialized
CALL test_fld_num_time_step_not_initialized
CALL test_fld_num_time_step_initialized
CALL test_fld_node_allocation_MSG
CALL test_fld_node_allocation_SZE
CALL test_fld_num_node_not_allocated
CALL test_fld_num_node_allocated
CALL test_fld_get_coord_POSIT
CALL test_fld_set_coord_POSIT
CALL test_fld_set_coord_EXCEED
CALL test_fld_get_set_coord_VAL
CALL test_fld_get_fix_POSIT
CALL test_fld_set_fix_POSIT
CALL test_fld_get_set_fix_VAL
CALL test_fld_dof_initialization_SZE
CALL test_fld_num_dof_not_initialized
CALL test_fld_num_dof_initialized
CALL test_fld_get_dof_POSIT
CALL test_fld_get_dof_VAL
CALL test_fld_get_disp_POSIT
CALL test_fld_set_disp_POSIT
CALL test_fld_set_disp_EXCEED
CALL test_fld_get_set_disp_VAL
CALL test_fld_get_vel_POSIT
CALL test_fld_set_vel_POSIT
CALL test_fld_set_vel_EXCEED
CALL test_fld_get_set_vel_VAL
CALL test_fld_get_acc_POSIT
CALL test_fld_set_acc_POSIT
CALL test_fld_set_acc_EXCEED
CALL test_fld_get_set_acc_VAL
CALL test_fld_get_body_acc_POSIT
CALL test_fld_set_body_acc_POSIT
CALL test_fld_set_body_acc_EXCEED
CALL test_fld_get_set_body_acc_VAL
CALL test_fld_get_stress_node_POSIT
CALL test_fld_set_stress_node_POSIT
CALL test_fld_set_stress_node_EXCEED
CALL test_fld_get_set_stress_node_VAL
CALL test_fld_get_strain_node_POSIT
CALL test_fld_set_strain_node_POSIT
CALL test_fld_set_strain_node_EXCEED
CALL test_fld_get_set_strain_node_VAL
CALL test_fld_elem_allocation_MSG
CALL test_fld_elem_allocation_SZE
CALL test_fld_num_elem_not_allocated
CALL test_fld_num_elem_allocated
CALL test_fld_get_connect_POSIT
CALL test_fld_set_connect_POSIT
CALL test_fld_set_connect_EXCEED
CALL test_fld_get_set_connect_VAL
CALL test_fld_vol_elem_POSIT
CALL test_fld_vol_elem_ZERO
CALL test_fld_vol_elem_VAL
CALL test_fld_get_stress_elem_POSIT
CALL test_fld_set_stress_elem_POSIT
CALL test_fld_set_stress_elem_EXCEED
CALL test_fld_get_set_stress_elem_VAL
CALL test_fld_get_strain_elem_POSIT
CALL test_fld_set_strain_elem_POSIT
CALL test_fld_set_strain_elem_EXCEED
CALL test_fld_get_set_strain_elem_VAL
! boundary data tests
CALL test_bnd_elem_allocation_MSG
CALL test_bnd_elem_allocation_SZE
CALL test_bnd_num_elem_not_allocated
CALL test_bnd_num_elem_allocated
CALL test_bnd_get_connect_POSIT
CALL test_bnd_set_connect_POSIT
CALL test_bnd_set_connect_EXCEED
CALL test_bnd_get_set_connect_VAL
CALL test_bnd_len_bound_elem_POSIT
CALL test_bnd_len_bound_elem_ZERO
CALL test_bnd_len_bound_elem_VAL
CALL test_bnd_get_trac_POSIT
CALL test_bnd_set_trac_POSIT
CALL test_bnd_set_trac_EXCEED
CALL test_bnd_get_set_trac_VAL
! constitutive matrix tests
CALL test_constitutive_EXCEED
CALL test_constitutive_ZERO
CALL test_constitutive_VAL
! pde solver tests
CALL test_pde_solver_initialization
CALL fruit_summary
END PROGRAM test_driver
16
1 2 4
2 5 4
2 6 5
2 3 6
4 5 7
5 8 7
5 9 8
5 6 9
7 8 10
8 11 10
8 12 11
8 9 12
10 11 13
11 14 13
11 15 14
11 12 15
15
0.d0 0.d0 1 1
2.5d0 0.d0 1 1
5.d0 0.d0 1 1
0.d0 2.d0 0 0
2.5d0 2.d0 0 0
5.d0 2.d0 0 0
0.d0 4.d0 0 0
2.5d0 4.d0 0 0
5.d0 4.d0 0 0
0.d0 6.d0 0 0
2.5d0 6.d0 0 0
5.d0 6.d0 0 0
0.d0 8.d0 0 0
2.5d0 8.d0 0 0
5.d0 8.d0 0 0
! ------------------------------------------------------------------------
!> \brief Module defining Vector data type
! ------------------------------------------------------------------------
MODULE vector_def
USE log_message_control !> Print log/error messages
USE log_messages !> Log/error codes
IMPLICIT NONE
PRIVATE
! ************************************************************************
! EXPORTS
! ************************************************************************
!> Exported data types
PUBLIC :: vectorT
!> Exported interfaces
PUBLIC :: vec_init, vec_clean, &
vec_length, &
vec_get, vec_set, &
vec_add, OPERATOR (+), vec_mappedAdd, &
vec_scalMul, OPERATOR (*), vec_dotProd
! ************************************************************************
! LOCAL CONSTANTS
! ************************************************************************
!> Sender code for VECTOR module
INTEGER, PARAMETER :: sdr = VECTOR
! ************************************************************************
! DATA TYPES
! ************************************************************************
! ------------------------------------------------------------------------
!> \brief Vector ADT structure
!!
!! \param dat Array to store vector data
! ------------------------------------------------------------------------
TYPE vectorT
DOUBLE PRECISION, ALLOCATABLE :: dat(:)
END TYPE vectorT
! ************************************************************************
! INTERFACES
! ************************************************************************
!> \brief Interface to constructor
INTERFACE vec_init
MODULE PROCEDURE vec_init_
MODULE PROCEDURE vec_init_exc_
END INTERFACE vec_init
!> \brief Interface to destructor
INTERFACE vec_clean
MODULE PROCEDURE vec_clean_
END INTERFACE vec_clean
!> \brief Interface to length of vector
INTERFACE vec_length
MODULE PROCEDURE vec_length_
END INTERFACE vec_length
!> \brief Interface to getter for individual entries in vector
INTERFACE vec_get
MODULE PROCEDURE vec_get_
MODULE PROCEDURE vec_get_exc_
END INTERFACE vec_get
!> \brief Interface to setter for individual entries in vector
INTERFACE vec_set
MODULE PROCEDURE vec_set_
MODULE PROCEDURE vec_set_exc_
END INTERFACE vec_set
!> \brief Interface for addition of two vectorT
INTERFACE vec_add
MODULE PROCEDURE vec_add_
MODULE PROCEDURE vec_add_exc_
END INTERFACE vec_add
!> \brief Operator overload for addition
INTERFACE OPERATOR (+)
MODULE PROCEDURE vec_add_
END INTERFACE
!> \brief Interface for adding a vectorT to a vectorT in place with mapping indices
INTERFACE vec_mappedAdd
MODULE PROCEDURE vec_mapped_add_
MODULE PROCEDURE vec_mapped_add_exc_
END INTERFACE vec_mappedAdd
!> \brief Interface for scalar multiplication
INTERFACE vec_scalMul
MODULE PROCEDURE vec_scal_mul_vec_scal_
END INTERFACE vec_scalMul
!> \brief Operator overload for multiplication
INTERFACE OPERATOR (*)
MODULE PROCEDURE vec_scal_mul_vec_scal_
MODULE PROCEDURE vec_scal_mul_scal_vec_
END INTERFACE
!> \brief Interface to dot product of two vectorT
INTERFACE vec_dotProd
MODULE PROCEDURE vec_dot_prod_
MODULE PROCEDURE vec_dot_prod_exc_
END INTERFACE vec_dotProd
CONTAINS
! ************************************************************************
! ACCESS PROGRAMS
! ************************************************************************
! ------------------------------------------------------------------------
!> \brief Constructor for vectorT (non-exception checking)
!!
!! \param self Reference to the vector to be initialized
!! \param n Number of entries in the vector
!!
!! This routine initializes the vectorT object referenced by self.
!! The data structures contained in self are allocated and initial values
!! are set to zero.
! ------------------------------------------------------------------------
SUBROUTINE vec_init_ (self, n)
TYPE(vectorT), INTENT(INOUT) :: self
INTEGER, INTENT(IN) :: n
INTEGER :: i !> loop variable
!> only reallocate if new dimensions do not match existing dimensions
IF (vec_length(self).NE.n) THEN
!> reset object if it was previously initialized
CALL vec_clean(self)
!> allocate new data structure
ALLOCATE(self%dat(n))
END IF
!> ensure data is initialized to zero
DO i = 1,n
self%dat(i) = 0.d0
END DO
END SUBROUTINE vec_init_
! ------------------------------------------------------------------------
!> \brief Constructor for vectorT (exception checking)
!!
!! \param self Reference to the vector to be initialized
!! \param n Number of entries in the vector
!! \param exc Error code
!!
!! This routine initializes the vectorT object referenced by self.
!! The data structures contained in self are allocated and initial values
!! are set to zero. If the specified dimension is invalid, a SZE
!! exception is returned. If allocation of data structures fails, an
!! ALLOC exception is returned.
! ------------------------------------------------------------------------
SUBROUTINE vec_init_exc_ (self, n, exc)
TYPE(vectorT), INTENT(INOUT) :: self
INTEGER, INTENT(IN) :: n
INTEGER, INTENT(OUT) :: exc
INTEGER :: e !> allocation info code
INTEGER :: i !> loop variable
!> if dimension is invalid, raise SZE exception
IF (n.LE.0) THEN
exc=SZE
CALL log_printLogMsg(exc,sdr)
RETURN
ELSE
exc=OK
END IF
!> only reallocate if new dimensions do not match existing dimensions
IF (vec_length(self).NE.n) THEN
!> reset object if it was previously initialized
CALL vec_clean(self)
!> allocate new data structure for vector storage
ALLOCATE(self%dat(n), STAT=e)
!> if error code is returned, raise ALLOC exception
IF (e.NE.0) THEN
exc=ALLOC
CALL log_printLogMsg(exc,sdr)
RETURN
ELSE
exc=OK
END IF
END IF
!> ensure data is initialized to zero
DO i = 1,n
self%dat(i) = 0.d0
END DO
END SUBROUTINE vec_init_exc_
! ------------------------------------------------------------------------
!> \brief Destructor for vectorT
!!
!! \param self Reference to the vector to be destroyed
!!
!! This routine deallocates existing data structures.
! ------------------------------------------------------------------------
SUBROUTINE vec_clean_ (self)
TYPE(vectorT), INTENT(INOUT) :: self
IF (ALLOCATED(self%dat)) DEALLOCATE(self%dat)
END SUBROUTINE vec_clean_
! ------------------------------------------------------------------------
!> \brief Getter for length of vector
!!
!! \param self Reference to the vector object
!! \return n Number of entries in the vector
!!
!! This routine determines the number of entries allocated to the vector
!! object. If the vector is not initialized it returns 0.
! ------------------------------------------------------------------------
FUNCTION vec_length_ (self) RESULT(n)
TYPE(vectorT), INTENT(IN) :: self
INTEGER :: n
!> if data is initialized, return number of entries
IF (ALLOCATED(self%dat)) THEN
n = SIZE(self%dat)
ELSE
n = 0 !> if not initialized, there are no entries
END IF
END FUNCTION vec_length_
! ------------------------------------------------------------------------
!> \brief Getter for vector entries (non-exception checking)
!!
!! \param self Reference to the vector object
!! \param i Location index
!! \return v Value at location (i) of the vector
!!
!! This routine determines the value at a particular location in the
!! vector.
! ------------------------------------------------------------------------
FUNCTION vec_get_ (self, i) RESULT(v)
TYPE(vectorT), INTENT(IN) :: self
INTEGER, INTENT(IN) :: i
DOUBLE PRECISION :: v
v = self%dat(i)
END FUNCTION vec_get_
! ------------------------------------------------------------------------
!> \brief Getter for vector entries (exception checking)
!!
!! \param self Reference to the vector object
!! \param i Location index
!! \param exc Error code
!! \return v Value at location (i) of the vector
!!
!! This routine determines the value at a particular location in the
!! vector. If the location is not inside the vector, it returns a POSIT
!! exception.
! ------------------------------------------------------------------------
FUNCTION vec_get_exc_ (self, i, exc) RESULT(v)
TYPE(vectorT), INTENT(IN) :: self
INTEGER, INTENT(IN) :: i
INTEGER, INTENT(OUT) :: exc
DOUBLE PRECISION :: v
!> make sure desired index are is the vector
IF (i.GT.vec_length(self) .OR. i.LE.0) THEN
exc=POSIT
CALL log_printLogMsg(exc,sdr)
v = 0.d0
RETURN
ELSE
exc=OK
END IF
!> call non-exception getter
v = vec_get(self, i)
END FUNCTION vec_get_exc_
! ------------------------------------------------------------------------
!> \brief Setter for vector entries (non-exception checking)
!!
!! \param self Reference to the vector object
!! \param i Location index
!! \param v Value to be stored at location (i) of the vector
!!
!! This routine sets the value at a particular location in the vector.
! ------------------------------------------------------------------------
SUBROUTINE vec_set_ (self, i,v)
TYPE(vectorT), INTENT(INOUT) :: self
INTEGER, INTENT(IN) :: i
DOUBLE PRECISION, INTENT(IN) :: v
self%dat(i) = v
END SUBROUTINE vec_set_
! ------------------------------------------------------------------------
!> \brief Setter for vector entries (exception checking)
!!
!! \param self Reference to the vector object
!! \param i Location index
!! \param exc Error code
!! \return v Value to be stored at location (i) of the vector
!!
!! This routine sets the value at a particular location in the vector. If
!! the location is not inside the vector, it returns a POSIT exception.
! ------------------------------------------------------------------------
SUBROUTINE vec_set_exc_ (self, i,v, exc)
TYPE(vectorT), INTENT(INOUT) :: self
INTEGER, INTENT(IN) :: i
DOUBLE PRECISION, INTENT(IN) :: v
INTEGER, INTENT(OUT) :: exc
!> make sure desired index is inside the vector
IF (i.GT.vec_length(self) .OR. i.LE.0) THEN
exc=POSIT
CALL log_printLogMsg(exc,sdr)
RETURN
ELSE
exc=OK
END IF
!> call non-exception setter
CALL vec_set(self, i,v)
END SUBROUTINE vec_set_exc_
! ------------------------------------------------------------------------
!> \brief Add two vector objects (non-exception checking)
!!
!! \param self Reference to the first (left-hand) vector object
!! \param other Reference to the second (right-hand) vector object
!! \return new Reference to the resulting vector object
!!
!! This routine adds two vector objects.
! ------------------------------------------------------------------------
FUNCTION vec_add_ (self,other) RESULT(new)
TYPE(vectorT), INTENT(IN) :: self,other
TYPE(vectorT) :: new
!> initialize solution vector
CALL vec_init(new, vec_length(self))
!> Add the vectors (using array ops for efficiency)
new%dat = self%dat + other%dat
END FUNCTION vec_add_
! ------------------------------------------------------------------------
!> \brief Add two vector objects (exception checking)
!!
!! \param self Reference to the first (left-hand) vector object
!! \param other Reference to the second (right-hand) vector object
!! \param exc Error code
!! \return new Reference to the resulting vector object
!!
!! This routine adds two vector objects. If the dimensions of the
!! two input vectors do not match, it returns a DIMEN exception.
! ------------------------------------------------------------------------
FUNCTION vec_add_exc_ (self,other, exc) RESULT(new)
TYPE(vectorT), INTENT(IN) :: self,other
INTEGER, INTENT(OUT) :: exc
TYPE(vectorT) :: new
!> make sure that the two vectors have the same number of entries
IF(vec_length(self).NE.vec_length(other)) THEN
exc=DIMEN
CALL log_printLogMsg(exc,sdr)
RETURN
ELSE
exc=OK
END IF
!> call non-exception version
new = vec_add(self,other)
END FUNCTION vec_add_exc_
! ------------------------------------------------------------------------
!> \brief Add a vectorT to a vectorT in place with mapping (non-exception checking)
!!
!! \param self Reference to the target vector object
!! \param other Reference to the input vector object
!! \param ind Integer mapping indices
!!
!! This routine adds a vector to another vector in place according to an
!! indexed mapping. That is, the element at (i) in other is added to the
!! element at (ind(i)) of self.
! ------------------------------------------------------------------------
SUBROUTINE vec_mapped_add_ (self, other,ind)
TYPE(vectorT), INTENT(INOUT) :: self
TYPE(vectorT), INTENT(IN) :: other
INTEGER, INTENT(IN) :: ind(:)
INTEGER :: i !> loop variable
!> Add vector entries corresponding to mapping indices
DO i = 1,SIZE(ind)
IF (ind(i).EQ.0) CYCLE
CALL vec_set(self, ind(i), vec_get(self,ind(i)) + vec_get(other,i))
END DO
END SUBROUTINE vec_mapped_add_
! ------------------------------------------------------------------------
!> \brief Add a vectorT to a vectorT in place with mapping (exception checking)
!!
!! \param self Reference to the target vector object
!! \param other Reference to the input vector object
!! \param ind Integer mapping indices
!! \param exc Error code
!!
!! This routine adds a vector to another vector in place according to an
!! indexed mapping. That is, the element at (i) in other is added to the
!! element at (ind(i)) of self. If the number of mapping indices does not
!! match the size of other, it returns a DIMEN exception. If any of the
!! indices indicate a location outside the vector, it returns a POSIT
!! exception. Note that a zero index is valid and ind(i)=0 indicates that
!! the value at (i) in the vector object will not be added to self.
! ------------------------------------------------------------------------
SUBROUTINE vec_mapped_add_exc_ (self, other,ind, exc)
TYPE(vectorT), INTENT(INOUT) :: self
TYPE(vectorT), INTENT(IN) :: other
INTEGER, INTENT(IN) :: ind(:)
INTEGER, INTENT(OUT) :: exc
!> ensure that the number of indices matches the size of other
IF (vec_length(other).NE.SIZE(ind)) THEN
exc=DIMEN
CALL log_printLogMsg(exc,sdr)
RETURN
!> ensure that there are no mapping indices outside of self
ELSEIF ( MAXVAL(ind).GT.vec_length(self) .OR. MINVAL(ind).LT.0 ) THEN
exc=POSIT
CALL log_printLogMsg(exc,sdr)
RETURN
ELSE
exc=OK
END IF
!> call non-exception version
CALL vec_mappedAdd(self,other,ind)
END SUBROUTINE vec_mapped_add_exc_
! ------------------------------------------------------------------------
!> \brief Scalar multiplication (self*k version)
!!
!! \param self Reference to the input vector object
!! \param k Scalar multiplication factor
!! \return new Reference to the resulting vector object
!!
!! This routine multiplies a vector by a scalar factor.
! ------------------------------------------------------------------------
FUNCTION vec_scal_mul_vec_scal_ (self, k) RESULT(new)
TYPE(vectorT), INTENT(IN) :: self
DOUBLE PRECISION, INTENT(IN) :: k
TYPE(vectorT) :: new
!> initialize solution vector
CALL vec_init(new, vec_length(self))
!> perform multiplication
new%dat = k * self%dat
END FUNCTION vec_scal_mul_vec_scal_
! ------------------------------------------------------------------------
!> \brief Scalar multiplication (k*self version)
!!
!! \param self Reference to the input vector object
!! \param k Scalar multiplication factor
!! \return new Reference to the resulting vector object
!!
!! This routine multiplies a vector by a scalar factor. The
!! overload is necessary for the OPERATOR (*) overload. This version
!! simply calls the other version for better maintainability.
! ------------------------------------------------------------------------
FUNCTION vec_scal_mul_scal_vec_ (k, self) RESULT(new)
TYPE(vectorT), INTENT(IN) :: self
DOUBLE PRECISION, INTENT(IN) :: k
TYPE(vectorT) :: new
new = vec_scalMul(self,k)
END FUNCTION vec_scal_mul_scal_vec_
! ------------------------------------------------------------------------
!> \brief Dot product of two vectors (non-exception checking)
!!
!! \param self Reference to the first vector object
!! \param other Reference to the second vector object
!! \return v Value of the dot product
!!
!! This routine takes the dot product of two vectors. That is, it takes
!! the sum of the element-wise products of the entries in the vectors.
! ------------------------------------------------------------------------
FUNCTION vec_dot_prod_ (self,other) RESULT(v)
TYPE(vectorT), INTENT(IN) :: self,other
DOUBLE PRECISION :: v
!> perform the dot product (using Fortran built-in for efficiency)
v = DOT_PRODUCT(self%dat,other%dat)
END FUNCTION vec_dot_prod_
! ------------------------------------------------------------------------
!> \brief Dot product of two vectors (exception checking)
!!
!! \param self Reference to the first vector object
!! \param other Reference to the second vector object
!! \return v Value of the dot product
!!
!! This routine takes the dot product of two vectors. That is, it takes
!! the sum of the element-wise products of the entries in the vectors. If
!! the length of the two vectors do not match, it returns a DIMEN
!! exception.
! ------------------------------------------------------------------------
FUNCTION vec_dot_prod_exc_ (self,other, exc) RESULT(v)
TYPE(vectorT), INTENT(IN) :: self,other
INTEGER, INTENT(OUT) :: exc
DOUBLE PRECISION :: v
!> ensure that the vectors have the same length
IF (vec_length(self).NE.vec_length(other)) THEN
exc=DIMEN
CALL log_printLogMsg(exc,sdr)
v=0.d0
RETURN
ELSE
exc=OK
END IF
!> call non-exception version
v = vec_dotProd(self,other)
END FUNCTION vec_dot_prod_exc_
END MODULE vector_def
! ------------------------------------------------------------------------
!> \brief Module for testing Vector data type
! ------------------------------------------------------------------------
MODULE vector_test
USE fruit !> Unit testing framework
USE log_message_control !> Printing log/error messages
USE log_messages !> Log/error codes
USE vector_def !> Vector data type
IMPLICIT NONE
CONTAINS
! ------------------------------------------------------------------------
!> \test Test for OK exception message on allocation
!!
!! \param unit_name Name of unit test (for FRUIT)
!! \param test Test vector
!! \param testName Filename for log file (required for exceptions)
!! \param n Number of entries in the vector
!! \param expMsg Expected log message
!! \param actMsg Actual log message
!!
!! This test initializes a vectorT and makes sure that the exception
!! message is OK (i.e. allocation did not fail).
! ------------------------------------------------------------------------
SUBROUTINE test_vec_allocation_MSG
CHARACTER (LEN=*), PARAMETER :: unit_name = 'test_vec_allocation_MSG'
TYPE(vectorT) :: test
CHARACTER (LEN=*), PARAMETER :: testName = 'testName'
INTEGER, PARAMETER :: n=3
INTEGER, PARAMETER :: expMsg=OK
INTEGER :: actMsg
!> initialize unit test
CALL set_unit_name(unit_name)
!> initialize log message file
CALL log_setFileName(testName)
CALL log_initLogFile()
!> initialize vector and check the exception
CALL vec_init(test, n, actMsg)
CALL assertEquals(expMsg,actMsg)
!> finalize log file and deallocate vector
CALL log_closeLogFile()
CALL vec_clean(test)
END SUBROUTINE test_vec_allocation_MSG
! ------------------------------------------------------------------------
!> \test Test for SZE exception message on allocation
!!
!! \param unit_name Name of unit test (for FRUIT)
!! \param test Test vector
!! \param testName Filename for log file (required for exceptions)
!! \param n Number of entries in the vector
!! \param expMsg Expected log message
!! \param actMsg Actual log message
!!
!! This test attempts to initialize a vectorT with invalid size
!! parameters and verifies that the correct exception is returned.
! ------------------------------------------------------------------------
SUBROUTINE test_vec_allocation_SZE
CHARACTER (LEN=*), PARAMETER :: unit_name = 'test_vec_allocation_SZE'
TYPE(vectorT) :: test
CHARACTER (LEN=*), PARAMETER :: testName = 'testName'
INTEGER, PARAMETER :: n=-1
INTEGER, PARAMETER :: expMsg=SZE
INTEGER :: actMsg
!> initialize unit test
CALL set_unit_name(unit_name)
!> initialize log message file
CALL log_setFileName(testName)
CALL log_initLogFile()
!> try to initialize with n=-1
CALL vec_init(test, n, actMsg)
CALL assertEquals(expMsg,actMsg)
!> finalize log file and deallocate vector
CALL log_closeLogFile()
CALL vec_clean(test)
END SUBROUTINE test_vec_allocation_SZE
! ------------------------------------------------------------------------
!> \test Test for initialization of vector data to zeros.
!!
!! \param unit_name Name of unit test (for FRUIT)
!! \param test Test dense matrix
!! \param n Number of entries in the vector
!! \param expDat Expected initial contents of vector data
!!
!! This test initializes a vectorT and ensures that the data is
!! initialized to zeros.
! ------------------------------------------------------------------------
SUBROUTINE test_vec_allocation_DAT
CHARACTER (LEN=*), PARAMETER :: unit_name = 'test_vec_allocation_DAT'
TYPE(vectorT) :: test
INTEGER, PARAMETER :: n=3
DOUBLE PRECISION, DIMENSION(n) :: expDat
!> initialize unit test
CALL set_unit_name(unit_name)
!> set up the expected data
expDat = RESHAPE( (/ 0.d0,0.d0,0.d0 /), SHAPE(expDat) )
!> initialize vector and test actual data
CALL vec_init(test, n)
CALL assertEquals(expDat,test%dat, n)
!> deallocate vector
CALL vec_clean(test)
END SUBROUTINE test_vec_allocation_DAT
! ------------------------------------------------------------------------
!> \test Test for deallocation
!!
!! \param unit_name Name of unit test (for FRUIT)
!! \param test Test vector
!! \param n Number of entries in the vector
!! \param expBefore Expected allocation status before deallocation
!! \param expAfter Expected allocation status after deallocation
!! \param actBefore Actual allocation status before deallocation
!! \param actAfter Actual allocation status after deallocation
!!
!! This test initializes a vectorT and ensures that it is allocated. It
!! then deallocates the object and ensures that it has been deallocated.
! ------------------------------------------------------------------------
SUBROUTINE test_vec_deallocation
CHARACTER (LEN=*), PARAMETER :: unit_name = 'test_vec_deallocation'
TYPE(vectorT) :: test
INTEGER, PARAMETER :: n=3
LOGICAL, PARAMETER :: expBefore = .TRUE.
LOGICAL, PARAMETER :: expAfter = .FALSE.
LOGICAL :: actBefore, actAfter
!> initialize unit test
CALL set_unit_name(unit_name)
!> initialize the vector
CALL vec_init(test, n)
!> make sure dat is allocated
actBefore = ALLOCATED(test%dat)
CALL assertEquals(expBefore,actBefore)
!> deallocate the vector
CALL vec_clean(test)
!> make sure dat is deallocated
actAfter = ALLOCATED(test%dat)
CALL assertEquals(expAfter,actAfter)
END SUBROUTINE test_vec_deallocation
! ------------------------------------------------------------------------
!> \test Test for length when vector is not allocated
!!
!! \param unit_name Name of unit test (for FRUIT)
!! \param test Test vector
!! \param expected Expected length
!! \param actual Actual length
!!
!! This test makes sure that the length is returned as 0 when
!! the vector is not allocated
! ------------------------------------------------------------------------
SUBROUTINE test_vec_length_not_allocated
CHARACTER (LEN=*), PARAMETER :: unit_name = 'test_vec_length_not_allocated'
TYPE(vectorT) :: test
INTEGER, PARAMETER :: expected = 0
INTEGER :: actual
!> initialize unit test
CALL set_unit_name(unit_name)
!> check length
actual = vec_length(test)
CALL assertEquals(expected, actual)
END SUBROUTINE test_vec_length_not_allocated
! ------------------------------------------------------------------------
!> \test Test for length when vector is allocated
!!
!! \param unit_name Name of unit test (for FRUIT)
!! \param test Test vector
!! \param expected Expected length
!! \param actual Actual length
!!
!! This test checks that the length returned is correct when the
!! vector is allocated.
! ------------------------------------------------------------------------
SUBROUTINE test_vec_length_allocated
CHARACTER (LEN=*), PARAMETER :: unit_name = 'test_vec_length_allocated'
TYPE(vectorT) :: test
INTEGER, PARAMETER :: n=3
INTEGER, PARAMETER :: expected = n
INTEGER :: actual
!> initialize unit test
CALL set_unit_name(unit_name)
!> initialize the vector
CALL vec_init(test, n)
!> check length
actual = vec_length(test)
CALL assertEquals(expected, actual)
!> deallocate the matrix
CALL vec_clean(test)
END SUBROUTINE test_vec_length_allocated
! ------------------------------------------------------------------------
!> \test Test for POSIT exception from vec_get
!!
!! \param unit_name Name of unit test (for FRUIT)
!! \param test Test vector
!! \param testName Filename for log file (required for exceptions)
!! \param m Number of entries in the vector
!! \param expMsg Expected log message
!! \param actMsg Actual log message
!! \param v Dummy variable for get function return
!!
!! This test checks that a POSIT exception is returned when the requested
!! location is not inside the vector.
! ------------------------------------------------------------------------
SUBROUTINE test_vec_get_POSIT
CHARACTER (LEN=*), PARAMETER :: unit_name = 'test_vec_get_POSIT'
TYPE(vectorT) :: test
CHARACTER (LEN=*), PARAMETER :: testName = 'testName'
INTEGER, PARAMETER :: m=3
INTEGER, PARAMETER :: expMsg = POSIT
INTEGER :: actMsg
DOUBLE PRECISION :: v
!> initialize unit test
CALL set_unit_name(unit_name)
!> initialize log file
CALL log_setFileName(testName)
CALL log_initLogFile()
!> initialize vector
CALL vec_init(test, m)
!> try to get beyond last entry
v = vec_get(test, m+1, actMsg)
CALL assertEquals(expMsg,actMsg)
!> try to get before first entry
v = vec_get(test, 0, actMsg)
CALL assertEquals(expMsg,actMsg)
!> finalize the log file and deallocate the vector
CALL log_closeLogFile()
CALL vec_clean(test)
END SUBROUTINE test_vec_get_POSIT
! ------------------------------------------------------------------------
!> \test Test for correct value return from vec_get
!!
!! \param unit_name Name of unit test (for FRUIT)
!! \param test Test vector
!! \param m Number of entries in the vector
!! \param i Index for test location
!! \param expVal Expected data value
!! \param actVal Actual data value
!!
!! This test checks that the correct value is returned from the get
!! access program.
! ------------------------------------------------------------------------
SUBROUTINE test_vec_get_VAL
CHARACTER (LEN=*), PARAMETER :: unit_name = 'test_vec_get_VAL'
TYPE(vectorT) :: test
INTEGER, PARAMETER :: m=3
INTEGER, PARAMETER :: i=2
DOUBLE PRECISION, PARAMETER :: expVal = 3.d0
DOUBLE PRECISION :: actVal
!> initialize unit test
CALL set_unit_name(unit_name)
!> initialize the vector
CALL vec_init(test, m)
!> set the value manually in the internal data structure
test%dat(i) = expVal
!> get the value using the access program
actVal = vec_get(test, i)
CALL assertEquals(expVal,actVal)
!> deallocate the vector
CALL vec_clean(test)
END SUBROUTINE test_vec_get_VAL
! ------------------------------------------------------------------------
!> \test Test for POSIT exception from vec_set
!!
!! \param unit_name Name of unit test (for FRUIT)
!! \param test Test vector
!! \param testName Filename for log file (required for exceptions)
!! \param m Number of entries in the vector
!! \param expMsg Expected log message
!! \param actMsg Actual log message
!! \param v Dummy variable for input to set routine
!!
!! This test checks that a POSIT exception is returned when the requested
!! location is not inside the vector.
! ------------------------------------------------------------------------
SUBROUTINE test_vec_set_POSIT
CHARACTER (LEN=*), PARAMETER :: unit_name = 'test_vec_set_POSIT'
TYPE(vectorT) :: test
CHARACTER (LEN=*), PARAMETER :: testName = 'testName'
INTEGER, PARAMETER :: m=3
INTEGER, PARAMETER :: expMsg = POSIT
DOUBLE PRECISION, PARAMETER :: v=0.d0
INTEGER :: actMsg
!> initialize unit test
CALL set_unit_name(unit_name)
!> initialize the log file
CALL log_setFileName(testName)
CALL log_initLogFile()
!> initialize the vector
CALL vec_init(test, m)
!> try to set after last entry
CALL vec_set(test, m+1,v, actMsg)
CALL assertEquals(expMsg,actMsg)
!> try to set before first entry
CALL vec_set(test, 0,v, actMsg)
CALL assertEquals(expMsg,actMsg)
!> finalize log file and deallocate vector
CALL log_closeLogFile()
CALL vec_clean(test)
END SUBROUTINE test_vec_set_POSIT
! ------------------------------------------------------------------------
!> \test Test for correct value return after vec_set
!!
!! \param unit_name Name of unit test (for FRUIT)
!! \param test Test vector
!! \param m Number of entries in the vector
!! \param i Index for test location
!! \param expVal Expected data value
!! \param actVal Actual data value
!!
!! This test checks that the correct value is entered by the set
!! access program.
! ------------------------------------------------------------------------
SUBROUTINE test_vec_set_VAL
CHARACTER (LEN=*), PARAMETER :: unit_name = 'test_vec_set_VAL'
TYPE(vectorT) :: test
INTEGER, PARAMETER :: m=3
INTEGER, PARAMETER :: i=2
DOUBLE PRECISION, PARAMETER :: expVal = 3.d0
DOUBLE PRECISION :: actVal
!> initialize unit test
CALL set_unit_name(unit_name)
!> initialize the vector
CALL vec_init(test, m)
!> set the value
CALL vec_set(test, i,expVal)
actVal = vec_get(test, i)
CALL assertEquals(expVal,actVal)
!> deallocate vector
CALL vec_clean(test)
END SUBROUTINE test_vec_set_VAL
! ------------------------------------------------------------------------
!> \test Test for DIMEN exception when adding vectors
!!
!! \param unit_name Name of unit test (for FRUIT)
!! \param test1 First input vector
!! \param test2 Second input vector
!! \param test3 Output vector
!! \param testName Filename for log file (required for exceptions)
!! \param m Number of entries in the vector
!! \param expMsg Expected exception message
!! \param actMsg Actual exception message
!!
!! This test checks that a DIMEN exception is raised when vectors with
!! incompatible dimensions are added.
! ------------------------------------------------------------------------
SUBROUTINE test_vec_add_DIMEN
CHARACTER (LEN=*), PARAMETER :: unit_name = 'test_vec_add_DIMEN'
TYPE(vectorT) :: test1, test2, test3
CHARACTER (LEN=*), PARAMETER :: testName = 'testName'
INTEGER, PARAMETER :: m=3
INTEGER, PARAMETER :: expMsg=DIMEN
INTEGER :: actMsg
!> initialize unit test
CALL set_unit_name(unit_name)
!> initialize log file
CALL log_setFileName(testName)
CALL log_initLogFile()
!> initialize input vectors (data contents not important)
CALL vec_init(test1, m)
CALL vec_init(test2, m+1) !> note different number of entries
!> attempt to add the vectors
test3 = vec_add(test1,test2, actMsg)
CALL assertEquals(expMsg,actMsg)
!> finalize log file and deallocate vectors
CALL log_closeLogFile()
CALL vec_clean(test1)
CALL vec_clean(test2)
CALL vec_clean(test3)
END SUBROUTINE test_vec_add_DIMEN
! ------------------------------------------------------------------------
!> \test Test for correct addition of vectors
!!
!! \param unit_name Name of unit test (for FRUIT)
!! \param test1 First input vector
!! \param test2 Second input vector
!! \param test3 Output vector
!! \param m Number of rows in the vector
!! \param expDat Expected result of addition
!!
!! This test checks that the correct result is obtained when adding two
!! dense vectors.
! ------------------------------------------------------------------------
SUBROUTINE test_vec_add_VAL
CHARACTER (LEN=*), PARAMETER :: unit_name = 'test_vec_add_VAL'
TYPE(vectorT) :: test1, test2, test3
INTEGER, PARAMETER :: m=3
DOUBLE PRECISION, DIMENSION(m) :: expDat
INTEGER :: i !> loop variable
!> initialize unit test
CALL set_unit_name(unit_name)
!> initialize expected result
expDat = RESHAPE( (/ 3.d0,3.d0,3.d0 /), SHAPE(expDat) )
!> initialize first input vector
!> (loop sets vector to all ones)
CALL vec_init(test1, m)
DO i = 1,m
CALL vec_set(test1, i, 1.d0)
END DO
!> initialize second input vector
!> (loop sets vector to all twos)
CALL vec_init(test2, m)
DO i = 1,m
CALL vec_set(test2, i, 2.d0)
END DO
!> add the vectors
test3 = vec_add(test1,test2)
CALL assertEquals(expDat,test3%dat, m)
!> deallocate vectors
CALL vec_clean(test1)
CALL vec_clean(test2)
CALL vec_clean(test3)
END SUBROUTINE test_vec_add_VAL
! ------------------------------------------------------------------------
!> \test Test for correct addition of vectors ( using OPERATOR (+) )
!!
!! \param unit_name Name of unit test (for FRUIT)
!! \param test1 First input vector
!! \param test2 Second input vector
!! \param test3 Output vector
!! \param m Number of rows in the vector
!! \param expDat Expected result of addition
!!
!! This test checks that the correct result is obtained when adding two
!! dense vectors. It uses the overloaded operator (+).
! ------------------------------------------------------------------------
SUBROUTINE test_vec_add_OP
CHARACTER (LEN=*), PARAMETER :: unit_name = 'test_vec_add_OP'
TYPE(vectorT) :: test1, test2, test3
INTEGER, PARAMETER :: m=3
DOUBLE PRECISION, DIMENSION(m) :: expDat
INTEGER :: i !> loop variable
!> initialize unit test
CALL set_unit_name(unit_name)
!> initialize expected result
expDat = RESHAPE( (/ 3.d0,3.d0,3.d0 /), SHAPE(expDat) )
!> initialize first input vector
!> (loop sets vector to all ones)
CALL vec_init(test1, m)
DO i = 1,m
CALL vec_set(test1, i, 1.d0)
END DO
!> initialize second input vector
!> (loop sets vector to all twos)
CALL vec_init(test2, m)
DO i = 1,m
CALL vec_set(test2, i, 2.d0)
END DO
!> add the vectors
test3 = test1 + test2
CALL assertEquals(expDat,test3%dat, m)
!> deallocate vectors
CALL vec_clean(test1)
CALL vec_clean(test2)
CALL vec_clean(test3)
END SUBROUTINE test_vec_add_OP
! ------------------------------------------------------------------------
!> \test Test for DIMEN exception when performing mapped add
!!
!! \param unit_name Name of unit test (for FRUIT)
!! \param test1 Test target vector
!! \param test2 Test input vector
!! \param testName Filename for log file (required for exceptions)
!! \param m Number of entries in target vector
!! \param n Number of entries in input vector
!! \param expMsg Expected exception message
!! \param actMsg Actual exception message
!! \param ind Mapping indices (size does not match test2)
!!
!! This test checks that a DIMEN exception is raised when mapped addition
!! is attempted with the dimension of the index array not matching the
!! dimensions of the input vector.
! ------------------------------------------------------------------------
SUBROUTINE test_vec_mapped_add_DIMEN
CHARACTER (LEN=*), PARAMETER :: unit_name = 'test_vec_mapped_add_DIMEN'
TYPE(vectorT) :: test1, test2
CHARACTER (LEN=*), PARAMETER :: testName = 'testName'
INTEGER, PARAMETER :: m=5,n=3
INTEGER, PARAMETER :: expMsg=DIMEN
INTEGER, PARAMETER, DIMENSION(2) :: ind = (/ 1,2 /)
INTEGER :: actMsg
!> initialize unit test
CALL set_unit_name(unit_name)
!> initialize log file
CALL log_setFileName(testName)
CALL log_initLogFile()
!> initialize vectors (data content not important)
CALL vec_init(test1,m)
CALL vec_init(test2,n)
!> try mapped add (note n=3, SIZE(ind)=2)
CALL vec_mappedAdd(test1, test2,ind, actMsg)
CALL assertEquals(expMsg,actMsg)
!> finalize log file and deallocate vectors
CALL log_closeLogFile()
CALL vec_clean(test1)
CALL vec_clean(test2)
END SUBROUTINE test_vec_mapped_add_DIMEN
! ------------------------------------------------------------------------
!> \test Test for POSIT exception when performing mapped add
!!
!! \param unit_name Name of unit test (for FRUIT)
!! \param test1 Test target vector
!! \param test2 Test input vector
!! \param testName Filename for log file (required for exceptions)
!! \param m Number of entries in target vector
!! \param n Number of entries in input vector
!! \param expMsg Expected exception message
!! \param actMsg Actual exception message
!! \param ind1 Mapping indices (with index below minimum)
!! \param ind2 Mapping indices (with index above maximum)
!!
!! This test checks that a POSIT exception is raised when mapped addition
!! is attempted with mapping indices that are outside the target vector.
! ------------------------------------------------------------------------
SUBROUTINE test_vec_mapped_add_POSIT
CHARACTER (LEN=*), PARAMETER :: unit_name = 'test_vec_mapped_add_POSIT'
TYPE(vectorT) :: test1, test2
CHARACTER (LEN=*), PARAMETER :: testName = 'testName'
INTEGER, PARAMETER :: m=5,n=3
INTEGER, PARAMETER :: expMsg=POSIT
INTEGER, PARAMETER, DIMENSION(n) :: ind1 = (/ -1,3,5 /)
INTEGER, PARAMETER, DIMENSION(n) :: ind2 = (/ 1,3,6 /)
INTEGER :: actMsg
!> initialize unit test
CALL set_unit_name(unit_name)
!> initialize log file
CALL log_setFileName(testName)
CALL log_initLogFile()
!> initialize vectors (data not important)
CALL vec_init(test1,m)
CALL vec_init(test2,n)
!> attempt first mapped add
CALL vec_mappedAdd(test1, test2,ind1, actMsg)
CALL assertEquals(expMsg,actMsg)
!> attempt second mapped add
CALL vec_mappedAdd(test1, test2,ind2, actMsg)
CALL assertEquals(expMsg,actMsg)
!> finalize log file and deallocate vectors
CALL log_closeLogFile()
CALL vec_clean(test1)
CALL vec_clean(test2)
END SUBROUTINE test_vec_mapped_add_POSIT
! ------------------------------------------------------------------------
!> \test Test for correct mapped addition (single operation)
!!
!! \param unit_name Name of unit test (for FRUIT)
!! \param test1 Test target vector
!! \param test2 Test input vector
!! \param m Number of entries in target vector
!! \param n Number of entries in input vector
!! \param expDat Expected data contents
!! \param ind Mapping indices
!!
!! This test checks that mapped addition is performed correctly. The
!! operation is performed once on a blank target vector.
! ------------------------------------------------------------------------
SUBROUTINE test_vec_mapped_add_VAL1
CHARACTER (LEN=*), PARAMETER :: unit_name = 'test_vec_mapped_add_VAL1'
TYPE(vectorT) :: test1, test2
INTEGER, PARAMETER :: m=5,n=3
INTEGER, PARAMETER, DIMENSION(n) :: ind = (/ 1,3,5 /)
DOUBLE PRECISION, DIMENSION(m) :: expDat
INTEGER :: i !> loop variable
!> initialize unit test
CALL set_unit_name(unit_name)
!> set up expected data
expDat = RESHAPE( (/ 1.d0,0.d0,2.d0,0.d0,3.d0 /), SHAPE(expDat) )
!> initialize target vector
CALL vec_init(test1,m)
!> initialize input vector
!> (loop sets the data contents)
CALL vec_init(test2,n)
DO i = 1,n
CALL vec_set(test2,i,DBLE(i))
END DO
!> perform mapped addition
CALL vec_mappedAdd(test1, test2,ind)
CALL assertEquals(expDat,test1%dat,m)
!> deallocate vectors
CALL vec_clean(test1)
CALL vec_clean(test2)
END SUBROUTINE test_vec_mapped_add_VAL1
! ------------------------------------------------------------------------
!> \test Test for correct mapped addition (zero index)
!!
!! \param unit_name Name of unit test (for FRUIT)
!! \param test1 Test target vector
!! \param test2 Test input vector
!! \param m Number of entries in target vector
!! \param n Number of entries in input vector
!! \param expDat Expected data contents
!! \param ind Mapping indices (with zero index indicating no-op)
!!
!! This test checks that mapped addition is performed correctly. The
!! mapping index contains a zero, which should tell the mapped adder to
!! skip that location in the input vector.
! ------------------------------------------------------------------------
SUBROUTINE test_vec_mapped_add_VAL2
CHARACTER (LEN=*), PARAMETER :: unit_name = 'test_vec_mapped_add_VAL2'
TYPE(vectorT) :: test1, test2
INTEGER, PARAMETER :: m=5,n=3
INTEGER, PARAMETER, DIMENSION(n) :: ind = (/ 1,0,5 /)
DOUBLE PRECISION, DIMENSION(m) :: expDat
INTEGER :: i !> loop variable
!> initialize unit test
CALL set_unit_name(unit_name)
!> set up expected data
expDat = RESHAPE( (/ 1.d0,0.d0,0.d0,0.d0,3.d0 /), SHAPE(expDat) )
!> initialize target vector
CALL vec_init(test1,m)
!> initialize input vector
!> (loop sets the data contents)
CALL vec_init(test2,n)
DO i = 1,n
CALL vec_set(test2,i,DBLE(i))
END DO
!> perform mapped addition
CALL vec_mappedAdd(test1, test2,ind)
CALL assertEquals(expDat,test1%dat,m)
!> deallocate vectors
CALL vec_clean(test1)
CALL vec_clean(test2)
END SUBROUTINE test_vec_mapped_add_VAL2
! ------------------------------------------------------------------------
!> \test Test for correct mapped addition (multiple operations)
!!
!! \param unit_name Name of unit test (for FRUIT)
!! \param test1 Test target vector
!! \param test2 Test input vector
!! \param m Number of entries in target vector
!! \param n Number of entries in input vector
!! \param expDat Expected data contents
!! \param ind2 Mapping indices for first add
!! \param ind3 Mapping indices for second add
!!
!! This test checks that mapped addition is performed correctly. The
!! operation is performed twice to ensure summation of overlapping
!! values. That is, input is added to existing data in the target vector
!! rather than overwriting.
! ------------------------------------------------------------------------
SUBROUTINE test_vec_mapped_add_VAL3
CHARACTER (LEN=*), PARAMETER :: unit_name = 'test_vec_mapped_add_VAL3'
TYPE(vectorT) :: test1, test2
INTEGER, PARAMETER :: m=5,n=3
INTEGER, PARAMETER, DIMENSION(n) :: ind1 = (/ 1,3,5 /)
INTEGER, PARAMETER, DIMENSION(n) :: ind2 = (/ 1,0,5 /)
DOUBLE PRECISION, DIMENSION(m) :: expDat
INTEGER :: i !> loop variable
!> initialize unit test
CALL set_unit_name(unit_name)
!> set up expected data
expDat = RESHAPE( (/ 2.d0,0.d0,2.d0,0.d0,6.d0 /), SHAPE(expDat) )
!> initialize target vector
CALL vec_init(test1,m)
!> initialize input vector
!> (loop sets the data contents)
CALL vec_init(test2,n)
DO i = 1,n
CALL vec_set(test2,i,DBLE(i))
END DO
!> perform the mapped addition for both input indices
CALL vec_mappedAdd(test1, test2,ind1)
CALL vec_mappedAdd(test1, test2,ind2)
CALL assertEquals(expDat,test1%dat,m)
!> deallocate vectors
CALL vec_clean(test1)
CALL vec_clean(test2)
END SUBROUTINE test_vec_mapped_add_VAL3
! ------------------------------------------------------------------------
!> \test Test for scalar multiplication
!!
!! \param unit_name Name of unit test (for FRUIT)
!! \param test1 Input vector
!! \param test2 Output vector
!! \param k Scalar coefficient
!! \param m Number of entries in the vector
!! \param expDat Expected data contents
!!
!! This test checks that scalar multiplication is performed correctly.
! ------------------------------------------------------------------------
SUBROUTINE test_vec_scal_mul_VAL
CHARACTER (LEN=*), PARAMETER :: unit_name = 'test_vec_scal_mul_VAL'
TYPE(vectorT) :: test1, test2
DOUBLE PRECISION, PARAMETER :: k=3.d0
INTEGER, PARAMETER :: m=3
DOUBLE PRECISION, DIMENSION(m) :: expDat
INTEGER :: i !> loop variable
!> initialize unit test
CALL set_unit_name(unit_name)
!> set up expected data
expDat = RESHAPE( (/ 3.d0,3.d0,3.d0 /), SHAPE(expDat) )
!> initialize input vector
!> (loop sets the vector to ones)
CALL vec_init(test1, m)
DO i = 1,m
CALL vec_set(test1, i, 1.d0)
END DO
!> multiply by scalar
test2 = vec_scalMul(test1,k)
CALL assertEquals(expDat,test2%dat, m)
!> deallocate vectors
CALL vec_clean(test1)
CALL vec_clean(test2)
END SUBROUTINE test_vec_scal_mul_VAL
! ------------------------------------------------------------------------
!> \test Test for scalar multiplication (by zero)
!!
!! \param unit_name Name of unit test (for FRUIT)
!! \param test1 Input vector
!! \param test2 Output vector
!! \param k Scalar coefficient
!! \param m Number of entries in the vector
!! \param expDat Expected data contents
!!
!! This test checks that scalar multiplication is performed correctly
!! when the scalar is zero.
! ------------------------------------------------------------------------
SUBROUTINE test_vec_scal_mul_ZERO
CHARACTER (LEN=*), PARAMETER :: unit_name = 'test_vec_scal_mul_ZERO'
TYPE(vectorT) :: test1, test2
DOUBLE PRECISION, PARAMETER :: k=0.d0
INTEGER, PARAMETER :: m=3
DOUBLE PRECISION, DIMENSION(m) :: expDat
INTEGER :: i !> loop variable
!> initialize unit test
CALL set_unit_name(unit_name)
!> set up expected data
expDat = RESHAPE( (/ 0.d0,0.d0,0.d0 /), SHAPE(expDat) )
!> initialize input vector
!> (loop sets the vector to ones)
CALL vec_init(test1, m)
DO i = 1,m
CALL vec_set(test1, i, 1.d0)
END DO
!> multiply by zero
test2 = vec_scalMul(test1,k)
CALL assertEquals(expDat,test2%dat, m)
!> deallocate vectors
CALL vec_clean(test1)
CALL vec_clean(test2)
END SUBROUTINE test_vec_scal_mul_ZERO
! ------------------------------------------------------------------------
!> \test Test for scalar multiplication ( using OPERATOR (*) )
!!
!! \param unit_name Name of unit test (for FRUIT)
!! \param test1 Input vector
!! \param test2 Output vector
!! \param k Scalar coefficient
!! \param m Number of entries in the vector
!! \param expDat Expected data contents
!!
!! This test checks that scalar multiplication is performed correctly. It
!! uses the overloaded operator (*).
! ------------------------------------------------------------------------
SUBROUTINE test_vec_scal_mul_OP
CHARACTER (LEN=*), PARAMETER :: unit_name = 'test_vec_scal_mul_OP'
TYPE(vectorT) :: test1, test2
DOUBLE PRECISION, PARAMETER :: k=3.d0
INTEGER, PARAMETER :: m=3
DOUBLE PRECISION, DIMENSION(m) :: expDat
INTEGER :: i !> loop variable
!> initialize unit test
CALL set_unit_name(unit_name)
!> set up expected data
expDat = RESHAPE( (/ 3.d0,3.d0,3.d0 /), SHAPE(expDat) )
!> initialize input vector
!> (loop sets the vector to ones)
CALL vec_init(test1, m)
DO i = 1,m
CALL vec_set(test1, i, 1.d0)
END DO
!> multiply by scalar
test2 = k*test1
CALL assertEquals(expDat,test2%dat, m)
!> reset output vector
CALL vec_clean(test2)
!> multiply by scalar (switch order of inputs)
test2 = test1*k
CALL assertEquals(expDat,test2%dat, m)
!> deallocate vectors
CALL vec_clean(test1)
CALL vec_clean(test2)
END SUBROUTINE test_vec_scal_mul_OP
! ------------------------------------------------------------------------
!> \test Test for DIMEN exception when performing dot product
!!
!! \param unit_name Name of unit test (for FRUIT)
!! \param test1 First test vector
!! \param test2 Second test vector
!! \param testName Filename for log file (required for exceptions)
!! \param m Number of entries in vector
!! \param expMsg Expected exception message
!! \param actMsg Actual exception message
!! \param v Dummy variable for dot product output
!!
!! This test checks that a DIMEN exception is raised when a dot product
!! is attempted when the vectors do not have the same length.
! ------------------------------------------------------------------------
SUBROUTINE test_vec_dot_prod_DIMEN
CHARACTER (LEN=*), PARAMETER :: unit_name = 'test_vec_dot_prod_DIMEN'
TYPE(vectorT) :: test1, test2
CHARACTER (LEN=*), PARAMETER :: testName = 'testName'
INTEGER, PARAMETER :: m=3
INTEGER, PARAMETER :: expMsg=DIMEN
INTEGER :: actMsg
DOUBLE PRECISION :: v
!> initialize unit test
CALL set_unit_name(unit_name)
!> initialize log file
CALL log_setFileName(testName)
CALL log_initLogFile()
!> set up vectors (data contents not important)
CALL vec_init(test1,m)
CALL vec_init(test2,m+1) !> note the different dimension
!> attempt the dot product
v = vec_dotProd(test1, test2, actMsg)
CALL assertEquals(expMsg,actMsg)
!> finalize log file and deallocate vectors
CALL log_closeLogFile()
CALL vec_clean(test1)
CALL vec_clean(test2)
END SUBROUTINE test_vec_dot_prod_DIMEN
! ------------------------------------------------------------------------
!> \test Test for dot product (with zero vector)
!!
!! \param unit_name Name of unit test (for FRUIT)
!! \param test1 First input vector (zeros)
!! \param test2 Second input vector
!! \param m Number of entries in the vector
!! \param expected Expected result
!! \param actual Actual result
!!
!! This test checks that the dot product result is zero when one vector
!! is all zeros.
! ------------------------------------------------------------------------
SUBROUTINE test_vec_dot_prod_ZERO
CHARACTER (LEN=*), PARAMETER :: unit_name = 'test_vec_dot_prod_ZERO'
TYPE(vectorT) :: test1, test2
INTEGER, PARAMETER :: m=3
DOUBLE PRECISION, PARAMETER :: expected=0.d0
DOUBLE PRECISION :: actual
INTEGER :: i !> loop variable
!> initialize unit test
CALL set_unit_name(unit_name)
!> initialize first input vector (zeros)
CALL vec_init(test1,m)
!> initialize second input vector
!! (loop sets up data content)
CALL vec_init(test2,m)
DO i = 1,m
CALL vec_set(test2, i, ( 2.d0 * DBLE(i) ) )
END DO
!> perform dot product
actual = vec_dotProd(test1, test2)
CALL assertEquals(expected,actual)
!> deallocate vectors
CALL vec_clean(test1)
CALL vec_clean(test2)
END SUBROUTINE test_vec_dot_prod_ZERO
! ------------------------------------------------------------------------
!> \test Test for correct dot product
!!
!! \param unit_name Name of unit test (for FRUIT)
!! \param test1 First input vector
!! \param test2 Second input vector
!! \param m Number of entries in the vector
!! \param expected Expected result
!! \param actual Actual result
!!
!! This test checks that the dot product result is correct in the general
!! case (when the data content is non-zero).
! ------------------------------------------------------------------------
SUBROUTINE test_vec_dot_prod_VAL
CHARACTER (LEN=*), PARAMETER :: unit_name = 'test_vec_dot_prod_VAL'
TYPE(vectorT) :: test1, test2
INTEGER, PARAMETER :: m=3
DOUBLE PRECISION, PARAMETER :: expected=28.d0
DOUBLE PRECISION :: actual
INTEGER :: i !> loop variable
!> initialize unit test
CALL set_unit_name(unit_name)
!> initialize first input vector
!! (loop sets up data content)
CALL vec_init(test1,m)
DO i = 1,m
CALL vec_set(test1, i, DBLE(i))
END DO
!> initialize second input vector
!! (loop sets up data content)
CALL vec_init(test2,m)
DO i = 1,m
CALL vec_set(test2, i, ( 2.d0 * DBLE(i) ) )
END DO
!> perform dot product
actual = vec_dotProd(test1, test2)
CALL assertEquals(expected,actual)
!> deallocate vectors
CALL vec_clean(test1)
CALL vec_clean(test2)
END SUBROUTINE test_vec_dot_prod_VAL
END MODULE vector_test
# Fortran compiler
FF = gfortran
# general compiler flags
FLAGS =
# compiler flags for linear algebra
LINALG = -llapack -lblas
# list of required object files
OBJECTS = fruit_util.o fruit.o \
system_constants.o \
log_messages.o log_message_control.o \
vector_def.o dense_matrix_def.o band_sym_matrix_def.o \
linear_solver.o \
material_data.o field_data.o boundary_data.o \
pde_solver_constants.o \
constitutive.o kinematic.o \
material_model.o \
interpolation.o integration.o \
pde_solver_control.o \
log_messages_test.o log_message_control_test.o \
vector_test.o dense_matrix_test.o band_sym_matrix_test.o \
linear_solver_test.o \
material_data_test.o field_data_test.o boundary_data_test.o \
constitutive_test.o \
pde_solver_control_test.o \
test_driver.o
all: test_driver check
check:
./test_driver.a
doc:
doxygen doc-dynsws
test_driver: $(OBJECTS)
$(FF) -o test_driver.a $(OBJECTS) $(LINALG) $(FLAGS)
fruit_util.o: fruit_util.f90
$(FF) -c fruit_util.f90 $(FLAGS)
fruit.o: fruit.f90
$(FF) -c fruit.f90 $(FLAGS)
test_driver.o: test_driver.f90
$(FF) -c test_driver.f90 $(LINALG) $(FLAGS)
band_sym_matrix_def.o: band_sym_matrix_def.f90
$(FF) -c band_sym_matrix_def.f90 $(FLAGS)
band_sym_matrix_test.o: band_sym_matrix_test.f90
$(FF) -c band_sym_matrix_test.f90 $(FLAGS)
boundary_data.o: boundary_data.f90
$(FF) -c boundary_data.f90 $(FLAGS)
boundary_data_test.o: boundary_data_test.f90
$(FF) -c boundary_data_test.f90 $(FLAGS)
constitutive.o: constitutive.f90
$(FF) -c constitutive.f90 $(FLAGS)
constitutive_test.o: constitutive_test.f90
$(FF) -c constitutive_test.f90 $(FLAGS)
dense_matrix_def.o: dense_matrix_def.f90
$(FF) -c dense_matrix_def.f90 $(FLAGS)
dense_matrix_test.o: dense_matrix_test.f90
$(FF) -c dense_matrix_test.f90 $(FLAGS)
field_data.o: field_data.f90
$(FF) -c field_data.f90 $(FLAGS)
field_data_test.o: field_data_test.f90
$(FF) -c field_data_test.f90 $(FLAGS)
integration.o: integration.f90
$(FF) -c integration.f90 $(FLAGS)
interpolation.o: interpolation.f90
$(FF) -c interpolation.f90 $(FLAGS)
kinematic.o: kinematic.f90
$(FF) -c kinematic.f90 $(FLAGS)
linear_solver.o: linear_solver.f90
$(FF) -c linear_solver.f90 $(LINALG) $(FLAGS)
linear_solver_test.o: linear_solver_test.f90
$(FF) -c linear_solver_test.f90 $(LINALG) $(FLAGS)
log_message_control.o: log_message_control.f90
$(FF) -c log_message_control.f90 $(FLAGS)
log_message_control_test.o: log_message_control_test.f90
$(FF) -c log_message_control_test.f90 $(FLAGS)
log_messages.o: log_messages.f90
$(FF) -c log_messages.f90 $(FLAGS)
log_messages_test.o: log_messages_test.f90
$(FF) -c log_messages_test.f90 $(FLAGS)
material_model.o: material_model.f90
$(FF) -c material_model.f90 $(FLAGS)
material_data.o: material_data.f90
$(FF) -c material_data.f90 $(FLAGS)
material_data_test.o: material_data_test.f90
$(FF) -c material_data_test.f90 $(FLAGS)
pde_solver_constants.o: pde_solver_constants.f90
$(FF) -c pde_solver_constants.f90 $(FLAGS)
pde_solver_control.o: pde_solver_control.f90
$(FF) -c pde_solver_control.f90 $(FLAGS)
pde_solver_control_test.o: pde_solver_control_test.f90
$(FF) -c pde_solver_control_test.f90 $(FLAGS)
system_constants.o: system_constants.f90
$(FF) -c system_constants.f90 $(FLAGS)
vector_def.o: vector_def.f90
$(FF) -c vector_def.f90 $(FLAGS)
vector_test.o: vector_test.f90
$(FF) -c vector_test.f90 $(FLAGS)
clean:
rm -rf *.o
clean_test:
rm -rf test_driver.o
clean_boundary_data: clean_test \
clean_integration clean_interpolation \
clean_pde_solver_control
rm -rf boundary_data.o boundary_data_test.o
clean_bsm: clean_test \
clean_pde_solver_control
rm -rf band_sym_matrix_def.o band_sym_matrix_test.o
clean_constitutive: clean_test \
clean_integration clean_material_model
rm -rf constitutive.o constitutive_test.o
clean_dm: clean_test \
clean_bsm clean_constitutive clean_integration \
clean_interpolation clean_kinematic clean_material_model \
clean_pde_solver_control
rm -rf dense_matrix_def.o dense_matrix_test.o
clean_field_data: clean_test \
clean_integration clean_interpolation \
clean_kinematic clean_boundary_data \
clean_pde_solver_control
rm -rf field_data.o field_data_test.o
clean_integration: clean_test \
clean_pde_solver_control
rm -rf integration.o
clean_interpolation: clean_test \
clean_integration
rm -rf interpolation.o
clean_kinematic: clean_test \
clean_integration
rm -rf kinematic.o
clean_linear_solver: clean_test
rm -rf linear_solver.o linear_solver_test.o
clean_log: clean_test \
clean_bsm clean_dm clean_vec \
clean_material_data clean_field_data \
clean_constitutive \
clean_pde_solver_control
rm -rf log_message_control.o log_message_control_test.o
clean_material_data: clean_test \
clean_integration clean_field_data \
clean_pde_solver_control
rm -rf material_data.o material_data_test.o
clean_material_model: clean_test
rm -rf material_model.o
clean_msg: clean_test \
clean_bsm clean_dm clean_log clean_vec \
clean_material_data clean_field_data \
clean_constitutive \
clean_pde_solver_control
rm -rf log_messages.o log_messages_test.o
clean_pde_solver_constants: clean_test \
clean_integration \
clean_pde_solver_control
rm -rf pde_solver_constants.o
clean_pde_solver_control: clean_test
rm -rf pde_solver_control.o pde_solver_control_test.o
clean_system_constants: clean_test \
clean_log clean_msg \
clean_constitutive clean_kinematic \
clean_interpolation \
clean_pde_solver_constants \
clean_material_data clean_field_data \
clean_pde_solver_control
rm -rf system_constants.o
clean_vec: clean_test \
clean_bsm clean_dm clean_integration \
clean_material_model \
clean_pde_solver_control
rm -rf vector_def.o vector_test.o
* ------------------------------------------------------------------------
*
* DynSWS 1.0
* Dynamic Model of Soil-Water-Structure Interaction
*
* Contact:
* Brandon Karchewski
* c/o Dept. of Civil Engineering (JHE-301)
* McMaster University
* 1280 Main Street West
* Hamilton, Ontario, Canada
* L8S 4L7
* T: (905) 529-6569
* E: karcheba@mcmaster.ca
*
* ------------------------------------------------------------------------
------------------
REVISION HISTORY:
------------------
[26 March 2012]
-Initialized this README file
[29 March 2012]
-Added build instructions for prerequisite libraries
-Modified build instructions for DynSWS
[1 April 2012]
-Added descriptions of new modules
[2 April 2012]
-Added descriptions of new modules
[3 April 2012]
-Added descriptions of new modules
-Modified build instructions for clarity
[5 April 2012]
-Added documentation instructions
[6 April 2012]
-Added descriptions of new modules
------------------------
BACKGROUND INFORMATION:
------------------------
This file relates to the program DynSWS. New users/developers should see
the following documents to become acquainted with the project:
Software Requirements Specification
DynSWS-SRS-1.0.pdf
Module Guide:
DynSWS-MG-1.0.pdf
Module Interface Specification:
DynSWS-MIS-1.0.pdf
SRS, MG, and MIS for PDE Solver Module:
DynSWS-PDE-1.0.pdf
-----------------------
PROJECT PREREQUISITES:
-----------------------
The following netlib linear algebra packages should be available on
the build path to be linked against:
BLAS (Basic Linear Algebra Subprograms)
http://www.netlib.org/blas/
LAPACK (Linear Algebra PACKage)
http://www.netlib.org/lapack/
Both can be obtained by visiting the LAPACK project website and
downloading the latest version of LAPACK. As of this moment it
is LAPACK 3.4.0. Here is a minimal instruction set for building
the package (assuming the compiler is gfortran):
1. Extract downloaded package to desired directory.
2. cd to the root directory of the LAPACK package.
3. Delete the .example extension from make.inc.example.
-Note: The user may want to look inside this file to make
sure the configuration is appropriate for their
system.
4. cd BLAS/SRC
5. make
6. cd ../../
7. make
This should build and test the reference BLAS and the LAPACK
package. The user may want to use their own machine-tuned version,
but that will be left at their discretion. At any rate, the
instructions above should leave the user with a generic BLAS and
LAPACK build. The libraries generated will have the filenames:
librefblas.a
libtmglib.a
liblapack.a
The user should copy these into a folder that is on the build
path for their compiler (generally a folder called 'lib' within
the file system of the shell program or the compiler suite).
Generally, the user should also change the name of 'librefblas.a'
to 'libblas.a' so that the compiler can find it with the -lblas
switch.
-----------------------------
DOCUMENTATION PREREQUISITES:
-----------------------------
To build the documentation from the source code, the doxygen system is
required. This can be obtained from:
http://www.stack.nl/~dimitri/doxygen/
The user should follow the installation instructions associated with their
system. Note that this item is not required to build the actual program.
------------------
PROJECT CONTENTS:
------------------
README.txt
Contains general information about project and build instructions
Makefile
Makefile for building the program including unit tests
fruit.f90
fruit_util.f90
Unit testing framework (FRUIT) for Fortran
See http://sourceforge.net/apps/mediawiki/fortranxunit/index.php?title=Main_Page
http://sourceforge.net/projects/fortranxunit/
http://fortranxunit.sourceforge.net/
band_sym_matrix_def.f90
band_sym_matrix_test.f90
Banded Symmetric Matrix ADT and associated unit tests
boundary_data.f90
boundary_data_test.f90
Boundary Data Module and associated tests
constitutive.f90
Constitutive Matrix module
dense_matrix_def.f90
dense_matrix_test.f90
Dense Matrix ADT and associated unit tests
field_data.f90
field_data_test.f90
Field Data Module and associated tests
integration.f90
Body Element Integration and Traction Element Integration modules
interpolation.f90
Body Element Interpolation and Traction Element Interpolation modules
kinematic.f90
Kinematic Matrix Module
log_message_control.f90
log_message_control_test.f90
Log Message Control module and associated unit tests
log_messages.f90
log_messages_test.f90
Log Messages Module and associated unit tests
material_data.f90
material_data_test.f90
Material Property Data module and associated unit tests
pde_solver_control.f90
pde_solver_control_test.f90
PDE Solver Control module and associated unit tests
system_constants.f90
System Constants Module
test_driver.f90
Driver program for unit tests
vector_def.f90
vector_test.f90
Vector ADT and associated unit tests
--------------------
BUILD INSTRUCTIONS:
--------------------
To build and run the test suite:
1. Open shell
2. cd to directory of DynSWS
3. Open Makefile and set FF to the name of your Fortran compiler
(the default is gfortran)
4. make
This will build the program and run the unit test suite. The results of
the unit tests will be printed to the console. The test suite will also
generate testName.log and test_straight_coarse.log files. Assuming that
the unit tests all pass, the contents are not important as these are just
by-products of the exception checking tests.
--------------------
BUILD DOCUMENTATION:
--------------------
To build documentation from the source code:
1. Open shell
2. cd to directory of DynSWS
3. make doc
Note that this generates both html and latex format documentation. The
html version will work out of the box and is contained in the directory
<dir of DynSWS>/doc/html. The latex documentation may be build as follows
(assuming the shell is still open and the current directory is that of
DynSWS):
1. cd doc/latex
2. make
Note that the latex version has issues at this point in time. The author's
recommended version of the documentation is the html version.
! ------------------------------------------------------------------------
!> \brief Module defining Banded Symmetric Matrix data type
! ------------------------------------------------------------------------
MODULE band_sym_matrix_def
USE log_message_control !> Printing log/error messages
USE log_messages !> Log/error codes
USE vector_def !> Vector data type
USE dense_matrix_def !> Dense Matrix data type
IMPLICIT NONE
PRIVATE
! ************************************************************************
! EXPORTS
! ************************************************************************
!> Exported data types
PUBLIC :: bandSymMatrixT
!> Exported interfaces
PUBLIC :: bsm_init, bsm_clean, &
bsm_numRows, bsm_halfBW, &
bsm_get, bsm_set, &
bsm_setDecomp, bsm_isDecomposed, &
bsm_add, OPERATOR (+), bsm_mappedAdd, &
bsm_scalMul, OPERATOR (*), bsm_vecMul
! ************************************************************************
! LOCAL CONSTANTS
! ************************************************************************
!> Sender code for Banded SYmmetric MATrix module
INTEGER, PARAMETER :: sdr = BSYMAT
! ************************************************************************
! DATA TYPES
! ************************************************************************
! ------------------------------------------------------------------------
!> \brief Banded Symmetric Matrix ADT structure
!!
!! \param dat Array to store packed (banded symmetric) data
!! \param decomp Array to store packed Cholesky decomposition
!! \param is_decomposed Switch indicating whether decomposition is present
! ------------------------------------------------------------------------
TYPE bandSymMatrixT
DOUBLE PRECISION, ALLOCATABLE :: dat(:,:)
DOUBLE PRECISION, ALLOCATABLE :: decomp(:,:)
LOGICAL :: is_decomposed
END TYPE bandSymMatrixT
! ************************************************************************
! INTERFACES
! ************************************************************************
!> \brief Interface to constructor
INTERFACE bsm_init
MODULE PROCEDURE bsm_init_
MODULE PROCEDURE bsm_init_exc_
END INTERFACE bsm_init
!> \brief Interface to destructor
INTERFACE bsm_clean
MODULE PROCEDURE bsm_clean_
END INTERFACE bsm_clean
!> \brief Interface to number of rows
INTERFACE bsm_numRows
MODULE PROCEDURE bsm_num_rows_
END INTERFACE bsm_numRows
!> \brief Interface to half bandwidth
INTERFACE bsm_halfBW
MODULE PROCEDURE bsm_half_bw_
END INTERFACE bsm_halfBW
!> \brief Interface to getter for individual entries in matrix
INTERFACE bsm_get
MODULE PROCEDURE bsm_get_
MODULE PROCEDURE bsm_get_exc_
END INTERFACE bsm_get
!> \brief Interface to setter for individual entries in matrix
INTERFACE bsm_set
MODULE PROCEDURE bsm_set_
MODULE PROCEDURE bsm_set_exc_
END INTERFACE bsm_set
!> \brief Interface to setter for Cholesky decomposition
INTERFACE bsm_setDecomp
MODULE PROCEDURE bsm_set_decomp_
MODULE PROCEDURE bsm_set_decomp_exc_
END INTERFACE bsm_setDecomp
!> \brief Interface to check if decomposition exists
INTERFACE bsm_isDecomposed
MODULE PROCEDURE bsm_is_decomposed_
END INTERFACE bsm_isDecomposed
!> \brief Interface for addition of two bandSymMatrixT
INTERFACE bsm_add
MODULE PROCEDURE bsm_add_
MODULE PROCEDURE bsm_add_exc_
END INTERFACE bsm_add
!> \brief Operator overload for addition
INTERFACE OPERATOR (+)
MODULE PROCEDURE bsm_add_
END INTERFACE
!> \brief Interface for adding a matrixT to a bandSymMatrixT in place with mapping indices
INTERFACE bsm_mappedAdd
MODULE PROCEDURE bsm_mapped_add_
MODULE PROCEDURE bsm_mapped_add_exc_
END INTERFACE bsm_mappedAdd
!> \brief Interface for scalar multiplication
INTERFACE bsm_scalMul
MODULE PROCEDURE bsm_scal_mul_mat_scal_
END INTERFACE bsm_scalMul
!> \brief Interface for matrix-vector multiplication
INTERFACE bsm_vecMul
MODULE PROCEDURE bsm_vec_mul_
MODULE PROCEDURE bsm_vec_mul_exc_
END INTERFACE bsm_vecMul
!> \brief Operator overload for multiplication (includes scalar and vector multiplication)
INTERFACE OPERATOR (*)
MODULE PROCEDURE bsm_scal_mul_mat_scal_
MODULE PROCEDURE bsm_scal_mul_scal_mat_
MODULE PROCEDURE bsm_vec_mul_
END INTERFACE
CONTAINS
! ************************************************************************
! ACCESS PROGRAMS
! ************************************************************************
! ------------------------------------------------------------------------
!> \brief Constructor for bandSymMatrixT (non-exception checking)
!!
!! \param self Reference to the banded symmetric matrix to be initialized
!! \param hbw Half bandwidth of the matrix
!! \param n Number of rows/columns in the matrix
!!
!! This routine initializes the bandSymMatrixT object referenced by self.
!! The data structures contained in self are allocated and initial values
!! are set to zero.
! ------------------------------------------------------------------------
SUBROUTINE bsm_init_ (self, hbw,n)
TYPE(bandSymMatrixT), INTENT(INOUT) :: self
INTEGER, INTENT(IN) :: hbw,n
INTEGER :: i,j !> loop variables
!> only reallocate if new dimensions do not match existing dimensions
IF (bsm_halfBW(self).NE.hbw .OR. bsm_numRows(self).NE.n) THEN
!> reset object if it was previously initialized
CALL bsm_clean(self)
!> allocate new data structures
ALLOCATE(self%dat(hbw,n))
ALLOCATE(self%decomp(hbw,n))
END IF
!> ensure data is initialized to zero
DO j = 1,n
DO i = 1,hbw
self%dat(i,j) = 0.d0
self%decomp(i,j) = 0.d0
END DO
END DO
!> reset boolean for decomposition
self%is_decomposed = .FALSE.
END SUBROUTINE bsm_init_
! ------------------------------------------------------------------------
!> \brief Constructor for bandSymMatrixT (exception checking)
!!
!! \param self Reference to the banded symmetric matrix to be initialized
!! \param hbw Half bandwidth of the matrix
!! \param n Number of rows/columns in the matrix
!! \param exc Error code
!!
!! This routine initializes the bandSymMatrixT object referenced by self.
!! The data structures contained in self are allocated and initial values
!! are set to zero. If the specified dimensions are invalid, a SZE
!! exception is returned. If allocation of data structures fails, an
!! ALLOC exception is returned.
! ------------------------------------------------------------------------
SUBROUTINE bsm_init_exc_ (self, hbw,n, exc)
TYPE(bandSymMatrixT), INTENT(INOUT) :: self
INTEGER, INTENT(IN) :: hbw,n
INTEGER, INTENT(OUT) :: exc
INTEGER :: e !> allocation info code
INTEGER :: i,j !> loop variables
!> if dimensions are invalid, raise SZE exception
IF (hbw.LE.0 .OR. n.LE.0 .OR. hbw.GT.n) THEN
exc=SZE
CALL log_printLogMsg(exc,sdr)
RETURN
ELSE
exc=OK
END IF
!> only reallocate if new dimensions do not match existing dimensions
IF (bsm_halfBW(self).NE.hbw .OR. bsm_numRows(self).NE.n) THEN
!> reset object if it was previously initialized
CALL bsm_clean(self)
!> allocate new data structure for matrix storage
ALLOCATE(self%dat(hbw,n), STAT=e)
!> if error code is returned, raise ALLOC exception
IF (e.NE.0) THEN
exc=ALLOC
CALL log_printLogMsg(exc,sdr)
CALL bsm_clean(self)
RETURN
ELSE
exc=OK
END IF
!> allocate new data structure for decomposition storage
ALLOCATE(self%decomp(hbw,n), STAT=e)
!> if error code is returned, raise ALLOC exception
IF (e.NE.0) THEN
exc=ALLOC
CALL log_printLogMsg(exc,sdr)
CALL bsm_clean(self)
RETURN
ELSE
exc=OK
END IF
END IF
!> ensure data is initialized to zero
DO j = 1,n
DO i = 1,hbw
self%dat(i,j) = 0.d0
self%decomp(i,j) = 0.d0
END DO
END DO
!> reset boolean for decomposition
self%is_decomposed = .FALSE.
END SUBROUTINE bsm_init_exc_
! ------------------------------------------------------------------------
!> \brief Destructor for bandSymMatrixT
!!
!! \param self Reference to the banded symmetric matrix to be destroyed
!!
!! This routine deallocates existing data structures and resets the
!! switch indicating decomposition.
! ------------------------------------------------------------------------
SUBROUTINE bsm_clean_ (self)
TYPE(bandSymMatrixT), INTENT(INOUT) :: self
!> deallocate data structures
IF (ALLOCATED(self%dat)) DEALLOCATE(self%dat)
IF (ALLOCATED(self%decomp)) DEALLOCATE(self%decomp)
!> reset boolean for decomposition
self%is_decomposed = .FALSE.
END SUBROUTINE bsm_clean_
! ------------------------------------------------------------------------
!> \brief Getter for number of rows
!!
!! \param self Reference to the banded symmetric matrix object
!! \return n Number of rows in the matrix
!!
!! This routine determines the number of rows allocated to the matrix
!! object. If the matrix is not initialized it returns 0.
! ------------------------------------------------------------------------
FUNCTION bsm_num_rows_ (self) RESULT(n)
TYPE(bandSymMatrixT), INTENT(IN) :: self
INTEGER :: n
!> if data is initialized, return number of rows
IF (ALLOCATED(self%dat)) THEN
n = SIZE(self%dat,2)
ELSE
n = 0 !> if not initialized, there are no rows
END IF
END FUNCTION bsm_num_rows_
! ------------------------------------------------------------------------
!> \brief Getter for half bandwidth
!!
!! \param self Reference to the banded symmetric matrix object
!! \return hbw Half bandwidth of the matrix
!!
!! This routine determines the half bandwidth allocated to the matrix
!! object. If the matrix is not initialized it returns 0.
! ------------------------------------------------------------------------
FUNCTION bsm_half_bw_ (self) RESULT(hbw)
TYPE(bandSymMatrixT), INTENT(IN) :: self
INTEGER :: hbw
!> if data is initialized, return half bandwidth
IF (ALLOCATED(self%dat)) THEN
hbw = SIZE(self%dat,1)
ELSE
hbw = 0 !> if not initialized, there are no bands
END IF
END FUNCTION bsm_half_bw_
! ------------------------------------------------------------------------
!> \brief Getter for matrix entries (non-exception checking)
!!
!! \param self Reference to the banded symmetric matrix object
!! \param i Row index (in unpacked version)
!! \param j Column index (in unpacked version)
!! \return v Value at location (i,j) of the matrix
!!
!! This routine determines the value at a particular location in the
!! matrix. If the location is outside the band, it returns 0.
! ------------------------------------------------------------------------
FUNCTION bsm_get_ (self, i,j) RESULT(v)
TYPE(bandSymMatrixT), INTENT(IN) :: self
INTEGER, INTENT(IN) :: i,j
DOUBLE PRECISION :: v
INTEGER :: r,c !> indices in packed format
!> get packed indices
CALL packed_index(self, i,j, r,c)
!> if desired location is within the bands, return the value
IF (r.GT.0) THEN
v = self%dat(r,c)
ELSE
v = 0.d0 !> if off-band, return 0
END IF
END FUNCTION bsm_get_
! ------------------------------------------------------------------------
!> \brief Getter for matrix entries (exception checking)
!!
!! \param self Reference to the banded symmetric matrix object
!! \param i Row index (in unpacked version)
!! \param j Column index (in unpacked version)
!! \param exc Error code
!! \return v Value at location (i,j) of the matrix
!!
!! This routine determines the value at a particular location in the
!! matrix. If the location is outside the band, it returns 0. If the
!! location is not inside the matrix, it returns a POSIT exception.
! ------------------------------------------------------------------------
FUNCTION bsm_get_exc_ (self, i,j, exc) RESULT(v)
TYPE(bandSymMatrixT), INTENT(IN) :: self
INTEGER, INTENT(IN) :: i,j
INTEGER, INTENT(OUT) :: exc
DOUBLE PRECISION :: v
INTEGER :: n !> number of rows
!> get number of rows (for efficiency)
n = bsm_numRows(self)
!> make sure desired indices are inside the matrix
IF (i.GT.n .OR. i.LE.0 &
.OR. j.GT.n .OR. j.LE.0) THEN
exc=POSIT
CALL log_printLogMsg(exc,sdr)
v = 0.d0
RETURN
ELSE
exc=OK
END IF
!> call non-exception getter
v = bsm_get(self, i,j)
END FUNCTION bsm_get_exc_
! ------------------------------------------------------------------------
!> \brief Setter for matrix entries (non-exception checking)
!!
!! \param self Reference to the banded symmetric matrix object
!! \param i Row index (in unpacked version)
!! \param j Column index (in unpacked version)
!! \param v Value to be stored at location (i,j) of the matrix
!!
!! This routine sets the value at a particular location in the
!! matrix.
! ------------------------------------------------------------------------
SUBROUTINE bsm_set_ (self, i,j,v)
TYPE(bandSymMatrixT), INTENT(INOUT) :: self
INTEGER, INTENT(IN) :: i,j
DOUBLE PRECISION, INTENT(IN) :: v
INTEGER :: r,c !> indices in packed format
!> get packed indices
CALL packed_index(self, i,j, r,c)
!> set the data value
self%dat(r,c) = v
END SUBROUTINE bsm_set_
! ------------------------------------------------------------------------
!> \brief Setter for matrix entries (exception checking)
!!
!! \param self Reference to the banded symmetric matrix object
!! \param i Row index (in unpacked version)
!! \param j Column index (in unpacked version)
!! \param v Value to be stored at location (i,j) of the matrix
!! \param exc Error code
!!
!! This routine sets the value at a particular location in the
!! matrix. If the location is outside the band or if the
!! location is not inside the matrix, it returns a POSIT exception.
! ------------------------------------------------------------------------
SUBROUTINE bsm_set_exc_ (self, i,j,v, exc)
TYPE(bandSymMatrixT), INTENT(INOUT) :: self
INTEGER, INTENT(IN) :: i,j
DOUBLE PRECISION, INTENT(IN) :: v
INTEGER, INTENT(OUT) :: exc
INTEGER :: n !> number of rows
!> get number of rows (for efficiency)
n = bsm_numRows(self)
!> ensure that desired indices are within the matrix
!> and furthermore within the bands
IF (i.GT.n .OR. i.LE.0 &
.OR. j.GT.n .OR. j.LE.0 &
.OR. ABS(j-i).GE.bsm_halfBW(self)) THEN
exc=POSIT
CALL log_printLogMsg(exc,sdr)
RETURN
ELSE
exc=OK
END IF
!> call non-exception version
CALL bsm_set(self, i,j,v)
END SUBROUTINE bsm_set_exc_
! ------------------------------------------------------------------------
!> \brief Setter for Cholesky decomposition (non-exception checking)
!!
!! \param self Reference to the banded symmetric matrix object
!! \param decomp Array containing the decomposition in packed format
!!
!! This routine sets the Cholesky decomposition of the matrix object.
!! The decomposition is typically determined using the DPBTRF subroutine
!! from the LAPACK library.
! ------------------------------------------------------------------------
SUBROUTINE bsm_set_decomp_ (self,decomp)
TYPE(bandSymMatrixT), INTENT(INOUT) :: self
DOUBLE PRECISION, INTENT(IN) :: decomp(:,:)
!> set the decomposition data and flip the boolean
self%decomp = decomp
self%is_decomposed = .TRUE.
END SUBROUTINE bsm_set_decomp_
! ------------------------------------------------------------------------
!> \brief Setter for Cholesky decomposition (exception checking)
!!
!! \param self Reference to the banded symmetric matrix object
!! \param decomp Array containing the decomposition in packed format
!! \param exc Error code
!!
!! This routine sets the Cholesky decomposition of the matrix object.
!! The decomposition is typically determined using the DPBTRF subroutine
!! from the LAPACK library. If the dimensions of the provided
!! decomposition array do not match those of the allocated array, it
!! returns a DIMEN exception.
! ------------------------------------------------------------------------
SUBROUTINE bsm_set_decomp_exc_ (self,decomp, exc)
TYPE(bandSymMatrixT), INTENT(INOUT) :: self
DOUBLE PRECISION, INTENT(IN) :: decomp(:,:)
INTEGER, INTENT(OUT) :: exc
!> make sure that the dimensions of the proposed decomposition match
!> the actual dimensions of the packed storage
IF (bsm_halfBW(self).NE.SIZE(decomp,1) &
.OR. bsm_numRows(self).NE.SIZE(decomp,2)) THEN
exc=DIMEN
CALL log_printLogMsg(exc,sdr)
RETURN
ELSE
exc=OK
END IF
!> call the non-exception version
CALL bsm_setDecomp(self,decomp)
END SUBROUTINE bsm_set_decomp_exc_
! ------------------------------------------------------------------------
!> \brief Getter for boolean indicating presence of decomposition
!!
!! \param self Reference to the banded symmetric matrix object
!! \return is_decomposed Boolean indicating whether the decomposition is present
! ------------------------------------------------------------------------
FUNCTION bsm_is_decomposed_ (self) RESULT(is_decomposed)
TYPE(bandSymMatrixT), INTENT(IN) :: self
LOGICAL :: is_decomposed
is_decomposed = self%is_decomposed
END FUNCTION bsm_is_decomposed_
! ------------------------------------------------------------------------
!> \brief Add two bandSymMatrixT objects (non-exception checking)
!!
!! \param self Reference to the first (left-hand) banded symmetric matrix object
!! \param other Reference to the second (right-hand) banded symmetric matrix object
!! \return new Reference to the resulting banded symmetric matrix object
!!
!! This routine adds two banded symmetric matrix objects. The half
!! bandwidth of the result is the maximum of the half bandwidths of the
!! input matrix objects.
! ------------------------------------------------------------------------
FUNCTION bsm_add_ (self,other) RESULT(new)
TYPE(bandSymMatrixT), INTENT(IN) :: self,other
TYPE(bandSymMatrixT) :: new
INTEGER :: hbw1,hbw2 !> half bandwidths of inputs
INTEGER :: hbw,n !> half bandwidth of output and number of rows
!> get number of rows and half bandwidths
n = bsm_numRows(self)
hbw1 = bsm_halfBW(self)
hbw2 = bsm_halfBW(other)
!> new half bandwidth is the maximum of the previous
hbw = MAX(hbw1,hbw2)
!> intialize new bandSymMatrixT
CALL bsm_init(new, hbw,n)
!> add the two matrices (using array ops for efficiency)
new%dat(hbw-hbw1+1:hbw,:) = self%dat(:,:)
new%dat(hbw-hbw2+1:hbw,:) = new%dat(hbw-hbw2+1:hbw,:) + other%dat(:,:)
END FUNCTION bsm_add_
! ------------------------------------------------------------------------
!> \brief Add two bandSymMatrixT objects (exception checking)
!!
!! \param self Reference to the first (left-hand) banded symmetric matrix object
!! \param other Reference to the second (right-hand) banded symmetric matrix object
!! \param exc Error code
!! \return new Reference to the resulting banded symmetric matrix object
!!
!! This routine adds two banded symmetric matrix objects. The half
!! bandwidth of the result is the maximum of the half bandwidths of the
!! input matrix objects. If the dimensions of the two input matrices do
!! not match, it returns a DIMEN exception.
! ------------------------------------------------------------------------
FUNCTION bsm_add_exc_ (self,other, exc) RESULT(new)
TYPE(bandSymMatrixT), INTENT(IN) :: self,other
INTEGER, INTENT(OUT) :: exc
TYPE(bandSymMatrixT) :: new
!> make sure that the two matrices have the same number of rows
IF (bsm_numRows(self).NE.bsm_numRows(other)) THEN
exc=DIMEN
CALL log_printLogMsg(exc,sdr)
RETURN
ELSE
exc=OK
END IF
!> call non-exception version
new = bsm_add(self,other)
END FUNCTION bsm_add_exc_
! ------------------------------------------------------------------------
!> \brief Add a matrixT to a bandSymMatrixT in place with mapping (non-exception checking)
!!
!! \param self Reference to the banded symmetric matrix object
!! \param other Reference to the dense matrix object
!! \param ind Integer mapping indices
!!
!! This routine adds a dense matrix to a banded symmetric matrix in place
!! according to an indexed mapping. That is, the element at (i,j) in
!! other is added to the element at (ind(i),ind(j)) of self.
! ------------------------------------------------------------------------
SUBROUTINE bsm_mapped_add_ (self, other,ind)
TYPE(bandSymMatrixT), INTENT(INOUT) :: self
TYPE(matrixT), INTENT(IN) :: other
INTEGER, INTENT(IN) :: ind(:)
INTEGER :: i,j !> loop variables
!> Add matrix entries corresponding to mapping indices
DO i = 1,SIZE(ind)
IF (ind(i).EQ.0) CYCLE
DO j = i,SIZE(ind)
IF (ind(j).EQ.0) CYCLE
CALL bsm_set(self, ind(i),ind(j), &
bsm_get(self,ind(i),ind(j)) &
+ dm_get(other,i,j) )
END DO
END DO
END SUBROUTINE bsm_mapped_add_
! ------------------------------------------------------------------------
!> \brief Add a matrixT to a bandSymMatrixT in place with mapping (exception checking)
!!
!! \param self Reference to the banded symmetric matrix object
!! \param other Reference to the dense matrix object
!! \param ind Integer mapping indices
!! \param exc Error code
!!
!! This routine adds a dense matrix to a banded symmetric matrix in place
!! according to an indexed mapping. That is, the element at (i,j) in
!! other is added to the element at (ind(i),ind(j)) of self. If the
!! dense matrix is not square or if the its dimensions exceed the half
!! bandwidth of the banded symmetric matrix, it returns a DIMEN
!! exception. If the number of mapping indices does not match the
!! dimension of the dense matrix, it returns a DIMEN exception. If any of
!! the index pairs indicate a location outside the matrix bands, it
!! returns a POSIT exception. Note that a zero index is valid and
!! ind(i)=0 or ind(j)=0 indicate that the value at (i,j) in the dense
!! matrix object will not be added to the banded symmetric matrix object.
! ------------------------------------------------------------------------
SUBROUTINE bsm_mapped_add_exc_ (self, other,ind, exc)
TYPE(bandSymMatrixT), INTENT(INOUT) :: self
TYPE(matrixT), INTENT(IN) :: other
INTEGER, INTENT(IN) :: ind(:)
INTEGER, INTENT(OUT) :: exc
!> ensure that matrixT is square (it is assumed to be symmetric)
!> and that the number of rows in the matrixT matches the number
!> of mapping indices
!> and that the matrixT is not wider than the half bandwidth
!> of the bandSymMatrixT
IF (dm_numRows(other).NE.dm_numCols(other) &
.OR. dm_numRows(other).NE.SIZE(ind) &
.OR. dm_numRows(other).GT.bsm_halfBW(self)) THEN
exc=DIMEN
CALL log_printLogMsg(exc,sdr)
RETURN
!> ensure that there are no mapping indices outside the bandSymMatrixT
!> and that all indices are within the bands
ELSEIF ( MAXVAL(ind).GT.bsm_numRows(self) .OR. MINVAL(ind).LT.0 &
.OR. MAXVAL(ind)-MINVAL(ind,MASK=ind.GT.0) .GE. bsm_halfBW(self) ) THEN
exc=POSIT
CALL log_printLogMsg(exc,sdr)
RETURN
ELSE
exc=OK
END IF
!> call non-exception version
CALL bsm_mappedAdd(self,other,ind)
END SUBROUTINE bsm_mapped_add_exc_
! ------------------------------------------------------------------------
!> \brief Scalar multiplication (self*k version)
!!
!! \param self Reference to the banded symmetric matrix object
!! \param k Scalar multiplication factor
!! \return new Reference to the resulting banded symmetric matrix object
!!
!! This routine multiplies a banded symmetric matrix by a scalar factor.
! ------------------------------------------------------------------------
FUNCTION bsm_scal_mul_mat_scal_ (self,k) RESULT(new)
TYPE(bandSymMatrixT), INTENT(IN) :: self
DOUBLE PRECISION, INTENT(IN) :: k
TYPE(bandSymMatrixT) :: new
!> initialize output
CALL bsm_init(new, bsm_halfBW(self),bsm_numRows(self))
!> perform multiplication
new%dat = k * self%dat
END FUNCTION bsm_scal_mul_mat_scal_
! ------------------------------------------------------------------------
!> \brief Scalar multiplication (k*self version)
!!
!! \param self Reference to the banded symmetric matrix object
!! \param k Scalar multiplication factor
!! \return new Reference to the resulting banded symmetric matrix object
!!
!! This routine multiplies a banded symmetric matrix by a scalar factor.
!! The overload is necessary for the OPERATOR (*) overload. This version
!! simply calls the other version for better maintainability.
! ------------------------------------------------------------------------
FUNCTION bsm_scal_mul_scal_mat_ (k,self) RESULT(new)
TYPE(bandSymMatrixT), INTENT(IN) :: self
DOUBLE PRECISION, INTENT(IN) :: k
TYPE(bandSymMatrixT) :: new
!> call self*k version
new = bsm_scalMul(self,k)
END FUNCTION bsm_scal_mul_scal_mat_
! ------------------------------------------------------------------------
!> \brief Post-multiplication of a banded symmetric matrix by a vector (non-exception checking)
!!
!! \param self Reference to the banded symmetric matrix object
!! \param other Reference to the vector object
!! \return new Reference to the resulting vector object
!!
!! This routine post-multiplies a banded symmetric matrix by a vector.
!! That is, it performs self*other, not other*self.
! ------------------------------------------------------------------------
FUNCTION bsm_vec_mul_ (self,other) RESULT(new)
TYPE(bandSymMatrixT), INTENT(IN) :: self
TYPE(vectorT), INTENT(IN) :: other
TYPE(vectorT) :: new
INTEGER :: hbw,n !> half bandwidth and number of rows
INTEGER :: i,j !> loop variables
!> get size parameters
n = vec_length(other)
hbw = bsm_halfBW(self)
!> initialize solution
CALL vec_init(new, n)
!> perform partial dot products of rows in self with the vector
!> (ignoring off-band zeros)
DO i = 1,n
DO j = MAX(i-hbw+1,1), MIN(i+hbw-1,n)
CALL vec_set(new, i, vec_get(new,i) + bsm_get(self,i,j)*vec_get(other,j))
END DO
END DO
END FUNCTION bsm_vec_mul_
! ------------------------------------------------------------------------
!> \brief Post-multiplication of a banded symmetric matrix by a vector (exception checking)
!!
!! \param self Reference to the banded symmetric matrix object
!! \param other Reference to the vector object
!! \param exc Error code
!! \return new Reference to the resulting vector object
!!
!! This routine post-multiplies a banded symmetric matrix by a vector.
!! That is, it performs self*other, not other*self. If the dimensions
!! of the two objects are not compatible, it returns a DIMEN exception.
! ------------------------------------------------------------------------
FUNCTION bsm_vec_mul_exc_ (self,other, exc) RESULT(new)
TYPE(bandSymMatrixT), INTENT(IN) :: self
TYPE(vectorT), INTENT(IN) :: other
INTEGER, INTENT(OUT) :: exc
TYPE(vectorT) :: new
!> ensure that the number of rows in the bandSymMatrixT and
!> the vectorT match
IF (bsm_numRows(self).NE.vec_length(other)) THEN
exc=DIMEN
CALL log_printLogMsg(exc,sdr)
RETURN
ELSE
exc=OK
END IF
!> call non-exception version
new = bsm_vecMul(self,other)
END FUNCTION bsm_vec_mul_exc_
! ************************************************************************
! LOCAL FUNCTIONS
! ************************************************************************
! ------------------------------------------------------------------------
!> \brief Determine the packed indices from the non-packed indices
!!
!! \param self Reference to the banded symmetric matrix object
!! \param i Row index (non-packed version)
!! \param j Column index (non-packed version)
!! \param r Row index (packed version)
!! \param c Column index (packed version)
!!
!! This routine determines the indices of the desired location in the
!! matrix in the packed data structure. It accounts for symmetry by
!! ensuring that i <= j. After that is checked, the packed indices are
!! computed as: r = hbw - (j-i)
!! c = j
! ------------------------------------------------------------------------
SUBROUTINE packed_index (self, i,j, r,c)
TYPE(bandSymMatrixT), INTENT(IN) :: self
INTEGER, INTENT(IN) :: i,j
INTEGER, INTENT(OUT) :: r,c
!> flip indices - symmetry
IF (i.GT.j) THEN
r=j
c=i
ELSE
r=i
c=j
END IF
!> convert to packed index
r = bsm_halfBW(self) - (c-r)
END SUBROUTINE packed_index
END MODULE band_sym_matrix_def
GFORTRAN module version '6' created from band_sym_matrix_def.f90 on Sun Apr 29 22:07:07 2012
MD5:bde4e23fc359ee86c4aea2c7103d4b1a -- If you edit this, you'll get what you deserve.
(() () (2 3 4) () (5 6 7 8 9 10 11 12 13) () () () () () () () () () ()
() () () () () () () () () () () ())
()
(('bsm_add' 'band_sym_matrix_def' 14 2) ('bsm_get' 'band_sym_matrix_def'
15 16) ('bsm_clean' 'band_sym_matrix_def' 17) ('bsm_init'
'band_sym_matrix_def' 18 19) ('bsm_halfbw' 'band_sym_matrix_def' 20) (
'bsm_isdecomposed' 'band_sym_matrix_def' 21) ('bsm_numrows'
'band_sym_matrix_def' 22) ('bsm_mappedadd' 'band_sym_matrix_def' 23 24)
('bsm_scalmul' 'band_sym_matrix_def' 7) ('bsm_setdecomp'
'band_sym_matrix_def' 25 26) ('bsm_vecmul' 'band_sym_matrix_def' 27 5) (
'bsm_set' 'band_sym_matrix_def' 28 29))
()
()
()
(30 'bandsymmatrixt' 'band_sym_matrix_def' 'bandsymmatrixt' 1 ((DERIVED
UNKNOWN-INTENT UNKNOWN-PROC UNKNOWN UNKNOWN 0 0 ALLOC_COMP) (UNKNOWN 0 0
0 UNKNOWN ()) 0 0 () () 0 ((31 'dat' (REAL 8 0 0 REAL ()) (2 0 DEFERRED
() () () ()) (UNKNOWN-FL UNKNOWN-INTENT UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
ALLOCATABLE DIMENSION) UNKNOWN-ACCESS ()) (32 'decomp' (REAL 8 0 0 REAL
()) (2 0 DEFERRED () () () ()) (UNKNOWN-FL UNKNOWN-INTENT UNKNOWN-PROC
UNKNOWN UNKNOWN 0 0 ALLOCATABLE DIMENSION) UNKNOWN-ACCESS ()) (33
'is_decomposed' (LOGICAL 4 0 0 LOGICAL ()) () (UNKNOWN-FL UNKNOWN-INTENT
UNKNOWN-PROC UNKNOWN UNKNOWN 0 0) UNKNOWN-ACCESS ())) PUBLIC (() () () ())
() 0 0 5919959)
19 'bsm_init_' 'band_sym_matrix_def' 'bsm_init_' 1 ((PROCEDURE
UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 SUBROUTINE) (UNKNOWN 0 0 0
UNKNOWN ()) 34 0 (35 36 37) () 0 () () () 0 0)
18 'bsm_init_exc_' 'band_sym_matrix_def' 'bsm_init_exc_' 1 ((PROCEDURE
UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 SUBROUTINE) (UNKNOWN 0 0 0
UNKNOWN ()) 38 0 (39 40 41 42) () 0 () () () 0 0)
17 'bsm_clean_' 'band_sym_matrix_def' 'bsm_clean_' 1 ((PROCEDURE
UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 SUBROUTINE IMPLICIT_PURE) (
UNKNOWN 0 0 0 UNKNOWN ()) 43 0 (44) () 0 () () () 0 0)
22 'bsm_num_rows_' 'band_sym_matrix_def' 'bsm_num_rows_' 1 ((PROCEDURE
UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 FUNCTION IMPLICIT_PURE) (
INTEGER 4 0 0 INTEGER ()) 45 0 (46) () 47 () () () 0 0)
20 'bsm_half_bw_' 'band_sym_matrix_def' 'bsm_half_bw_' 1 ((PROCEDURE
UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 FUNCTION IMPLICIT_PURE) (
INTEGER 4 0 0 INTEGER ()) 48 0 (49) () 50 () () () 0 0)
16 'bsm_get_' 'band_sym_matrix_def' 'bsm_get_' 1 ((PROCEDURE
UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 FUNCTION IMPLICIT_PURE) (
REAL 8 0 0 REAL ()) 51 0 (52 53 54) () 55 () () () 0 0)
15 'bsm_get_exc_' 'band_sym_matrix_def' 'bsm_get_exc_' 1 ((PROCEDURE
UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 FUNCTION) (REAL 8 0 0 REAL ())
56 0 (57 58 59 60) () 61 () () () 0 0)
29 'bsm_set_' 'band_sym_matrix_def' 'bsm_set_' 1 ((PROCEDURE
UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 SUBROUTINE IMPLICIT_PURE) (
UNKNOWN 0 0 0 UNKNOWN ()) 62 0 (63 64 65 66) () 0 () () () 0 0)
28 'bsm_set_exc_' 'band_sym_matrix_def' 'bsm_set_exc_' 1 ((PROCEDURE
UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 SUBROUTINE) (UNKNOWN 0 0 0
UNKNOWN ()) 67 0 (68 69 70 71 72) () 0 () () () 0 0)
26 'bsm_set_decomp_' 'band_sym_matrix_def' 'bsm_set_decomp_' 1 ((
PROCEDURE UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 SUBROUTINE
IMPLICIT_PURE ALWAYS_EXPLICIT) (UNKNOWN 0 0 0 UNKNOWN ()) 73 0 (74 75) ()
0 () () () 0 0)
25 'bsm_set_decomp_exc_' 'band_sym_matrix_def' 'bsm_set_decomp_exc_' 1 (
(PROCEDURE UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 SUBROUTINE
ALWAYS_EXPLICIT) (UNKNOWN 0 0 0 UNKNOWN ()) 76 0 (77 78 79) () 0 () () ()
0 0)
21 'bsm_is_decomposed_' 'band_sym_matrix_def' 'bsm_is_decomposed_' 1 ((
PROCEDURE UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 FUNCTION
IMPLICIT_PURE) (LOGICAL 4 0 0 LOGICAL ()) 80 0 (81) () 82 () () () 0 0)
2 'bsm_add_' 'band_sym_matrix_def' 'bsm_add_' 1 ((PROCEDURE
UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 FUNCTION) (DERIVED 30 0 0
DERIVED ()) 83 0 (84 85) () 86 () () () 0 0)
14 'bsm_add_exc_' 'band_sym_matrix_def' 'bsm_add_exc_' 1 ((PROCEDURE
UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 FUNCTION) (DERIVED 30 0 0
DERIVED ()) 87 0 (88 89 90) () 91 () () () 0 0)
24 'bsm_mapped_add_' 'band_sym_matrix_def' 'bsm_mapped_add_' 1 ((
PROCEDURE UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 SUBROUTINE
ALWAYS_EXPLICIT) (UNKNOWN 0 0 0 UNKNOWN ()) 92 0 (93 94 95) () 0 () () ()
0 0)
23 'bsm_mapped_add_exc_' 'band_sym_matrix_def' 'bsm_mapped_add_exc_' 1 (
(PROCEDURE UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 SUBROUTINE
ALWAYS_EXPLICIT) (UNKNOWN 0 0 0 UNKNOWN ()) 96 0 (97 98 99 100) () 0 ()
() () 0 0)
7 'bsm_scal_mul_mat_scal_' 'band_sym_matrix_def' 'bsm_scal_mul_mat_scal_'
1 ((PROCEDURE UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 FUNCTION) (
DERIVED 30 0 0 DERIVED ()) 101 0 (102 103) () 104 () () () 0 0)
5 'bsm_vec_mul_' 'band_sym_matrix_def' 'bsm_vec_mul_' 1 ((PROCEDURE
UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 FUNCTION) (DERIVED 105 0 0
DERIVED ()) 106 0 (107 108) () 109 () () () 0 0)
27 'bsm_vec_mul_exc_' 'band_sym_matrix_def' 'bsm_vec_mul_exc_' 1 ((
PROCEDURE UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 FUNCTION) (
DERIVED 105 0 0 DERIVED ()) 110 0 (111 112 113) () 114 () () () 0 0)
6 'bsm_scal_mul_scal_mat_' 'band_sym_matrix_def' 'bsm_scal_mul_scal_mat_'
1 ((PROCEDURE UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 FUNCTION) (
DERIVED 30 0 0 DERIVED ()) 115 0 (116 117) () 118 () () () 0 0)
13 'dm_scal_mul_mat_scal_' 'dense_matrix_def' 'dm_scal_mul_mat_scal_' 1
((PROCEDURE UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 FUNCTION) (
DERIVED 119 0 0 DERIVED ()) 120 0 (121 122) () 123 () () () 0 0)
12 'dm_scal_mul_scal_mat_' 'dense_matrix_def' 'dm_scal_mul_scal_mat_' 1
((PROCEDURE UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 FUNCTION) (
DERIVED 119 0 0 DERIVED ()) 124 0 (125 126) () 127 () () () 0 0)
11 'dm_vec_mul_' 'dense_matrix_def' 'dm_vec_mul_' 1 ((PROCEDURE
UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 FUNCTION) (DERIVED 105 0 0
DERIVED ()) 128 0 (129 130) () 131 () () () 0 0)
10 'dm_mat_mul_' 'dense_matrix_def' 'dm_mat_mul_' 1 ((PROCEDURE
UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 FUNCTION) (DERIVED 119 0 0
DERIVED ()) 132 0 (133 134) () 135 () () () 0 0)
4 'dm_add_' 'dense_matrix_def' 'dm_add_' 1 ((PROCEDURE UNKNOWN-INTENT
MODULE-PROC DECL UNKNOWN 0 0 FUNCTION) (DERIVED 119 0 0 DERIVED ()) 136
0 (137 138) () 139 () () () 0 0)
137 'self' '' 'self' 136 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (DERIVED 119 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
44 'self' '' 'self' 43 ((VARIABLE INOUT UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (DERIVED 30 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
46 'self' '' 'self' 45 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (DERIVED 30 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
47 'n' '' 'n' 45 ((VARIABLE UNKNOWN-INTENT UNKNOWN-PROC UNKNOWN UNKNOWN
0 0 RESULT) (INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
49 'self' '' 'self' 48 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (DERIVED 30 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
50 'hbw' '' 'hbw' 48 ((VARIABLE UNKNOWN-INTENT UNKNOWN-PROC UNKNOWN
UNKNOWN 0 0 RESULT) (INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
35 'self' '' 'self' 34 ((VARIABLE INOUT UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (DERIVED 30 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
36 'hbw' '' 'hbw' 34 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
37 'n' '' 'n' 34 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0 DUMMY) (
INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
39 'self' '' 'self' 38 ((VARIABLE INOUT UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (DERIVED 30 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
40 'hbw' '' 'hbw' 38 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
41 'n' '' 'n' 38 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0 DUMMY) (
INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
42 'exc' '' 'exc' 38 ((VARIABLE OUT UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
105 'vectort' 'vector_def' 'vectort' 1 ((DERIVED UNKNOWN-INTENT
UNKNOWN-PROC UNKNOWN UNKNOWN 0 0 ALLOC_COMP) (UNKNOWN 0 0 0 UNKNOWN ())
0 0 () () 0 ((140 'dat' (REAL 8 0 0 REAL ()) (1 0 DEFERRED () ()) (
UNKNOWN-FL UNKNOWN-INTENT UNKNOWN-PROC UNKNOWN UNKNOWN 0 0 ALLOCATABLE
DIMENSION) UNKNOWN-ACCESS ())) PUBLIC (() () () ()) () 0 0 58143611)
8 'vec_scal_mul_scal_vec_' 'vector_def' 'vec_scal_mul_scal_vec_' 1 ((
PROCEDURE UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 FUNCTION) (
DERIVED 105 0 0 DERIVED ()) 141 0 (142 143) () 144 () () () 0 0)
9 'vec_scal_mul_vec_scal_' 'vector_def' 'vec_scal_mul_vec_scal_' 1 ((
PROCEDURE UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 FUNCTION) (
DERIVED 105 0 0 DERIVED ()) 145 0 (146 147) () 148 () () () 0 0)
3 'vec_add_' 'vector_def' 'vec_add_' 1 ((PROCEDURE UNKNOWN-INTENT
MODULE-PROC DECL UNKNOWN 0 0 FUNCTION) (DERIVED 105 0 0 DERIVED ()) 149
0 (150 151) () 152 () () () 0 0)
119 'matrixt' 'dense_matrix_def' 'matrixt' 1 ((DERIVED UNKNOWN-INTENT
UNKNOWN-PROC UNKNOWN UNKNOWN 0 0 ALLOC_COMP) (UNKNOWN 0 0 0 UNKNOWN ())
0 0 () () 0 ((153 'dat' (REAL 8 0 0 REAL ()) (2 0 DEFERRED () () () ())
(UNKNOWN-FL UNKNOWN-INTENT UNKNOWN-PROC UNKNOWN UNKNOWN 0 0 ALLOCATABLE
DIMENSION) UNKNOWN-ACCESS ())) PUBLIC (() () () ()) () 0 0 72249915)
139 'new' '' 'new' 136 ((VARIABLE UNKNOWN-INTENT UNKNOWN-PROC UNKNOWN
UNKNOWN 0 0 RESULT) (DERIVED 119 0 0 DERIVED ()) 0 0 () () 0 () () () 0
0)
123 'new' '' 'new' 120 ((VARIABLE UNKNOWN-INTENT UNKNOWN-PROC UNKNOWN
UNKNOWN 0 0 RESULT) (DERIVED 119 0 0 DERIVED ()) 0 0 () () 0 () () () 0
0)
131 'new' '' 'new' 128 ((VARIABLE UNKNOWN-INTENT UNKNOWN-PROC UNKNOWN
UNKNOWN 0 0 RESULT) (DERIVED 105 0 0 DERIVED ()) 0 0 () () 0 () () () 0
0)
130 'other' '' 'other' 128 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0
0 DUMMY) (DERIVED 105 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
129 'self' '' 'self' 128 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (DERIVED 119 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
122 'k' '' 'k' 120 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0 DUMMY)
(REAL 8 0 0 REAL ()) 0 0 () () 0 () () () 0 0)
121 'self' '' 'self' 120 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (DERIVED 119 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
133 'self' '' 'self' 132 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (DERIVED 119 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
135 'new' '' 'new' 132 ((VARIABLE UNKNOWN-INTENT UNKNOWN-PROC UNKNOWN
UNKNOWN 0 0 RESULT) (DERIVED 119 0 0 DERIVED ()) 0 0 () () 0 () () () 0
0)
134 'other' '' 'other' 132 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0
0 DUMMY) (DERIVED 119 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
125 'k' '' 'k' 124 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0 DUMMY)
(REAL 8 0 0 REAL ()) 0 0 () () 0 () () () 0 0)
127 'new' '' 'new' 124 ((VARIABLE UNKNOWN-INTENT UNKNOWN-PROC UNKNOWN
UNKNOWN 0 0 RESULT) (DERIVED 119 0 0 DERIVED ()) 0 0 () () 0 () () () 0
0)
126 'self' '' 'self' 124 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (DERIVED 119 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
138 'other' '' 'other' 136 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0
0 DUMMY) (DERIVED 119 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
52 'self' '' 'self' 51 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (DERIVED 30 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
53 'i' '' 'i' 51 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0 DUMMY) (
INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
54 'j' '' 'j' 51 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0 DUMMY) (
INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
55 'v' '' 'v' 51 ((VARIABLE UNKNOWN-INTENT UNKNOWN-PROC UNKNOWN UNKNOWN
0 0 RESULT) (REAL 8 0 0 REAL ()) 0 0 () () 0 () () () 0 0)
57 'self' '' 'self' 56 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (DERIVED 30 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
58 'i' '' 'i' 56 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0 DUMMY) (
INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
59 'j' '' 'j' 56 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0 DUMMY) (
INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
60 'exc' '' 'exc' 56 ((VARIABLE OUT UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
61 'v' '' 'v' 56 ((VARIABLE UNKNOWN-INTENT UNKNOWN-PROC UNKNOWN UNKNOWN
0 0 RESULT) (REAL 8 0 0 REAL ()) 0 0 () () 0 () () () 0 0)
63 'self' '' 'self' 62 ((VARIABLE INOUT UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (DERIVED 30 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
64 'i' '' 'i' 62 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0 DUMMY) (
INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
65 'j' '' 'j' 62 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0 DUMMY) (
INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
66 'v' '' 'v' 62 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0 DUMMY) (
REAL 8 0 0 REAL ()) 0 0 () () 0 () () () 0 0)
68 'self' '' 'self' 67 ((VARIABLE INOUT UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (DERIVED 30 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
69 'i' '' 'i' 67 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0 DUMMY) (
INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
70 'j' '' 'j' 67 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0 DUMMY) (
INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
71 'v' '' 'v' 67 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0 DUMMY) (
REAL 8 0 0 REAL ()) 0 0 () () 0 () () () 0 0)
72 'exc' '' 'exc' 67 ((VARIABLE OUT UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
74 'self' '' 'self' 73 ((VARIABLE INOUT UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (DERIVED 30 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
75 'decomp' '' 'decomp' 73 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0
0 DIMENSION DUMMY) (REAL 8 0 0 REAL ()) 0 0 () (2 0 ASSUMED_SHAPE (
CONSTANT (INTEGER 4 0 0 INTEGER ()) 0 '1') () (CONSTANT (INTEGER 4 0 0
INTEGER ()) 0 '1') ()) 0 () () () 0 0)
77 'self' '' 'self' 76 ((VARIABLE INOUT UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (DERIVED 30 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
78 'decomp' '' 'decomp' 76 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0
0 DIMENSION DUMMY) (REAL 8 0 0 REAL ()) 0 0 () (2 0 ASSUMED_SHAPE (
CONSTANT (INTEGER 4 0 0 INTEGER ()) 0 '1') () (CONSTANT (INTEGER 4 0 0
INTEGER ()) 0 '1') ()) 0 () () () 0 0)
79 'exc' '' 'exc' 76 ((VARIABLE OUT UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
81 'self' '' 'self' 80 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (DERIVED 30 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
82 'is_decomposed' '' 'is_decomposed' 80 ((VARIABLE UNKNOWN-INTENT
UNKNOWN-PROC UNKNOWN UNKNOWN 0 0 RESULT) (LOGICAL 4 0 0 LOGICAL ()) 0 0
() () 0 () () () 0 0)
84 'self' '' 'self' 83 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (DERIVED 30 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
85 'other' '' 'other' 83 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (DERIVED 30 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
86 'new' '' 'new' 83 ((VARIABLE UNKNOWN-INTENT UNKNOWN-PROC UNKNOWN
UNKNOWN 0 0 RESULT) (DERIVED 30 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
88 'self' '' 'self' 87 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (DERIVED 30 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
89 'other' '' 'other' 87 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (DERIVED 30 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
90 'exc' '' 'exc' 87 ((VARIABLE OUT UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
91 'new' '' 'new' 87 ((VARIABLE UNKNOWN-INTENT UNKNOWN-PROC UNKNOWN
UNKNOWN 0 0 RESULT) (DERIVED 30 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
93 'self' '' 'self' 92 ((VARIABLE INOUT UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (DERIVED 30 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
94 'other' '' 'other' 92 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (DERIVED 119 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
95 'ind' '' 'ind' 92 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DIMENSION DUMMY) (INTEGER 4 0 0 INTEGER ()) 0 0 () (1 0 ASSUMED_SHAPE (
CONSTANT (INTEGER 4 0 0 INTEGER ()) 0 '1') ()) 0 () () () 0 0)
97 'self' '' 'self' 96 ((VARIABLE INOUT UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (DERIVED 30 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
98 'other' '' 'other' 96 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (DERIVED 119 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
99 'ind' '' 'ind' 96 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DIMENSION DUMMY) (INTEGER 4 0 0 INTEGER ()) 0 0 () (1 0 ASSUMED_SHAPE (
CONSTANT (INTEGER 4 0 0 INTEGER ()) 0 '1') ()) 0 () () () 0 0)
100 'exc' '' 'exc' 96 ((VARIABLE OUT UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
102 'self' '' 'self' 101 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (DERIVED 30 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
103 'k' '' 'k' 101 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0 DUMMY)
(REAL 8 0 0 REAL ()) 0 0 () () 0 () () () 0 0)
104 'new' '' 'new' 101 ((VARIABLE UNKNOWN-INTENT UNKNOWN-PROC UNKNOWN
UNKNOWN 0 0 RESULT) (DERIVED 30 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
116 'k' '' 'k' 115 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0 DUMMY)
(REAL 8 0 0 REAL ()) 0 0 () () 0 () () () 0 0)
117 'self' '' 'self' 115 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (DERIVED 30 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
118 'new' '' 'new' 115 ((VARIABLE UNKNOWN-INTENT UNKNOWN-PROC UNKNOWN
UNKNOWN 0 0 RESULT) (DERIVED 30 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
107 'self' '' 'self' 106 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (DERIVED 30 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
108 'other' '' 'other' 106 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0
0 DUMMY) (DERIVED 105 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
109 'new' '' 'new' 106 ((VARIABLE UNKNOWN-INTENT UNKNOWN-PROC UNKNOWN
UNKNOWN 0 0 RESULT) (DERIVED 105 0 0 DERIVED ()) 0 0 () () 0 () () () 0
0)
111 'self' '' 'self' 110 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (DERIVED 30 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
112 'other' '' 'other' 110 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0
0 DUMMY) (DERIVED 105 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
113 'exc' '' 'exc' 110 ((VARIABLE OUT UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
114 'new' '' 'new' 110 ((VARIABLE UNKNOWN-INTENT UNKNOWN-PROC UNKNOWN
UNKNOWN 0 0 RESULT) (DERIVED 105 0 0 DERIVED ()) 0 0 () () 0 () () () 0
0)
150 'self' '' 'self' 149 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (DERIVED 105 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
151 'other' '' 'other' 149 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0
0 DUMMY) (DERIVED 105 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
152 'new' '' 'new' 149 ((VARIABLE UNKNOWN-INTENT UNKNOWN-PROC UNKNOWN
UNKNOWN 0 0 RESULT) (DERIVED 105 0 0 DERIVED ()) 0 0 () () 0 () () () 0
0)
146 'self' '' 'self' 145 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (DERIVED 105 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
147 'k' '' 'k' 145 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0 DUMMY)
(REAL 8 0 0 REAL ()) 0 0 () () 0 () () () 0 0)
142 'k' '' 'k' 141 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0 DUMMY)
(REAL 8 0 0 REAL ()) 0 0 () () 0 () () () 0 0)
143 'self' '' 'self' 141 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (DERIVED 105 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
144 'new' '' 'new' 141 ((VARIABLE UNKNOWN-INTENT UNKNOWN-PROC UNKNOWN
UNKNOWN 0 0 RESULT) (DERIVED 105 0 0 DERIVED ()) 0 0 () () 0 () () () 0
0)
148 'new' '' 'new' 145 ((VARIABLE UNKNOWN-INTENT UNKNOWN-PROC UNKNOWN
UNKNOWN 0 0 RESULT) (DERIVED 105 0 0 DERIVED ()) 0 0 () () 0 () () () 0
0)
)
('bandsymmatrixt' 0 30)
! ------------------------------------------------------------------------
!> \brief Module for testing Banded Symmetric Matrix data type
! ------------------------------------------------------------------------
MODULE band_sym_matrix_test
USE fruit !> Unit testing framework
USE log_message_control !> Printing log/error messages
USE log_messages !> Log/error codes
USE band_sym_matrix_def !> Banded Symmetric Matrix data type
USE dense_matrix_def !> Dense Matrix data type
USE vector_def !> Vector data type
IMPLICIT NONE
CONTAINS
! ------------------------------------------------------------------------
!> \test Test for OK exception message on allocation
!!
!! \param unit_name Name of unit test (for FRUIT)
!! \param test Test banded symmetric matrix
!! \param testName Filename for log file (required for exceptions)
!! \param hbw Half bandwidth of the matrix
!! \param n Number of rows/columns in the matrix
!! \param expMsg Expected log message
!! \param actMsg Actual log message
!!
!! This test initializes a bandSymMatrixT and makes sure that the
!! exception message is OK (i.e. allocation did not fail).
! ------------------------------------------------------------------------
SUBROUTINE test_bsm_allocation_MSG
CHARACTER (LEN=*), PARAMETER :: unit_name = 'test_bsm_allocation_MSG'
TYPE(bandSymMatrixT) :: test
CHARACTER (LEN=*), PARAMETER :: testName = 'testName'
INTEGER, PARAMETER :: hbw=3,n=10
INTEGER, PARAMETER :: expMsg=OK
INTEGER :: actMsg
!> initialize unit test
CALL set_unit_name(unit_name)
!> initialize log message file
CALL log_setFileName(testName)
CALL log_initLogFile()
!> initialize matrix and check the exception
CALL bsm_init(test, hbw,n, actMsg)
CALL assertEquals(expMsg,actMsg)
!> finalize log file and deallocate matrix
CALL log_closeLogFile()
CALL bsm_clean(test)
END SUBROUTINE test_bsm_allocation_MSG
! ------------------------------------------------------------------------
!> \test Test for SZE exception message on allocation
!!
!! \param unit_name Name of unit test (for FRUIT)
!! \param test Test banded symmetric matrix
!! \param testName Filename for log file (required for exceptions)
!! \param hbw Half bandwidth of the matrix
!! \param n Number of rows/columns in the matrix
!! \param expMsg Expected log message
!! \param actMsg Actual log message
!!
!! This test attempts to initialize a bandSymMatrixT with invalid size
!! parameters and verifies that the correct exception is returned.
! ------------------------------------------------------------------------
SUBROUTINE test_bsm_allocation_SZE
CHARACTER (LEN=*), PARAMETER :: unit_name = 'test_bsm_allocation_SZE'
TYPE(bandSymMatrixT) :: test
CHARACTER (LEN=*), PARAMETER :: testName = 'testName'
INTEGER, PARAMETER :: hbw=3,n=10
INTEGER, PARAMETER :: expMsg=SZE
INTEGER :: actMsg
!> initialize unit test
CALL set_unit_name(unit_name)
!> initialize log file
CALL log_setFileName(testName)
CALL log_initLogFile()
!> try to initialize with hbw=-1
CALL bsm_init(test, -1,n, actMsg)
CALL assertEquals(expMsg,actMsg)
!> try to initialize with n=-1
CALL bsm_init(test, hbw,-1, actMsg)
CALL assertEquals(expMsg,actMsg)
!> finalize log file and deallocate matrix
CALL log_closeLogFile()
CALL bsm_clean(test)
END SUBROUTINE test_bsm_allocation_SZE
! ------------------------------------------------------------------------
!> \test Test for initialization of matrix data to zeros.
!!
!! \param unit_name Name of unit test (for FRUIT)
!! \param test Test banded symmetric matrix
!! \param hbw Half bandwidth of the matrix
!! \param n Number of rows/columns in the matrix
!! \param expDat Expected initial contents of matrix data
!!
!! This test initializes a bandSymMatrixT and ensures that the data is
!! initialized to zeros.
! ------------------------------------------------------------------------
SUBROUTINE test_bsm_allocation_DAT
CHARACTER (LEN=*), PARAMETER :: unit_name = 'test_bsm_allocation_DAT'
TYPE(bandSymMatrixT) :: test
INTEGER, PARAMETER :: hbw=3,n=10
DOUBLE PRECISION, DIMENSION(hbw,n) :: expDat
!> initialize unit test
CALL set_unit_name(unit_name)
!> set up the expected data (note: Fortran uses column-major storage)
expDat = RESHAPE( (/ &
0.d0,0.d0,0.d0,0.d0,0.d0,0.d0,0.d0,0.d0,0.d0,0.d0, &
0.d0,0.d0,0.d0,0.d0,0.d0,0.d0,0.d0,0.d0,0.d0,0.d0, &
0.d0,0.d0,0.d0,0.d0,0.d0,0.d0,0.d0,0.d0,0.d0,0.d0 &
/), SHAPE(expDat) )
!> initialize matrix and test actual data
CALL bsm_init(test, hbw,n)
CALL assertEquals(expDat,test%dat, hbw,n)
CALL assertEquals(expDat,test%decomp, hbw,n)
!> deallocate matrix
CALL bsm_clean(test)
END SUBROUTINE test_bsm_allocation_DAT
! ------------------------------------------------------------------------
!> \test Test for deallocation
!!
!! \param unit_name Name of unit test (for FRUIT)
!! \param test Test banded symmetric matrix
!! \param hbw Half bandwidth of the matrix
!! \param n Number of rows/columns in the matrix
!! \param expBefore Expected allocation status before deallocation
!! \param expAfter Expected allocation status after deallocation
!! \param actBefore Actual allocation status before deallocation
!! \param actAfter Actual allocation status after deallocation
!!
!! This test initializes a bandSymMatrixT and ensures that it is
!! allocated. It then deallocates the object and ensures that it has
!! been deallocated.
! ------------------------------------------------------------------------
SUBROUTINE test_bsm_deallocation
CHARACTER (LEN=*), PARAMETER :: unit_name = 'test_bsm_deallocation'
TYPE(bandSymMatrixT) :: test
INTEGER, PARAMETER :: hbw=3,n=10
LOGICAL, PARAMETER :: expBefore = .TRUE.
LOGICAL, PARAMETER :: expAfter = .FALSE.
LOGICAL :: actBefore, actAfter
!> initialize unit test
CALL set_unit_name(unit_name)
!> initialize the matrix
CALL bsm_init(test, hbw,n)
!> make sure dat is allocated
actBefore = ALLOCATED(test%dat)
CALL assertEquals(expBefore,actBefore)
!> make sure decomp is allocated
actBefore = ALLOCATED(test%decomp)
CALL assertEquals(expBefore,actBefore)
!> deallocate the matrix
CALL bsm_clean(test)
!> make sure dat is deallocated
actAfter = ALLOCATED(test%dat)
CALL assertEquals(expAfter,actAfter)
!> make sure decomp is deallocated
actAfter = ALLOCATED(test%decomp)
CALL assertEquals(expAfter,actAfter)
END SUBROUTINE test_bsm_deallocation
! ------------------------------------------------------------------------
!> \test Test for number of rows when matrix is not allocated
!!
!! \param unit_name Name of unit test (for FRUIT)
!! \param test Test banded symmetric matrix
!! \param expected Expected number of rows
!! \param actual Actual number of rows
!!
!! This test makes sure that the number of rows is returned as 0 when
!! the matrix is not allocated
! ------------------------------------------------------------------------
SUBROUTINE test_bsm_num_rows_not_allocated
CHARACTER (LEN=*), PARAMETER :: unit_name = 'test_bsm_num_rows_not_allocated'
TYPE(bandSymMatrixT) :: test
INTEGER, PARAMETER :: expected = 0
INTEGER :: actual
!> initialize unit test
CALL set_unit_name(unit_name)
!> check number of rows
actual = bsm_numRows(test)
CALL assertEquals(expected, actual)
END SUBROUTINE test_bsm_num_rows_not_allocated
! ------------------------------------------------------------------------
!> \test Test for number of rows when matrix is allocated
!!
!! \param unit_name Name of unit test (for FRUIT)
!! \param test Test banded symmetric matrix
!! \param hbw Half bandwidth of the matrix
!! \param n Number of rows/columns in the matrix
!! \param expected Expected number of rows
!! \param actual Actual number of rows
!!
!! This test checks that the number of rows returned is correct when the
!! matrix is allocated.
! ------------------------------------------------------------------------
SUBROUTINE test_bsm_num_rows_allocated
CHARACTER (LEN=*), PARAMETER :: unit_name = 'test_bsm_num_rows_allocated'
TYPE(bandSymMatrixT) :: test
INTEGER, PARAMETER :: hbw=3,n=10
INTEGER, PARAMETER :: expected = n
INTEGER :: actual
!> initialize unit test
CALL set_unit_name(unit_name)
!> initialize the matrix
CALL bsm_init(test, hbw,n)
!> check number of rows
actual = bsm_numRows(test)
CALL assertEquals(expected, actual)
!> deallocate the matrix
CALL bsm_clean(test)
END SUBROUTINE test_bsm_num_rows_allocated
! ------------------------------------------------------------------------
!> \test Test for half bandwidth when matrix is not allocated
!!
!! \param unit_name Name of unit test (for FRUIT)
!! \param test Test banded symmetric matrix
!! \param expected Expected number of rows
!! \param actual Actual number of rows
!!
!! This test makes sure that the half bandwidth is returned as 0 when
!! the matrix is not allocated
! ------------------------------------------------------------------------
SUBROUTINE test_bsm_half_bw_not_allocated
CHARACTER (LEN=*), PARAMETER :: unit_name = 'test_bsm_half_bw_not_allocated'
TYPE(bandSymMatrixT) :: test
INTEGER, PARAMETER :: expected = 0
INTEGER :: actual
!> initialize unit test
CALL set_unit_name(unit_name)
!> check the half bandwidth
actual = bsm_halfBW(test)
CALL assertEquals(expected, actual)
END SUBROUTINE test_bsm_half_bw_not_allocated
! ------------------------------------------------------------------------
!> \test Test for half bandwidth when matrix is allocated
!!
!! \param unit_name Name of unit test (for FRUIT)
!! \param test Test banded symmetric matrix
!! \param hbw Half bandwidth of the matrix
!! \param n Number of rows/columns in the matrix
!! \param expected Expected number of rows
!! \param actual Actual number of rows
!!
!! This test checks that the half bandwidth returned is correct when the
!! matrix is allocated.
! ------------------------------------------------------------------------
SUBROUTINE test_bsm_half_bw_allocated
CHARACTER (LEN=*), PARAMETER :: unit_name = 'test_bsm_half_bw_allocated'
TYPE(bandSymMatrixT) :: test
INTEGER, PARAMETER :: hbw=3,n=10
INTEGER, PARAMETER :: expected = hbw
INTEGER :: actual
!> initialize unit test
CALL set_unit_name(unit_name)
!> initialize the matrix
CALL bsm_init(test, hbw,n)
!> check the half bandwidth
actual = bsm_halfBW(test)
CALL assertEquals(expected, actual)
!> deallocate the matrix
CALL bsm_clean(test)
END SUBROUTINE test_bsm_half_bw_allocated
! ------------------------------------------------------------------------
!> \test Test for POSIT exception from bsm_get
!!
!! \param unit_name Name of unit test (for FRUIT)
!! \param test Test banded symmetric matrix
!! \param testName Filename for log file (required for exceptions)
!! \param hbw Half bandwidth of the matrix
!! \param n Number of rows/columns in the matrix
!! \param expMsg Expected log message
!! \param actMsg Actual log message
!! \param v Dummy variable for get function return
!!
!! This test checks that a POSIT exception is returned when the requested
!! location is not inside the matrix.
! ------------------------------------------------------------------------
SUBROUTINE test_bsm_get_POSIT
CHARACTER (LEN=*), PARAMETER :: unit_name = 'test_bsm_get_POSIT'
TYPE(bandSymMatrixT) :: test
CHARACTER (LEN=*), PARAMETER :: testName = 'testName'
INTEGER, PARAMETER :: hbw=3,n=10
INTEGER, PARAMETER :: expMsg = POSIT
INTEGER :: actMsg
DOUBLE PRECISION :: v
!> initialize unit test
CALL set_unit_name(unit_name)
!> initialize log file
CALL log_setFileName(testName)
CALL log_initLogFile()
!> initialize matrix
CALL bsm_init(test, hbw,n)
!> try to get beyond last row
v = bsm_get(test, n+1,n, actMsg)
CALL assertEquals(expMsg,actMsg)
!> try to get before first row
v = bsm_get(test, 0,n, actMsg)
CALL assertEquals(expMsg,actMsg)
!> try to get after last column
v = bsm_get(test, n,n+1, actMsg)
CALL assertEquals(expMsg,actMsg)
!> try to get before first column
v = bsm_get(test, n,0, actMsg)
CALL assertEquals(expMsg,actMsg)
!> finalize the log file and deallocate the matrix
CALL log_closeLogFile()
CALL bsm_clean(test)
END SUBROUTINE test_bsm_get_POSIT
! ------------------------------------------------------------------------
!> \test Test for correct value return from bsm_get
!!
!! \param unit_name Name of unit test (for FRUIT)
!! \param test Test banded symmetric matrix
!! \param hbw Half bandwidth of the matrix
!! \param n Number of rows/columns in the matrix
!! \param i Row index for test location
!! \param j Column index for test location
!! \param expVal Expected data value
!! \param actVal Actual data value
!!
!! This test checks that the correct value is returned from the get
!! access program (i.e. that the location is interpreted correctly from
!! the unpacked indices).
! ------------------------------------------------------------------------
SUBROUTINE test_bsm_get_VAL
CHARACTER (LEN=*), PARAMETER :: unit_name = 'test_bsm_get_VAL'
TYPE(bandSymMatrixT) :: test
INTEGER, PARAMETER :: hbw=3,n=10
INTEGER, PARAMETER :: i=3,j=5
DOUBLE PRECISION, PARAMETER :: expVal = 3.d0
DOUBLE PRECISION :: actVal
!> initialize unit test
CALL set_unit_name(unit_name)
!> initialize the matrix
CALL bsm_init(test, hbw,n)
!> set the value manually in the internal data structure
test%dat(hbw+i-j,j) = expVal
!> get the value using the access program
actVal = bsm_get(test, i,j)
CALL assertEquals(expVal,actVal)
!> get the value using the access program (testing symmetry)
actVal = bsm_get(test, j,i)
CALL assertEquals(expVal,actVal)
!> deallocate the matrix
CALL bsm_clean(test)
END SUBROUTINE test_bsm_get_VAL
! ------------------------------------------------------------------------
!> \test Test for POSIT exception from bsm_set
!!
!! \param unit_name Name of unit test (for FRUIT)
!! \param test Test banded symmetric matrix
!! \param testName Filename for log file (required for exceptions)
!! \param hbw Half bandwidth of the matrix
!! \param n Number of rows/columns in the matrix
!! \param expMsg Expected log message
!! \param actMsg Actual log message
!! \param v Dummy variable for set function input
!!
!! This test checks that a POSIT exception is returned when the requested
!! location is not inside the matrix.
! ------------------------------------------------------------------------
SUBROUTINE test_bsm_set_POSIT
CHARACTER (LEN=*), PARAMETER :: unit_name = 'test_bsm_set_POSIT'
TYPE(bandSymMatrixT) :: test
CHARACTER (LEN=*), PARAMETER :: testName = 'testName'
INTEGER, PARAMETER :: hbw=3,n=10
INTEGER, PARAMETER :: expMsg = POSIT
DOUBLE PRECISION, PARAMETER :: v=0.d0
INTEGER :: actMsg
!> initialize unit test
CALL set_unit_name(unit_name)
!> initialize the log file
CALL log_setFileName(testName)
CALL log_initLogFile()
!> initialize the matrix
CALL bsm_init(test, hbw,n)
!> try to set after last row
CALL bsm_set(test, n+1,n,v, actMsg)
CALL assertEquals(expMsg,actMsg)
!> try to set before first row
CALL bsm_set(test, 0,n,v, actMsg)
CALL assertEquals(expMsg,actMsg)
!> try to set after last column
CALL bsm_set(test, n,n+1,v, actMsg)
CALL assertEquals(expMsg,actMsg)
!> try to set before first column
CALL bsm_set(test, n,0,v, actMsg)
CALL assertEquals(expMsg,actMsg)
!> finalize log file and deallocate matrix
CALL log_closeLogFile()
CALL bsm_clean(test)
END SUBROUTINE test_bsm_set_POSIT
! ------------------------------------------------------------------------
!> \test Test for correct value return after bsm_set
!!
!! \param unit_name Name of unit test (for FRUIT)
!! \param test Test banded symmetric matrix
!! \param hbw Half bandwidth of the matrix
!! \param n Number of rows/columns in the matrix
!! \param i Row index for test location
!! \param j Column index for test location
!! \param expVal Expected data value
!! \param actVal Actual data value
!! \param reset For resetting data value before symmetry test
!!
!! This test checks that the correct value is entered by the set
!! access program (i.e. that the location is interpreted correctly from
!! the unpacked indices).
! ------------------------------------------------------------------------
SUBROUTINE test_bsm_set_VAL
CHARACTER (LEN=*), PARAMETER :: unit_name = 'test_bsm_set_VAL'
TYPE(bandSymMatrixT) :: test
INTEGER, PARAMETER :: hbw=3,n=10
INTEGER, PARAMETER :: i=3,j=5
DOUBLE PRECISION, PARAMETER :: expVal = 3.d0
DOUBLE PRECISION, PARAMETER :: reset = 0.d0
DOUBLE PRECISION :: actVal
!> initialize unit test
CALL set_unit_name(unit_name)
!> initialize the matrix
CALL bsm_init(test, hbw,n)
!> set the value
CALL bsm_set(test, i,j,expVal)
actVal = bsm_get(test, i,j)
CALL assertEquals(expVal,actVal)
!> set the value (symmetry)
CALL bsm_set(test, i,j,reset)
CALL bsm_set(test, j,i,expVal)
actVal = bsm_get(test, i,j)
CALL assertEquals(expVal,actVal)
!> deallocate matrix
CALL bsm_clean(test)
END SUBROUTINE test_bsm_set_VAL
! ------------------------------------------------------------------------
!> \test Test for DIMEN exception on setting decomposed matrix data
!!
!! \param unit_name Name of unit test (for FRUIT)
!! \param test Test banded symmetric matrix
!! \param testName Filename for log file (required for exceptions)
!! \param hbw Half bandwidth of the matrix
!! \param n Number of rows/columns in the matrix
!! \param expMsg Expected log message
!! \param actMsg Actual log message
!! \param decomp Dummy data that has incorrect dimensions
!!
!! This test checks that a DIMEN exception is returned when the
!! decomposed data has incorrect dimensions. That is, not (hbw,n).
! ------------------------------------------------------------------------
SUBROUTINE test_bsm_set_decomp_DIMEN
CHARACTER (LEN=*), PARAMETER :: unit_name = 'test_bsm_set_decomp_DIMEN'
TYPE(bandSymMatrixT) :: test
CHARACTER (LEN=*), PARAMETER :: testName = 'testName'
INTEGER, PARAMETER :: hbw=3,n=10
INTEGER, PARAMETER :: expMsg = DIMEN
DOUBLE PRECISION, DIMENSION(hbw-1,n) :: decomp
INTEGER :: actMsg
!> initialize unit test
CALL set_unit_name(unit_name)
!> set up dummy data (note: Fortran uses column-major storage)
decomp = RESHAPE( (/ &
0.d0,0.d0,0.d0,0.d0,0.d0,0.d0,0.d0,0.d0,0.d0,0.d0, &
0.d0,0.d0,0.d0,0.d0,0.d0,0.d0,0.d0,0.d0,0.d0,0.d0 &
/), SHAPE(decomp) )
!> initialize log file
CALL log_setFileName(testName)
CALL log_initLogFile()
!> initialize matrix
CALL bsm_init(test, hbw,n)
!> try to set the decomposed data
CALL bsm_setDecomp(test,decomp, actMsg)
CALL assertEquals(expMsg, actMsg)
!> finalize log file and deallocate matrix
CALL log_closeLogFile()
CALL bsm_clean(test)
END SUBROUTINE test_bsm_set_decomp_DIMEN
! ------------------------------------------------------------------------
!> \test Test for correct setting of decomposed data
!!
!! \param unit_name Name of unit test (for FRUIT)
!! \param test Test banded symmetric matrix
!! \param hbw Half bandwidth of the matrix
!! \param n Number of rows/columns in the matrix
!! \param expDecomp Expected decomposed data
!!
!! This test checks that the decomposed data is correctly set.
! ------------------------------------------------------------------------
SUBROUTINE test_bsm_set_decomp_VAL
CHARACTER (LEN=*), PARAMETER :: unit_name = 'test_bsm_set_decomp_VAL'
TYPE(bandSymMatrixT) :: test
INTEGER, PARAMETER :: hbw=3,n=10
DOUBLE PRECISION, DIMENSION(hbw,n) :: expDecomp
!> initialize unit test
CALL set_unit_name(unit_name)
!> set up decomposed data (note: Fortran uses column-major storage)
expDecomp = RESHAPE((/ &
0.d0,0.d0,1.d0,0.d0,2.d0,3.d0,4.d0,5.d0,6.d0,7.d0, &
8.d0,9.d0,0.d0,1.d0,2.d0,3.d0,4.d0,5.d0,6.d0,7.d0, &
8.d0,9.d0,0.d0,1.d0,2.d0,3.d0,4.d0,5.d0,6.d0,7.d0 &
/), SHAPE(expDecomp) )
!> initialize matrix
CALL bsm_init(test, hbw,n)
!> set the decomposed data
CALL bsm_setDecomp(test,expDecomp)
CALL assertEquals(expDecomp, test%decomp, hbw,n)
!> deallocate matrix
CALL bsm_clean(test)
END SUBROUTINE test_bsm_set_decomp_VAL
! ------------------------------------------------------------------------
!> \test Test for correct status of switch for decomposed data
!!
!! \param unit_name Name of unit test (for FRUIT)
!! \param test Test banded symmetric matrix
!! \param hbw Half bandwidth of the matrix
!! \param n Number of rows/columns in the matrix
!! \param expBefore Expected value of switch before setting decomp
!! \param expAfter Expected value of switch after setting decomp
!! \param expClean Expected value of switch after deallocating matrix
!! \param actBefore Actual value of switch before setting decomp
!! \param actAfter Actual value of switch after setting decomp
!! \param actClean Actual value of switch after deallocating matrix
!! \param decomp Dummy decomposed data
!!
!! This test checks that the presence of decomposed data is correctly
!! identified.
! ------------------------------------------------------------------------
SUBROUTINE test_bsm_is_decomposed
CHARACTER (LEN=*), PARAMETER :: unit_name = 'test_bsm_is_decomposed'
TYPE(bandSymMatrixT) :: test
INTEGER, PARAMETER :: hbw=3,n=10
LOGICAL, PARAMETER :: expBefore = .FALSE.
LOGICAL, PARAMETER :: expAfter = .TRUE.
LOGICAL, PARAMETER :: expClean = .FALSE.
DOUBLE PRECISION, DIMENSION(hbw,n) :: decomp
LOGICAL :: actBefore, actAfter, actClean
!> initialize unit test
CALL set_unit_name(unit_name)
!> initialize matrix and check initial value of switch
CALL bsm_init(test, hbw,n)
actBefore = bsm_isDecomposed(test)
CALL assertEquals(expBefore,actBefore)
!> set up decomposed data (note: Fortran uses column-major storage)
decomp = RESHAPE( (/ &
0.d0,0.d0,1.d0,0.d0,2.d0,3.d0,4.d0,5.d0,6.d0,7.d0, &
8.d0,9.d0,0.d0,1.d0,2.d0,3.d0,4.d0,5.d0,6.d0,7.d0, &
8.d0,9.d0,0.d0,1.d0,2.d0,3.d0,4.d0,5.d0,6.d0,7.d0 &
/), SHAPE(decomp) )
!> set decomposed data
CALL bsm_setDecomp(test,decomp)
actAfter = bsm_isDecomposed(test)
CALL assertEquals(expAfter,actAfter)
!> deallocate matrix and check final value of decomposed switch
CALL bsm_clean(test)
actClean = bsm_isDecomposed(test)
CALL assertEquals(expClean,actClean)
END SUBROUTINE test_bsm_is_decomposed
! ------------------------------------------------------------------------
!> \test Test for DIMEN exception when adding matrices
!!
!! \param unit_name Name of unit test (for FRUIT)
!! \param test1 First input banded symmetric matrix
!! \param test2 Second input banded symmetric matrix
!! \param test3 Output banded symmetric matrix
!! \param testName Filename for log file (required for exceptions)
!! \param hbw Half bandwidth of the matrix
!! \param n Number of rows/columns in the matrix
!! \param expMsg Expected exception message
!! \param actMsg Actual exception message
!!
!! This test checks that a DIMEN exception is raised when matrices with
!! incompatible dimensions are added.
! ------------------------------------------------------------------------
SUBROUTINE test_bsm_add_DIMEN
CHARACTER (LEN=*), PARAMETER :: unit_name = 'test_bsm_add_DIMEN'
TYPE(bandSymMatrixT) :: test1, test2, test3
CHARACTER (LEN=*), PARAMETER :: testName = 'testName'
INTEGER, PARAMETER :: hbw=3,n=10
INTEGER, PARAMETER :: expMsg=DIMEN
INTEGER :: actMsg
!> initialize unit test
CALL set_unit_name(unit_name)
!> initialize log file
CALL log_setFileName(testName)
CALL log_initLogFile()
!> initialize input matrices (data contents not important)
CALL bsm_init(test1, hbw,n)
CALL bsm_init(test2, hbw,n+1) !> note different dimension
!> attempt to add the matrices
test3 = bsm_add(test1,test2, actMsg)
CALL assertEquals(expMsg,actMsg)
!> finalize log file and deallocate matrices
CALL log_closeLogFile()
CALL bsm_clean(test1)
CALL bsm_clean(test2)
CALL bsm_clean(test3)
END SUBROUTINE test_bsm_add_DIMEN
! ------------------------------------------------------------------------
!> \test Test for correct addition of matrices
!!
!! \param unit_name Name of unit test (for FRUIT)
!! \param test1 First input banded symmetric matrix
!! \param test2 Second input banded symmetric matrix
!! \param test3 Output banded symmetric matrix
!! \param hbw Half bandwidth of the matrix
!! \param n Number of rows/columns in the matrix
!! \param expDat Expected result of addition
!!
!! This test checks that the correct result is obtained when adding two
!! banded symmetric matrices.
! ------------------------------------------------------------------------
SUBROUTINE test_bsm_add_VAL
CHARACTER (LEN=*), PARAMETER :: unit_name = 'test_bsm_add_VAL'
TYPE(bandSymMatrixT) :: test1, test2, test3
INTEGER, PARAMETER :: hbw=3,n=10
DOUBLE PRECISION, DIMENSION(hbw,n) :: expDat
INTEGER :: i,j !> loop variables
!> initialize unit test
CALL set_unit_name(unit_name)
!> initialize expected result (note: Fortran uses column-major storage)
expDat = RESHAPE( (/ &
0.d0,0.d0,3.d0,0.d0,3.d0,3.d0,1.d0,3.d0,3.d0,1.d0, &
3.d0,3.d0,1.d0,3.d0,3.d0,1.d0,3.d0,3.d0,1.d0,3.d0, &
3.d0,1.d0,3.d0,3.d0,1.d0,3.d0,3.d0,1.d0,3.d0,3.d0 &
/), SHAPE(expDat) )
!> initialize first input matrix
!! (loop sets matrix on bands to all ones)
CALL bsm_init(test1, hbw,n)
DO i = 1,n
DO j = i,MIN(i+hbw-1,n)
CALL bsm_set(test1, i,j, 1.d0)
END DO
END DO
!> initialize second input matrix (note different bandwidth)
!! (loop sets matrix on bands to all twos)
CALL bsm_init(test2, hbw-1,n)
DO i = 1,n
DO j = i,MIN(i+(hbw-1)-1,n)
CALL bsm_set(test2, i,j, 2.d0)
END DO
END DO
!> add the matrices
test3 = bsm_add(test1,test2)
CALL assertEquals(expDat,test3%dat, hbw,n)
!> deallocate matrices
CALL bsm_clean(test1)
CALL bsm_clean(test2)
CALL bsm_clean(test3)
END SUBROUTINE test_bsm_add_VAL
! ------------------------------------------------------------------------
!> \test Test for correct addition of matrices ( with OPERATOR (+) )
!!
!! \param unit_name Name of unit test (for FRUIT)
!! \param test1 First input banded symmetric matrix
!! \param test2 Second input banded symmetric matrix
!! \param test3 Output banded symmetric matrix
!! \param hbw Half bandwidth of the matrix
!! \param n Number of rows/columns in the matrix
!! \param expDat Expected result of addition
!!
!! This test checks that the correct result is obtained when adding two
!! banded symmetric matrices using the (+) operator.
! ------------------------------------------------------------------------
SUBROUTINE test_bsm_add_OP
CHARACTER (LEN=*), PARAMETER :: unit_name = 'test_bsm_add_OP'
TYPE(bandSymMatrixT) :: test1, test2, test3
INTEGER, PARAMETER :: hbw=3,n=10
DOUBLE PRECISION, DIMENSION(hbw,n) :: expDat
INTEGER :: i,j !> loop variables
!> initialize unit test
CALL set_unit_name(unit_name)
!> initialize expected result (note: Fortran uses column-major storage)
expDat = RESHAPE( (/ &
0.d0,0.d0,3.d0,0.d0,3.d0,3.d0,1.d0,3.d0,3.d0,1.d0, &
3.d0,3.d0,1.d0,3.d0,3.d0,1.d0,3.d0,3.d0,1.d0,3.d0, &
3.d0,1.d0,3.d0,3.d0,1.d0,3.d0,3.d0,1.d0,3.d0,3.d0 &
/), SHAPE(expDat) )
!> initialize first input matrix
!! (loop sets matrix on bands to all ones)
CALL bsm_init(test1, hbw,n)
DO i = 1,n
DO j = i,MIN(i+hbw-1,n)
CALL bsm_set(test1, i,j, 1.d0)
END DO
END DO
!> initialize second input matrix (note different bandwidth)
!! (loop sets matrix on bands to all twos)
CALL bsm_init(test2, hbw-1,n)
DO i = 1,n
DO j = i,MIN(i+(hbw-1)-1,n)
CALL bsm_set(test2, i,j, 2.d0)
END DO
END DO
!> add the matrices
test3 = test1 + test2
CALL assertEquals(expDat,test3%dat, hbw,n)
!> deallocate matrices
CALL bsm_clean(test1)
CALL bsm_clean(test2)
CALL bsm_clean(test3)
END SUBROUTINE test_bsm_add_OP
! ------------------------------------------------------------------------
!> \test Test for DIMEN exception when performing mapped add
!!
!! \param unit_name Name of unit test (for FRUIT)
!! \param test1 Test banded symmetric matrix
!! \param test2 Test input dense matrix
!! \param testName Filename for log file (required for exceptions)
!! \param hbw Half bandwidth of the matrix
!! \param n Number of rows/columns in the matrix
!! \param expMsg Expected exception message
!! \param actMsg Actual exception message
!! \param ind Mapping indices (size does not match test2)
!!
!! This test checks that a DIMEN exception is raised when mapped addition
!! is attempted with the dimension of the index array not matching the
!! dimensions of the dense matrix.
! ------------------------------------------------------------------------
SUBROUTINE test_bsm_mapped_add_DIMEN1
CHARACTER (LEN=*), PARAMETER :: unit_name = 'test_bsm_mapped_add_DIMEN1'
TYPE(bandSymMatrixT) :: test1
TYPE(matrixT) :: test2
CHARACTER (LEN=*), PARAMETER :: testName = 'testName'
INTEGER, PARAMETER :: hbw=3,n=10
INTEGER, PARAMETER :: expMsg=DIMEN
INTEGER, PARAMETER, DIMENSION(hbw-1) :: ind = (/ 1,2 /)
INTEGER :: actMsg
!> initialize unit test
CALL set_unit_name(unit_name)
!> initialize log file
CALL log_setFileName(testName)
CALL log_initLogFile()
!> initialize matrices (data content not important)
CALL bsm_init(test1, hbw,n)
CALL dm_init(test2, hbw,hbw)
!> try mapped add (note hbw=3, SIZE(ind)=2)
CALL bsm_mappedAdd(test1, test2,ind, actMsg)
CALL assertEquals(expMsg,actMsg)
!> finalize log file and deallocate matrices
CALL log_closeLogFile()
CALL bsm_clean(test1)
CALL dm_clean(test2)
END SUBROUTINE test_bsm_mapped_add_DIMEN1
! ------------------------------------------------------------------------
!> \test Test for DIMEN exception when performing mapped add
!!
!! \param unit_name Name of unit test (for FRUIT)
!! \param test1 Test banded symmetric matrix
!! \param test2 Test input dense matrix (not square)
!! \param testName Filename for log file (required for exceptions)
!! \param hbw Half bandwidth of the matrix
!! \param n Number of rows/columns in the matrix
!! \param expMsg Expected exception message
!! \param actMsg Actual exception message
!! \param ind Mapping indices
!!
!! This test checks that a DIMEN exception is raised when mapped addition
!! is attempted with a rectangular input dense matrix.
! ------------------------------------------------------------------------
SUBROUTINE test_bsm_mapped_add_DIMEN2
CHARACTER (LEN=*), PARAMETER :: unit_name = 'test_bsm_mapped_add_DIMEN2'
TYPE(bandSymMatrixT) :: test1
TYPE(matrixT) :: test2
CHARACTER (LEN=*), PARAMETER :: testName = 'testName'
INTEGER, PARAMETER :: hbw=3,n=10
INTEGER, PARAMETER :: expMsg=DIMEN
INTEGER, PARAMETER, DIMENSION(hbw) :: ind = (/ 1,2,3 /)
INTEGER :: actMsg
!> initialize unit test
CALL set_unit_name(unit_name)
!> initialize log file
CALL log_setFileName(testName)
CALL log_initLogFile()
!> initialize matrices (note test2 is not square)
CALL bsm_init(test1, hbw,n)
CALL dm_init(test2, hbw+1,hbw)
!> attempt mapped add
CALL bsm_mappedAdd(test1, test2,ind, actMsg)
CALL assertEquals(expMsg,actMsg)
!> finalize log file and deallocate matrices
CALL log_closeLogFile()
CALL bsm_clean(test1)
CALL dm_clean(test2)
END SUBROUTINE test_bsm_mapped_add_DIMEN2
! ------------------------------------------------------------------------
!> \test Test for DIMEN exception when performing mapped add
!!
!! \param unit_name Name of unit test (for FRUIT)
!! \param test1 Test banded symmetric matrix
!! \param test2 Test input dense matrix (larger than hbw)
!! \param testName Filename for log file (required for exceptions)
!! \param hbw Half bandwidth of the matrix
!! \param n Number of rows/columns in the matrix
!! \param expMsg Expected exception message
!! \param actMsg Actual exception message
!! \param ind Mapping indices (larger than hbw)
!!
!! This test checks that a DIMEN exception is raised when mapped addition
!! is attempted with an input dense matrix whose size exceeds the half
!! bandwidth of the banded symmetric matrix.
! ------------------------------------------------------------------------
SUBROUTINE test_bsm_mapped_add_DIMEN3
CHARACTER (LEN=*), PARAMETER :: unit_name = 'test_bsm_mapped_add_DIMEN3'
TYPE(bandSymMatrixT) :: test1
TYPE(matrixT) :: test2
CHARACTER (LEN=*), PARAMETER :: testName = 'testName'
INTEGER, PARAMETER :: hbw=3,n=10
INTEGER, PARAMETER :: expMsg=DIMEN
INTEGER, PARAMETER, DIMENSION(hbw+1) :: ind = (/ 1,2,3,4 /)
INTEGER :: actMsg
!> initialize unit test
CALL set_unit_name(unit_name)
!> initialize log file
CALL log_setFileName(testName)
CALL log_initLogFile()
!> initialize matrices (note that test2 is wider than hbw)
CALL bsm_init(test1, hbw,n)
CALL dm_init(test2, hbw+1,hbw+1)
!> attempt mapped add
CALL bsm_mappedAdd(test1, test2,ind, actMsg)
CALL assertEquals(expMsg,actMsg)
!> finalize log file and deallocate matrices
CALL log_closeLogFile()
CALL bsm_clean(test1)
CALL dm_clean(test2)
END SUBROUTINE test_bsm_mapped_add_DIMEN3
! ------------------------------------------------------------------------
!> \test Test for POSIT exception when performing mapped add
!!
!! \param unit_name Name of unit test (for FRUIT)
!! \param test1 Test banded symmetric matrix
!! \param test2 Test input dense matrix
!! \param testName Filename for log file (required for exceptions)
!! \param hbw Half bandwidth of the matrix
!! \param n Number of rows/columns in the matrix
!! \param expMsg Expected exception message
!! \param actMsg Actual exception message
!! \param ind1 Mapping indices (with index below minimum)
!! \param ind2 Mapping indices (with index above maximum)
!!
!! This test checks that a POSIT exception is raised when mapped addition
!! is attempted with mapping indices that are outside the matrix.
! ------------------------------------------------------------------------
SUBROUTINE test_bsm_mapped_add_POSIT1
CHARACTER (LEN=*), PARAMETER :: unit_name = 'test_bsm_mapped_add_POSIT1'
TYPE(bandSymMatrixT) :: test1
TYPE(matrixT) :: test2
CHARACTER (LEN=*), PARAMETER :: testName = 'testName'
INTEGER, PARAMETER :: hbw=3,n=10
INTEGER, PARAMETER :: expMsg=POSIT
INTEGER, PARAMETER, DIMENSION(hbw) :: ind1 = (/ -1,0,1 /)
INTEGER, PARAMETER, DIMENSION(hbw) :: ind2 = (/ 9,10,11 /)
INTEGER :: actMsg
!> initialize unit test
CALL set_unit_name(unit_name)
!> initialize log file
CALL log_setFileName(testName)
CALL log_initLogFile()
!> initialize matrices (data not important)
CALL bsm_init(test1, hbw,n)
CALL dm_init(test2, hbw,hbw)
!> attempt first mapped add
CALL bsm_mappedAdd(test1, test2,ind1, actMsg)
CALL assertEquals(expMsg,actMsg)
!> attempt second mapped add
CALL bsm_mappedAdd(test1, test2,ind2, actMsg)
CALL assertEquals(expMsg,actMsg)
!> finalize log file and deallocate matrices
CALL log_closeLogFile()
CALL bsm_clean(test1)
CALL dm_clean(test2)
END SUBROUTINE test_bsm_mapped_add_POSIT1
! ------------------------------------------------------------------------
!> \test Test for POSIT exception when performing mapped add
!!
!! \param unit_name Name of unit test (for FRUIT)
!! \param test1 Test banded symmetric matrix
!! \param test2 Test input dense matrix
!! \param testName Filename for log file (required for exceptions)
!! \param hbw Half bandwidth of the matrix
!! \param n Number of rows/columns in the matrix
!! \param expMsg Expected exception message
!! \param actMsg Actual exception message
!! \param ind Mapping indices (range of indices >= half bandwidth)
!!
!! This test checks that a POSIT exception is raised when mapped addition
!! is attempted with mapping indices that have a difference equal to the
!! half bandwidth (i.e. trying to set a value outside the band).
! ------------------------------------------------------------------------
SUBROUTINE test_bsm_mapped_add_POSIT2
CHARACTER (LEN=*), PARAMETER :: unit_name = 'test_bsm_mapped_add_POSIT2'
TYPE(bandSymMatrixT) :: test1
TYPE(matrixT) :: test2
CHARACTER (LEN=*), PARAMETER :: testName = 'testName'
INTEGER, PARAMETER :: hbw=3,n=10
INTEGER, PARAMETER :: expMsg=POSIT
INTEGER, PARAMETER, DIMENSION(hbw) :: ind = (/ 4,6,9 /)
INTEGER :: actMsg
!> initialize unit test
CALL set_unit_name(unit_name)
!> initialize log file
CALL log_setFileName(testName)
CALL log_initLogFile()
!> initialize matrices (data content not important)
CALL bsm_init(test1, hbw,n)
CALL dm_init(test2, hbw,hbw)
!> attempt mapped add
CALL bsm_mappedAdd(test1, test2,ind, actMsg)
CALL assertEquals(expMsg,actMsg)
!> finalize log file and deallocate matrices
CALL log_closeLogFile()
CALL bsm_clean(test1)
CALL dm_clean(test2)
END SUBROUTINE test_bsm_mapped_add_POSIT2
! ------------------------------------------------------------------------
!> \test Test for correct mapped addition (single operation)
!!
!! \param unit_name Name of unit test (for FRUIT)
!! \param test1 Test banded symmetric matrix
!! \param test2 Test input dense matrix
!! \param hbw Half bandwidth of the matrix
!! \param n Number of rows/columns in the matrix
!! \param expDat Expected data contents
!! \param ind Mapping indices
!!
!! This test checks that mapped addition is performed correctly. The
!! operation is performed once on a blank matrix.
! ------------------------------------------------------------------------
SUBROUTINE test_bsm_mapped_add_VAL1
CHARACTER (LEN=*), PARAMETER :: unit_name = 'test_bsm_mapped_add_VAL1'
TYPE(bandSymMatrixT) :: test1
TYPE(matrixT) :: test2
INTEGER, PARAMETER :: hbw=3,n=10
INTEGER, PARAMETER, DIMENSION(2) :: ind = (/ 1,3 /)
DOUBLE PRECISION, DIMENSION(hbw,n) :: expDat
INTEGER :: i,j !> loop variables
!> initialize unit test
CALL set_unit_name(unit_name)
!> set expected result of mapped addition (note: Fortran uses column-major storage)
expDat = RESHAPE( (/ &
0.d0,0.d0,1.d0,0.d0,0.d0,0.d0,2.d0,0.d0,3.d0,0.d0, &
0.d0,0.d0,0.d0,0.d0,0.d0,0.d0,0.d0,0.d0,0.d0,0.d0, &
0.d0,0.d0,0.d0,0.d0,0.d0,0.d0,0.d0,0.d0,0.d0,0.d0 &
/), SHAPE(expDat) )
!> initialize target matrix
CALL bsm_init(test1, hbw,n)
!> initialize input matrix
!! (loop sets the data contents)
CALL dm_init(test2, 2,2)
DO j = 1,2
DO i = 1,2
CALL dm_set(test2, i,j, ( (DBLE(j)-1.d0) + DBLE(i) ) )
END DO
END DO
!> perform mapped addition
CALL bsm_mappedAdd(test1, test2,ind)
CALL assertEquals(expDat,test1%dat, hbw,n)
!> deallocate matrices
CALL bsm_clean(test1)
CALL dm_clean(test2)
END SUBROUTINE test_bsm_mapped_add_VAL1
! ------------------------------------------------------------------------
!> \test Test for correct mapped addition (zero index)
!!
!! \param unit_name Name of unit test (for FRUIT)
!! \param test1 Test banded symmetric matrix
!! \param test2 Test input dense matrix
!! \param hbw Half bandwidth of the matrix
!! \param n Number of rows/columns in the matrix
!! \param expDat Expected data contents
!! \param ind Mapping indices (with zero index indicating no-op)
!!
!! This test checks that mapped addition is performed correctly. The
!! mapping index contains a zero, which should tell the mapped adder to
!! skip that location in the input matrix.
! ------------------------------------------------------------------------
SUBROUTINE test_bsm_mapped_add_VAL2
CHARACTER (LEN=*), PARAMETER :: unit_name = 'test_bsm_mapped_add_VAL2'
TYPE(bandSymMatrixT) :: test1
TYPE(matrixT) :: test2
INTEGER, PARAMETER :: hbw=3,n=10
INTEGER, PARAMETER, DIMENSION(3) :: ind = (/ 1,0,3 /)
DOUBLE PRECISION, DIMENSION(hbw,n) :: expDat
INTEGER :: i,j !> loop variables
!> initialize unit test
CALL set_unit_name(unit_name)
!> set up expected result (note: Fortran uses column-major storage)
expDat = RESHAPE( (/ &
0.d0,0.d0,1.d0,0.d0,0.d0,0.d0,3.d0,0.d0,5.d0,0.d0, &
0.d0,0.d0,0.d0,0.d0,0.d0,0.d0,0.d0,0.d0,0.d0,0.d0, &
0.d0,0.d0,0.d0,0.d0,0.d0,0.d0,0.d0,0.d0,0.d0,0.d0 &
/), SHAPE(expDat) )
!> initialize target matrix
CALL bsm_init(test1, hbw,n)
!> initialize input matrix
!! (loop sets the input data)
CALL dm_init(test2, 3,3)
DO j = 1,3
DO i = 1,3
CALL dm_set(test2, i,j, ( (DBLE(j)-1.d0) + DBLE(i) ) )
END DO
END DO
!> perform mapped addition
CALL bsm_mappedAdd(test1, test2,ind)
CALL assertEquals(expDat,test1%dat, hbw,n)
!> deallocate matrices
CALL bsm_clean(test1)
CALL dm_clean(test2)
END SUBROUTINE test_bsm_mapped_add_VAL2
! ------------------------------------------------------------------------
!> \test Test for correct mapped addition (multiple operations)
!!
!! \param unit_name Name of unit test (for FRUIT)
!! \param test1 Test banded symmetric matrix
!! \param test2 First test input dense matrix
!! \param test3 Second test input dense matrix
!! \param hbw Half bandwidth of the matrix
!! \param n Number of rows/columns in the matrix
!! \param expDat Expected data contents
!! \param ind2 Mapping indices for test2
!! \param ind3 Mapping indices for test3
!!
!! This test checks that mapped addition is performed correctly. The
!! operation is performed twice to ensure summation of overlapping
!! values. That is, input is added to existing data in the target matrix
!! rather than overwriting.
! ------------------------------------------------------------------------
SUBROUTINE test_bsm_mapped_add_VAL3
CHARACTER (LEN=*), PARAMETER :: unit_name = 'test_bsm_mapped_add_VAL3'
TYPE(bandSymMatrixT) :: test1
TYPE(matrixT) :: test2,test3
INTEGER, PARAMETER :: hbw=3,n=10
INTEGER, PARAMETER, DIMENSION(2) :: ind2 = (/ 1,3 /)
INTEGER, PARAMETER, DIMENSION(3) :: ind3 = (/ 1,0,3 /)
DOUBLE PRECISION, DIMENSION(hbw,n) :: expDat
INTEGER :: i,j !> loop variables
!> initialize unit test
CALL set_unit_name(unit_name)
!> set up expected result (note: Fortran uses column-major storage)
expDat = RESHAPE( (/ &
0.d0,0.d0,2.d0,0.d0,0.d0,0.d0,5.d0,0.d0,8.d0,0.d0, &
0.d0,0.d0,0.d0,0.d0,0.d0,0.d0,0.d0,0.d0,0.d0,0.d0, &
0.d0,0.d0,0.d0,0.d0,0.d0,0.d0,0.d0,0.d0,0.d0,0.d0 &
/), SHAPE(expDat) )
!> initialize target matrix
CALL bsm_init(test1, hbw,n)
!> initialize first input matrix
!! (loop sets up the data)
CALL dm_init(test2, 2,2)
DO j = 1,2
DO i = 1,2
CALL dm_set(test2, i,j, ( (DBLE(j)-1.d0) + DBLE(i) ) )
END DO
END DO
!> initialize second input matrix
!! (loop sets up the data)
CALL dm_init(test3, 3,3)
DO j = 1,3
DO i = 1,3
CALL dm_set(test3, i,j, ( (DBLE(j)-1.d0) + DBLE(i) ) )
END DO
END DO
!> perform the mapped addition for both inputs
CALL bsm_mappedAdd(test1, test2,ind2)
CALL bsm_mappedAdd(test1, test3,ind3)
CALL assertEquals(expDat,test1%dat, hbw,n)
!> deallocate matrices
CALL bsm_clean(test1)
CALL dm_clean(test2)
CALL dm_clean(test3)
END SUBROUTINE test_bsm_mapped_add_VAL3
! ------------------------------------------------------------------------
!> \test Test for scalar multiplication
!!
!! \param unit_name Name of unit test (for FRUIT)
!! \param test1 Input banded symmetric matrix
!! \param test2 Output banded symmetric matrix
!! \param k Scalar coefficient
!! \param hbw Half bandwidth of the matrix
!! \param n Number of rows/columns in the matrix
!! \param expDat Expected data contents
!!
!! This test checks that scalar multiplication is performed correctly.
! ------------------------------------------------------------------------
SUBROUTINE test_bsm_scal_mul_VAL
CHARACTER (LEN=*), PARAMETER :: unit_name = 'test_bsm_scal_mul_VAL'
TYPE(bandSymMatrixT) :: test1, test2
DOUBLE PRECISION, PARAMETER :: k=3.d0
INTEGER, PARAMETER :: hbw=3,n=10
DOUBLE PRECISION, DIMENSION(hbw,n) :: expDat
INTEGER :: i,j !> loop variable
!> initialize unit test
CALL set_unit_name(unit_name)
!> set up expected result (note: Fortran uses column-major storage)
expDat = RESHAPE( (/ &
0.d0,0.d0,3.d0,0.d0,3.d0,3.d0,3.d0,3.d0,3.d0,3.d0, &
3.d0,3.d0,3.d0,3.d0,3.d0,3.d0,3.d0,3.d0,3.d0,3.d0, &
3.d0,3.d0,3.d0,3.d0,3.d0,3.d0,3.d0,3.d0,3.d0,3.d0 &
/), SHAPE(expDat) )
!> initialize matrix
!! (loop sets band to ones)
CALL bsm_init(test1, hbw,n)
DO i = 1,n
DO j = i,MIN(i+hbw-1,n)
CALL bsm_set(test1, i,j, 1.d0)
END DO
END DO
!> multiply by scalar
test2 = bsm_scalMul(test1,k)
CALL assertEquals(expDat,test2%dat, hbw,n)
!> deallocate matrices
CALL bsm_clean(test1)
CALL bsm_clean(test2)
END SUBROUTINE test_bsm_scal_mul_VAL
! ------------------------------------------------------------------------
!> \test Test for scalar multiplication (by zero)
!!
!! \param unit_name Name of unit test (for FRUIT)
!! \param test1 Input banded symmetric matrix
!! \param test2 Output banded symmetric matrix
!! \param k Scalar coefficient (zero)
!! \param hbw Half bandwidth of the matrix
!! \param n Number of rows/columns in the matrix
!! \param expDat Expected data contents
!!
!! This test checks that scalar multiplication results in a zero matrix
!! when the scalar factor is zero.
! ------------------------------------------------------------------------
SUBROUTINE test_bsm_scal_mul_ZERO
CHARACTER (LEN=*), PARAMETER :: unit_name = 'test_bsm_scal_mul_ZERO'
TYPE(bandSymMatrixT) :: test1, test2
DOUBLE PRECISION, PARAMETER :: k=0.d0
INTEGER, PARAMETER :: hbw=3,n=10
DOUBLE PRECISION, DIMENSION(hbw,n) :: expDat
INTEGER :: i,j !> loop variables
!> initialize unit test
CALL set_unit_name(unit_name)
!> set up expected data (note: Fortran uses column-major storage)
expDat = RESHAPE( (/ &
0.d0,0.d0,0.d0,0.d0,0.d0,0.d0,0.d0,0.d0,0.d0,0.d0, &
0.d0,0.d0,0.d0,0.d0,0.d0,0.d0,0.d0,0.d0,0.d0,0.d0, &
0.d0,0.d0,0.d0,0.d0,0.d0,0.d0,0.d0,0.d0,0.d0,0.d0 &
/), SHAPE(expDat) )
!> initialize matrix
!! (loop sets band to ones)
CALL bsm_init(test1, hbw,n)
DO i = 1,n
DO j = i,MIN(i+hbw-1,n)
CALL bsm_set(test1, i,j, 1.d0)
END DO
END DO
!> multiply by zero
test2 = bsm_scalMul(test1,k)
CALL assertEquals(expDat,test2%dat, hbw,n)
!> deallocate matrices
CALL bsm_clean(test1)
CALL bsm_clean(test2)
END SUBROUTINE test_bsm_scal_mul_ZERO
! ------------------------------------------------------------------------
!> \test Test for scalar multiplication ( using OPERATOR (*) )
!!
!! \param unit_name Name of unit test (for FRUIT)
!! \param test1 Input banded symmetric matrix
!! \param test2 Output banded symmetric matrix
!! \param k Scalar coefficient
!! \param hbw Half bandwidth of the matrix
!! \param n Number of rows/columns in the matrix
!! \param expDat Expected data contents
!!
!! This test checks that scalar multiplication is performed correctly
!! when using the overloaded (*) operator.
! ------------------------------------------------------------------------
SUBROUTINE test_bsm_scal_mul_OP
CHARACTER (LEN=*), PARAMETER :: unit_name = 'test_bsm_scal_mul_OP'
TYPE(bandSymMatrixT) :: test1, test2
DOUBLE PRECISION, PARAMETER :: k=3.d0
INTEGER, PARAMETER :: hbw=3,n=10
DOUBLE PRECISION, DIMENSION(hbw,n) :: expDat
INTEGER :: i,j !> loop variables
!> initialize unit test
CALL set_unit_name(unit_name)
!> set up expected result (note: Fortran uses column-major storage)
expDat = RESHAPE( (/ &
0.d0,0.d0,3.d0,0.d0,3.d0,3.d0,3.d0,3.d0,3.d0,3.d0, &
3.d0,3.d0,3.d0,3.d0,3.d0,3.d0,3.d0,3.d0,3.d0,3.d0, &
3.d0,3.d0,3.d0,3.d0,3.d0,3.d0,3.d0,3.d0,3.d0,3.d0 &
/), SHAPE(expDat) )
!> initialize input matrix
!! (loop sets bands to ones)
CALL bsm_init(test1, hbw,n)
DO i = 1,n
DO j = i,MIN(i+hbw-1,n)
CALL bsm_set(test1, i,j, 1.d0)
END DO
END DO
!> perform scalar multiplication
test2 = k * test1
CALL assertEquals(expDat,test2%dat, hbw,n)
!> clear output matrix
CALL bsm_clean(test2)
!> perform scalar multiplication (switch order of inputs)
test2 = test1 * k
CALL assertEquals(expDat,test2%dat, hbw,n)
!> deallocate matrices
CALL bsm_clean(test1)
CALL bsm_clean(test2)
END SUBROUTINE test_bsm_scal_mul_OP
! ------------------------------------------------------------------------
!> \test Test for DIMEN exception when performing matrix-vector multiplication
!!
!! \param unit_name Name of unit test (for FRUIT)
!! \param test1 Input banded symmetric matrix
!! \param test2 Input vector
!! \param test3 Dummy output vector
!! \param testName Filename for log file (required for exceptions)
!! \param hbw Half bandwidth of the matrix
!! \param n Number of rows/columns in the matrix
!! \param expMsg Expected exception message
!! \param actMsg Actual exception message
!!
!! This test checks that a DIMEN exception is raised when matrix-vector
!! multiplication is attempted with a vector whose length does not equal
!! the number of rows in the matrix.
! ------------------------------------------------------------------------
SUBROUTINE test_bsm_vec_mul_DIMEN
CHARACTER (LEN=*), PARAMETER :: unit_name = 'test_bsm_vec_mul_DIMEN'
TYPE(bandSymMatrixT) :: test1
TYPE(vectorT) :: test2, test3
CHARACTER (LEN=*), PARAMETER :: testName = 'testName'
INTEGER, PARAMETER :: hbw=3,n=10
INTEGER, PARAMETER :: expMsg=DIMEN
INTEGER :: actMsg
!> initialize unit test
CALL set_unit_name(unit_name)
!> initialize log file
CALL log_setFileName(testName)
CALL log_initLogFile()
!> set up matrix and vector (data contents not important)
CALL bsm_init(test1, hbw,n)
CALL vec_init(test2, n+1) !> note different size
!> attempt matrix-vector multiplication
test3 = bsm_vecMul(test1,test2, actMsg)
CALL assertEquals(expMsg,actMsg)
!> finalize log file and deallocate objects
CALL log_closeLogFile()
CALL bsm_clean(test1)
CALL vec_clean(test2)
CALL vec_clean(test3)
END SUBROUTINE test_bsm_vec_mul_DIMEN
! ------------------------------------------------------------------------
!> \test Test for correct matrix-vector multiplication
!!
!! \param unit_name Name of unit test (for FRUIT)
!! \param test1 Input banded symmetric matrix
!! \param test2 Input vector
!! \param test3 Output vector
!! \param hbw Half bandwidth of the matrix
!! \param n Number of rows/columns in the matrix
!! \param expDat Expected result
!!
!! This test checks that matrix-vector multiplication is performed
!! correctly in the general case (input matrix and vector contain data,
!! but it is not of a special form).
! ------------------------------------------------------------------------
SUBROUTINE test_bsm_vec_mul_VAL
CHARACTER (LEN=*), PARAMETER :: unit_name = 'test_bsm_vec_mul_VAL'
TYPE(bandSymMatrixT) :: test1
TYPE(vectorT) :: test2, test3
INTEGER, PARAMETER :: hbw=3,n=10
DOUBLE PRECISION, DIMENSION(n) :: expDat
INTEGER :: i,j !> loop variables
!> initialize unit test
CALL set_unit_name(unit_name)
!> set expected result (note: Fortran uses column-major storage)
expDat = RESHAPE( (/ &
14.d0, 40.d0, 85.d0, 150.d0, 235.d0, &
340.d0, 465.d0, 610.d0, 566.d0, 488.d0 &
/), SHAPE(expDat) )
!> initialize input matrix
!! (loop sets up data)
CALL bsm_init(test1, hbw,n)
DO i = 1,n
DO j = i,MIN(i+hbw-1,n)
CALL bsm_set(test1, i,j, ( (DBLE(j)-1.d0) + DBLE(i) ) )
END DO
END DO
!> initialize input vector
!! (loop sets up data)
CALL vec_init(test2, n)
DO i = 1,n
CALL vec_set(test2, i, DBLE(i))
END DO
!> perform multiplication
test3 = bsm_vecMul(test1,test2)
CALL assertEquals(expDat,test3%dat, n)
!> deallocate objects
CALL bsm_clean(test1)
CALL vec_clean(test2)
CALL vec_clean(test3)
END SUBROUTINE test_bsm_vec_mul_VAL
! ------------------------------------------------------------------------
!> \test Test for matrix-vector multiplication (by the zero vector)
!!
!! \param unit_name Name of unit test (for FRUIT)
!! \param test1 Input banded symmetric matrix
!! \param test2 Input vector (zeros)
!! \param test3 Output vector
!! \param hbw Half bandwidth of the matrix
!! \param n Number of rows/columns in the matrix
!! \param expDat Expected result
!!
!! This test checks that matrix-vector multiplication is performed
!! correctly when the input vector is all zeros.
! ------------------------------------------------------------------------
SUBROUTINE test_bsm_vec_mul_ZERO
CHARACTER (LEN=*), PARAMETER :: unit_name = 'test_bsm_vec_mul_ZERO'
TYPE(bandSymMatrixT) :: test1
TYPE(vectorT) :: test2, test3
INTEGER, PARAMETER :: hbw=3,n=10
DOUBLE PRECISION, DIMENSION(n) :: expDat
INTEGER :: i,j !> loop variables
!> initialize unit test
CALL set_unit_name(unit_name)
!> set up expected result (note: Fortran uses column-major storage)
expDat = RESHAPE( (/ &
0.d0,0.d0,0.d0,0.d0,0.d0,0.d0,0.d0,0.d0,0.d0,0.d0 &
/), SHAPE(expDat) )
!> initialize input matrix
!! (loop sets up data)
CALL bsm_init(test1, hbw,n)
DO i = 1,n
DO j = i,MIN(i+hbw-1,n)
CALL bsm_set(test1, i,j, ( (DBLE(j)-1.d0) + DBLE(i) ) )
END DO
END DO
!> initialize input vector (all zeros)
CALL vec_init(test2, n)
!> perform multiplication
test3 = bsm_vecMul(test1,test2)
CALL assertEquals(expDat,test3%dat, n)
!> deallocate objects
CALL bsm_clean(test1)
CALL vec_clean(test2)
CALL vec_clean(test3)
END SUBROUTINE test_bsm_vec_mul_ZERO
! ------------------------------------------------------------------------
!> \test Test for matrix-vector multiplication (by the identity matrix)
!!
!! \param unit_name Name of unit test (for FRUIT)
!! \param test1 Input banded symmetric matrix (identity)
!! \param test2 Input vector
!! \param test3 Output vector
!! \param hbw Half bandwidth of the matrix
!! \param n Number of rows/columns in the matrix
!! \param expDat Expected result
!!
!! This test checks that matrix-vector multiplication is performed
!! correctly when the input matrix is the identity for multiplication.
! ------------------------------------------------------------------------
SUBROUTINE test_bsm_vec_mul_IDENT
CHARACTER (LEN=*), PARAMETER :: unit_name = 'test_bsm_vec_mul_IDENT'
TYPE(bandSymMatrixT) :: test1
TYPE(vectorT) :: test2, test3
INTEGER, PARAMETER :: hbw=3,n=10
DOUBLE PRECISION, DIMENSION(n) :: expDat
INTEGER :: i,j !> loop variables
!> initialize unit test
CALL set_unit_name(unit_name)
!> initialize input matrix
!! (loop sets up identity matrix)
CALL bsm_init(test1, hbw,n)
DO i = 1,n
CALL bsm_set(test1, i,i, 1.d0)
END DO
!> initialize input vector
!! (loop sets data)
CALL vec_init(test2, n)
DO i = 1,n
CALL vec_set(test2, i, DBLE(i))
END DO
!> expected result is the same as the initial vector
expDat = test2%dat
!> perform multiplication
test3 = bsm_vecMul(test1,test2)
CALL assertEquals(expDat,test3%dat, n)
!> deallocate objects
CALL bsm_clean(test1)
CALL vec_clean(test2)
CALL vec_clean(test3)
END SUBROUTINE test_bsm_vec_mul_IDENT
! ------------------------------------------------------------------------
!> \test Test for correct matrix-vector multiplication ( using OPERATOR (*) )
!!
!! \param unit_name Name of unit test (for FRUIT)
!! \param test1 Input banded symmetric matrix
!! \param test2 Input vector
!! \param test3 Output vector
!! \param hbw Half bandwidth of the matrix
!! \param n Number of rows/columns in the matrix
!! \param expDat Expected result
!!
!! This test checks that matrix-vector multiplication is performed
!! correctly in the general case (input matrix and vector contain data,
!! but it is not of a special form). The overloaded operator (*) is used.
! ------------------------------------------------------------------------
SUBROUTINE test_bsm_vec_mul_OP
CHARACTER (LEN=*), PARAMETER :: unit_name = 'test_bsm_vec_mul_OP'
TYPE(bandSymMatrixT) :: test1
TYPE(vectorT) :: test2, test3
INTEGER, PARAMETER :: hbw=3,n=10
DOUBLE PRECISION, DIMENSION(n) :: expDat
INTEGER :: i,j !> loop variables
!> initialize unit test
CALL set_unit_name(unit_name)
!> set up expected result (note: Fortran uses column-major storage)
expDat = RESHAPE( (/ &
14.d0, 40.d0, 85.d0, 150.d0, 235.d0, &
340.d0, 465.d0, 610.d0, 566.d0, 488.d0 &
/), SHAPE(expDat) )
!> initialize input matrix
!! (loop sets data)
CALL bsm_init(test1, hbw,n)
DO i = 1,n
DO j = i,MIN(i+hbw-1,n)
CALL bsm_set(test1, i,j, ( (DBLE(j)-1.d0) + DBLE(i) ) )
END DO
END DO
!> initialize input vector
!! (loop sets data)
CALL vec_init(test2, n)
DO i = 1,n
CALL vec_set(test2, i, DBLE(i))
END DO
!> perform multiplication
test3 = test1 * test2
CALL assertEquals(expDat,test3%dat, n)
!> deallocate objects
CALL bsm_clean(test1)
CALL vec_clean(test2)
CALL vec_clean(test3)
END SUBROUTINE test_bsm_vec_mul_OP
END MODULE band_sym_matrix_test
GFORTRAN module version '6' created from band_sym_matrix_test.f90 on Sun Apr 29 22:07:08 2012
MD5:43b8504a086b0fb9319c651b07177c42 -- If you edit this, you'll get what you deserve.
(() () (2 3 4) () (5 6 7 8 9 10 11 12 13) () () () () () () () () () ()
() () () () () () () () () () () ())
()
(('add_fail' 'fruit' 14 15) ('addsuccess' 'fruit' 16) ('addfail' 'fruit'
14 15) ('assert_not_equals' 'fruit' 17 18 19) ('assert_equals' 'fruit'
20 21 22 23 24 25 26 27 28 29 30 31 32 33 34 35 36 37 38 39 40) (
'assertequals' 'fruit' 20 21 22 23 24 25 26 27 28 29 30 31 32 33 34 35
36 37 38 39 40) ('bsm_clean' 'band_sym_matrix_def' 41) ('bsm_add'
'band_sym_matrix_def' 42 2) ('bsm_get' 'band_sym_matrix_def' 43 44) (
'asserttrue' 'fruit' 45) ('assertnotequals' 'fruit' 17 18 19) ('bsm_init'
'band_sym_matrix_def' 46 47) ('bsm_mappedadd' 'band_sym_matrix_def' 48
49) ('bsm_scalmul' 'band_sym_matrix_def' 7) ('bsm_numrows'
'band_sym_matrix_def' 50) ('bsm_isdecomposed' 'band_sym_matrix_def' 51)
('bsm_halfbw' 'band_sym_matrix_def' 52) ('bsm_setdecomp'
'band_sym_matrix_def' 53 54) ('bsm_vecmul' 'band_sym_matrix_def' 55 5) (
'dm_get' 'dense_matrix_def' 56 57) ('dm_clean' 'dense_matrix_def' 58) (
'dm_init' 'dense_matrix_def' 59 60) ('dm_matmul' 'dense_matrix_def' 61
10) ('dm_add' 'dense_matrix_def' 62 4) ('bsm_set' 'band_sym_matrix_def'
63 64) ('dm_scalmul' 'dense_matrix_def' 13) ('dm_set' 'dense_matrix_def'
65 66) ('dm_vecmul' 'dense_matrix_def' 67 11) ('dm_transpose'
'dense_matrix_def' 68) ('dm_numrows' 'dense_matrix_def' 69) ('dm_numcols'
'dense_matrix_def' 70) ('gettestsummary' 'fruit' 71) ('getfailedcount'
'fruit' 72) ('initializefruit' 'fruit' 73) ('gettotalcount' 'fruit' 74)
('isallsuccessful' 'fruit' 75) ('runtestcase' 'fruit' 76 77) (
'run_test_case' 'fruit' 76 77) ('vec_clean' 'vector_def' 78) (
'vec_dotprod' 'vector_def' 79 80) ('vec_add' 'vector_def' 81 3) (
'vec_init' 'vector_def' 82 83) ('vec_length' 'vector_def' 84) ('vec_get'
'vector_def' 85 86) ('vec_set' 'vector_def' 87 88) ('vec_scalmul'
'vector_def' 9) ('vec_mappedadd' 'vector_def' 89 90))
()
()
()
(14 'add_fail_unit_' 'fruit' 'add_fail_unit_' 1 ((PROCEDURE
UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 SUBROUTINE IMPLICIT_PURE) (
UNKNOWN 0 0 0 UNKNOWN ()) 91 0 (92 93) () 0 () () () 0 0)
15 'add_fail_' 'fruit' 'add_fail_' 1 ((PROCEDURE UNKNOWN-INTENT
MODULE-PROC DECL UNKNOWN 0 0 SUBROUTINE IMPLICIT_PURE ALWAYS_EXPLICIT) (
UNKNOWN 0 0 0 UNKNOWN ()) 94 0 (95) () 0 () () () 0 0)
29 'assert_eq_1d_string_' 'fruit' 'assert_eq_1d_string_' 1 ((PROCEDURE
UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 SUBROUTINE ALWAYS_EXPLICIT)
(UNKNOWN 0 0 0 UNKNOWN ()) 96 0 (97 98 99 100) () 0 () () () 0 0)
32 'assert_eq_1d_int_' 'fruit' 'assert_eq_1d_int_' 1 ((PROCEDURE
UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 SUBROUTINE ALWAYS_EXPLICIT)
(UNKNOWN 0 0 0 UNKNOWN ()) 101 0 (102 103 104 105) () 0 () () () 0 0)
34 'assert_eq_real_in_range_' 'fruit' 'assert_eq_real_in_range_' 1 ((
PROCEDURE UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 SUBROUTINE
ALWAYS_EXPLICIT) (UNKNOWN 0 0 0 UNKNOWN ()) 106 0 (107 108 109 110) () 0
() () () 0 0)
33 'assert_eq_double_in_range_' 'fruit' 'assert_eq_double_in_range_' 1 (
(PROCEDURE UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 SUBROUTINE
ALWAYS_EXPLICIT) (UNKNOWN 0 0 0 UNKNOWN ()) 111 0 (112 113 114 115) () 0
() () () 0 0)
31 'assert_eq_1d_double_' 'fruit' 'assert_eq_1d_double_' 1 ((PROCEDURE
UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 SUBROUTINE ALWAYS_EXPLICIT)
(UNKNOWN 0 0 0 UNKNOWN ()) 116 0 (117 118 119 120) () 0 () () () 0 0)
35 'assert_eq_complex_' 'fruit' 'assert_eq_complex_' 1 ((PROCEDURE
UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 SUBROUTINE ALWAYS_EXPLICIT)
(UNKNOWN 0 0 0 UNKNOWN ()) 121 0 (122 123 124) () 0 () () () 0 0)
39 'assert_eq_double_' 'fruit' 'assert_eq_double_' 1 ((PROCEDURE
UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 SUBROUTINE ALWAYS_EXPLICIT)
(UNKNOWN 0 0 0 UNKNOWN ()) 125 0 (126 127 128) () 0 () () () 0 0)
3 'vec_add_' 'vector_def' 'vec_add_' 1 ((PROCEDURE UNKNOWN-INTENT
MODULE-PROC DECL UNKNOWN 0 0 FUNCTION) (DERIVED 129 0 0 DERIVED ()) 130
0 (131 132) () 133 () () () 0 0)
2 'bsm_add_' 'band_sym_matrix_def' 'bsm_add_' 1 ((PROCEDURE
UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 FUNCTION) (DERIVED 134 0 0
DERIVED ()) 135 0 (136 137) () 138 () () () 0 0)
4 'dm_add_' 'dense_matrix_def' 'dm_add_' 1 ((PROCEDURE UNKNOWN-INTENT
MODULE-PROC DECL UNKNOWN 0 0 FUNCTION) (DERIVED 139 0 0 DERIVED ()) 140
0 (141 142) () 143 () () () 0 0)
6 'bsm_scal_mul_scal_mat_' 'band_sym_matrix_def' 'bsm_scal_mul_scal_mat_'
1 ((PROCEDURE UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 FUNCTION) (
DERIVED 134 0 0 DERIVED ()) 144 0 (145 146) () 147 () () () 0 0)
7 'bsm_scal_mul_mat_scal_' 'band_sym_matrix_def' 'bsm_scal_mul_mat_scal_'
1 ((PROCEDURE UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 FUNCTION) (
DERIVED 134 0 0 DERIVED ()) 148 0 (149 150) () 151 () () () 0 0)
8 'vec_scal_mul_scal_vec_' 'vector_def' 'vec_scal_mul_scal_vec_' 1 ((
PROCEDURE UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 FUNCTION) (
DERIVED 129 0 0 DERIVED ()) 152 0 (153 154) () 155 () () () 0 0)
5 'bsm_vec_mul_' 'band_sym_matrix_def' 'bsm_vec_mul_' 1 ((PROCEDURE
UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 FUNCTION) (DERIVED 129 0 0
DERIVED ()) 156 0 (157 158) () 159 () () () 0 0)
10 'dm_mat_mul_' 'dense_matrix_def' 'dm_mat_mul_' 1 ((PROCEDURE
UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 FUNCTION) (DERIVED 139 0 0
DERIVED ()) 160 0 (161 162) () 163 () () () 0 0)
13 'dm_scal_mul_mat_scal_' 'dense_matrix_def' 'dm_scal_mul_mat_scal_' 1
((PROCEDURE UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 FUNCTION) (
DERIVED 139 0 0 DERIVED ()) 164 0 (165 166) () 167 () () () 0 0)
38 'assert_eq_real_' 'fruit' 'assert_eq_real_' 1 ((PROCEDURE
UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 SUBROUTINE ALWAYS_EXPLICIT)
(UNKNOWN 0 0 0 UNKNOWN ()) 168 0 (169 170 171) () 0 () () () 0 0)
43 'bsm_get_exc_' 'band_sym_matrix_def' 'bsm_get_exc_' 1 ((PROCEDURE
UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 FUNCTION) (REAL 8 0 0 REAL ())
172 0 (173 174 175 176) () 177 () () () 0 0)
42 'bsm_add_exc_' 'band_sym_matrix_def' 'bsm_add_exc_' 1 ((PROCEDURE
UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 FUNCTION) (DERIVED 134 0 0
DERIVED ()) 178 0 (179 180 181) () 182 () () () 0 0)
44 'bsm_get_' 'band_sym_matrix_def' 'bsm_get_' 1 ((PROCEDURE
UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 FUNCTION IMPLICIT_PURE) (
REAL 8 0 0 REAL ()) 183 0 (184 185 186) () 187 () () () 0 0)
41 'bsm_clean_' 'band_sym_matrix_def' 'bsm_clean_' 1 ((PROCEDURE
UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 SUBROUTINE IMPLICIT_PURE) (
UNKNOWN 0 0 0 UNKNOWN ()) 188 0 (189) () 0 () () () 0 0)
12 'dm_scal_mul_scal_mat_' 'dense_matrix_def' 'dm_scal_mul_scal_mat_' 1
((PROCEDURE UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 FUNCTION) (
DERIVED 139 0 0 DERIVED ()) 190 0 (191 192) () 193 () () () 0 0)
47 'bsm_init_' 'band_sym_matrix_def' 'bsm_init_' 1 ((PROCEDURE
UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 SUBROUTINE) (UNKNOWN 0 0 0
UNKNOWN ()) 194 0 (195 196 197) () 0 () () () 0 0)
52 'bsm_half_bw_' 'band_sym_matrix_def' 'bsm_half_bw_' 1 ((PROCEDURE
UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 FUNCTION IMPLICIT_PURE) (
INTEGER 4 0 0 INTEGER ()) 198 0 (199) () 200 () () () 0 0)
46 'bsm_init_exc_' 'band_sym_matrix_def' 'bsm_init_exc_' 1 ((PROCEDURE
UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 SUBROUTINE) (UNKNOWN 0 0 0
UNKNOWN ()) 201 0 (202 203 204 205) () 0 () () () 0 0)
48 'bsm_mapped_add_exc_' 'band_sym_matrix_def' 'bsm_mapped_add_exc_' 1 (
(PROCEDURE UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 SUBROUTINE
ALWAYS_EXPLICIT) (UNKNOWN 0 0 0 UNKNOWN ()) 206 0 (207 208 209 210) () 0
() () () 0 0)
50 'bsm_num_rows_' 'band_sym_matrix_def' 'bsm_num_rows_' 1 ((PROCEDURE
UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 FUNCTION IMPLICIT_PURE) (
INTEGER 4 0 0 INTEGER ()) 211 0 (212) () 213 () () () 0 0)
19 'assert_not_equals_real_' 'fruit' 'assert_not_equals_real_' 1 ((
PROCEDURE UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 SUBROUTINE
ALWAYS_EXPLICIT) (UNKNOWN 0 0 0 UNKNOWN ()) 214 0 (215 216 217) () 0 ()
() () 0 0)
53 'bsm_set_decomp_exc_' 'band_sym_matrix_def' 'bsm_set_decomp_exc_' 1 (
(PROCEDURE UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 SUBROUTINE
ALWAYS_EXPLICIT) (UNKNOWN 0 0 0 UNKNOWN ()) 218 0 (219 220 221) () 0 ()
() () 0 0)
54 'bsm_set_decomp_' 'band_sym_matrix_def' 'bsm_set_decomp_' 1 ((
PROCEDURE UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 SUBROUTINE
IMPLICIT_PURE ALWAYS_EXPLICIT) (UNKNOWN 0 0 0 UNKNOWN ()) 222 0 (223 224)
() 0 () () () 0 0)
55 'bsm_vec_mul_exc_' 'band_sym_matrix_def' 'bsm_vec_mul_exc_' 1 ((
PROCEDURE UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 FUNCTION) (
DERIVED 129 0 0 DERIVED ()) 225 0 (226 227 228) () 229 () () () 0 0)
64 'bsm_set_' 'band_sym_matrix_def' 'bsm_set_' 1 ((PROCEDURE
UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 SUBROUTINE IMPLICIT_PURE) (
UNKNOWN 0 0 0 UNKNOWN ()) 230 0 (231 232 233 234) () 0 () () () 0 0)
63 'bsm_set_exc_' 'band_sym_matrix_def' 'bsm_set_exc_' 1 ((PROCEDURE
UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 SUBROUTINE) (UNKNOWN 0 0 0
UNKNOWN ()) 235 0 (236 237 238 239 240) () 0 () () () 0 0)
49 'bsm_mapped_add_' 'band_sym_matrix_def' 'bsm_mapped_add_' 1 ((
PROCEDURE UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 SUBROUTINE
ALWAYS_EXPLICIT) (UNKNOWN 0 0 0 UNKNOWN ()) 241 0 (242 243 244) () 0 ()
() () 0 0)
51 'bsm_is_decomposed_' 'band_sym_matrix_def' 'bsm_is_decomposed_' 1 ((
PROCEDURE UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 FUNCTION
IMPLICIT_PURE) (LOGICAL 4 0 0 LOGICAL ()) 245 0 (246) () 247 () () () 0
0)
11 'dm_vec_mul_' 'dense_matrix_def' 'dm_vec_mul_' 1 ((PROCEDURE
UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 FUNCTION) (DERIVED 129 0 0
DERIVED ()) 248 0 (249 250) () 251 () () () 0 0)
9 'vec_scal_mul_vec_scal_' 'vector_def' 'vec_scal_mul_vec_scal_' 1 ((
PROCEDURE UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 FUNCTION) (
DERIVED 129 0 0 DERIVED ()) 252 0 (253 254) () 255 () () () 0 0)
45 'obsolete_assert_true_logical_' 'fruit' 'obsolete_assert_true_logical_'
1 ((PROCEDURE UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 SUBROUTINE
IMPLICIT_PURE ALWAYS_EXPLICIT) (UNKNOWN 0 0 0 UNKNOWN ()) 256 0 (257 258)
() 0 () () () 0 0)
20 'assert_eq_2d_double_in_range_' 'fruit' 'assert_eq_2d_double_in_range_'
1 ((PROCEDURE UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 SUBROUTINE
ALWAYS_EXPLICIT) (UNKNOWN 0 0 0 UNKNOWN ()) 259 0 (260 261 262 263 264
265) () 0 () () () 0 0)
74 'obsolete_gettotalcount_' 'fruit' 'obsolete_gettotalcount_' 1 ((
PROCEDURE UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 SUBROUTINE
IMPLICIT_PURE) (UNKNOWN 0 0 0 UNKNOWN ()) 266 0 (267) () 0 () () () 0 0)
18 'assert_not_equals_1d_real_' 'fruit' 'assert_not_equals_1d_real_' 1 (
(PROCEDURE UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 SUBROUTINE) (
UNKNOWN 0 0 0 UNKNOWN ()) 268 0 (269 270 271) () 0 () () () 0 0)
17 'assert_not_equals_double_' 'fruit' 'assert_not_equals_double_' 1 ((
PROCEDURE UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 SUBROUTINE
ALWAYS_EXPLICIT) (UNKNOWN 0 0 0 UNKNOWN ()) 272 0 (273 274 275) () 0 ()
() () 0 0)
40 'assert_eq_int_' 'fruit' 'assert_eq_int_' 1 ((PROCEDURE
UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 SUBROUTINE ALWAYS_EXPLICIT)
(UNKNOWN 0 0 0 UNKNOWN ()) 276 0 (277 278 279) () 0 () () () 0 0)
37 'assert_eq_logical_' 'fruit' 'assert_eq_logical_' 1 ((PROCEDURE
UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 SUBROUTINE ALWAYS_EXPLICIT)
(UNKNOWN 0 0 0 UNKNOWN ()) 280 0 (281 282 283) () 0 () () () 0 0)
129 'vectort' 'vector_def' 'vectort' 1 ((DERIVED UNKNOWN-INTENT
UNKNOWN-PROC UNKNOWN UNKNOWN 0 0 ALLOC_COMP) (UNKNOWN 0 0 0 UNKNOWN ())
0 0 () () 0 ((284 'dat' (REAL 8 0 0 REAL ()) (1 0 DEFERRED () ()) (
UNKNOWN-FL UNKNOWN-INTENT UNKNOWN-PROC UNKNOWN UNKNOWN 0 0 ALLOCATABLE
DIMENSION) UNKNOWN-ACCESS ())) PUBLIC (() () () ()) () 0 0 58143611)
73 'obsolete_initializefruit_' 'fruit' 'obsolete_initializefruit_' 1 ((
PROCEDURE UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 SUBROUTINE
IMPLICIT_PURE) (UNKNOWN 0 0 0 UNKNOWN ()) 0 0 () () 0 () () () 0 0)
139 'matrixt' 'dense_matrix_def' 'matrixt' 1 ((DERIVED UNKNOWN-INTENT
UNKNOWN-PROC UNKNOWN UNKNOWN 0 0 ALLOC_COMP) (UNKNOWN 0 0 0 UNKNOWN ())
0 0 () () 0 ((285 'dat' (REAL 8 0 0 REAL ()) (2 0 DEFERRED () () () ())
(UNKNOWN-FL UNKNOWN-INTENT UNKNOWN-PROC UNKNOWN UNKNOWN 0 0 ALLOCATABLE
DIMENSION) UNKNOWN-ACCESS ())) PUBLIC (() () () ()) () 0 0 72249915)
71 'obsolete_gettestsummary_' 'fruit' 'obsolete_gettestsummary_' 1 ((
PROCEDURE UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 SUBROUTINE
IMPLICIT_PURE) (UNKNOWN 0 0 0 UNKNOWN ()) 0 0 () () 0 () () () 0 0)
72 'obsolete_getfailedcount_' 'fruit' 'obsolete_getfailedcount_' 1 ((
PROCEDURE UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 SUBROUTINE
IMPLICIT_PURE) (UNKNOWN 0 0 0 UNKNOWN ()) 286 0 (287) () 0 () () () 0 0)
77 'run_test_case_' 'fruit' 'run_test_case_' 1 ((PROCEDURE
UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 SUBROUTINE) (UNKNOWN 0 0 0
UNKNOWN ()) 288 0 (289) () 0 () () () 0 0)
58 'dm_clean_' 'dense_matrix_def' 'dm_clean_' 1 ((PROCEDURE
UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 SUBROUTINE IMPLICIT_PURE) (
UNKNOWN 0 0 0 UNKNOWN ()) 290 0 (291) () 0 () () () 0 0)
56 'dm_get_exc_' 'dense_matrix_def' 'dm_get_exc_' 1 ((PROCEDURE
UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 FUNCTION) (REAL 8 0 0 REAL ())
292 0 (293 294 295 296) () 297 () () () 0 0)
57 'dm_get_' 'dense_matrix_def' 'dm_get_' 1 ((PROCEDURE UNKNOWN-INTENT
MODULE-PROC DECL UNKNOWN 0 0 FUNCTION IMPLICIT_PURE) (REAL 8 0 0 REAL ())
298 0 (299 300 301) () 302 () () () 0 0)
62 'dm_add_exc_' 'dense_matrix_def' 'dm_add_exc_' 1 ((PROCEDURE
UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 FUNCTION) (DERIVED 139 0 0
DERIVED ()) 303 0 (304 305 306) () 307 () () () 0 0)
76 'run_test_case_named_' 'fruit' 'run_test_case_named_' 1 ((PROCEDURE
UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 SUBROUTINE) (UNKNOWN 0 0 0
UNKNOWN ()) 308 0 (309 310) () 0 () () () 0 0)
60 'dm_init_' 'dense_matrix_def' 'dm_init_' 1 ((PROCEDURE UNKNOWN-INTENT
MODULE-PROC DECL UNKNOWN 0 0 SUBROUTINE) (UNKNOWN 0 0 0 UNKNOWN ()) 311
0 (312 313 314) () 0 () () () 0 0)
59 'dm_init_exc_' 'dense_matrix_def' 'dm_init_exc_' 1 ((PROCEDURE
UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 SUBROUTINE) (UNKNOWN 0 0 0
UNKNOWN ()) 315 0 (316 317 318 319) () 0 () () () 0 0)
70 'dm_num_cols_' 'dense_matrix_def' 'dm_num_cols_' 1 ((PROCEDURE
UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 FUNCTION IMPLICIT_PURE) (
INTEGER 4 0 0 INTEGER ()) 320 0 (321) () 322 () () () 0 0)
65 'dm_set_exc_' 'dense_matrix_def' 'dm_set_exc_' 1 ((PROCEDURE
UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 SUBROUTINE) (UNKNOWN 0 0 0
UNKNOWN ()) 323 0 (324 325 326 327 328) () 0 () () () 0 0)
68 'dm_transpose_' 'dense_matrix_def' 'dm_transpose_' 1 ((PROCEDURE
UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 FUNCTION) (DERIVED 139 0 0
DERIVED ()) 329 0 (330) () 331 () () () 0 0)
61 'dm_mat_mul_exc_' 'dense_matrix_def' 'dm_mat_mul_exc_' 1 ((PROCEDURE
UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 FUNCTION) (DERIVED 139 0 0
DERIVED ()) 332 0 (333 334 335) () 336 () () () 0 0)
67 'dm_vec_mul_exc_' 'dense_matrix_def' 'dm_vec_mul_exc_' 1 ((PROCEDURE
UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 FUNCTION) (DERIVED 129 0 0
DERIVED ()) 337 0 (338 339 340) () 341 () () () 0 0)
21 'assert_eq_2d_real_in_range_' 'fruit' 'assert_eq_2d_real_in_range_' 1
((PROCEDURE UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 SUBROUTINE
ALWAYS_EXPLICIT) (UNKNOWN 0 0 0 UNKNOWN ()) 342 0 (343 344 345 346 347
348) () 0 () () () 0 0)
75 'obsolete_isallsuccessful_' 'fruit' 'obsolete_isallsuccessful_' 1 ((
PROCEDURE UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 SUBROUTINE
IMPLICIT_PURE) (UNKNOWN 0 0 0 UNKNOWN ()) 349 0 (350) () 0 () () () 0 0)
66 'dm_set_' 'dense_matrix_def' 'dm_set_' 1 ((PROCEDURE UNKNOWN-INTENT
MODULE-PROC DECL UNKNOWN 0 0 SUBROUTINE IMPLICIT_PURE) (UNKNOWN 0 0 0
UNKNOWN ()) 351 0 (352 353 354 355) () 0 () () () 0 0)
36 'assert_eq_string_' 'fruit' 'assert_eq_string_' 1 ((PROCEDURE
UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 SUBROUTINE ALWAYS_EXPLICIT)
(UNKNOWN 0 0 0 UNKNOWN ()) 356 0 (357 358 359) () 0 () () () 0 0)
28 'assert_eq_1d_complex_' 'fruit' 'assert_eq_1d_complex_' 1 ((
PROCEDURE UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 SUBROUTINE
ALWAYS_EXPLICIT) (UNKNOWN 0 0 0 UNKNOWN ()) 360 0 (361 362 363 364) () 0
() () () 0 0)
69 'dm_num_rows_' 'dense_matrix_def' 'dm_num_rows_' 1 ((PROCEDURE
UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 FUNCTION IMPLICIT_PURE) (
INTEGER 4 0 0 INTEGER ()) 365 0 (366) () 367 () () () 0 0)
26 'assert_eq_1d_double_in_range_' 'fruit' 'assert_eq_1d_double_in_range_'
1 ((PROCEDURE UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 SUBROUTINE
ALWAYS_EXPLICIT) (UNKNOWN 0 0 0 UNKNOWN ()) 368 0 (369 370 371 372 373)
() 0 () () () 0 0)
22 'assert_eq_2d_complex_' 'fruit' 'assert_eq_2d_complex_' 1 ((
PROCEDURE UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 SUBROUTINE
ALWAYS_EXPLICIT) (UNKNOWN 0 0 0 UNKNOWN ()) 374 0 (375 376 377 378 379)
() 0 () () () 0 0)
81 'vec_add_exc_' 'vector_def' 'vec_add_exc_' 1 ((PROCEDURE
UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 FUNCTION) (DERIVED 129 0 0
DERIVED ()) 380 0 (381 382 383) () 384 () () () 0 0)
78 'vec_clean_' 'vector_def' 'vec_clean_' 1 ((PROCEDURE UNKNOWN-INTENT
MODULE-PROC DECL UNKNOWN 0 0 SUBROUTINE IMPLICIT_PURE) (UNKNOWN 0 0 0
UNKNOWN ()) 385 0 (386) () 0 () () () 0 0)
80 'vec_dot_prod_' 'vector_def' 'vec_dot_prod_' 1 ((PROCEDURE
UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 FUNCTION IMPLICIT_PURE) (
REAL 8 0 0 REAL ()) 387 0 (388 389) () 390 () () () 0 0)
79 'vec_dot_prod_exc_' 'vector_def' 'vec_dot_prod_exc_' 1 ((PROCEDURE
UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 FUNCTION) (REAL 8 0 0 REAL ())
391 0 (392 393 394) () 395 () () () 0 0)
82 'vec_init_exc_' 'vector_def' 'vec_init_exc_' 1 ((PROCEDURE
UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 SUBROUTINE) (UNKNOWN 0 0 0
UNKNOWN ()) 396 0 (397 398 399) () 0 () () () 0 0)
83 'vec_init_' 'vector_def' 'vec_init_' 1 ((PROCEDURE UNKNOWN-INTENT
MODULE-PROC DECL UNKNOWN 0 0 SUBROUTINE) (UNKNOWN 0 0 0 UNKNOWN ()) 400
0 (401 402) () 0 () () () 0 0)
89 'vec_mapped_add_exc_' 'vector_def' 'vec_mapped_add_exc_' 1 ((
PROCEDURE UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 SUBROUTINE
ALWAYS_EXPLICIT) (UNKNOWN 0 0 0 UNKNOWN ()) 403 0 (404 405 406 407) () 0
() () () 0 0)
90 'vec_mapped_add_' 'vector_def' 'vec_mapped_add_' 1 ((PROCEDURE
UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 SUBROUTINE ALWAYS_EXPLICIT)
(UNKNOWN 0 0 0 UNKNOWN ()) 408 0 (409 410 411) () 0 () () () 0 0)
86 'vec_get_' 'vector_def' 'vec_get_' 1 ((PROCEDURE UNKNOWN-INTENT
MODULE-PROC DECL UNKNOWN 0 0 FUNCTION IMPLICIT_PURE) (REAL 8 0 0 REAL ())
412 0 (413 414) () 415 () () () 0 0)
88 'vec_set_' 'vector_def' 'vec_set_' 1 ((PROCEDURE UNKNOWN-INTENT
MODULE-PROC DECL UNKNOWN 0 0 SUBROUTINE IMPLICIT_PURE) (UNKNOWN 0 0 0
UNKNOWN ()) 416 0 (417 418 419) () 0 () () () 0 0)
84 'vec_length_' 'vector_def' 'vec_length_' 1 ((PROCEDURE UNKNOWN-INTENT
MODULE-PROC DECL UNKNOWN 0 0 FUNCTION IMPLICIT_PURE) (INTEGER 4 0 0
INTEGER ()) 420 0 (421) () 422 () () () 0 0)
87 'vec_set_exc_' 'vector_def' 'vec_set_exc_' 1 ((PROCEDURE
UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 SUBROUTINE) (UNKNOWN 0 0 0
UNKNOWN ()) 423 0 (424 425 426 427) () 0 () () () 0 0)
85 'vec_get_exc_' 'vector_def' 'vec_get_exc_' 1 ((PROCEDURE
UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 FUNCTION) (REAL 8 0 0 REAL ())
428 0 (429 430 431) () 432 () () () 0 0)
16 'obsolete_addsuccess_' 'fruit' 'obsolete_addsuccess_' 1 ((PROCEDURE
UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 SUBROUTINE IMPLICIT_PURE) (
UNKNOWN 0 0 0 UNKNOWN ()) 0 0 () () 0 () () () 0 0)
25 'assert_eq_2d_int_' 'fruit' 'assert_eq_2d_int_' 1 ((PROCEDURE
UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 SUBROUTINE ALWAYS_EXPLICIT)
(UNKNOWN 0 0 0 UNKNOWN ()) 433 0 (434 435 436 437 438) () 0 () () () 0 0)
24 'assert_eq_2d_double_' 'fruit' 'assert_eq_2d_double_' 1 ((PROCEDURE
UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 SUBROUTINE ALWAYS_EXPLICIT)
(UNKNOWN 0 0 0 UNKNOWN ()) 439 0 (440 441 442 443 444) () 0 () () () 0 0)
23 'assert_eq_2d_real_' 'fruit' 'assert_eq_2d_real_' 1 ((PROCEDURE
UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 SUBROUTINE ALWAYS_EXPLICIT)
(UNKNOWN 0 0 0 UNKNOWN ()) 445 0 (446 447 448 449 450) () 0 () () () 0 0)
27 'assert_eq_1d_real_in_range_' 'fruit' 'assert_eq_1d_real_in_range_' 1
((PROCEDURE UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 SUBROUTINE
ALWAYS_EXPLICIT) (UNKNOWN 0 0 0 UNKNOWN ()) 451 0 (452 453 454 455 456)
() 0 () () () 0 0)
30 'assert_eq_1d_real_' 'fruit' 'assert_eq_1d_real_' 1 ((PROCEDURE
UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 SUBROUTINE ALWAYS_EXPLICIT)
(UNKNOWN 0 0 0 UNKNOWN ()) 457 0 (458 459 460 461) () 0 () () () 0 0)
462 'acc_max' 'system_constants' 'acc_max' 1 ((PARAMETER UNKNOWN-INTENT
UNKNOWN-PROC UNKNOWN IMPLICIT-SAVE 0 0) (REAL 8 0 0 REAL ()) 0 0 () (
CONSTANT (REAL 8 0 0 REAL ()) 0 '0.174876e8000000@10') () 0 () () () 0 0)
463 'acc_min' 'system_constants' 'acc_min' 1 ((PARAMETER UNKNOWN-INTENT
UNKNOWN-PROC UNKNOWN IMPLICIT-SAVE 0 0) (REAL 8 0 0 REAL ()) 0 0 () (
CONSTANT (REAL 8 0 0 REAL ()) 0 '-0.174876e8000000@10') () 0 () () () 0
0)
464 'add_success' 'fruit' 'add_success' 1 ((PROCEDURE UNKNOWN-INTENT
MODULE-PROC DECL UNKNOWN 0 0 SUBROUTINE) (UNKNOWN 0 0 0 UNKNOWN ()) 0 0
() () 0 () () () 0 0)
465 'alloc' 'log_messages' 'alloc' 1 ((PARAMETER UNKNOWN-INTENT
UNKNOWN-PROC UNKNOWN IMPLICIT-SAVE 0 0) (INTEGER 4 0 0 INTEGER ()) 0 0 ()
(CONSTANT (INTEGER 4 0 0 INTEGER ()) 0 '2') () 0 () () () 0 0)
466 'assert_true' 'fruit' 'assert_true' 1 ((PROCEDURE UNKNOWN-INTENT
MODULE-PROC DECL UNKNOWN 0 0 SUBROUTINE ALWAYS_EXPLICIT) (UNKNOWN 0 0 0
UNKNOWN ()) 467 0 (468 469) () 0 () () () 0 0)
470 'band_sym_matrix_test' 'band_sym_matrix_test' 'band_sym_matrix_test'
1 ((MODULE UNKNOWN-INTENT UNKNOWN-PROC UNKNOWN UNKNOWN 0 0) (UNKNOWN 0 0
0 UNKNOWN ()) 0 0 () () 0 () () () 0 0)
134 'bandsymmatrixt' 'band_sym_matrix_def' 'bandsymmatrixt' 1 ((DERIVED
UNKNOWN-INTENT UNKNOWN-PROC UNKNOWN UNKNOWN 0 0 ALLOC_COMP) (UNKNOWN 0 0
0 UNKNOWN ()) 0 0 () () 0 ((471 'dat' (REAL 8 0 0 REAL ()) (2 0 DEFERRED
() () () ()) (UNKNOWN-FL UNKNOWN-INTENT UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
ALLOCATABLE DIMENSION) UNKNOWN-ACCESS ()) (472 'decomp' (REAL 8 0 0 REAL
()) (2 0 DEFERRED () () () ()) (UNKNOWN-FL UNKNOWN-INTENT UNKNOWN-PROC
UNKNOWN UNKNOWN 0 0 ALLOCATABLE DIMENSION) UNKNOWN-ACCESS ()) (473
'is_decomposed' (LOGICAL 4 0 0 LOGICAL ()) () (UNKNOWN-FL UNKNOWN-INTENT
UNKNOWN-PROC UNKNOWN UNKNOWN 0 0) UNKNOWN-ACCESS ())) PUBLIC (() () () ())
() 0 0 5919959)
474 'bfcrdr' 'log_messages' 'bfcrdr' 1 ((PARAMETER UNKNOWN-INTENT
UNKNOWN-PROC UNKNOWN IMPLICIT-SAVE 0 0) (INTEGER 4 0 0 INTEGER ()) 0 0 ()
(CONSTANT (INTEGER 4 0 0 INTEGER ()) 0 '1') () 0 () () () 0 0)
475 'bnddat' 'log_messages' 'bnddat' 1 ((PARAMETER UNKNOWN-INTENT
UNKNOWN-PROC UNKNOWN IMPLICIT-SAVE 0 0) (INTEGER 4 0 0 INTEGER ()) 0 0 ()
(CONSTANT (INTEGER 4 0 0 INTEGER ()) 0 '2') () 0 () () () 0 0)
476 'bndrdr' 'log_messages' 'bndrdr' 1 ((PARAMETER UNKNOWN-INTENT
UNKNOWN-PROC UNKNOWN IMPLICIT-SAVE 0 0) (INTEGER 4 0 0 INTEGER ()) 0 0 ()
(CONSTANT (INTEGER 4 0 0 INTEGER ()) 0 '3') () 0 () () () 0 0)
477 'bsymat' 'log_messages' 'bsymat' 1 ((PARAMETER UNKNOWN-INTENT
UNKNOWN-PROC UNKNOWN IMPLICIT-SAVE 0 0) (INTEGER 4 0 0 INTEGER ()) 0 0 ()
(CONSTANT (INTEGER 4 0 0 INTEGER ()) 0 '4') () 0 () () () 0 0)
478 'cnsmat' 'log_messages' 'cnsmat' 1 ((PARAMETER UNKNOWN-INTENT
UNKNOWN-PROC UNKNOWN IMPLICIT-SAVE 0 0) (INTEGER 4 0 0 INTEGER ()) 0 0 ()
(CONSTANT (INTEGER 4 0 0 INTEGER ()) 0 '5') () 0 () () () 0 0)
479 'coord_max' 'system_constants' 'coord_max' 1 ((PARAMETER
UNKNOWN-INTENT UNKNOWN-PROC UNKNOWN IMPLICIT-SAVE 0 0) (REAL 8 0 0 REAL
()) 0 0 () (CONSTANT (REAL 8 0 0 REAL ()) 0 '0.174876e8000000@10') () 0
() () () 0 0)
480 'coord_min' 'system_constants' 'coord_min' 1 ((PARAMETER
UNKNOWN-INTENT UNKNOWN-PROC UNKNOWN IMPLICIT-SAVE 0 0) (REAL 8 0 0 REAL
()) 0 0 () (CONSTANT (REAL 8 0 0 REAL ()) 0 '-0.174876e8000000@10') () 0
() () () 0 0)
481 'dimen' 'log_messages' 'dimen' 1 ((PARAMETER UNKNOWN-INTENT
UNKNOWN-PROC UNKNOWN IMPLICIT-SAVE 0 0) (INTEGER 4 0 0 INTEGER ()) 0 0 ()
(CONSTANT (INTEGER 4 0 0 INTEGER ()) 0 '3') () 0 () () () 0 0)
482 'disp_max' 'system_constants' 'disp_max' 1 ((PARAMETER
UNKNOWN-INTENT UNKNOWN-PROC UNKNOWN IMPLICIT-SAVE 0 0) (REAL 8 0 0 REAL
()) 0 0 () (CONSTANT (REAL 8 0 0 REAL ()) 0 '0.174876e8000000@10') () 0
() () () 0 0)
483 'disp_min' 'system_constants' 'disp_min' 1 ((PARAMETER
UNKNOWN-INTENT UNKNOWN-PROC UNKNOWN IMPLICIT-SAVE 0 0) (REAL 8 0 0 REAL
()) 0 0 () (CONSTANT (REAL 8 0 0 REAL ()) 0 '-0.174876e8000000@10') () 0
() () () 0 0)
484 'dmnrdr' 'log_messages' 'dmnrdr' 1 ((PARAMETER UNKNOWN-INTENT
UNKNOWN-PROC UNKNOWN IMPLICIT-SAVE 0 0) (INTEGER 4 0 0 INTEGER ()) 0 0 ()
(CONSTANT (INTEGER 4 0 0 INTEGER ()) 0 '6') () 0 () () () 0 0)
485 'dnsmat' 'log_messages' 'dnsmat' 1 ((PARAMETER UNKNOWN-INTENT
UNKNOWN-PROC UNKNOWN IMPLICIT-SAVE 0 0) (INTEGER 4 0 0 INTEGER ()) 0 0 ()
(CONSTANT (INTEGER 4 0 0 INTEGER ()) 0 '7') () 0 () () () 0 0)
486 'dtime_max' 'system_constants' 'dtime_max' 1 ((PARAMETER
UNKNOWN-INTENT UNKNOWN-PROC UNKNOWN IMPLICIT-SAVE 0 0) (REAL 8 0 0 REAL
()) 0 0 () (CONSTANT (REAL 8 0 0 REAL ()) 0 '0.27100000000000@4') () 0 ()
() () 0 0)
487 'dtime_min' 'system_constants' 'dtime_min' 1 ((PARAMETER
UNKNOWN-INTENT UNKNOWN-PROC UNKNOWN IMPLICIT-SAVE 0 0) (REAL 8 0 0 REAL
()) 0 0 () (CONSTANT (REAL 8 0 0 REAL ()) 0 '0.afebff0bcb24a8@-9') () 0
() () () 0 0)
488 'e_max' 'system_constants' 'e_max' 1 ((PARAMETER UNKNOWN-INTENT
UNKNOWN-PROC UNKNOWN IMPLICIT-SAVE 0 0) (REAL 8 0 0 REAL ()) 0 0 () (
CONSTANT (REAL 8 0 0 REAL ()) 0 '0.174876e8000000@10') () 0 () () () 0 0)
489 'e_min' 'system_constants' 'e_min' 1 ((PARAMETER UNKNOWN-INTENT
UNKNOWN-PROC UNKNOWN IMPLICIT-SAVE 0 0) (REAL 8 0 0 REAL ()) 0 0 () (
CONSTANT (REAL 8 0 0 REAL ()) 0 '0.00000000000000@0') () 0 () () () 0 0)
490 'exceed' 'log_messages' 'exceed' 1 ((PARAMETER UNKNOWN-INTENT
UNKNOWN-PROC UNKNOWN IMPLICIT-SAVE 0 0) (INTEGER 4 0 0 INTEGER ()) 0 0 ()
(CONSTANT (INTEGER 4 0 0 INTEGER ()) 0 '4') () 0 () () () 0 0)
491 'exists' 'log_messages' 'exists' 1 ((PARAMETER UNKNOWN-INTENT
UNKNOWN-PROC UNKNOWN IMPLICIT-SAVE 0 0) (INTEGER 4 0 0 INTEGER ()) 0 0 ()
(CONSTANT (INTEGER 4 0 0 INTEGER ()) 0 '5') () 0 () () () 0 0)
492 'failed_assert_action' 'fruit' 'failed_assert_action' 1 ((PROCEDURE
UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 SUBROUTINE ALWAYS_EXPLICIT)
(UNKNOWN 0 0 0 UNKNOWN ()) 493 0 (494 495 496) () 0 () () () 0 0)
497 'flddat' 'log_messages' 'flddat' 1 ((PARAMETER UNKNOWN-INTENT
UNKNOWN-PROC UNKNOWN IMPLICIT-SAVE 0 0) (INTEGER 4 0 0 INTEGER ()) 0 0 ()
(CONSTANT (INTEGER 4 0 0 INTEGER ()) 0 '8') () 0 () () () 0 0)
498 'formt' 'log_messages' 'formt' 1 ((PARAMETER UNKNOWN-INTENT
UNKNOWN-PROC UNKNOWN IMPLICIT-SAVE 0 0) (INTEGER 4 0 0 INTEGER ()) 0 0 ()
(CONSTANT (INTEGER 4 0 0 INTEGER ()) 0 '6') () 0 () () () 0 0)
499 'fruit_summary' 'fruit' 'fruit_summary' 1 ((PROCEDURE UNKNOWN-INTENT
MODULE-PROC DECL UNKNOWN 0 0 SUBROUTINE) (UNKNOWN 0 0 0 UNKNOWN ()) 0 0
() () 0 () () () 0 0)
500 'get_failed_count' 'fruit' 'get_failed_count' 1 ((PROCEDURE
UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 SUBROUTINE IMPLICIT_PURE) (
UNKNOWN 0 0 0 UNKNOWN ()) 501 0 (502) () 0 () () () 0 0)
503 'get_last_message' 'fruit' 'get_last_message' 1 ((PROCEDURE
UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 FUNCTION) (CHARACTER 1 0 0
CHARACTER ((CONSTANT (INTEGER 4 0 0 INTEGER ()) 0 '256'))) 0 0 () () 503
() () () 0 0)
504 'get_total_count' 'fruit' 'get_total_count' 1 ((PROCEDURE
UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 SUBROUTINE IMPLICIT_PURE) (
UNKNOWN 0 0 0 UNKNOWN ()) 505 0 (506) () 0 () () () 0 0)
507 'get_unit_name' 'fruit' 'get_unit_name' 1 ((PROCEDURE UNKNOWN-INTENT
MODULE-PROC DECL UNKNOWN 0 0 SUBROUTINE) (UNKNOWN 0 0 0 UNKNOWN ()) 508
0 (509) () 0 () () () 0 0)
510 'ictrdr' 'log_messages' 'ictrdr' 1 ((PARAMETER UNKNOWN-INTENT
UNKNOWN-PROC UNKNOWN IMPLICIT-SAVE 0 0) (INTEGER 4 0 0 INTEGER ()) 0 0 ()
(CONSTANT (INTEGER 4 0 0 INTEGER ()) 0 '9') () 0 () () () 0 0)
511 'icvrdr' 'log_messages' 'icvrdr' 1 ((PARAMETER UNKNOWN-INTENT
UNKNOWN-PROC UNKNOWN IMPLICIT-SAVE 0 0) (INTEGER 4 0 0 INTEGER ()) 0 0 ()
(CONSTANT (INTEGER 4 0 0 INTEGER ()) 0 '10') () 0 () () () 0 0)
512 'init_fruit' 'fruit' 'init_fruit' 1 ((PROCEDURE UNKNOWN-INTENT
MODULE-PROC DECL UNKNOWN 0 0 SUBROUTINE) (UNKNOWN 0 0 0 UNKNOWN ()) 0 0
() () 0 () () () 0 0)
513 'is_all_successful' 'fruit' 'is_all_successful' 1 ((PROCEDURE
UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 SUBROUTINE IMPLICIT_PURE) (
UNKNOWN 0 0 0 UNKNOWN ()) 514 0 (515) () 0 () () () 0 0)
516 'is_last_passed' 'fruit' 'is_last_passed' 1 ((PROCEDURE
UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 FUNCTION IMPLICIT_PURE) (
LOGICAL 4 0 0 LOGICAL ()) 0 0 () () 516 () () () 0 0)
517 'kbcrdr' 'log_messages' 'kbcrdr' 1 ((PARAMETER UNKNOWN-INTENT
UNKNOWN-PROC UNKNOWN IMPLICIT-SAVE 0 0) (INTEGER 4 0 0 INTEGER ()) 0 0 ()
(CONSTANT (INTEGER 4 0 0 INTEGER ()) 0 '11') () 0 () () () 0 0)
518 'linslv' 'log_messages' 'linslv' 1 ((PARAMETER UNKNOWN-INTENT
UNKNOWN-PROC UNKNOWN IMPLICIT-SAVE 0 0) (INTEGER 4 0 0 INTEGER ()) 0 0 ()
(CONSTANT (INTEGER 4 0 0 INTEGER ()) 0 '12') () 0 () () () 0 0)
519 'log_closelogfile' 'log_message_control' 'log_closelogfile' 1 ((
PROCEDURE UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 SUBROUTINE) (
UNKNOWN 0 0 0 UNKNOWN ()) 0 0 () () 0 () () () 0 0)
520 'log_getfilename' 'log_message_control' 'log_getfilename' 1 ((
PROCEDURE UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 FUNCTION
IMPLICIT_PURE) (CHARACTER 1 0 0 CHARACTER ((CONSTANT (INTEGER 4 0 0
INTEGER ()) 0 '200'))) 0 0 () () 521 () () () 0 0)
522 'log_initlogfile' 'log_message_control' 'log_initlogfile' 1 ((
PROCEDURE UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 SUBROUTINE) (
UNKNOWN 0 0 0 UNKNOWN ()) 0 0 () () 0 () () () 0 0)
523 'log_messages' 'log_messages' 'log_messages' 1 ((MODULE
UNKNOWN-INTENT UNKNOWN-PROC UNKNOWN UNKNOWN 0 0) (UNKNOWN 0 0 0 UNKNOWN
()) 0 0 () () 0 () () () 0 0)
524 'log_printlogmsg' 'log_message_control' 'log_printlogmsg' 1 ((
PROCEDURE UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 SUBROUTINE) (
UNKNOWN 0 0 0 UNKNOWN ()) 525 0 (526 527) () 0 () () () 0 0)
528 'log_setfilename' 'log_message_control' 'log_setfilename' 1 ((
PROCEDURE UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 SUBROUTINE) (
UNKNOWN 0 0 0 UNKNOWN ()) 529 0 (530) () 0 () () () 0 0)
531 'max_boundels' 'system_constants' 'max_boundels' 1 ((PARAMETER
UNKNOWN-INTENT UNKNOWN-PROC UNKNOWN IMPLICIT-SAVE 0 0) (INTEGER 4 0 0
INTEGER ()) 0 0 () (CONSTANT (INTEGER 4 0 0 INTEGER ()) 0 '2000') () 0 ()
() () 0 0)
532 'max_dofs' 'system_constants' 'max_dofs' 1 ((PARAMETER
UNKNOWN-INTENT UNKNOWN-PROC UNKNOWN IMPLICIT-SAVE 0 0) (INTEGER 4 0 0
INTEGER ()) 0 0 () (CONSTANT (INTEGER 4 0 0 INTEGER ()) 0 '3990') () 0 ()
() () 0 0)
533 'max_elements' 'system_constants' 'max_elements' 1 ((PARAMETER
UNKNOWN-INTENT UNKNOWN-PROC UNKNOWN IMPLICIT-SAVE 0 0) (INTEGER 4 0 0
INTEGER ()) 0 0 () (CONSTANT (INTEGER 4 0 0 INTEGER ()) 0 '5000') () 0 ()
() () 0 0)
534 'max_materials' 'system_constants' 'max_materials' 1 ((PARAMETER
UNKNOWN-INTENT UNKNOWN-PROC UNKNOWN IMPLICIT-SAVE 0 0) (INTEGER 4 0 0
INTEGER ()) 0 0 () (CONSTANT (INTEGER 4 0 0 INTEGER ()) 0 '30') () 0 ()
() () 0 0)
535 'max_nodes' 'system_constants' 'max_nodes' 1 ((PARAMETER
UNKNOWN-INTENT UNKNOWN-PROC UNKNOWN IMPLICIT-SAVE 0 0) (INTEGER 4 0 0
INTEGER ()) 0 0 () (CONSTANT (INTEGER 4 0 0 INTEGER ()) 0 '2000') () 0 ()
() () 0 0)
536 'max_timesteps' 'system_constants' 'max_timesteps' 1 ((PARAMETER
UNKNOWN-INTENT UNKNOWN-PROC UNKNOWN IMPLICIT-SAVE 0 0) (INTEGER 4 0 0
INTEGER ()) 0 0 () (CONSTANT (INTEGER 4 0 0 INTEGER ()) 0 '10000') () 0
() () () 0 0)
537 'maxlen' 'system_constants' 'maxlen' 1 ((PARAMETER UNKNOWN-INTENT
UNKNOWN-PROC UNKNOWN IMPLICIT-SAVE 0 0) (INTEGER 4 0 0 INTEGER ()) 0 0 ()
(CONSTANT (INTEGER 4 0 0 INTEGER ()) 0 '200') () 0 () () () 0 0)
538 'msg_getmsg' 'log_messages' 'msg_getmsg' 1 ((PROCEDURE
UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 FUNCTION IMPLICIT_PURE) (
CHARACTER 1 0 0 CHARACTER ((CONSTANT (INTEGER 4 0 0 INTEGER ()) 0 '200')))
539 0 (540) () 541 () () () 0 0)
542 'msg_getsdr' 'log_messages' 'msg_getsdr' 1 ((PROCEDURE
UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 FUNCTION IMPLICIT_PURE) (
CHARACTER 1 0 0 CHARACTER ((CONSTANT (INTEGER 4 0 0 INTEGER ()) 0 '200')))
543 0 (544) () 545 () () () 0 0)
546 'mtldat' 'log_messages' 'mtldat' 1 ((PARAMETER UNKNOWN-INTENT
UNKNOWN-PROC UNKNOWN IMPLICIT-SAVE 0 0) (INTEGER 4 0 0 INTEGER ()) 0 0 ()
(CONSTANT (INTEGER 4 0 0 INTEGER ()) 0 '13') () 0 () () () 0 0)
547 'mtlrdr' 'log_messages' 'mtlrdr' 1 ((PARAMETER UNKNOWN-INTENT
UNKNOWN-PROC UNKNOWN IMPLICIT-SAVE 0 0) (INTEGER 4 0 0 INTEGER ()) 0 0 ()
(CONSTANT (INTEGER 4 0 0 INTEGER ()) 0 '14') () 0 () () () 0 0)
548 'nbcrdr' 'log_messages' 'nbcrdr' 1 ((PARAMETER UNKNOWN-INTENT
UNKNOWN-PROC UNKNOWN IMPLICIT-SAVE 0 0) (INTEGER 4 0 0 INTEGER ()) 0 0 ()
(CONSTANT (INTEGER 4 0 0 INTEGER ()) 0 '15') () 0 () () () 0 0)
549 'ndim' 'system_constants' 'ndim' 1 ((PARAMETER UNKNOWN-INTENT
UNKNOWN-PROC UNKNOWN IMPLICIT-SAVE 0 0) (INTEGER 4 0 0 INTEGER ()) 0 0 ()
(CONSTANT (INTEGER 4 0 0 INTEGER ()) 0 '2') () 0 () () () 0 0)
550 'nnodel' 'system_constants' 'nnodel' 1 ((PARAMETER UNKNOWN-INTENT
UNKNOWN-PROC UNKNOWN IMPLICIT-SAVE 0 0) (INTEGER 4 0 0 INTEGER ()) 0 0 ()
(CONSTANT (INTEGER 4 0 0 INTEGER ()) 0 '3') () 0 () () () 0 0)
551 'nnodelb' 'system_constants' 'nnodelb' 1 ((PARAMETER UNKNOWN-INTENT
UNKNOWN-PROC UNKNOWN IMPLICIT-SAVE 0 0) (INTEGER 4 0 0 INTEGER ()) 0 0 ()
(CONSTANT (INTEGER 4 0 0 INTEGER ()) 0 '2') () 0 () () () 0 0)
552 'ntns' 'system_constants' 'ntns' 1 ((PARAMETER UNKNOWN-INTENT
UNKNOWN-PROC UNKNOWN IMPLICIT-SAVE 0 0) (INTEGER 4 0 0 INTEGER ()) 0 0 ()
(CONSTANT (INTEGER 4 0 0 INTEGER ()) 0 '3') () 0 () () () 0 0)
553 'nu_max' 'system_constants' 'nu_max' 1 ((PARAMETER UNKNOWN-INTENT
UNKNOWN-PROC UNKNOWN IMPLICIT-SAVE 0 0) (REAL 8 0 0 REAL ()) 0 0 () (
CONSTANT (REAL 8 0 0 REAL ()) 0 '0.7fbe76c8b43958@0') () 0 () () () 0 0)
554 'nu_min' 'system_constants' 'nu_min' 1 ((PARAMETER UNKNOWN-INTENT
UNKNOWN-PROC UNKNOWN IMPLICIT-SAVE 0 0) (REAL 8 0 0 REAL ()) 0 0 () (
CONSTANT (REAL 8 0 0 REAL ()) 0 '0.00000000000000@0') () 0 () () () 0 0)
555 'ok' 'log_messages' 'ok' 1 ((PARAMETER UNKNOWN-INTENT UNKNOWN-PROC
UNKNOWN IMPLICIT-SAVE 0 0) (INTEGER 4 0 0 INTEGER ()) 0 0 () (CONSTANT (
INTEGER 4 0 0 INTEGER ()) 0 '1') () 0 () () () 0 0)
556 'one_third' 'system_constants' 'one_third' 1 ((PARAMETER
UNKNOWN-INTENT UNKNOWN-PROC UNKNOWN IMPLICIT-SAVE 0 0) (REAL 8 0 0 REAL
()) 0 0 () (CONSTANT (REAL 8 0 0 REAL ()) 0 '0.55555555555554@0') () 0 ()
() () 0 0)
557 'posdef' 'log_messages' 'posdef' 1 ((PARAMETER UNKNOWN-INTENT
UNKNOWN-PROC UNKNOWN IMPLICIT-SAVE 0 0) (INTEGER 4 0 0 INTEGER ()) 0 0 ()
(CONSTANT (INTEGER 4 0 0 INTEGER ()) 0 '8') () 0 () () () 0 0)
558 'posit' 'log_messages' 'posit' 1 ((PARAMETER UNKNOWN-INTENT
UNKNOWN-PROC UNKNOWN IMPLICIT-SAVE 0 0) (INTEGER 4 0 0 INTEGER ()) 0 0 ()
(CONSTANT (INTEGER 4 0 0 INTEGER ()) 0 '7') () 0 () () () 0 0)
559 'rho_max' 'system_constants' 'rho_max' 1 ((PARAMETER UNKNOWN-INTENT
UNKNOWN-PROC UNKNOWN IMPLICIT-SAVE 0 0) (REAL 8 0 0 REAL ()) 0 0 () (
CONSTANT (REAL 8 0 0 REAL ()) 0 '0.174876e8000000@10') () 0 () () () 0 0)
560 'rho_min' 'system_constants' 'rho_min' 1 ((PARAMETER UNKNOWN-INTENT
UNKNOWN-PROC UNKNOWN IMPLICIT-SAVE 0 0) (REAL 8 0 0 REAL ()) 0 0 () (
CONSTANT (REAL 8 0 0 REAL ()) 0 '0.00000000000000@0') () 0 () () () 0 0)
561 'set_unit_name' 'fruit' 'set_unit_name' 1 ((PROCEDURE UNKNOWN-INTENT
MODULE-PROC DECL UNKNOWN 0 0 SUBROUTINE) (UNKNOWN 0 0 0 UNKNOWN ()) 562
0 (563) () 0 () () () 0 0)
564 'sig_max' 'system_constants' 'sig_max' 1 ((PARAMETER UNKNOWN-INTENT
UNKNOWN-PROC UNKNOWN IMPLICIT-SAVE 0 0) (REAL 8 0 0 REAL ()) 0 0 () (
CONSTANT (REAL 8 0 0 REAL ()) 0 '0.174876e8000000@10') () 0 () () () 0 0)
565 'sig_min' 'system_constants' 'sig_min' 1 ((PARAMETER UNKNOWN-INTENT
UNKNOWN-PROC UNKNOWN IMPLICIT-SAVE 0 0) (REAL 8 0 0 REAL ()) 0 0 () (
CONSTANT (REAL 8 0 0 REAL ()) 0 '-0.174876e8000000@10') () 0 () () () 0
0)
566 'str_max' 'system_constants' 'str_max' 1 ((PARAMETER UNKNOWN-INTENT
UNKNOWN-PROC UNKNOWN IMPLICIT-SAVE 0 0) (REAL 8 0 0 REAL ()) 0 0 () (
CONSTANT (REAL 8 0 0 REAL ()) 0 '0.28f5c28f5c28f6@-1') () 0 () () () 0 0)
567 'str_min' 'system_constants' 'str_min' 1 ((PARAMETER UNKNOWN-INTENT
UNKNOWN-PROC UNKNOWN IMPLICIT-SAVE 0 0) (REAL 8 0 0 REAL ()) 0 0 () (
CONSTANT (REAL 8 0 0 REAL ()) 0 '-0.28f5c28f5c28f6@-1') () 0 () () () 0
0)
568 'str_small' 'system_constants' 'str_small' 1 ((PARAMETER
UNKNOWN-INTENT UNKNOWN-PROC UNKNOWN IMPLICIT-SAVE 0 0) (REAL 8 0 0 REAL
()) 0 0 () (CONSTANT (REAL 8 0 0 REAL ()) 0 '0.28f5c28f5c28f6@-1') () 0
() () () 0 0)
569 'system_constants' 'system_constants' 'system_constants' 1 ((MODULE
UNKNOWN-INTENT UNKNOWN-PROC UNKNOWN UNKNOWN 0 0) (UNKNOWN 0 0 0 UNKNOWN
()) 0 0 () () 0 () () () 0 0)
570 'sze' 'log_messages' 'sze' 1 ((PARAMETER UNKNOWN-INTENT UNKNOWN-PROC
UNKNOWN IMPLICIT-SAVE 0 0) (INTEGER 4 0 0 INTEGER ()) 0 0 () (CONSTANT (
INTEGER 4 0 0 INTEGER ()) 0 '9') () 0 () () () 0 0)
571 'test_bsm_add_dimen' 'band_sym_matrix_test' 'test_bsm_add_dimen' 1 (
(PROCEDURE UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 SUBROUTINE) (
UNKNOWN 0 0 0 UNKNOWN ()) 0 0 () () 0 () () () 0 0)
572 'test_bsm_add_op' 'band_sym_matrix_test' 'test_bsm_add_op' 1 ((
PROCEDURE UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 SUBROUTINE) (
UNKNOWN 0 0 0 UNKNOWN ()) 0 0 () () 0 () () () 0 0)
573 'test_bsm_add_val' 'band_sym_matrix_test' 'test_bsm_add_val' 1 ((
PROCEDURE UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 SUBROUTINE) (
UNKNOWN 0 0 0 UNKNOWN ()) 0 0 () () 0 () () () 0 0)
574 'test_bsm_allocation_dat' 'band_sym_matrix_test'
'test_bsm_allocation_dat' 1 ((PROCEDURE UNKNOWN-INTENT MODULE-PROC DECL
UNKNOWN 0 0 SUBROUTINE IMPLICIT_PURE) (UNKNOWN 0 0 0 UNKNOWN ()) 0 0 ()
() 0 () () () 0 0)
575 'test_bsm_allocation_msg' 'band_sym_matrix_test'
'test_bsm_allocation_msg' 1 ((PROCEDURE UNKNOWN-INTENT MODULE-PROC DECL
UNKNOWN 0 0 SUBROUTINE IMPLICIT_PURE) (UNKNOWN 0 0 0 UNKNOWN ()) 0 0 ()
() 0 () () () 0 0)
576 'test_bsm_allocation_sze' 'band_sym_matrix_test'
'test_bsm_allocation_sze' 1 ((PROCEDURE UNKNOWN-INTENT MODULE-PROC DECL
UNKNOWN 0 0 SUBROUTINE IMPLICIT_PURE) (UNKNOWN 0 0 0 UNKNOWN ()) 0 0 ()
() 0 () () () 0 0)
577 'test_bsm_deallocation' 'band_sym_matrix_test' 'test_bsm_deallocation'
1 ((PROCEDURE UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 SUBROUTINE
IMPLICIT_PURE) (UNKNOWN 0 0 0 UNKNOWN ()) 0 0 () () 0 () () () 0 0)
578 'test_bsm_get_posit' 'band_sym_matrix_test' 'test_bsm_get_posit' 1 (
(PROCEDURE UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 SUBROUTINE) (
UNKNOWN 0 0 0 UNKNOWN ()) 0 0 () () 0 () () () 0 0)
579 'test_bsm_get_val' 'band_sym_matrix_test' 'test_bsm_get_val' 1 ((
PROCEDURE UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 SUBROUTINE) (
UNKNOWN 0 0 0 UNKNOWN ()) 0 0 () () 0 () () () 0 0)
580 'test_bsm_half_bw_allocated' 'band_sym_matrix_test'
'test_bsm_half_bw_allocated' 1 ((PROCEDURE UNKNOWN-INTENT MODULE-PROC
DECL UNKNOWN 0 0 SUBROUTINE) (UNKNOWN 0 0 0 UNKNOWN ()) 0 0 () () 0 () ()
() 0 0)
581 'test_bsm_half_bw_not_allocated' 'band_sym_matrix_test'
'test_bsm_half_bw_not_allocated' 1 ((PROCEDURE UNKNOWN-INTENT
MODULE-PROC DECL UNKNOWN 0 0 SUBROUTINE) (UNKNOWN 0 0 0 UNKNOWN ()) 0 0
() () 0 () () () 0 0)
582 'test_bsm_is_decomposed' 'band_sym_matrix_test'
'test_bsm_is_decomposed' 1 ((PROCEDURE UNKNOWN-INTENT MODULE-PROC DECL
UNKNOWN 0 0 SUBROUTINE) (UNKNOWN 0 0 0 UNKNOWN ()) 0 0 () () 0 () () ()
0 0)
583 'test_bsm_mapped_add_dimen1' 'band_sym_matrix_test'
'test_bsm_mapped_add_dimen1' 1 ((PROCEDURE UNKNOWN-INTENT MODULE-PROC
DECL UNKNOWN 0 0 SUBROUTINE IMPLICIT_PURE) (UNKNOWN 0 0 0 UNKNOWN ()) 0
0 () () 0 () () () 0 0)
584 'test_bsm_mapped_add_dimen2' 'band_sym_matrix_test'
'test_bsm_mapped_add_dimen2' 1 ((PROCEDURE UNKNOWN-INTENT MODULE-PROC
DECL UNKNOWN 0 0 SUBROUTINE IMPLICIT_PURE) (UNKNOWN 0 0 0 UNKNOWN ()) 0
0 () () 0 () () () 0 0)
585 'test_bsm_mapped_add_dimen3' 'band_sym_matrix_test'
'test_bsm_mapped_add_dimen3' 1 ((PROCEDURE UNKNOWN-INTENT MODULE-PROC
DECL UNKNOWN 0 0 SUBROUTINE IMPLICIT_PURE) (UNKNOWN 0 0 0 UNKNOWN ()) 0
0 () () 0 () () () 0 0)
586 'test_bsm_mapped_add_posit1' 'band_sym_matrix_test'
'test_bsm_mapped_add_posit1' 1 ((PROCEDURE UNKNOWN-INTENT MODULE-PROC
DECL UNKNOWN 0 0 SUBROUTINE IMPLICIT_PURE) (UNKNOWN 0 0 0 UNKNOWN ()) 0
0 () () 0 () () () 0 0)
587 'test_bsm_mapped_add_posit2' 'band_sym_matrix_test'
'test_bsm_mapped_add_posit2' 1 ((PROCEDURE UNKNOWN-INTENT MODULE-PROC
DECL UNKNOWN 0 0 SUBROUTINE IMPLICIT_PURE) (UNKNOWN 0 0 0 UNKNOWN ()) 0
0 () () 0 () () () 0 0)
588 'test_bsm_mapped_add_val1' 'band_sym_matrix_test'
'test_bsm_mapped_add_val1' 1 ((PROCEDURE UNKNOWN-INTENT MODULE-PROC DECL
UNKNOWN 0 0 SUBROUTINE IMPLICIT_PURE) (UNKNOWN 0 0 0 UNKNOWN ()) 0 0 ()
() 0 () () () 0 0)
589 'test_bsm_mapped_add_val2' 'band_sym_matrix_test'
'test_bsm_mapped_add_val2' 1 ((PROCEDURE UNKNOWN-INTENT MODULE-PROC DECL
UNKNOWN 0 0 SUBROUTINE IMPLICIT_PURE) (UNKNOWN 0 0 0 UNKNOWN ()) 0 0 ()
() 0 () () () 0 0)
590 'test_bsm_mapped_add_val3' 'band_sym_matrix_test'
'test_bsm_mapped_add_val3' 1 ((PROCEDURE UNKNOWN-INTENT MODULE-PROC DECL
UNKNOWN 0 0 SUBROUTINE IMPLICIT_PURE) (UNKNOWN 0 0 0 UNKNOWN ()) 0 0 ()
() 0 () () () 0 0)
591 'test_bsm_num_rows_allocated' 'band_sym_matrix_test'
'test_bsm_num_rows_allocated' 1 ((PROCEDURE UNKNOWN-INTENT MODULE-PROC
DECL UNKNOWN 0 0 SUBROUTINE) (UNKNOWN 0 0 0 UNKNOWN ()) 0 0 () () 0 () ()
() 0 0)
592 'test_bsm_num_rows_not_allocated' 'band_sym_matrix_test'
'test_bsm_num_rows_not_allocated' 1 ((PROCEDURE UNKNOWN-INTENT
MODULE-PROC DECL UNKNOWN 0 0 SUBROUTINE) (UNKNOWN 0 0 0 UNKNOWN ()) 0 0
() () 0 () () () 0 0)
593 'test_bsm_scal_mul_op' 'band_sym_matrix_test' 'test_bsm_scal_mul_op'
1 ((PROCEDURE UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 SUBROUTINE) (
UNKNOWN 0 0 0 UNKNOWN ()) 0 0 () () 0 () () () 0 0)
594 'test_bsm_scal_mul_val' 'band_sym_matrix_test' 'test_bsm_scal_mul_val'
1 ((PROCEDURE UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 SUBROUTINE) (
UNKNOWN 0 0 0 UNKNOWN ()) 0 0 () () 0 () () () 0 0)
595 'test_bsm_scal_mul_zero' 'band_sym_matrix_test'
'test_bsm_scal_mul_zero' 1 ((PROCEDURE UNKNOWN-INTENT MODULE-PROC DECL
UNKNOWN 0 0 SUBROUTINE) (UNKNOWN 0 0 0 UNKNOWN ()) 0 0 () () 0 () () ()
0 0)
596 'test_bsm_set_decomp_dimen' 'band_sym_matrix_test'
'test_bsm_set_decomp_dimen' 1 ((PROCEDURE UNKNOWN-INTENT MODULE-PROC
DECL UNKNOWN 0 0 SUBROUTINE IMPLICIT_PURE) (UNKNOWN 0 0 0 UNKNOWN ()) 0
0 () () 0 () () () 0 0)
597 'test_bsm_set_decomp_val' 'band_sym_matrix_test'
'test_bsm_set_decomp_val' 1 ((PROCEDURE UNKNOWN-INTENT MODULE-PROC DECL
UNKNOWN 0 0 SUBROUTINE IMPLICIT_PURE) (UNKNOWN 0 0 0 UNKNOWN ()) 0 0 ()
() 0 () () () 0 0)
598 'test_bsm_set_posit' 'band_sym_matrix_test' 'test_bsm_set_posit' 1 (
(PROCEDURE UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 SUBROUTINE
IMPLICIT_PURE) (UNKNOWN 0 0 0 UNKNOWN ()) 0 0 () () 0 () () () 0 0)
599 'test_bsm_set_val' 'band_sym_matrix_test' 'test_bsm_set_val' 1 ((
PROCEDURE UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 SUBROUTINE) (
UNKNOWN 0 0 0 UNKNOWN ()) 0 0 () () 0 () () () 0 0)
600 'test_bsm_vec_mul_dimen' 'band_sym_matrix_test'
'test_bsm_vec_mul_dimen' 1 ((PROCEDURE UNKNOWN-INTENT MODULE-PROC DECL
UNKNOWN 0 0 SUBROUTINE) (UNKNOWN 0 0 0 UNKNOWN ()) 0 0 () () 0 () () ()
0 0)
601 'test_bsm_vec_mul_ident' 'band_sym_matrix_test'
'test_bsm_vec_mul_ident' 1 ((PROCEDURE UNKNOWN-INTENT MODULE-PROC DECL
UNKNOWN 0 0 SUBROUTINE) (UNKNOWN 0 0 0 UNKNOWN ()) 0 0 () () 0 () () ()
0 0)
602 'test_bsm_vec_mul_op' 'band_sym_matrix_test' 'test_bsm_vec_mul_op' 1
((PROCEDURE UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 SUBROUTINE) (
UNKNOWN 0 0 0 UNKNOWN ()) 0 0 () () 0 () () () 0 0)
603 'test_bsm_vec_mul_val' 'band_sym_matrix_test' 'test_bsm_vec_mul_val'
1 ((PROCEDURE UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 SUBROUTINE) (
UNKNOWN 0 0 0 UNKNOWN ()) 0 0 () () 0 () () () 0 0)
604 'test_bsm_vec_mul_zero' 'band_sym_matrix_test' 'test_bsm_vec_mul_zero'
1 ((PROCEDURE UNKNOWN-INTENT MODULE-PROC DECL UNKNOWN 0 0 SUBROUTINE) (
UNKNOWN 0 0 0 UNKNOWN ()) 0 0 () () 0 () () () 0 0)
605 'tnswtr' 'log_messages' 'tnswtr' 1 ((PARAMETER UNKNOWN-INTENT
UNKNOWN-PROC UNKNOWN IMPLICIT-SAVE 0 0) (INTEGER 4 0 0 INTEGER ()) 0 0 ()
(CONSTANT (INTEGER 4 0 0 INTEGER ()) 0 '16') () 0 () () () 0 0)
606 'typ' 'log_messages' 'typ' 1 ((PARAMETER UNKNOWN-INTENT UNKNOWN-PROC
UNKNOWN IMPLICIT-SAVE 0 0) (INTEGER 4 0 0 INTEGER ()) 0 0 () (CONSTANT (
INTEGER 4 0 0 INTEGER ()) 0 '10') () 0 () () () 0 0)
607 'vector' 'log_messages' 'vector' 1 ((PARAMETER UNKNOWN-INTENT
UNKNOWN-PROC UNKNOWN IMPLICIT-SAVE 0 0) (INTEGER 4 0 0 INTEGER ()) 0 0 ()
(CONSTANT (INTEGER 4 0 0 INTEGER ()) 0 '17') () 0 () () () 0 0)
608 'vecwtr' 'log_messages' 'vecwtr' 1 ((PARAMETER UNKNOWN-INTENT
UNKNOWN-PROC UNKNOWN IMPLICIT-SAVE 0 0) (INTEGER 4 0 0 INTEGER ()) 0 0 ()
(CONSTANT (INTEGER 4 0 0 INTEGER ()) 0 '18') () 0 () () () 0 0)
609 'vel_max' 'system_constants' 'vel_max' 1 ((PARAMETER UNKNOWN-INTENT
UNKNOWN-PROC UNKNOWN IMPLICIT-SAVE 0 0) (REAL 8 0 0 REAL ()) 0 0 () (
CONSTANT (REAL 8 0 0 REAL ()) 0 '0.174876e8000000@10') () 0 () () () 0 0)
610 'vel_min' 'system_constants' 'vel_min' 1 ((PARAMETER UNKNOWN-INTENT
UNKNOWN-PROC UNKNOWN IMPLICIT-SAVE 0 0) (REAL 8 0 0 REAL ()) 0 0 () (
CONSTANT (REAL 8 0 0 REAL ()) 0 '-0.174876e8000000@10') () 0 () () () 0
0)
527 'sdr' '' 'sdr' 525 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
526 'msg' '' 'msg' 525 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
530 'fname' '' 'fname' 529 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0
0 DUMMY) (CHARACTER 1 0 0 CHARACTER (())) 0 0 () () 0 () () () 0 0)
521 'fname' '' 'fname' 611 ((VARIABLE UNKNOWN-INTENT UNKNOWN-PROC
UNKNOWN UNKNOWN 0 0 RESULT) (CHARACTER 1 0 0 CHARACTER ((CONSTANT (
INTEGER 4 0 0 INTEGER ()) 0 '200'))) 0 0 () () 0 () () () 0 0)
312 'self' '' 'self' 311 ((VARIABLE INOUT UNKNOWN-PROC UNKNOWN UNKNOWN 0
0 DUMMY) (DERIVED 139 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
314 'n' '' 'n' 311 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0 DUMMY)
(INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
313 'm' '' 'm' 311 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0 DUMMY)
(INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
317 'm' '' 'm' 315 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0 DUMMY)
(INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
316 'self' '' 'self' 315 ((VARIABLE INOUT UNKNOWN-PROC UNKNOWN UNKNOWN 0
0 DUMMY) (DERIVED 139 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
319 'exc' '' 'exc' 315 ((VARIABLE OUT UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
322 'n' '' 'n' 320 ((VARIABLE UNKNOWN-INTENT UNKNOWN-PROC UNKNOWN
UNKNOWN 0 0 RESULT) (INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
321 'self' '' 'self' 320 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (DERIVED 139 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
291 'self' '' 'self' 290 ((VARIABLE INOUT UNKNOWN-PROC UNKNOWN UNKNOWN 0
0 DUMMY) (DERIVED 139 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
299 'self' '' 'self' 298 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (DERIVED 139 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
301 'j' '' 'j' 298 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0 DUMMY)
(INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
302 'v' '' 'v' 298 ((VARIABLE UNKNOWN-INTENT UNKNOWN-PROC UNKNOWN
UNKNOWN 0 0 RESULT) (REAL 8 0 0 REAL ()) 0 0 () () 0 () () () 0 0)
541 'exc' '' 'exc' 539 ((VARIABLE UNKNOWN-INTENT UNKNOWN-PROC UNKNOWN
UNKNOWN 0 0 RESULT) (CHARACTER 1 0 0 CHARACTER ((CONSTANT (INTEGER 4 0 0
INTEGER ()) 0 '200'))) 0 0 () () 0 () () () 0 0)
545 'sdr' '' 'sdr' 543 ((VARIABLE UNKNOWN-INTENT UNKNOWN-PROC UNKNOWN
UNKNOWN 0 0 RESULT) (CHARACTER 1 0 0 CHARACTER ((CONSTANT (INTEGER 4 0 0
INTEGER ()) 0 '200'))) 0 0 () () 0 () () () 0 0)
544 'code' '' 'code' 543 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
540 'code' '' 'code' 539 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
469 'message' '' 'message' 467 ((VARIABLE IN UNKNOWN-PROC UNKNOWN
UNKNOWN 0 0 OPTIONAL DUMMY) (CHARACTER 1 0 0 CHARACTER (())) 0 0 () () 0
() () () 0 0)
495 'got' '' 'got' 493 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (CHARACTER 1 0 0 CHARACTER (())) 0 0 () () 0 () () () 0 0)
494 'expected' '' 'expected' 493 ((VARIABLE IN UNKNOWN-PROC UNKNOWN
UNKNOWN 0 0 DUMMY) (CHARACTER 1 0 0 CHARACTER (())) 0 0 () () 0 () () ()
0 0)
506 'count' '' 'count' 505 ((VARIABLE OUT UNKNOWN-PROC UNKNOWN UNKNOWN 0
0 DUMMY) (INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
515 'result' '' 'result' 514 ((VARIABLE OUT UNKNOWN-PROC UNKNOWN UNKNOWN
0 0 DUMMY) (LOGICAL 4 0 0 LOGICAL ()) 0 0 () () 0 () () () 0 0)
509 'value' '' 'value' 508 ((VARIABLE OUT UNKNOWN-PROC UNKNOWN UNKNOWN 0
0 DUMMY) (CHARACTER 1 0 0 CHARACTER (())) 0 0 () () 0 () () () 0 0)
496 'message' '' 'message' 493 ((VARIABLE IN UNKNOWN-PROC UNKNOWN
UNKNOWN 0 0 OPTIONAL DUMMY) (CHARACTER 1 0 0 CHARACTER (())) 0 0 () () 0
() () () 0 0)
258 'message' '' 'message' 256 ((VARIABLE IN UNKNOWN-PROC UNKNOWN
UNKNOWN 0 0 OPTIONAL DUMMY) (CHARACTER 1 0 0 CHARACTER (())) 0 0 () () 0
() () () 0 0)
278 'var2' '' 'var2' 276 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
277 'var1' '' 'var1' 276 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
279 'message' '' 'message' 276 ((VARIABLE IN UNKNOWN-PROC UNKNOWN
UNKNOWN 0 0 OPTIONAL DUMMY) (CHARACTER 1 0 0 CHARACTER (())) 0 0 () () 0
() () () 0 0)
127 'var2' '' 'var2' 125 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (REAL 8 0 0 REAL ()) 0 0 () () 0 () () () 0 0)
128 'message' '' 'message' 125 ((VARIABLE IN UNKNOWN-PROC UNKNOWN
UNKNOWN 0 0 OPTIONAL DUMMY) (CHARACTER 1 0 0 CHARACTER (())) 0 0 () () 0
() () () 0 0)
171 'message' '' 'message' 168 ((VARIABLE IN UNKNOWN-PROC UNKNOWN
UNKNOWN 0 0 OPTIONAL DUMMY) (CHARACTER 1 0 0 CHARACTER (())) 0 0 () () 0
() () () 0 0)
170 'var2' '' 'var2' 168 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (REAL 4 0 0 REAL ()) 0 0 () () 0 () () () 0 0)
169 'var1' '' 'var1' 168 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (REAL 4 0 0 REAL ()) 0 0 () () 0 () () () 0 0)
126 'var1' '' 'var1' 125 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (REAL 8 0 0 REAL ()) 0 0 () () 0 () () () 0 0)
281 'var1' '' 'var1' 280 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (LOGICAL 4 0 0 LOGICAL ()) 0 0 () () 0 () () () 0 0)
283 'message' '' 'message' 280 ((VARIABLE IN UNKNOWN-PROC UNKNOWN
UNKNOWN 0 0 OPTIONAL DUMMY) (CHARACTER 1 0 0 CHARACTER (())) 0 0 () () 0
() () () 0 0)
282 'var2' '' 'var2' 280 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (LOGICAL 4 0 0 LOGICAL ()) 0 0 () () 0 () () () 0 0)
357 'var1' '' 'var1' 356 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (CHARACTER 1 0 0 CHARACTER (())) 0 0 () () 0 () () () 0 0)
359 'message' '' 'message' 356 ((VARIABLE IN UNKNOWN-PROC UNKNOWN
UNKNOWN 0 0 OPTIONAL DUMMY) (CHARACTER 1 0 0 CHARACTER (())) 0 0 () () 0
() () () 0 0)
358 'var2' '' 'var2' 356 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (CHARACTER 1 0 0 CHARACTER (())) 0 0 () () 0 () () () 0 0)
124 'message' '' 'message' 121 ((VARIABLE IN UNKNOWN-PROC UNKNOWN
UNKNOWN 0 0 OPTIONAL DUMMY) (CHARACTER 1 0 0 CHARACTER (())) 0 0 () () 0
() () () 0 0)
123 'var2' '' 'var2' 121 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (COMPLEX 8 0 0 COMPLEX ()) 0 0 () () 0 () () () 0 0)
122 'var1' '' 'var1' 121 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (COMPLEX 8 0 0 COMPLEX ()) 0 0 () () 0 () () () 0 0)
109 'var3' '' 'var3' 106 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (REAL 4 0 0 REAL ()) 0 0 () () 0 () () () 0 0)
110 'message' '' 'message' 106 ((VARIABLE IN UNKNOWN-PROC UNKNOWN
UNKNOWN 0 0 OPTIONAL DUMMY) (CHARACTER 1 0 0 CHARACTER (())) 0 0 () () 0
() () () 0 0)
114 'var3' '' 'var3' 111 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (REAL 8 0 0 REAL ()) 0 0 () () 0 () () () 0 0)
113 'var2' '' 'var2' 111 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (REAL 8 0 0 REAL ()) 0 0 () () 0 () () () 0 0)
112 'var1' '' 'var1' 111 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (REAL 8 0 0 REAL ()) 0 0 () () 0 () () () 0 0)
108 'var2' '' 'var2' 106 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (REAL 4 0 0 REAL ()) 0 0 () () 0 () () () 0 0)
107 'var1' '' 'var1' 106 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (REAL 4 0 0 REAL ()) 0 0 () () 0 () () () 0 0)
103 'var2' '' 'var2' 101 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DIMENSION DUMMY) (INTEGER 4 0 0 INTEGER ()) 0 0 () (1 0 EXPLICIT (
CONSTANT (INTEGER 4 0 0 INTEGER ()) 0 '1') (VARIABLE (INTEGER 4 0 0
INTEGER ()) 0 104 ())) 0 () () () 0 0)
102 'var1' '' 'var1' 101 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DIMENSION DUMMY) (INTEGER 4 0 0 INTEGER ()) 0 0 () (1 0 EXPLICIT (
CONSTANT (INTEGER 4 0 0 INTEGER ()) 0 '1') (VARIABLE (INTEGER 4 0 0
INTEGER ()) 0 104 ())) 0 () () () 0 0)
105 'message' '' 'message' 101 ((VARIABLE IN UNKNOWN-PROC UNKNOWN
UNKNOWN 0 0 OPTIONAL DUMMY) (CHARACTER 1 0 0 CHARACTER (())) 0 0 () () 0
() () () 0 0)
104 'n' '' 'n' 101 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0 DUMMY)
(INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
115 'message' '' 'message' 111 ((VARIABLE IN UNKNOWN-PROC UNKNOWN
UNKNOWN 0 0 OPTIONAL DUMMY) (CHARACTER 1 0 0 CHARACTER (())) 0 0 () () 0
() () () 0 0)
119 'n' '' 'n' 116 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0 DUMMY)
(INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
118 'var2' '' 'var2' 116 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DIMENSION DUMMY) (REAL 8 0 0 REAL ()) 0 0 () (1 0 EXPLICIT (CONSTANT (
INTEGER 4 0 0 INTEGER ()) 0 '1') (VARIABLE (INTEGER 4 0 0 INTEGER ()) 0
119 ())) 0 () () () 0 0)
458 'var1' '' 'var1' 457 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DIMENSION DUMMY) (REAL 4 0 0 REAL ()) 0 0 () (1 0 EXPLICIT (CONSTANT (
INTEGER 4 0 0 INTEGER ()) 0 '1') (VARIABLE (INTEGER 4 0 0 INTEGER ()) 0
460 ())) 0 () () () 0 0)
459 'var2' '' 'var2' 457 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DIMENSION DUMMY) (REAL 4 0 0 REAL ()) 0 0 () (1 0 EXPLICIT (CONSTANT (
INTEGER 4 0 0 INTEGER ()) 0 '1') (VARIABLE (INTEGER 4 0 0 INTEGER ()) 0
460 ())) 0 () () () 0 0)
120 'message' '' 'message' 116 ((VARIABLE IN UNKNOWN-PROC UNKNOWN
UNKNOWN 0 0 OPTIONAL DUMMY) (CHARACTER 1 0 0 CHARACTER (())) 0 0 () () 0
() () () 0 0)
461 'message' '' 'message' 457 ((VARIABLE IN UNKNOWN-PROC UNKNOWN
UNKNOWN 0 0 OPTIONAL DUMMY) (CHARACTER 1 0 0 CHARACTER (())) 0 0 () () 0
() () () 0 0)
460 'n' '' 'n' 457 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0 DUMMY)
(INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
117 'var1' '' 'var1' 116 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DIMENSION DUMMY) (REAL 8 0 0 REAL ()) 0 0 () (1 0 EXPLICIT (CONSTANT (
INTEGER 4 0 0 INTEGER ()) 0 '1') (VARIABLE (INTEGER 4 0 0 INTEGER ()) 0
119 ())) 0 () () () 0 0)
97 'var1' '' 'var1' 96 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DIMENSION DUMMY) (CHARACTER 1 0 0 CHARACTER (())) 0 0 () (1 0 EXPLICIT (
CONSTANT (INTEGER 4 0 0 INTEGER ()) 0 '1') (VARIABLE (INTEGER 4 0 0
INTEGER ()) 0 99 ())) 0 () () () 0 0)
99 'n' '' 'n' 96 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0 DUMMY) (
INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
100 'message' '' 'message' 96 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN
0 0 OPTIONAL DUMMY) (CHARACTER 1 0 0 CHARACTER (())) 0 0 () () 0 () () ()
0 0)
363 'n' '' 'n' 360 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0 DUMMY)
(INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
362 'var2' '' 'var2' 360 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DIMENSION DUMMY) (COMPLEX 8 0 0 COMPLEX ()) 0 0 () (1 0 EXPLICIT (
CONSTANT (INTEGER 4 0 0 INTEGER ()) 0 '1') (VARIABLE (INTEGER 4 0 0
INTEGER ()) 0 363 ())) 0 () () () 0 0)
361 'var1' '' 'var1' 360 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DIMENSION DUMMY) (COMPLEX 8 0 0 COMPLEX ()) 0 0 () (1 0 EXPLICIT (
CONSTANT (INTEGER 4 0 0 INTEGER ()) 0 '1') (VARIABLE (INTEGER 4 0 0
INTEGER ()) 0 363 ())) 0 () () () 0 0)
452 'var1' '' 'var1' 451 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DIMENSION DUMMY) (REAL 4 0 0 REAL ()) 0 0 () (1 0 EXPLICIT (CONSTANT (
INTEGER 4 0 0 INTEGER ()) 0 '1') (VARIABLE (INTEGER 4 0 0 INTEGER ()) 0
454 ())) 0 () () () 0 0)
364 'message' '' 'message' 360 ((VARIABLE IN UNKNOWN-PROC UNKNOWN
UNKNOWN 0 0 OPTIONAL DUMMY) (CHARACTER 1 0 0 CHARACTER (())) 0 0 () () 0
() () () 0 0)
454 'n' '' 'n' 451 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0 DUMMY)
(INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
455 'var3' '' 'var3' 451 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (REAL 4 0 0 REAL ()) 0 0 () () 0 () () () 0 0)
456 'message' '' 'message' 451 ((VARIABLE IN UNKNOWN-PROC UNKNOWN
UNKNOWN 0 0 OPTIONAL DUMMY) (CHARACTER 1 0 0 CHARACTER (())) 0 0 () () 0
() () () 0 0)
453 'var2' '' 'var2' 451 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DIMENSION DUMMY) (REAL 4 0 0 REAL ()) 0 0 () (1 0 EXPLICIT (CONSTANT (
INTEGER 4 0 0 INTEGER ()) 0 '1') (VARIABLE (INTEGER 4 0 0 INTEGER ()) 0
454 ())) 0 () () () 0 0)
98 'var2' '' 'var2' 96 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DIMENSION DUMMY) (CHARACTER 1 0 0 CHARACTER (())) 0 0 () (1 0 EXPLICIT (
CONSTANT (INTEGER 4 0 0 INTEGER ()) 0 '1') (VARIABLE (INTEGER 4 0 0
INTEGER ()) 0 99 ())) 0 () () () 0 0)
371 'n' '' 'n' 368 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0 DUMMY)
(INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
370 'var2' '' 'var2' 368 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DIMENSION DUMMY) (REAL 8 0 0 REAL ()) 0 0 () (1 0 EXPLICIT (CONSTANT (
INTEGER 4 0 0 INTEGER ()) 0 '1') (VARIABLE (INTEGER 4 0 0 INTEGER ()) 0
371 ())) 0 () () () 0 0)
369 'var1' '' 'var1' 368 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DIMENSION DUMMY) (REAL 8 0 0 REAL ()) 0 0 () (1 0 EXPLICIT (CONSTANT (
INTEGER 4 0 0 INTEGER ()) 0 '1') (VARIABLE (INTEGER 4 0 0 INTEGER ()) 0
371 ())) 0 () () () 0 0)
257 'var1' '' 'var1' 256 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (LOGICAL 4 0 0 LOGICAL ()) 0 0 () () 0 () () () 0 0)
434 'var1' '' 'var1' 433 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DIMENSION DUMMY) (INTEGER 4 0 0 INTEGER ()) 0 0 () (2 0 EXPLICIT (
CONSTANT (INTEGER 4 0 0 INTEGER ()) 0 '1') (VARIABLE (INTEGER 4 0 0
INTEGER ()) 0 436 ()) (CONSTANT (INTEGER 4 0 0 INTEGER ()) 0 '1') (
VARIABLE (INTEGER 4 0 0 INTEGER ()) 0 437 ())) 0 () () () 0 0)
435 'var2' '' 'var2' 433 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DIMENSION DUMMY) (INTEGER 4 0 0 INTEGER ()) 0 0 () (2 0 EXPLICIT (
CONSTANT (INTEGER 4 0 0 INTEGER ()) 0 '1') (VARIABLE (INTEGER 4 0 0
INTEGER ()) 0 436 ()) (CONSTANT (INTEGER 4 0 0 INTEGER ()) 0 '1') (
VARIABLE (INTEGER 4 0 0 INTEGER ()) 0 437 ())) 0 () () () 0 0)
440 'var1' '' 'var1' 439 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DIMENSION DUMMY) (REAL 8 0 0 REAL ()) 0 0 () (2 0 EXPLICIT (CONSTANT (
INTEGER 4 0 0 INTEGER ()) 0 '1') (VARIABLE (INTEGER 4 0 0 INTEGER ()) 0
442 ()) (CONSTANT (INTEGER 4 0 0 INTEGER ()) 0 '1') (VARIABLE (INTEGER 4
0 0 INTEGER ()) 0 443 ())) 0 () () () 0 0)
438 'message' '' 'message' 433 ((VARIABLE IN UNKNOWN-PROC UNKNOWN
UNKNOWN 0 0 OPTIONAL DUMMY) (CHARACTER 1 0 0 CHARACTER (())) 0 0 () () 0
() () () 0 0)
441 'var2' '' 'var2' 439 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DIMENSION DUMMY) (REAL 8 0 0 REAL ()) 0 0 () (2 0 EXPLICIT (CONSTANT (
INTEGER 4 0 0 INTEGER ()) 0 '1') (VARIABLE (INTEGER 4 0 0 INTEGER ()) 0
442 ()) (CONSTANT (INTEGER 4 0 0 INTEGER ()) 0 '1') (VARIABLE (INTEGER 4
0 0 INTEGER ()) 0 443 ())) 0 () () () 0 0)
437 'm' '' 'm' 433 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0 DUMMY)
(INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
436 'n' '' 'n' 433 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0 DUMMY)
(INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
373 'message' '' 'message' 368 ((VARIABLE IN UNKNOWN-PROC UNKNOWN
UNKNOWN 0 0 OPTIONAL DUMMY) (CHARACTER 1 0 0 CHARACTER (())) 0 0 () () 0
() () () 0 0)
443 'm' '' 'm' 439 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0 DUMMY)
(INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
444 'message' '' 'message' 439 ((VARIABLE IN UNKNOWN-PROC UNKNOWN
UNKNOWN 0 0 OPTIONAL DUMMY) (CHARACTER 1 0 0 CHARACTER (())) 0 0 () () 0
() () () 0 0)
449 'm' '' 'm' 445 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0 DUMMY)
(INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
448 'n' '' 'n' 445 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0 DUMMY)
(INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
447 'var2' '' 'var2' 445 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DIMENSION DUMMY) (REAL 4 0 0 REAL ()) 0 0 () (2 0 EXPLICIT (CONSTANT (
INTEGER 4 0 0 INTEGER ()) 0 '1') (VARIABLE (INTEGER 4 0 0 INTEGER ()) 0
448 ()) (CONSTANT (INTEGER 4 0 0 INTEGER ()) 0 '1') (VARIABLE (INTEGER 4
0 0 INTEGER ()) 0 449 ())) 0 () () () 0 0)
446 'var1' '' 'var1' 445 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DIMENSION DUMMY) (REAL 4 0 0 REAL ()) 0 0 () (2 0 EXPLICIT (CONSTANT (
INTEGER 4 0 0 INTEGER ()) 0 '1') (VARIABLE (INTEGER 4 0 0 INTEGER ()) 0
448 ()) (CONSTANT (INTEGER 4 0 0 INTEGER ()) 0 '1') (VARIABLE (INTEGER 4
0 0 INTEGER ()) 0 449 ())) 0 () () () 0 0)
376 'var2' '' 'var2' 374 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DIMENSION DUMMY) (COMPLEX 8 0 0 COMPLEX ()) 0 0 () (2 0 EXPLICIT (
CONSTANT (INTEGER 4 0 0 INTEGER ()) 0 '1') (VARIABLE (INTEGER 4 0 0
INTEGER ()) 0 377 ()) (CONSTANT (INTEGER 4 0 0 INTEGER ()) 0 '1') (
VARIABLE (INTEGER 4 0 0 INTEGER ()) 0 378 ())) 0 () () () 0 0)
375 'var1' '' 'var1' 374 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DIMENSION DUMMY) (COMPLEX 8 0 0 COMPLEX ()) 0 0 () (2 0 EXPLICIT (
CONSTANT (INTEGER 4 0 0 INTEGER ()) 0 '1') (VARIABLE (INTEGER 4 0 0
INTEGER ()) 0 377 ()) (CONSTANT (INTEGER 4 0 0 INTEGER ()) 0 '1') (
VARIABLE (INTEGER 4 0 0 INTEGER ()) 0 378 ())) 0 () () () 0 0)
378 'm' '' 'm' 374 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0 DUMMY)
(INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
379 'message' '' 'message' 374 ((VARIABLE IN UNKNOWN-PROC UNKNOWN
UNKNOWN 0 0 OPTIONAL DUMMY) (CHARACTER 1 0 0 CHARACTER (())) 0 0 () () 0
() () () 0 0)
377 'n' '' 'n' 374 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0 DUMMY)
(INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
450 'message' '' 'message' 445 ((VARIABLE IN UNKNOWN-PROC UNKNOWN
UNKNOWN 0 0 OPTIONAL DUMMY) (CHARACTER 1 0 0 CHARACTER (())) 0 0 () () 0
() () () 0 0)
345 'n' '' 'n' 342 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0 DUMMY)
(INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
344 'var2' '' 'var2' 342 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DIMENSION DUMMY) (REAL 4 0 0 REAL ()) 0 0 () (2 0 EXPLICIT (CONSTANT (
INTEGER 4 0 0 INTEGER ()) 0 '1') (VARIABLE (INTEGER 4 0 0 INTEGER ()) 0
345 ()) (CONSTANT (INTEGER 4 0 0 INTEGER ()) 0 '1') (VARIABLE (INTEGER 4
0 0 INTEGER ()) 0 346 ())) 0 () () () 0 0)
343 'var1' '' 'var1' 342 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DIMENSION DUMMY) (REAL 4 0 0 REAL ()) 0 0 () (2 0 EXPLICIT (CONSTANT (
INTEGER 4 0 0 INTEGER ()) 0 '1') (VARIABLE (INTEGER 4 0 0 INTEGER ()) 0
345 ()) (CONSTANT (INTEGER 4 0 0 INTEGER ()) 0 '1') (VARIABLE (INTEGER 4
0 0 INTEGER ()) 0 346 ())) 0 () () () 0 0)
348 'message' '' 'message' 342 ((VARIABLE IN UNKNOWN-PROC UNKNOWN
UNKNOWN 0 0 OPTIONAL DUMMY) (CHARACTER 1 0 0 CHARACTER (())) 0 0 () () 0
() () () 0 0)
347 'var3' '' 'var3' 342 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (REAL 4 0 0 REAL ()) 0 0 () () 0 () () () 0 0)
262 'n' '' 'n' 259 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0 DUMMY)
(INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
261 'var2' '' 'var2' 259 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DIMENSION DUMMY) (REAL 8 0 0 REAL ()) 0 0 () (2 0 EXPLICIT (CONSTANT (
INTEGER 4 0 0 INTEGER ()) 0 '1') (VARIABLE (INTEGER 4 0 0 INTEGER ()) 0
262 ()) (CONSTANT (INTEGER 4 0 0 INTEGER ()) 0 '1') (VARIABLE (INTEGER 4
0 0 INTEGER ()) 0 263 ())) 0 () () () 0 0)
260 'var1' '' 'var1' 259 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DIMENSION DUMMY) (REAL 8 0 0 REAL ()) 0 0 () (2 0 EXPLICIT (CONSTANT (
INTEGER 4 0 0 INTEGER ()) 0 '1') (VARIABLE (INTEGER 4 0 0 INTEGER ()) 0
262 ()) (CONSTANT (INTEGER 4 0 0 INTEGER ()) 0 '1') (VARIABLE (INTEGER 4
0 0 INTEGER ()) 0 263 ())) 0 () () () 0 0)
264 'var3' '' 'var3' 259 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (REAL 8 0 0 REAL ()) 0 0 () () 0 () () () 0 0)
263 'm' '' 'm' 259 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0 DUMMY)
(INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
215 'var1' '' 'var1' 214 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (REAL 4 0 0 REAL ()) 0 0 () () 0 () () () 0 0)
217 'message' '' 'message' 214 ((VARIABLE IN UNKNOWN-PROC UNKNOWN
UNKNOWN 0 0 OPTIONAL DUMMY) (CHARACTER 1 0 0 CHARACTER (())) 0 0 () () 0
() () () 0 0)
269 'var1' '' 'var1' 268 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DIMENSION DUMMY) (REAL 4 0 0 REAL ()) 0 0 () (1 0 EXPLICIT (CONSTANT (
INTEGER 4 0 0 INTEGER ()) 0 '1') (VARIABLE (INTEGER 4 0 0 INTEGER ()) 0
271 ())) 0 () () () 0 0)
216 'var2' '' 'var2' 214 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (REAL 4 0 0 REAL ()) 0 0 () () 0 () () () 0 0)
265 'message' '' 'message' 259 ((VARIABLE IN UNKNOWN-PROC UNKNOWN
UNKNOWN 0 0 OPTIONAL DUMMY) (CHARACTER 1 0 0 CHARACTER (())) 0 0 () () 0
() () () 0 0)
270 'var2' '' 'var2' 268 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DIMENSION DUMMY) (REAL 4 0 0 REAL ()) 0 0 () (1 0 EXPLICIT (CONSTANT (
INTEGER 4 0 0 INTEGER ()) 0 '1') (VARIABLE (INTEGER 4 0 0 INTEGER ()) 0
271 ())) 0 () () () 0 0)
273 'var1' '' 'var1' 272 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (REAL 8 0 0 REAL ()) 0 0 () () 0 () () () 0 0)
275 'message' '' 'message' 272 ((VARIABLE IN UNKNOWN-PROC UNKNOWN
UNKNOWN 0 0 OPTIONAL DUMMY) (CHARACTER 1 0 0 CHARACTER (())) 0 0 () () 0
() () () 0 0)
95 'message' '' 'message' 94 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN
0 0 OPTIONAL DUMMY) (CHARACTER 1 0 0 CHARACTER (())) 0 0 () () 0 () () ()
0 0)
267 'count' '' 'count' 266 ((VARIABLE OUT UNKNOWN-PROC UNKNOWN UNKNOWN 0
0 DUMMY) (INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
93 'message' '' 'message' 91 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN
0 0 DUMMY) (CHARACTER 1 0 0 CHARACTER (())) 0 0 () () 0 () () () 0 0)
92 'unitname' '' 'unitname' 91 ((VARIABLE IN UNKNOWN-PROC UNKNOWN
UNKNOWN 0 0 DUMMY) (CHARACTER 1 0 0 CHARACTER (())) 0 0 () () 0 () () ()
0 0)
274 'var2' '' 'var2' 272 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (REAL 8 0 0 REAL ()) 0 0 () () 0 () () () 0 0)
287 'count' '' 'count' 286 ((VARIABLE OUT UNKNOWN-PROC UNKNOWN UNKNOWN 0
0 DUMMY) (INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
289 'tc' '' 'tc' 288 ((PROCEDURE UNKNOWN-INTENT UNKNOWN-PROC BODY
UNKNOWN 0 0 DUMMY SUBROUTINE) (UNKNOWN 0 0 0 UNKNOWN ()) 612 0 () () 0 ()
() () 0 0)
309 'tc' '' 'tc' 308 ((PROCEDURE UNKNOWN-INTENT DUMMY-PROC BODY UNKNOWN
0 0 DUMMY SUBROUTINE) (UNKNOWN 0 0 0 UNKNOWN ()) 613 0 () () 0 () () ()
0 0)
310 'tc_name' '' 'tc_name' 308 ((VARIABLE IN UNKNOWN-PROC UNKNOWN
UNKNOWN 0 0 DUMMY) (CHARACTER 1 0 0 CHARACTER (())) 0 0 () () 0 () () ()
0 0)
350 'result' '' 'result' 349 ((VARIABLE OUT UNKNOWN-PROC UNKNOWN UNKNOWN
0 0 DUMMY) (LOGICAL 4 0 0 LOGICAL ()) 0 0 () () 0 () () () 0 0)
271 'n' '' 'n' 268 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0 DUMMY)
(INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
346 'm' '' 'm' 342 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0 DUMMY)
(INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
442 'n' '' 'n' 439 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0 DUMMY)
(INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
372 'var3' '' 'var3' 368 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (REAL 8 0 0 REAL ()) 0 0 () () 0 () () () 0 0)
468 'var1' '' 'var1' 467 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (LOGICAL 4 0 0 LOGICAL ()) 0 0 () () 0 () () () 0 0)
502 'count' '' 'count' 501 ((VARIABLE OUT UNKNOWN-PROC UNKNOWN UNKNOWN 0
0 DUMMY) (INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
563 'value' '' 'value' 562 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0
0 DUMMY) (CHARACTER 1 0 0 CHARACTER (())) 0 0 () () 0 () () () 0 0)
195 'self' '' 'self' 194 ((VARIABLE INOUT UNKNOWN-PROC UNKNOWN UNKNOWN 0
0 DUMMY) (DERIVED 134 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
197 'n' '' 'n' 194 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0 DUMMY)
(INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
202 'self' '' 'self' 201 ((VARIABLE INOUT UNKNOWN-PROC UNKNOWN UNKNOWN 0
0 DUMMY) (DERIVED 134 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
203 'hbw' '' 'hbw' 201 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
205 'exc' '' 'exc' 201 ((VARIABLE OUT UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
189 'self' '' 'self' 188 ((VARIABLE INOUT UNKNOWN-PROC UNKNOWN UNKNOWN 0
0 DUMMY) (DERIVED 134 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
212 'self' '' 'self' 211 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (DERIVED 134 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
204 'n' '' 'n' 201 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0 DUMMY)
(INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
199 'self' '' 'self' 198 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (DERIVED 134 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
213 'n' '' 'n' 211 ((VARIABLE UNKNOWN-INTENT UNKNOWN-PROC UNKNOWN
UNKNOWN 0 0 RESULT) (INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
196 'hbw' '' 'hbw' 194 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
185 'i' '' 'i' 183 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0 DUMMY)
(INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
184 'self' '' 'self' 183 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (DERIVED 134 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
187 'v' '' 'v' 183 ((VARIABLE UNKNOWN-INTENT UNKNOWN-PROC UNKNOWN
UNKNOWN 0 0 RESULT) (REAL 8 0 0 REAL ()) 0 0 () () 0 () () () 0 0)
186 'j' '' 'j' 183 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0 DUMMY)
(INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
174 'i' '' 'i' 172 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0 DUMMY)
(INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
176 'exc' '' 'exc' 172 ((VARIABLE OUT UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
175 'j' '' 'j' 172 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0 DUMMY)
(INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
231 'self' '' 'self' 230 ((VARIABLE INOUT UNKNOWN-PROC UNKNOWN UNKNOWN 0
0 DUMMY) (DERIVED 134 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
177 'v' '' 'v' 172 ((VARIABLE UNKNOWN-INTENT UNKNOWN-PROC UNKNOWN
UNKNOWN 0 0 RESULT) (REAL 8 0 0 REAL ()) 0 0 () () 0 () () () 0 0)
173 'self' '' 'self' 172 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (DERIVED 134 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
200 'hbw' '' 'hbw' 198 ((VARIABLE UNKNOWN-INTENT UNKNOWN-PROC UNKNOWN
UNKNOWN 0 0 RESULT) (INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
234 'v' '' 'v' 230 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0 DUMMY)
(REAL 8 0 0 REAL ()) 0 0 () () 0 () () () 0 0)
236 'self' '' 'self' 235 ((VARIABLE INOUT UNKNOWN-PROC UNKNOWN UNKNOWN 0
0 DUMMY) (DERIVED 134 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
233 'j' '' 'j' 230 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0 DUMMY)
(INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
232 'i' '' 'i' 230 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0 DUMMY)
(INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
238 'j' '' 'j' 235 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0 DUMMY)
(INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
239 'v' '' 'v' 235 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0 DUMMY)
(REAL 8 0 0 REAL ()) 0 0 () () 0 () () () 0 0)
223 'self' '' 'self' 222 ((VARIABLE INOUT UNKNOWN-PROC UNKNOWN UNKNOWN 0
0 DUMMY) (DERIVED 134 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
219 'self' '' 'self' 218 ((VARIABLE INOUT UNKNOWN-PROC UNKNOWN UNKNOWN 0
0 DUMMY) (DERIVED 134 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
221 'exc' '' 'exc' 218 ((VARIABLE OUT UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
220 'decomp' '' 'decomp' 218 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN
0 0 DIMENSION DUMMY) (REAL 8 0 0 REAL ()) 0 0 () (2 0 ASSUMED_SHAPE (
CONSTANT (INTEGER 4 0 0 INTEGER ()) 0 '1') () (CONSTANT (INTEGER 4 0 0
INTEGER ()) 0 '1') ()) 0 () () () 0 0)
224 'decomp' '' 'decomp' 222 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN
0 0 DIMENSION DUMMY) (REAL 8 0 0 REAL ()) 0 0 () (2 0 ASSUMED_SHAPE (
CONSTANT (INTEGER 4 0 0 INTEGER ()) 0 '1') () (CONSTANT (INTEGER 4 0 0
INTEGER ()) 0 '1') ()) 0 () () () 0 0)
240 'exc' '' 'exc' 235 ((VARIABLE OUT UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
247 'is_decomposed' '' 'is_decomposed' 245 ((VARIABLE UNKNOWN-INTENT
UNKNOWN-PROC UNKNOWN UNKNOWN 0 0 RESULT) (LOGICAL 4 0 0 LOGICAL ()) 0 0
() () 0 () () () 0 0)
246 'self' '' 'self' 245 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (DERIVED 134 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
137 'other' '' 'other' 135 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0
0 DUMMY) (DERIVED 134 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
138 'new' '' 'new' 135 ((VARIABLE UNKNOWN-INTENT UNKNOWN-PROC UNKNOWN
UNKNOWN 0 0 RESULT) (DERIVED 134 0 0 DERIVED ()) 0 0 () () 0 () () () 0
0)
179 'self' '' 'self' 178 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (DERIVED 134 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
136 'self' '' 'self' 135 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (DERIVED 134 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
237 'i' '' 'i' 235 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0 DUMMY)
(INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
182 'new' '' 'new' 178 ((VARIABLE UNKNOWN-INTENT UNKNOWN-PROC UNKNOWN
UNKNOWN 0 0 RESULT) (DERIVED 134 0 0 DERIVED ()) 0 0 () () 0 () () () 0
0)
181 'exc' '' 'exc' 178 ((VARIABLE OUT UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
243 'other' '' 'other' 241 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0
0 DUMMY) (DERIVED 139 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
207 'self' '' 'self' 206 ((VARIABLE INOUT UNKNOWN-PROC UNKNOWN UNKNOWN 0
0 DUMMY) (DERIVED 134 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
244 'ind' '' 'ind' 241 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DIMENSION DUMMY) (INTEGER 4 0 0 INTEGER ()) 0 0 () (1 0 ASSUMED_SHAPE (
CONSTANT (INTEGER 4 0 0 INTEGER ()) 0 '1') ()) 0 () () () 0 0)
242 'self' '' 'self' 241 ((VARIABLE INOUT UNKNOWN-PROC UNKNOWN UNKNOWN 0
0 DUMMY) (DERIVED 134 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
209 'ind' '' 'ind' 206 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DIMENSION DUMMY) (INTEGER 4 0 0 INTEGER ()) 0 0 () (1 0 ASSUMED_SHAPE (
CONSTANT (INTEGER 4 0 0 INTEGER ()) 0 '1') ()) 0 () () () 0 0)
210 'exc' '' 'exc' 206 ((VARIABLE OUT UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
149 'self' '' 'self' 148 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (DERIVED 134 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
150 'k' '' 'k' 148 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0 DUMMY)
(REAL 8 0 0 REAL ()) 0 0 () () 0 () () () 0 0)
151 'new' '' 'new' 148 ((VARIABLE UNKNOWN-INTENT UNKNOWN-PROC UNKNOWN
UNKNOWN 0 0 RESULT) (DERIVED 134 0 0 DERIVED ()) 0 0 () () 0 () () () 0
0)
208 'other' '' 'other' 206 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0
0 DUMMY) (DERIVED 139 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
226 'self' '' 'self' 225 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (DERIVED 134 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
159 'new' '' 'new' 156 ((VARIABLE UNKNOWN-INTENT UNKNOWN-PROC UNKNOWN
UNKNOWN 0 0 RESULT) (DERIVED 129 0 0 DERIVED ()) 0 0 () () 0 () () () 0
0)
158 'other' '' 'other' 156 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0
0 DUMMY) (DERIVED 129 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
228 'exc' '' 'exc' 225 ((VARIABLE OUT UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
227 'other' '' 'other' 225 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0
0 DUMMY) (DERIVED 129 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
157 'self' '' 'self' 156 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (DERIVED 134 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
146 'self' '' 'self' 144 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (DERIVED 134 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
147 'new' '' 'new' 144 ((VARIABLE UNKNOWN-INTENT UNKNOWN-PROC UNKNOWN
UNKNOWN 0 0 RESULT) (DERIVED 134 0 0 DERIVED ()) 0 0 () () 0 () () () 0
0)
145 'k' '' 'k' 144 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0 DUMMY)
(REAL 8 0 0 REAL ()) 0 0 () () 0 () () () 0 0)
167 'new' '' 'new' 164 ((VARIABLE UNKNOWN-INTENT UNKNOWN-PROC UNKNOWN
UNKNOWN 0 0 RESULT) (DERIVED 139 0 0 DERIVED ()) 0 0 () () 0 () () () 0
0)
166 'k' '' 'k' 164 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0 DUMMY)
(REAL 8 0 0 REAL ()) 0 0 () () 0 () () () 0 0)
165 'self' '' 'self' 164 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (DERIVED 139 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
229 'new' '' 'new' 225 ((VARIABLE UNKNOWN-INTENT UNKNOWN-PROC UNKNOWN
UNKNOWN 0 0 RESULT) (DERIVED 129 0 0 DERIVED ()) 0 0 () () 0 () () () 0
0)
192 'self' '' 'self' 190 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (DERIVED 139 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
249 'self' '' 'self' 248 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (DERIVED 139 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
193 'new' '' 'new' 190 ((VARIABLE UNKNOWN-INTENT UNKNOWN-PROC UNKNOWN
UNKNOWN 0 0 RESULT) (DERIVED 139 0 0 DERIVED ()) 0 0 () () 0 () () () 0
0)
251 'new' '' 'new' 248 ((VARIABLE UNKNOWN-INTENT UNKNOWN-PROC UNKNOWN
UNKNOWN 0 0 RESULT) (DERIVED 129 0 0 DERIVED ()) 0 0 () () 0 () () () 0
0)
250 'other' '' 'other' 248 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0
0 DUMMY) (DERIVED 129 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
163 'new' '' 'new' 160 ((VARIABLE UNKNOWN-INTENT UNKNOWN-PROC UNKNOWN
UNKNOWN 0 0 RESULT) (DERIVED 139 0 0 DERIVED ()) 0 0 () () 0 () () () 0
0)
162 'other' '' 'other' 160 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0
0 DUMMY) (DERIVED 139 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
161 'self' '' 'self' 160 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (DERIVED 139 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
141 'self' '' 'self' 140 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (DERIVED 139 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
143 'new' '' 'new' 140 ((VARIABLE UNKNOWN-INTENT UNKNOWN-PROC UNKNOWN
UNKNOWN 0 0 RESULT) (DERIVED 139 0 0 DERIVED ()) 0 0 () () 0 () () () 0
0)
153 'k' '' 'k' 152 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0 DUMMY)
(REAL 8 0 0 REAL ()) 0 0 () () 0 () () () 0 0)
142 'other' '' 'other' 140 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0
0 DUMMY) (DERIVED 139 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
155 'new' '' 'new' 152 ((VARIABLE UNKNOWN-INTENT UNKNOWN-PROC UNKNOWN
UNKNOWN 0 0 RESULT) (DERIVED 129 0 0 DERIVED ()) 0 0 () () 0 () () () 0
0)
254 'k' '' 'k' 252 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0 DUMMY)
(REAL 8 0 0 REAL ()) 0 0 () () 0 () () () 0 0)
255 'new' '' 'new' 252 ((VARIABLE UNKNOWN-INTENT UNKNOWN-PROC UNKNOWN
UNKNOWN 0 0 RESULT) (DERIVED 129 0 0 DERIVED ()) 0 0 () () 0 () () () 0
0)
131 'self' '' 'self' 130 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (DERIVED 129 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
132 'other' '' 'other' 130 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0
0 DUMMY) (DERIVED 129 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
133 'new' '' 'new' 130 ((VARIABLE UNKNOWN-INTENT UNKNOWN-PROC UNKNOWN
UNKNOWN 0 0 RESULT) (DERIVED 129 0 0 DERIVED ()) 0 0 () () 0 () () () 0
0)
253 'self' '' 'self' 252 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (DERIVED 129 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
154 'self' '' 'self' 152 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (DERIVED 129 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
191 'k' '' 'k' 190 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0 DUMMY)
(REAL 8 0 0 REAL ()) 0 0 () () 0 () () () 0 0)
180 'other' '' 'other' 178 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0
0 DUMMY) (DERIVED 134 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
300 'i' '' 'i' 298 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0 DUMMY)
(INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
294 'i' '' 'i' 292 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0 DUMMY)
(INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
293 'self' '' 'self' 292 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (DERIVED 139 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
295 'j' '' 'j' 292 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0 DUMMY)
(INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
296 'exc' '' 'exc' 292 ((VARIABLE OUT UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
297 'v' '' 'v' 292 ((VARIABLE UNKNOWN-INTENT UNKNOWN-PROC UNKNOWN
UNKNOWN 0 0 RESULT) (REAL 8 0 0 REAL ()) 0 0 () () 0 () () () 0 0)
353 'i' '' 'i' 351 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0 DUMMY)
(INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
354 'j' '' 'j' 351 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0 DUMMY)
(INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
352 'self' '' 'self' 351 ((VARIABLE INOUT UNKNOWN-PROC UNKNOWN UNKNOWN 0
0 DUMMY) (DERIVED 139 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
318 'n' '' 'n' 315 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0 DUMMY)
(INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
325 'i' '' 'i' 323 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0 DUMMY)
(INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
327 'v' '' 'v' 323 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0 DUMMY)
(REAL 8 0 0 REAL ()) 0 0 () () 0 () () () 0 0)
326 'j' '' 'j' 323 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0 DUMMY)
(INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
324 'self' '' 'self' 323 ((VARIABLE INOUT UNKNOWN-PROC UNKNOWN UNKNOWN 0
0 DUMMY) (DERIVED 139 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
328 'exc' '' 'exc' 323 ((VARIABLE OUT UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
355 'v' '' 'v' 351 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0 DUMMY)
(REAL 8 0 0 REAL ()) 0 0 () () 0 () () () 0 0)
304 'self' '' 'self' 303 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (DERIVED 139 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
305 'other' '' 'other' 303 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0
0 DUMMY) (DERIVED 139 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
307 'new' '' 'new' 303 ((VARIABLE UNKNOWN-INTENT UNKNOWN-PROC UNKNOWN
UNKNOWN 0 0 RESULT) (DERIVED 139 0 0 DERIVED ()) 0 0 () () 0 () () () 0
0)
306 'exc' '' 'exc' 303 ((VARIABLE OUT UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
339 'other' '' 'other' 337 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0
0 DUMMY) (DERIVED 129 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
341 'new' '' 'new' 337 ((VARIABLE UNKNOWN-INTENT UNKNOWN-PROC UNKNOWN
UNKNOWN 0 0 RESULT) (DERIVED 129 0 0 DERIVED ()) 0 0 () () 0 () () () 0
0)
340 'exc' '' 'exc' 337 ((VARIABLE OUT UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
335 'exc' '' 'exc' 332 ((VARIABLE OUT UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
336 'new' '' 'new' 332 ((VARIABLE UNKNOWN-INTENT UNKNOWN-PROC UNKNOWN
UNKNOWN 0 0 RESULT) (DERIVED 139 0 0 DERIVED ()) 0 0 () () 0 () () () 0
0)
334 'other' '' 'other' 332 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0
0 DUMMY) (DERIVED 139 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
333 'self' '' 'self' 332 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (DERIVED 139 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
330 'self' '' 'self' 329 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (DERIVED 139 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
331 'new' '' 'new' 329 ((VARIABLE UNKNOWN-INTENT UNKNOWN-PROC UNKNOWN
UNKNOWN 0 0 RESULT) (DERIVED 139 0 0 DERIVED ()) 0 0 () () 0 () () () 0
0)
338 'self' '' 'self' 337 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (DERIVED 139 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
366 'self' '' 'self' 365 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (DERIVED 139 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
367 'm' '' 'm' 365 ((VARIABLE UNKNOWN-INTENT UNKNOWN-PROC UNKNOWN
UNKNOWN 0 0 RESULT) (INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
401 'self' '' 'self' 400 ((VARIABLE INOUT UNKNOWN-PROC UNKNOWN UNKNOWN 0
0 DUMMY) (DERIVED 129 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
397 'self' '' 'self' 396 ((VARIABLE INOUT UNKNOWN-PROC UNKNOWN UNKNOWN 0
0 DUMMY) (DERIVED 129 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
399 'exc' '' 'exc' 396 ((VARIABLE OUT UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
398 'n' '' 'n' 396 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0 DUMMY)
(INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
386 'self' '' 'self' 385 ((VARIABLE INOUT UNKNOWN-PROC UNKNOWN UNKNOWN 0
0 DUMMY) (DERIVED 129 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
422 'n' '' 'n' 420 ((VARIABLE UNKNOWN-INTENT UNKNOWN-PROC UNKNOWN
UNKNOWN 0 0 RESULT) (INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
415 'v' '' 'v' 412 ((VARIABLE UNKNOWN-INTENT UNKNOWN-PROC UNKNOWN
UNKNOWN 0 0 RESULT) (REAL 8 0 0 REAL ()) 0 0 () () 0 () () () 0 0)
414 'i' '' 'i' 412 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0 DUMMY)
(INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
413 'self' '' 'self' 412 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (DERIVED 129 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
421 'self' '' 'self' 420 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (DERIVED 129 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
402 'n' '' 'n' 400 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0 DUMMY)
(INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
419 'v' '' 'v' 416 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0 DUMMY)
(REAL 8 0 0 REAL ()) 0 0 () () 0 () () () 0 0)
418 'i' '' 'i' 416 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0 DUMMY)
(INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
417 'self' '' 'self' 416 ((VARIABLE INOUT UNKNOWN-PROC UNKNOWN UNKNOWN 0
0 DUMMY) (DERIVED 129 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
425 'i' '' 'i' 423 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0 DUMMY)
(INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
427 'exc' '' 'exc' 423 ((VARIABLE OUT UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
381 'self' '' 'self' 380 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (DERIVED 129 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
383 'exc' '' 'exc' 380 ((VARIABLE OUT UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
384 'new' '' 'new' 380 ((VARIABLE UNKNOWN-INTENT UNKNOWN-PROC UNKNOWN
UNKNOWN 0 0 RESULT) (DERIVED 129 0 0 DERIVED ()) 0 0 () () 0 () () () 0
0)
410 'other' '' 'other' 408 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0
0 DUMMY) (DERIVED 129 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
411 'ind' '' 'ind' 408 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DIMENSION DUMMY) (INTEGER 4 0 0 INTEGER ()) 0 0 () (1 0 ASSUMED_SHAPE (
CONSTANT (INTEGER 4 0 0 INTEGER ()) 0 '1') ()) 0 () () () 0 0)
409 'self' '' 'self' 408 ((VARIABLE INOUT UNKNOWN-PROC UNKNOWN UNKNOWN 0
0 DUMMY) (DERIVED 129 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
405 'other' '' 'other' 403 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0
0 DUMMY) (DERIVED 129 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
404 'self' '' 'self' 403 ((VARIABLE INOUT UNKNOWN-PROC UNKNOWN UNKNOWN 0
0 DUMMY) (DERIVED 129 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
382 'other' '' 'other' 380 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0
0 DUMMY) (DERIVED 129 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
388 'self' '' 'self' 387 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (DERIVED 129 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
389 'other' '' 'other' 387 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0
0 DUMMY) (DERIVED 129 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
392 'self' '' 'self' 391 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (DERIVED 129 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
394 'exc' '' 'exc' 391 ((VARIABLE OUT UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
393 'other' '' 'other' 391 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0
0 DUMMY) (DERIVED 129 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
390 'v' '' 'v' 387 ((VARIABLE UNKNOWN-INTENT UNKNOWN-PROC UNKNOWN
UNKNOWN 0 0 RESULT) (REAL 8 0 0 REAL ()) 0 0 () () 0 () () () 0 0)
407 'exc' '' 'exc' 403 ((VARIABLE OUT UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
406 'ind' '' 'ind' 403 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DIMENSION DUMMY) (INTEGER 4 0 0 INTEGER ()) 0 0 () (1 0 ASSUMED_SHAPE (
CONSTANT (INTEGER 4 0 0 INTEGER ()) 0 '1') ()) 0 () () () 0 0)
395 'v' '' 'v' 391 ((VARIABLE UNKNOWN-INTENT UNKNOWN-PROC UNKNOWN
UNKNOWN 0 0 RESULT) (REAL 8 0 0 REAL ()) 0 0 () () 0 () () () 0 0)
426 'v' '' 'v' 423 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0 DUMMY)
(REAL 8 0 0 REAL ()) 0 0 () () 0 () () () 0 0)
429 'self' '' 'self' 428 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (DERIVED 129 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
430 'i' '' 'i' 428 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0 DUMMY)
(INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
432 'v' '' 'v' 428 ((VARIABLE UNKNOWN-INTENT UNKNOWN-PROC UNKNOWN
UNKNOWN 0 0 RESULT) (REAL 8 0 0 REAL ()) 0 0 () () 0 () () () 0 0)
431 'exc' '' 'exc' 428 ((VARIABLE OUT UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) (INTEGER 4 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
424 'self' '' 'self' 423 ((VARIABLE INOUT UNKNOWN-PROC UNKNOWN UNKNOWN 0
0 DUMMY) (DERIVED 129 0 0 DERIVED ()) 0 0 () () 0 () () () 0 0)
)
('acc_max' 0 462 'acc_min' 0 463 'add_success' 0 464 'alloc' 0 465
'assert_true' 0 466 'band_sym_matrix_test' 0 470 'bandsymmatrixt' 0 134
'bfcrdr' 0 474 'bnddat' 0 475 'bndrdr' 0 476 'bsymat' 0 477 'cnsmat' 0
478 'coord_max' 0 479 'coord_min' 0 480 'dimen' 0 481 'disp_max' 0 482
'disp_min' 0 483 'dmnrdr' 0 484 'dnsmat' 0 485 'dtime_max' 0 486
'dtime_min' 0 487 'e_max' 0 488 'e_min' 0 489 'exceed' 0 490 'exists' 0
491 'failed_assert_action' 0 492 'flddat' 0 497 'formt' 0 498
'fruit_summary' 0 499 'get_failed_count' 0 500 'get_last_message' 0 503
'get_total_count' 0 504 'get_unit_name' 0 507 'ictrdr' 0 510 'icvrdr' 0
511 'init_fruit' 0 512 'is_all_successful' 0 513 'is_last_passed' 0 516
'kbcrdr' 0 517 'linslv' 0 518 'log_closelogfile' 0 519 'log_getfilename'
0 520 'log_initlogfile' 0 522 'log_messages' 0 523 'log_printlogmsg' 0
524 'log_setfilename' 0 528 'matrixt' 0 139 'max_boundels' 0 531
'max_dofs' 0 532 'max_elements' 0 533 'max_materials' 0 534 'max_nodes'
0 535 'max_timesteps' 0 536 'maxlen' 0 537 'msg_getmsg' 0 538 'msg_getsdr'
0 542 'mtldat' 0 546 'mtlrdr' 0 547 'nbcrdr' 0 548 'ndim' 0 549 'nnodel'
0 550 'nnodelb' 0 551 'ntns' 0 552 'nu_max' 0 553 'nu_min' 0 554 'ok' 0
555 'one_third' 0 556 'posdef' 0 557 'posit' 0 558 'rho_max' 0 559
'rho_min' 0 560 'set_unit_name' 0 561 'sig_max' 0 564 'sig_min' 0 565
'str_max' 0 566 'str_min' 0 567 'str_small' 0 568 'system_constants' 0
569 'sze' 0 570 'test_bsm_add_dimen' 0 571 'test_bsm_add_op' 0 572
'test_bsm_add_val' 0 573 'test_bsm_allocation_dat' 0 574
'test_bsm_allocation_msg' 0 575 'test_bsm_allocation_sze' 0 576
'test_bsm_deallocation' 0 577 'test_bsm_get_posit' 0 578
'test_bsm_get_val' 0 579 'test_bsm_half_bw_allocated' 0 580
'test_bsm_half_bw_not_allocated' 0 581 'test_bsm_is_decomposed' 0 582
'test_bsm_mapped_add_dimen1' 0 583 'test_bsm_mapped_add_dimen2' 0 584
'test_bsm_mapped_add_dimen3' 0 585 'test_bsm_mapped_add_posit1' 0 586
'test_bsm_mapped_add_posit2' 0 587 'test_bsm_mapped_add_val1' 0 588
'test_bsm_mapped_add_val2' 0 589 'test_bsm_mapped_add_val3' 0 590
'test_bsm_num_rows_allocated' 0 591 'test_bsm_num_rows_not_allocated' 0
592 'test_bsm_scal_mul_op' 0 593 'test_bsm_scal_mul_val' 0 594
'test_bsm_scal_mul_zero' 0 595 'test_bsm_set_decomp_dimen' 0 596
'test_bsm_set_decomp_val' 0 597 'test_bsm_set_posit' 0 598
'test_bsm_set_val' 0 599 'test_bsm_vec_mul_dimen' 0 600
'test_bsm_vec_mul_ident' 0 601 'test_bsm_vec_mul_op' 0 602
'test_bsm_vec_mul_val' 0 603 'test_bsm_vec_mul_zero' 0 604 'tnswtr' 0
605 'typ' 0 606 'vector' 0 607 'vectort' 0 129 'vecwtr' 0 608 'vel_max'
0 609 'vel_min' 0 610)