Initiate
Initiate() method constructs an instance of CSRMatrix_.
At present, there are 6 interfaces to initiate method. You can see their interface and examples below.
Calling example:
CALL Initiate(CSRMatrix_::obj, Integer::ncol, Integer::nrow &
& [, DOF_::idof, DOF_::jdof, CHAR::MatrixProp] )
!!
CALL Initiate(CSRMatrix_::obj, CSRSparsity_::csr [, CHAR::matrixProp])
!!
CALL Initiate(CSRMatrix_:: obj, Real::A(:), Integer::IA(:), Integer::JA(:) &
& [, CHAR::MatrixProp])
!!
CALL Initiate(CSRMatrix_::obj, CSRMatrix_::obj2)
!!
CALL Initiate(CSRMatrix_::obj, CSRMatrix_::obj2, &
& Integer::i1, Integer::i2, Integer::j1, Integer::j2)
Interface
- ܀ Initiate(obj, ncol, nrow, idof, jdof, matrixProp)
- ️܀ Example 1
- ️܀ Example 2
- ↢
INTERFACE
MODULE SUBROUTINE Initiate(obj, ncol, nrow, idof, jdof, matrixProp)
TYPE(CSRMatrix_), INTENT(INOUT) :: obj
INTEGER(I4B), INTENT(IN) :: ncol
!! number of columns in sparse matrix
INTEGER(I4B), INTENT(IN) :: nrow
!! number of rows in sparse matrix
TYPE(DOF_), OPTIONAL, INTENT(IN) :: idof, jdof
!! degree of freedom object; It contains information like
!! storage format (NODES_FMT, DOF_FMT), and names of physical variable
!! space-time component in each physical variables
!! Total number of nodes used for these physical variables
CHARACTER(LEN=*), OPTIONAL, INTENT(IN) :: MatrixProp
!! Matrix is `SYM`, `UNSYM`
END SUBROUTINE Initiate
END INTERFACE
If user has information about the number of rows nrow, number of columns ncol of sparse matrix, then the above interface can be used to initiate an instance of CSRMatrix_.
dofandmatrixPropare optional.dofis DOF object, and it is used to initiateobj%csr, CSRSparsity field.
PROGRAM main
USE easifemBase
IMPLICIT NONE
TYPE( CSRMatrix_ ) :: obj
TYPE( DOF_ ) :: dofobj
- First, we initiate DOF, which contains the structure of Degrees of freedom
- The degrees of freedom has:
- 1 physical variable
- 1 space component
- 1 time component
- 12 number of spatial nodes are stored in
NODES_FMT.
CALL Initiate( obj=dofobj, tNodes=[12], names=['K'], &
& spaceCompo=[1], timeCompo=[1], storageFMT=NODES_FMT )
- Below we create a sparse matrix with 12 number of rows and 12 number of cols.
CALL Initiate( obj, ncol=12, nrow=12, idof=dofobj, jdof=dofobj )
CALL Deallocate( obj )
END PROGRAM main
PROGRAM main
USE easifemBase
IMPLICIT NONE
TYPE( CSRMatrix_ ) :: obj
TYPE( DOF_ ) :: dofobj
REAL( DFP ), ALLOCATABLE :: m2(:,:)
Initiate degrees of freedom object DOF
CALL Initiate( obj=dofobj, tNodes=[4, 2], names=['V', 'P'], &
& spaceCompo=[2, 1], timeCompo=[1,1], storageFMT=FMT_DOF )
Initiate CSRMatrix
CALL Initiate( obj, &
& ncol=.tnodes. dofobj, &
& nrow=.tnodes. dofobj, &
& idof=dofobj, jdof=dofobj )
Convert CSRMatrix to dense matrix.
m2 = obj
CALL Display( m2, "test2" )
Cleanup
CALL Deallocate( obj )
END PROGRAM main
- Initiate(obj, csr, matrixProp)
- ️܀ See example
- ↢
We can also initiate the sparse matrix by providing an instance of CSRSparsity.
INTERFACE
MODULE SUBROUTINE Initiate(obj, csr, matrixProp)
TYPE(CSRMatrix_), INTENT(INOUT) :: obj
TYPE(CSRSparsity_), INTENT(IN) :: csr
!! number of columns in sparse matrix
!! number of rows in sparse matrix
!! degree of freedom object; It contains information like
!! storage format (NODES_FMT, DOF_FMT), and names of physical variable
!! space-time component in each physical variables
!! Total number of nodes used for these physical variables
CHARACTER(LEN=*), OPTIONAL, INTENT(IN) :: MatrixProp
!! Matrix is `SYM`, `UNSYM`
END SUBROUTINE Initiate
END INTERFACE
In the above call, CSRSparsity object, csr, should be initiated by the user before passing it to the routine. This is because initiate uses information such as ncol, nrow, nnz stored inside csr.
TODO
- Interface 3
- ️܀ See example
- ↢
We can also pass INT::IA(:), INT:JA(:) and matrix value REAL::A(:) to Initiate() method for constructing the sparse matrix. The interface is given below.
INTERFACE
MODULE SUBROUTINE Initiate(obj, A, IA, JA, MatrixProp)
TYPE(CSRMatrix_), INTENT(INOUT) :: obj
REAL(DFP), INTENT(IN) :: A(:)
INTEGER(I4B), INTENT(IN) :: IA(:), JA(:)
CHARACTER(LEN=*), OPTIONAL, INTENT(IN) :: MatrixProp
END SUBROUTINE Initiate
END INTERFACE
This subroutine will allocate memory for csr, which is an instance of CSRSparsity.
TODO
- Interface 4
- ️܀ See example
- ↢
EASIFEM also provides an assignment operator for copying contents of one sparse matrix into another sparse matrix. The syntax is given below.
INTERFACE
MODULE SUBROUTINE Initiate(obj, obj2)
TYPE(CSRMatrix_), INTENT(INOUT) :: obj
TYPE(CSRMatrix_), INTENT(IN) :: obj2
END SUBROUTINE Initiate
END INTERFACE
The above call is equivalent to obj=obj2, and it will also copy obj%csr.
TODO
- Interface 5
- ️܀ See example
- ↢
We can also create a csrmatrix from a subset of another csrmatrix.
INTERFACE
MODULE SUBROUTINE Initiate(obj, obj2, i1, i2, j1, j2)
TYPE(CSRMatrix_), INTENT(INOUT) :: obj
TYPE(CSRMatrix_), INTENT(IN) :: obj2
INTEGER(I4B), INTENT(IN) :: i1, i2
INTEGER(I4B), INTENT(IN) :: j1, j2
END SUBROUTINE Initiate
END INTERFACE
Symbolically the above call is equivalent to obj=obj2(i1:i2, j1:j2), and it will allocate memory for obj%csr.
TODO