FE-Project
Loading...
Searching...
No Matches
scale_sparsemat.F90
Go to the documentation of this file.
1!-------------------------------------------------------------------------------
2!> Module common / sparsemat
3!!
4!! @par Description
5!! A module to treat sparse matrix and the associated operations
6!!
7!! @author Yuta Kawai, Team SCALE
8!!
9!<
10#include "scaleFElib.h"
12 !-----------------------------------------------------------------------------
13 !
14 !++ used modules
15 !
16 use scale_precision
17 use scale_io
18 use scale_prc
19 use scale_const, only: &
20 undef8 => const_undef8, &
21 const_eps
22
23 !-----------------------------------------------------------------------------
24 implicit none
25 private
26
27 !-----------------------------------------------------------------------------
28 !
29 !++ Public type & procedure
30 !
31
32 !> Derived type to manage a sparse matrix
33 type, public :: sparsemat
34 integer :: m !< Number of row of original matrix
35 integer :: n !< Number of column of original matrix
36 integer :: nnz !< Number of nonzero of the matrix
37 real(rp), allocatable :: val(:) !< Array storing the values of the nonzeros
38 integer, allocatable :: colidx(:) !< Array saving the column indices of the nonzeros
39
40 ! for CSR format
41 integer, allocatable :: rowptr(:) !< Array saving the start and end pointers of the nonzeros of the rows.
42 integer :: rowptrsize !< Size of rowPtr
43
44 ! for ELL format
45 integer :: col_size
46
47 integer, private :: storage_format_id !< Number of row of original matrix
48 contains
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
55 end type sparsemat
56
58 module procedure sparsemat_matmul1
59 module procedure sparsemat_matmul2
60 end interface
61 public :: sparsemat_matmul
62
63 !-----------------------------------------------------------------------------
64 !
65 !++ Public parameters & variables
66 !
67 integer, public, parameter :: sparsemat_storage_typeid_csr = 1
68 integer, public, parameter :: sparsemat_storage_typeid_ell = 2
69
70 !-----------------------------------------------------------------------------
71 !
72 !++ Private procedure
73 !
74 private :: sparsemat_matmul_csr_1
75 private :: sparsemat_matmul_csr_2
76 private :: sparsemat_matmul_ell_1
77 private :: sparsemat_matmul_ell_2
78
79 !-----------------------------------------------------------------------------
80 !
81 !++ Private parameters & variables
82 !
83
84 !-----------------------------------------------------------------------------
85
86contains
87 subroutine sparsemat_init( this, mat, &
88 EPS, storage_format )
89 implicit none
90
91 class(sparsemat), intent(inout) :: this
92 real(rp), intent(in) :: mat(:,:)
93 real(rp), optional, intent(in) :: eps
94 character(len=*), optional, intent(in) :: storage_format
95
96 integer :: i
97 integer :: j
98 integer :: l
99
100 integer :: val_counter
101 integer :: rowptr_counter
102
103 real(dp) :: tmp_val(size(mat)+1)
104 integer :: tmp_colind(size(mat)+1)
105 integer :: tmp_rowptr(0:size(mat,1)+1)
106
107 real(rp) :: eps_
108 character(len=H_MID) :: storage_format_ = 'CSR'
109
110 integer :: row_nonzero_counter(size(mat,1))
111 integer :: col_size_l
112
113 !---------------------------------------------------------------------------
114
115 this%M = size(mat,1)
116 this%N = size(mat,2)
117
118 val_counter = 1
119 rowptr_counter = 1
120 tmp_rowptr(1) = 1
121 tmp_val(:) = 0.0_rp
122
123 if (present(eps)) then
124 eps_ = eps
125 else
126 eps_ = const_eps * 500.0_rp ! ~ 1x10^-13
127 end if
128
129 if (present(storage_format)) then
130 storage_format_ = storage_format
131 end if
132
133 select case (storage_format_)
134 case ('CSR')
135 this%storage_format_id = sparsemat_storage_typeid_csr
136
137 do i=1, this%M
138 do j=1, this%N
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
143 end if
144 end do
145 rowptr_counter = rowptr_counter + 1
146 tmp_rowptr(rowptr_counter) = val_counter
147 end do
148 case ('ELL')
149 this%storage_format_id = sparsemat_storage_typeid_ell
150
151 do i=1, this%M
152 row_nonzero_counter(i) = 0
153 do j=1, this%N
154 if ( abs(mat(i,j)) >= eps_ ) &
155 row_nonzero_counter(i) = row_nonzero_counter(i) + 1
156 end do
157 end do
158 this%col_size = maxval(row_nonzero_counter(:))
159 val_counter = this%M * this%col_size
160
161 tmp_val(:) = 0.0_rp
162 tmp_colind(:) = -1
163 do i=1, this%M
164 col_size_l = 0
165 do j=1,this%N
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)
170 tmp_colind(l) = j
171 end if
172 end do
173 end do
174 case default
175 log_error("SparseMat_Init",*) 'Not appropriate names of storage format. Check!', trim(storage_format_)
176 call prc_abort
177 end select
178
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)
184
185 select case (storage_format_)
186 case ('CSR')
187 allocate( this%rowPtr(rowptr_counter) )
188 this%rowPtr(:) = tmp_rowptr(1:rowptr_counter)
189 this%rowPtrSize = rowptr_counter
190 case('ELL')
191 do l=2, val_counter
192 if (this%colIdx(l) == -1) then
193 this%colIdx(l) = this%colIdx(l-1)
194 end if
195 end do
196 end select
197
198 !write(*,*) "--- Mat ------"
199 !write(*,*) "shape:", shape(mat)
200 !write(*,*) "size:", size(mat)
201 ! do j=1, size(mat,2)
202 ! write(*,*) mat(:,j)
203 ! end do
204 !write(*,*) "--- Compressed Mat ------"
205 !write(*,*) "shape (Mat, colInd, rowPtr):", &
206 ! & shape(this%val), shape(this%colInd), shape(this%rowPtr)
207 ! write(*,*) "val:", this%val(:)
208 ! write(*,*) "colInd:", this%colInd(:)
209 ! write(*,*) "rowPtr:", this%rowPtr(:)
210
211 return
212 end subroutine sparsemat_init
213
214 subroutine sparsemat_final(this)
215 implicit none
216 class(sparsemat), intent(inout) :: this
217
218 !---------------------------------------------------------------------------
219
220 deallocate( this%val )
221 deallocate( this%colIdx )
222
223 select case( this%storage_format_id )
225 deallocate( this%rowPtr )
226 end select
227
228 return
229 end subroutine sparsemat_final
230
231 function sparsemat_getval(A, i, j) result(v)
232 class(sparsemat), intent(in) :: a
233 integer, intent(in) :: i, j
234
235 real(dp) ::v
236 integer :: n
237 integer :: jj
238 !---------------------------------------------------------------------------
239
240 v = undef8
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
245 v = a%val(n); exit
246 end if
247 end do
249 do jj=1, a%col_size
250 n = i + (jj-1)*a%M
251 if (a%colIdx(n) == j) then
252 v = a%val(n); exit
253 end if
254 end do
255 end select
256
257 return
258 end function sparsemat_getval
259
260 subroutine sparsemat_replceval(A, i, j, v)
261
262 class(sparsemat), intent(inout) :: a
263 integer, intent(in) :: i, j
264 real(rp), intent(in) ::v
265
266 integer :: n
267 integer :: jj
268 !---------------------------------------------------------------------------
269
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
274 a%val(n) = v; exit
275 end if
276 end do
278 do jj=1, a%col_size
279 n = i + (jj-1)*a%M
280 if (a%colIdx(n) == j) then
281 a%val(n) = v; exit
282 end if
283 end do
284 end select
285
286 return
287 end subroutine sparsemat_replceval
288
289 subroutine sparsemat_print(A)
290 implicit none
291 class(sparsemat), intent(in) :: a
292
293 real(rp) :: row_val(a%n)
294 integer :: p
295 integer :: j1, j2
296 !---------------------------------------------------------------------------
297
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(:)
304 end select
305 write(*,*) "colInd:", a%colIdx(:)
306 write(*,*) "val:"
307
308 select case ( a%storage_format_id )
310 j1 = a%rowPtr(1)
311 do p=1, a%rowPtrSize-1
312 j2 = a%rowPtr(p+1)
313 row_val(:) = 0.0_rp
314 row_val(a%colIdx(j1:j2-1)) = a%val(j1:j2-1)
315 write(*,*) row_val(:)
316 j1 = j2
317 end do
319 do p=1, a%M
320 row_val(:) = 0.0_rp
321 do j1=1, a%col_size
322 j2 = p + (j1-1)*a%M
323 row_val(a%colIdx(j2)) = a%val(j2)
324 end do
325 write(*,*) row_val(:)
326 end do
327 end select
328
329 return
330 end subroutine sparsemat_print
331
332 function sparsemat_get_storage_format_id( A ) result(id)
333 implicit none
334 class(sparsemat), intent(in) :: a
335 real(rp) :: id
336 !------------------------------------------------------
337
338 id = a%storage_format_id
339 return
340 end function sparsemat_get_storage_format_id
341
342!OCL SERIAL
343 subroutine sparsemat_matmul1(A, b, c)
344 implicit none
345
346 type(sparsemat), intent(in) :: A
347 real(RP), intent(in ) :: b(:)
348 real(RP), intent(out) :: c(A%M)
349
350 !---------------------------------------------------------------------------
351
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 )
359 end select
360
361 return
362 end subroutine sparsemat_matmul1
363
364!OCL SERIAL
365 subroutine sparsemat_matmul2(A, b, c)
366 implicit none
367
368 type(sparsemat), intent(in) :: A
369 real(RP), intent(in ) :: b(:,:)
370 real(RP), intent(out) :: c(size(b,1),A%M)
371
372 !---------------------------------------------------------------------------
373
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) )
381 end select
382
383 return
384 end subroutine sparsemat_matmul2
385
386!--- private ----------------------------------------------
387
388!OCL SERIAL
389 subroutine sparsemat_matmul_csr_1(A, col_Ind, rowPtr, b, c, M, N, buf_size, rowPtr_size)
390 implicit none
391
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)
401
402 integer :: p, j
403 integer :: j1, j2
404
405 !---------------------------------------------------------------------------
406
407 !call mkl_dcsrgemv( 'N', rowPtr_size-1, A, rowPtr, col_Ind, b, c)
408 j1 = rowptr(1)
409 do p=1, rowptr_size-1
410 j2 = rowptr(p+1)
411 c(p) = 0.0_rp
412 do j=j1, j2-1
413 c(p) = c(p) + a(j) * b(col_ind(j))
414 end do
415 j1 = j2
416 end do
417
418 return
419 end subroutine sparsemat_matmul_csr_1
420
421!OCL SERIAL
422 subroutine sparsemat_matmul_csr_2(A, col_Ind, rowPtr, b, c, M, N, buf_size, rowPtr_size, NQ)
423 implicit none
424
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)
435
436 integer :: p, j
437 integer :: j1, j2
438
439 !---------------------------------------------------------------------------
440
441 !call mkl_dcsrgemv( 'N', rowPtr_size-1, A, rowPtr, col_Ind, b, c)
442 j1 = rowptr(1)
443 c(:,:) = 0.0_rp
444 do p=1, rowptr_size-1
445 j2 = rowptr(p+1)
446 do j=j1, j2-1
447 c(:,p) = c(:,p) + a(j) * b(:,col_ind(j))
448 end do
449 j1 = j2
450 end do
451
452 return
453 end subroutine sparsemat_matmul_csr_2
454
455!OCL SERIAL
456 subroutine sparsemat_matmul_ell_1(A, col_Ind, b, c, M, N, buf_size, col_size)
457 implicit none
458
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)
467
468 integer :: k, kk, i
469 integer :: j_ptr
470 !---------------------------------------------------------------------------
471
472 c(:) = 0.0_rp
473 do k=1, col_size
474 kk = m * (k-1)
475 do i=1, m
476 j_ptr = kk + i
477 c(i) = c(i) + a(j_ptr) * b(col_ind(j_ptr))
478 end do
479 end do
480
481 return
482 end subroutine sparsemat_matmul_ell_1
483
484!OCL SERIAL
485 subroutine sparsemat_matmul_ell_2(A, col_Ind, b, c, M, N, buf_size, col_size, NQ)
486 implicit none
487
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)
497
498 integer :: k, kk, i
499 integer :: j_ptr
500 !---------------------------------------------------------------------------
501
502 c(:,:) = 0.0_rp
503 do k=1, col_size
504 kk = m * (k-1)
505 do i=1, m
506 j_ptr = kk + i
507 c(:,i) = c(:,i) + a(j_ptr) * b(:,col_ind(j_ptr))
508 end do
509 end do
510
511 return
512 end subroutine sparsemat_matmul_ell_2
513
514end module scale_sparsemat
515
Module common / sparsemat.
integer, parameter, public sparsemat_storage_typeid_csr
integer, parameter, public sparsemat_storage_typeid_ell
Derived type to manage a sparse matrix.