10#include "scaleFElib.h"
19 use scale_const,
only: &
20 undef8 => const_undef8, &
37 real(rp),
allocatable :: val(:)
38 integer,
allocatable :: colidx(:)
41 integer,
allocatable :: rowptr(:)
47 integer,
private :: storage_format_id
49 procedure,
public :: init => sparsemat_init
50 procedure,
public :: final => sparsemat_final
51 procedure,
public :: print => sparsemat_print
52 procedure,
public :: replaceval => sparsemat_replceval
53 procedure,
public :: getval => sparsemat_getval
54 procedure,
public :: getstorageformatid => sparsemat_get_storage_format_id
58 module procedure sparsemat_matmul1
59 module procedure sparsemat_matmul2
74 private :: sparsemat_matmul_csr_1
75 private :: sparsemat_matmul_csr_2
76 private :: sparsemat_matmul_ell_1
77 private :: sparsemat_matmul_ell_2
87 subroutine sparsemat_init( this, mat, &
92 real(rp),
intent(in) :: mat(:,:)
93 real(rp),
optional,
intent(in) :: eps
94 character(len=*),
optional,
intent(in) :: storage_format
100 integer :: val_counter
101 integer :: rowptr_counter
103 real(dp) :: tmp_val(size(mat)+1)
104 integer :: tmp_colind(size(mat)+1)
105 integer :: tmp_rowptr(0:size(mat,1)+1)
108 character(len=H_MID) :: storage_format_ =
'CSR'
110 integer :: row_nonzero_counter(size(mat,1))
111 integer :: col_size_l
123 if (
present(eps))
then
126 eps_ = const_eps * 500.0_rp
129 if (
present(storage_format))
then
130 storage_format_ = storage_format
133 select case (storage_format_)
139 if ( abs(mat(i,j)) > eps_ )
then
140 tmp_val(val_counter) = mat(i,j)
141 tmp_colind(val_counter) = j
142 val_counter = val_counter + 1
145 rowptr_counter = rowptr_counter + 1
146 tmp_rowptr(rowptr_counter) = val_counter
152 row_nonzero_counter(i) = 0
154 if ( abs(mat(i,j)) >= eps_ ) &
155 row_nonzero_counter(i) = row_nonzero_counter(i) + 1
158 this%col_size = maxval(row_nonzero_counter(:))
159 val_counter = this%M * this%col_size
166 if ( abs(mat(i,j)) >= eps_ )
then
167 col_size_l = col_size_l + 1
168 l = i+(col_size_l-1)*this%M
169 tmp_val(l) = mat(i,j)
175 log_error(
"SparseMat_Init",*)
'Not appropriate names of storage format. Check!', trim(storage_format_)
179 this%nnz = val_counter
180 allocate( this%val(val_counter) )
181 allocate( this%colIdx(val_counter) )
182 this%val(:) = tmp_val(1:val_counter)
183 this%colIdx(:) = tmp_colind(1:val_counter)
185 select case (storage_format_)
187 allocate( this%rowPtr(rowptr_counter) )
188 this%rowPtr(:) = tmp_rowptr(1:rowptr_counter)
189 this%rowPtrSize = rowptr_counter
192 if (this%colIdx(l) == -1)
then
193 this%colIdx(l) = this%colIdx(l-1)
212 end subroutine sparsemat_init
214 subroutine sparsemat_final(this)
220 deallocate( this%val )
221 deallocate( this%colIdx )
223 select case( this%storage_format_id )
225 deallocate( this%rowPtr )
229 end subroutine sparsemat_final
231 function sparsemat_getval(A, i, j)
result(v)
233 integer,
intent(in) :: i, j
241 select case( a%storage_format_id )
243 do n=a%rowPtr(i),a%rowPtr(i+1)-1
244 if (a%colIdx(n) == j)
then
251 if (a%colIdx(n) == j)
then
258 end function sparsemat_getval
260 subroutine sparsemat_replceval(A, i, j, v)
263 integer,
intent(in) :: i, j
264 real(rp),
intent(in) ::v
270 select case ( a%storage_format_id )
272 do n=a%rowPtr(i),a%rowPtr(i+1)-1
273 if (a%colIdx(n) == j)
then
280 if (a%colIdx(n) == j)
then
287 end subroutine sparsemat_replceval
289 subroutine sparsemat_print(A)
293 real(rp) :: row_val(a%n)
298 write(*,*)
"-- print matrix:"
299 write(*,
'(a,i5,a,i5)')
"orginal matrix shape:", a%M,
'x', a%N
300 write(*,
'(a,i5)')
"size of compressed matrix:", a%nnz
301 select case ( a%storage_format_id )
303 write(*,*)
"rowPtr:", a%rowPtr(:)
305 write(*,*)
"colInd:", a%colIdx(:)
308 select case ( a%storage_format_id )
311 do p=1, a%rowPtrSize-1
314 row_val(a%colIdx(j1:j2-1)) = a%val(j1:j2-1)
315 write(*,*) row_val(:)
323 row_val(a%colIdx(j2)) = a%val(j2)
325 write(*,*) row_val(:)
330 end subroutine sparsemat_print
332 function sparsemat_get_storage_format_id( A )
result(id)
338 id = a%storage_format_id
340 end function sparsemat_get_storage_format_id
343 subroutine sparsemat_matmul1(A, b, c)
347 real(RP),
intent(in ) :: b(:)
348 real(RP),
intent(out) :: c(A%M)
352 select case( a%storage_format_id )
354 call sparsemat_matmul_csr_1( a%val, a%colIdx, a%rowPtr, b, c, &
355 a%M, a%N, a%nnz, a%rowPtrSize )
357 call sparsemat_matmul_ell_1( a%val, a%colIdx, b, c, &
358 a%M, a%N, a%nnz, a%col_size )
362 end subroutine sparsemat_matmul1
365 subroutine sparsemat_matmul2(A, b, c)
369 real(RP),
intent(in ) :: b(:,:)
370 real(RP),
intent(out) :: c(size(b,1),A%M)
374 select case( a%storage_format_id )
376 call sparsemat_matmul_csr_2( a%val, a%colIdx, a%rowPtr, b, c, &
377 a%M, a%N, a%nnz, a%rowPtrSize,
size(b,1) )
379 call sparsemat_matmul_ell_2( a%val, a%colIdx, b, c, &
380 a%M, a%N, a%nnz, a%col_size,
size(b,1) )
384 end subroutine sparsemat_matmul2
389 subroutine sparsemat_matmul_csr_1(A, col_Ind, rowPtr, b, c, M, N, buf_size, rowPtr_size)
392 integer,
intent(in) :: M
393 integer,
intent(in) :: N
394 integer,
intent(in) :: buf_size
395 integer,
intent(in) :: rowPtr_size
396 real(RP),
intent(in) :: A(buf_size)
397 integer,
intent(in) :: col_Ind(buf_size)
398 integer,
intent(in) :: rowPtr(rowPtr_size)
399 real(RP),
intent(in ) :: b(N)
400 real(RP),
intent(out) :: c(M)
409 do p=1, rowptr_size-1
413 c(p) = c(p) + a(j) * b(col_ind(j))
419 end subroutine sparsemat_matmul_csr_1
422 subroutine sparsemat_matmul_csr_2(A, col_Ind, rowPtr, b, c, M, N, buf_size, rowPtr_size, NQ)
425 integer,
intent(in) :: M
426 integer,
intent(in) :: N
427 integer,
intent(in) :: NQ
428 integer,
intent(in) :: buf_size
429 integer,
intent(in) :: rowPtr_size
430 real(RP),
intent(in) :: A(buf_size)
431 integer,
intent(in) :: col_Ind(buf_size)
432 integer,
intent(in) :: rowPtr(rowPtr_size)
433 real(RP),
intent(in ) :: b(NQ,N)
434 real(RP),
intent(out) :: c(NQ,M)
444 do p=1, rowptr_size-1
447 c(:,p) = c(:,p) + a(j) * b(:,col_ind(j))
453 end subroutine sparsemat_matmul_csr_2
456 subroutine sparsemat_matmul_ell_1(A, col_Ind, b, c, M, N, buf_size, col_size)
459 integer,
intent(in) :: M
460 integer,
intent(in) :: N
461 integer,
intent(in) :: buf_size
462 integer,
intent(in) :: col_size
463 real(RP),
intent(in) :: A(buf_size)
464 integer,
intent(in) :: col_Ind(buf_size)
465 real(RP),
intent(in ) :: b(N)
466 real(RP),
intent(out) :: c(M)
477 c(i) = c(i) + a(j_ptr) * b(col_ind(j_ptr))
482 end subroutine sparsemat_matmul_ell_1
485 subroutine sparsemat_matmul_ell_2(A, col_Ind, b, c, M, N, buf_size, col_size, NQ)
488 integer,
intent(in) :: M
489 integer,
intent(in) :: N
490 integer,
intent(in) :: buf_size
491 integer,
intent(in) :: col_size
492 integer,
intent(in) :: NQ
493 real(RP),
intent(in) :: A(buf_size)
494 integer,
intent(in) :: col_Ind(buf_size)
495 real(RP),
intent(in ) :: b(NQ,N)
496 real(RP),
intent(out) :: c(NQ,M)
507 c(:,i) = c(:,i) + a(j_ptr) * b(:,col_ind(j_ptr))
512 end subroutine sparsemat_matmul_ell_2
Module common / sparsemat.
integer, parameter, public sparsemat_storage_typeid_csr
integer, parameter, public sparsemat_storage_typeid_ell
Derived type to manage a sparse matrix.