Skip to content

Commit 872777d

Browse files
committed
Rename dense to dense_mat because of a naming conflict.
1 parent 3912f73 commit 872777d

File tree

1 file changed

+42
-42
lines changed

1 file changed

+42
-42
lines changed
Lines changed: 42 additions & 42 deletions
Original file line numberDiff line numberDiff line change
@@ -1,49 +1,49 @@
11
program example_sparse_data_accessors
2-
use stdlib_linalg_constants, only: dp
3-
use stdlib_sparse
4-
implicit none
2+
use stdlib_linalg_constants, only: dp
3+
use stdlib_sparse
4+
implicit none
55

6-
real(dp) :: mat(2,2)
7-
real(dp), allocatable :: dense(:,:)
8-
type(CSR_dp_type) :: CSR
9-
type(COO_dp_type) :: COO
10-
integer :: i, j, locdof(2)
6+
real(dp) :: mat(2, 2)
7+
real(dp), allocatable :: dense_matrix(:, :)
8+
type(CSR_dp_type) :: CSR
9+
type(COO_dp_type) :: COO
10+
integer :: i, j, locdof(2)
1111

12-
! Initial data
13-
mat(:,1) = [1._dp,2._dp]
14-
mat(:,2) = [2._dp,1._dp]
15-
allocate(dense(5,5) , source = 0._dp)
16-
do i = 0, 3
17-
dense(1+i:2+i,1+i:2+i) = dense(1+i:2+i,1+i:2+i) + mat
18-
end do
12+
! Initial data
13+
mat(:, 1) = [1._dp, 2._dp]
14+
mat(:, 2) = [2._dp, 1._dp]
15+
allocate (dense_matrix(5, 5), source=0._dp)
16+
do i = 0, 3
17+
dense_matrix(1 + i:2 + i, 1 + i:2 + i) = dense_matrix(1 + i:2 + i, 1 + i:2 + i) + mat
18+
end do
1919

20-
print *, 'Original Matrix'
21-
do j = 1 , 5
22-
print '(5f8.1)',dense(j,:)
23-
end do
20+
print *, 'Original Matrix'
21+
do j = 1, 5
22+
print '(5f8.1)', dense_matrix(j, :)
23+
end do
2424

25-
! Initialize CSR data and reset dense reference matrix
26-
call dense2coo(dense,COO)
27-
call coo2csr(COO,CSR)
28-
CSR%data = 0._dp
29-
dense = 0._dp
25+
! Initialize CSR data and reset dense reference matrix
26+
call dense2coo(dense_matrix, COO)
27+
call coo2csr(COO, CSR)
28+
CSR%data = 0._dp
29+
dense_matrix = 0._dp
3030

31-
! Iteratively add blocks of data
32-
do i = 0, 3
33-
locdof(1:2) = [1+i,2+i]
34-
call CSR%add(locdof,locdof,mat)
35-
! lets print a dense view of every step
36-
call csr2dense(CSR,dense)
37-
print '(A,I2)', 'Add block :', i+1
38-
do j = 1 , 5
39-
print '(5f8.1)',dense(j,:)
40-
end do
41-
end do
31+
! Iteratively add blocks of data
32+
do i = 0, 3
33+
locdof(1:2) = [1 + i, 2 + i]
34+
call CSR%add(locdof, locdof, mat)
35+
! lets print a dense view of every step
36+
call csr2dense(CSR, dense_matrix)
37+
print '(A,I2)', 'Add block :', i + 1
38+
do j = 1, 5
39+
print '(5f8.1)', dense_matrix(j, :)
40+
end do
41+
end do
4242

43-
! Request values from the matrix
44-
print *, ''
45-
print *, 'within sparse pattern :',CSR%at(2,1)
46-
print *, 'outside sparse pattern :',CSR%at(5,2)
47-
print *, 'outside matrix pattern :',CSR%at(7,7)
48-
49-
end program example_sparse_data_accessors
43+
! Request values from the matrix
44+
print *, ''
45+
print *, 'within sparse pattern :', CSR%at(2, 1)
46+
print *, 'outside sparse pattern :', CSR%at(5, 2)
47+
print *, 'outside matrix pattern :', CSR%at(7, 7)
48+
49+
end program example_sparse_data_accessors

0 commit comments

Comments
 (0)