5 ! Contributed by Salvatore Filippone and Dominique d'Humieres.
9 ! This is the default integer
10 integer, parameter :: ndig
=8
11 integer, parameter :: int_k_
= selected_int_kind(ndig
)
12 ! This is an 8-byte integer, and normally different from default integer.
13 integer, parameter :: longndig
=12
14 integer, parameter :: long_int_k_
= selected_int_kind(longndig
)
16 ! These must be the kind parameter corresponding to MPI_DOUBLE_PRECISION
19 integer, parameter :: dpk_
= kind(1.d0
)
20 integer, parameter :: spk_
= kind(1.e0
)
21 integer, save :: sizeof_dp
, sizeof_sp
22 integer, save :: sizeof_int
, sizeof_long_int
23 integer, save :: mpi_integer
25 integer, parameter :: invalid_
= -1
26 integer, parameter :: spmat_null_
=0, spmat_bld_
=1
27 integer, parameter :: spmat_asb_
=2, spmat_upd_
=4
32 integer, parameter, public
:: success_
=0
33 integer, parameter, public
:: err_iarg_neg_
=10
40 type :: base_sparse_mat
41 integer, private
:: m
, n
42 integer, private
:: state
, duplicate
43 logical, private
:: triangle
, unitd
, upper
, sorted
46 procedure
, pass(a
) :: get_fmt
=> base_get_fmt
47 procedure
, pass(a
) :: set_null
=> base_set_null
48 procedure
, pass(a
) :: allocate_mnnz
=> base_allocate_mnnz
49 generic
, public
:: allocate
=> allocate_mnnz
50 end type base_sparse_mat
53 subroutine base_allocate_mnnz(m
,n
,a
,nz
)
54 import base_sparse_mat
, long_int_k_
55 integer, intent(in
) :: m
,n
56 class(base_sparse_mat
), intent(inout
) :: a
57 integer, intent(in
), optional
:: nz
58 end subroutine base_allocate_mnnz
63 function base_get_fmt(a
) result(res
)
65 class(base_sparse_mat
), intent(in
) :: a
66 character(len
=5) :: res
68 end function base_get_fmt
70 subroutine base_set_null(a
)
72 class(base_sparse_mat
), intent(inout
) :: a
75 end subroutine base_set_null
78 end module base_mat_mod
84 type, extends(base_sparse_mat
) :: d_base_sparse_mat
86 end type d_base_sparse_mat
90 type, extends(d_base_sparse_mat
) :: d_coo_sparse_mat
93 integer, allocatable
:: ia(:), ja(:)
94 real(dpk_
), allocatable
:: val(:)
98 procedure
, pass(a
) :: get_fmt
=> d_coo_get_fmt
99 procedure
, pass(a
) :: allocate_mnnz
=> d_coo_allocate_mnnz
101 end type d_coo_sparse_mat
105 subroutine d_coo_allocate_mnnz(m
,n
,a
,nz
)
106 import d_coo_sparse_mat
107 integer, intent(in
) :: m
,n
108 class(d_coo_sparse_mat
), intent(inout
) :: a
109 integer, intent(in
), optional
:: nz
110 end subroutine d_coo_allocate_mnnz
115 function d_coo_get_fmt(a
) result(res
)
117 class(d_coo_sparse_mat
), intent(in
) :: a
118 character(len
=5) :: res
120 end function d_coo_get_fmt
122 end module d_base_mat_mod
124 subroutine base_allocate_mnnz(m
,n
,a
,nz
)
125 use base_mat_mod
, protect_name
=> base_allocate_mnnz
127 integer, intent(in
) :: m
,n
128 class(base_sparse_mat
), intent(inout
) :: a
129 integer, intent(in
), optional
:: nz
131 character(len
=20) :: name
='allocate_mnz', errfmt
132 logical, parameter :: debug
=.false
.
134 ! This is the base version. If we get here
135 ! it means the derived class is incomplete,
136 ! so we throw an error.
138 write(0,*) 'Error: Missing ovverriding impl for allocate in class ',errfmt
142 end subroutine base_allocate_mnnz
144 subroutine d_coo_allocate_mnnz(m
,n
,a
,nz
)
145 use d_base_mat_mod
, protect_name
=> d_coo_allocate_mnnz
147 integer, intent(in
) :: m
,n
148 class(d_coo_sparse_mat
), intent(inout
) :: a
149 integer, intent(in
), optional
:: nz
150 Integer :: err_act
, info
, nz_
151 character(len
=20) :: name
='allocate_mnz'
152 logical, parameter :: debug
=.false
.
161 if (present(nz
)) then
169 ! !$ if (info == success_) call realloc(nz_,a%ia,info)
170 ! !$ if (info == success_) call realloc(nz_,a%ja,info)
171 ! !$ if (info == success_) call realloc(nz_,a%val,info)
172 if (info
== success_
) then
173 ! !$ call a%set_nrows(m)
174 ! !$ call a%set_ncols(n)
175 ! !$ call a%set_nzeros(0)
176 ! !$ call a%set_bld()
177 ! !$ call a%set_triangle(.false.)
178 ! !$ call a%set_unit(.false.)
179 ! !$ call a%set_dupl(dupl_def_)
180 write(0,*) 'Allocated COO succesfully, should now set components'
182 write(0,*) 'COO allocation failed somehow. Go figure'
186 end subroutine d_coo_allocate_mnnz
193 integer :: ictxt
, iam
, np
196 type(d_coo_sparse_mat
) :: acoo
205 call acoo
%allocate(n
,n
,nz
=nnz
)
208 end program d_coo_err