Skip to content

Commit 6ae038b

Browse files
committed
add an ilp parameter to change in the future for int64 if needed for large arrays
1 parent dde88a7 commit 6ae038b

File tree

3 files changed

+120
-117
lines changed

3 files changed

+120
-117
lines changed

src/stdlib_sparse_conversion.fypp

Lines changed: 28 additions & 28 deletions
Original file line numberDiff line numberDiff line change
@@ -24,8 +24,8 @@ contains
2424
module subroutine dense2coo_${s1}$(dense,COO)
2525
${t1}$, intent(in) :: dense(:,:)
2626
type(COO_${s1}$), intent(out) :: COO
27-
integer :: num_rows, num_cols, nnz
28-
integer :: i, j, idx
27+
integer(ilp) :: num_rows, num_cols, nnz
28+
integer(ilp) :: i, j, idx
2929

3030
num_rows = size(dense,dim=1)
3131
num_cols = size(dense,dim=2)
@@ -52,7 +52,7 @@ contains
5252
module subroutine coo2dense_${s1}$(COO,dense)
5353
type(COO_${s1}$), intent(in) :: COO
5454
${t1}$, allocatable, intent(out) :: dense(:,:)
55-
integer :: idx
55+
integer(ilp) :: idx
5656

5757
if(.not.allocated(dense)) allocate(dense(COO%nrows,COO%nrows),source=zero_${s1}$)
5858
do concurrent(idx = 1:COO%nnz)
@@ -66,7 +66,7 @@ contains
6666
module subroutine coo2csr_${s1}$(COO,CSR)
6767
type(COO_${s1}$), intent(in) :: COO
6868
type(CSR_${s1}$), intent(out) :: CSR
69-
integer :: i
69+
integer(ilp) :: i
7070

7171
CSR%nnz = COO%nnz; CSR%nrows = COO%nrows; CSR%ncols = COO%ncols
7272
CSR%storage = COO%storage
@@ -96,7 +96,7 @@ contains
9696
module subroutine csr2dense_${s1}$(CSR,dense)
9797
type(CSR_${s1}$), intent(in) :: CSR
9898
${t1}$, allocatable, intent(out) :: dense(:,:)
99-
integer :: i, j
99+
integer(ilp) :: i, j
100100

101101
if(.not.allocated(dense)) allocate(dense(CSR%nrows,CSR%nrows),source=zero_${s1}$)
102102
if( CSR%storage == sparse_full) then
@@ -122,7 +122,7 @@ contains
122122
module subroutine csr2coo_${s1}$(CSR,COO)
123123
type(CSR_${s1}$), intent(in) :: CSR
124124
type(COO_${s1}$), intent(out) :: COO
125-
integer :: i, j
125+
integer(ilp) :: i, j
126126

127127
COO%nnz = CSR%nnz; COO%nrows = CSR%nrows; COO%ncols = CSR%ncols
128128
COO%storage = CSR%storage
@@ -150,7 +150,7 @@ contains
150150
type(ELL_${s1}$), intent(out) :: ELL
151151
integer, intent(in), optional :: num_nz_rows !! number of non zeros per row
152152

153-
integer :: i, j, num_nz_rows_, adr1, adr2
153+
integer(ilp) :: i, j, num_nz_rows_, adr1, adr2
154154
!-------------------------------------------
155155
num_nz_rows_ = 0
156156
if(present(num_nz_rows)) then
@@ -182,7 +182,7 @@ contains
182182
type(SELLC_${s1}$), intent(out) :: SELLC
183183
integer, intent(in), optional :: chunk
184184
${t1}$, parameter :: zero = zero_${s1}$
185-
integer :: i, j, num_chunks
185+
integer(ilp) :: i, j, num_chunks
186186

187187
if(present(chunk)) SELLC%chunk_size = chunk
188188

@@ -243,10 +243,10 @@ contains
243243
#:for k1, t1, s1 in (KINDS_TYPES)
244244
recursive subroutine quicksort_i_${s1}$(a, b, first, last)
245245
integer, parameter :: wp = sp
246-
integer, intent(inout) :: a(*) !! reference table to sort
246+
integer(ilp), intent(inout) :: a(*) !! reference table to sort
247247
${t1}$, intent(inout) :: b(*) !! secondary real data to sort w.r.t. a
248-
integer, intent(in) :: first, last
249-
integer :: i, j, x, t
248+
integer(ilp), intent(in) :: first, last
249+
integer(ilp) :: i, j, x, t
250250
${t1}$ :: d
251251

252252
x = a( (first+last) / 2 )
@@ -273,14 +273,14 @@ contains
273273

274274
subroutine sort_coo_unique( a, n, num_rows, num_cols )
275275
!! Sort a 2d array in increasing order first by index 1 and then by index 2
276-
integer, intent(inout) :: a(2,*)
277-
integer, intent(inout) :: n
278-
integer, intent(in) :: num_rows
279-
integer, intent(in) :: num_cols
280-
281-
integer :: stride, adr0, adr1, dd
282-
integer :: n_i, pos, ed
283-
integer, allocatable :: count_i(:), count_i_aux(:), rows_(:), cols_(:)
276+
integer(ilp), intent(inout) :: a(2,*)
277+
integer(ilp), intent(inout) :: n
278+
integer(ilp), intent(in) :: num_rows
279+
integer(ilp), intent(in) :: num_cols
280+
281+
integer(ilp) :: stride, adr0, adr1, dd
282+
integer(ilp) :: n_i, pos, ed
283+
integer(ilp), allocatable :: count_i(:), count_i_aux(:), rows_(:), cols_(:)
284284
!---------------------------------------------------------
285285
! Sort a first time with respect to first index using count sort
286286
allocate( count_i( 0:num_rows ) , source = 0 )
@@ -328,14 +328,14 @@ contains
328328
subroutine sort_coo_unique_${s1}$( a, data, n, num_rows, num_cols )
329329
!! Sort a 2d array in increasing order first by index 1 and then by index 2
330330
${t1}$, intent(inout) :: data(*)
331-
integer, intent(inout) :: a(2,*)
332-
integer, intent(inout) :: n
333-
integer, intent(in) :: num_rows
334-
integer, intent(in) :: num_cols
335-
336-
integer :: stride, adr0, adr1, dd
337-
integer :: n_i, pos, ed
338-
integer, allocatable :: count_i(:), count_i_aux(:), rows_(:), cols_(:)
331+
integer(ilp), intent(inout) :: a(2,*)
332+
integer(ilp), intent(inout) :: n
333+
integer(ilp), intent(in) :: num_rows
334+
integer(ilp), intent(in) :: num_cols
335+
336+
integer(ilp) :: stride, adr0, adr1, dd
337+
integer(ilp) :: n_i, pos, ed
338+
integer(ilp), allocatable :: count_i(:), count_i_aux(:), rows_(:), cols_(:)
339339
${t1}$, allocatable :: temp(:)
340340
!---------------------------------------------------------
341341
! Sort a first time with respect to first index using Count sort
@@ -390,7 +390,7 @@ contains
390390
module subroutine coo2ordered(COO,sort_data)
391391
class(COO_type), intent(inout) :: COO
392392
logical, intent(in), optional :: sort_data
393-
integer, allocatable :: itemp(:,:)
393+
integer(ilp), allocatable :: itemp(:,:)
394394
logical :: sort_data_
395395

396396
if(COO%is_sorted) return

0 commit comments

Comments
 (0)