Push some intermediate mods.

repack-csga
sfilippone 8 months ago
parent c547de218d
commit a3f839ad62

@ -44,7 +44,8 @@ FOBJS=cusparse_mod.o base_cusparse_mod.o \
COBJS= elldev.o hlldev.o diagdev.o hdiagdev.o vectordev.o ivectordev.o dnsdev.o\
svectordev.o dvectordev.o cvectordev.o zvectordev.o cuda_util.o \
fcusparse.o scusparse.o dcusparse.o ccusparse.o zcusparse.o
fcusparse.o scusparse.o dcusparse.o ccusparse.o zcusparse.o \
dcsga.o
OBJS=$(COBJS) $(FOBJS)

@ -28,10 +28,10 @@
! ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
! POSSIBILITY OF SUCH DAMAGE.
!
module d_csga_mod
use d_cusparse_mod
integer, parameter :: MAX_NNZ_PER_WG = 4096
integer, parameter :: MAX_GRID_SIZE = 65536
type, bind(c) :: d_CAmat
type(c_ptr) :: Mat = c_null_ptr
@ -47,5 +47,66 @@ module d_csga_mod
end function d_CSGADeviceFree
end interface
interface CSGADeviceAlloc
function d_CSGADeviceAlloc(Mat,nr,nc,nz) &
& bind(c,name="d_CSGADeviceAlloc") result(res)
use iso_c_binding
import d_CAmat
type(d_CAmat) :: Mat
integer(c_int), value :: nr, nc, nz
integer(c_int) :: res
end function d_CSGADeviceAlloc
end interface
interface CSGADeviceSetMatDiagType
function d_CSGADeviceSetMatDiagType(Mat,type) &
& bind(c,name="d_CSGADeviceSetMatDiagType") result(res)
use iso_c_binding
import d_CAmat
type(d_CAmat) :: Mat
integer(c_int),value :: type
integer(c_int) :: res
end function d_CSGADeviceSetMatDiagType
end interface
interface CSGADeviceSetMatFillMode
function d_CSGADeviceSetMatFillMode(Mat,type) &
& bind(c,name="d_CSGADeviceSetMatFillMode") result(res)
use iso_c_binding
import d_CAmat
type(d_CAmat) :: Mat
integer(c_int),value :: type
integer(c_int) :: res
end function d_CSGADeviceSetMatFillMode
end interface
interface CSGAHost2Device
function d_CSGAHost2Device(Mat,m,n,nz,irp,ja,val,rowBlocks) &
& bind(c,name="d_CSGAHost2Device") result(res)
use iso_c_binding
import d_CAmat
type(d_CAmat) :: Mat
integer(c_int), value :: m,n,nz
integer(c_int) :: irp(*), ja(*), rowBlocks(*)
real(c_double) :: val(*)
integer(c_int) :: res
end function d_CSGAHost2Device
end interface
interface CSGADevice2Host
function d_CSGADevice2Host(Mat,m,n,nz,irp,ja,val,rowBlocks) &
& bind(c,name="d_CSGADevice2Host") result(res)
use iso_c_binding
import d_CAmat
type(d_CAmat) :: Mat
integer(c_int), value :: m,n,nz
integer(c_int) :: irp(*), ja(*), rowBlocks(*)
real(c_double) :: val(*)
integer(c_int) :: res
end function d_CSGADevice2Host
end interface
end module d_csga_mod

@ -35,11 +35,13 @@ module psb_d_cuda_csga_mat_mod
use iso_c_binding
use psb_d_mat_mod
use psb_d_cuda_csrg_mat_mod
use d_csga_mod
type, extends(psb_d_cuda_csrg_sparse_mat) :: psb_d_cuda_csga_sparse_mat
!
! Format for CSR Adaptive.
!
!
type(d_CAmat) :: deviceAMat
integer(psb_ipk_), allocatable :: rowBlocks(:)
contains
procedure, nopass :: get_fmt => d_cuda_csga_get_fmt
@ -336,13 +338,12 @@ contains
!!$ end subroutine d_cuda_csga_sync
subroutine d_cuda_csga_free(a)
use cusparse_mod
implicit none
integer(psb_ipk_) :: info
class(psb_d_cuda_csga_sparse_mat), intent(inout) :: a
info = 0 !CSGADeviceFree(a%deviceMat)
info = CSGADeviceFree(a%deviceAMat)
call a%psb_d_csr_sparse_mat%free()
return
@ -350,13 +351,12 @@ contains
end subroutine d_cuda_csga_free
subroutine d_cuda_csga_finalize(a)
use cusparse_mod
implicit none
integer(psb_ipk_) :: info
type(psb_d_cuda_csga_sparse_mat), intent(inout) :: a
info = 0 !CSGADeviceFree(a%deviceMat)
info = CSGADeviceFree(a%deviceAMat)
return

Loading…
Cancel
Save