Added out-of-place psb_mlt subroutine interface

merge-paraggr-newops
Cirdans-Home 5 years ago
parent 37f6ed6077
commit 22e7df48da

@ -459,6 +459,17 @@ module psb_c_psblas_mod
type(psb_desc_type), intent (in) :: desc_a type(psb_desc_type), intent (in) :: desc_a
integer(psb_ipk_), intent(out) :: info integer(psb_ipk_), intent(out) :: info
end subroutine psb_cmlt_vect end subroutine psb_cmlt_vect
subroutine psb_cmlt_vect2(alpha,x,y,beta,z,desc_a,info,conjgx,conjgy)
import :: psb_desc_type, psb_ipk_, &
& psb_c_vect_type, psb_spk_
complex(psb_spk_), intent(in) :: alpha,beta
type(psb_c_vect_type), intent (inout) :: x
type(psb_c_vect_type), intent (inout) :: y
type(psb_c_vect_type), intent (inout) :: z
type(psb_desc_type), intent (in) :: desc_a
integer(psb_ipk_), intent(out) :: info
character(len=1), intent(in), optional :: conjgx, conjgy
end subroutine psb_cmlt_vect2
end interface end interface
interface psb_gediv interface psb_gediv

@ -470,6 +470,17 @@ module psb_d_psblas_mod
type(psb_desc_type), intent (in) :: desc_a type(psb_desc_type), intent (in) :: desc_a
integer(psb_ipk_), intent(out) :: info integer(psb_ipk_), intent(out) :: info
end subroutine psb_dmlt_vect end subroutine psb_dmlt_vect
subroutine psb_dmlt_vect2(alpha,x,y,beta,z,desc_a,info,conjgx,conjgy)
import :: psb_desc_type, psb_ipk_, &
& psb_d_vect_type, psb_dpk_
real(psb_dpk_), intent(in) :: alpha,beta
type(psb_d_vect_type), intent (inout) :: x
type(psb_d_vect_type), intent (inout) :: y
type(psb_d_vect_type), intent (inout) :: z
type(psb_desc_type), intent (in) :: desc_a
integer(psb_ipk_), intent(out) :: info
character(len=1), intent(in), optional :: conjgx, conjgy
end subroutine psb_dmlt_vect2
end interface end interface
interface psb_gediv interface psb_gediv

@ -470,6 +470,17 @@ module psb_s_psblas_mod
type(psb_desc_type), intent (in) :: desc_a type(psb_desc_type), intent (in) :: desc_a
integer(psb_ipk_), intent(out) :: info integer(psb_ipk_), intent(out) :: info
end subroutine psb_smlt_vect end subroutine psb_smlt_vect
subroutine psb_smlt_vect2(alpha,x,y,beta,z,desc_a,info,conjgx,conjgy)
import :: psb_desc_type, psb_ipk_, &
& psb_s_vect_type, psb_spk_
real(psb_spk_), intent(in) :: alpha,beta
type(psb_s_vect_type), intent (inout) :: x
type(psb_s_vect_type), intent (inout) :: y
type(psb_s_vect_type), intent (inout) :: z
type(psb_desc_type), intent (in) :: desc_a
integer(psb_ipk_), intent(out) :: info
character(len=1), intent(in), optional :: conjgx, conjgy
end subroutine psb_smlt_vect2
end interface end interface
interface psb_gediv interface psb_gediv

@ -459,6 +459,17 @@ module psb_z_psblas_mod
type(psb_desc_type), intent (in) :: desc_a type(psb_desc_type), intent (in) :: desc_a
integer(psb_ipk_), intent(out) :: info integer(psb_ipk_), intent(out) :: info
end subroutine psb_zmlt_vect end subroutine psb_zmlt_vect
subroutine psb_zmlt_vect2(alpha,x,y,beta,z,desc_a,info,conjgx,conjgy)
import :: psb_desc_type, psb_ipk_, &
& psb_z_vect_type, psb_dpk_
complex(psb_dpk_), intent(in) :: alpha,beta
type(psb_z_vect_type), intent (inout) :: x
type(psb_z_vect_type), intent (inout) :: y
type(psb_z_vect_type), intent (inout) :: z
type(psb_desc_type), intent (in) :: desc_a
integer(psb_ipk_), intent(out) :: info
character(len=1), intent(in), optional :: conjgx, conjgy
end subroutine psb_zmlt_vect2
end interface end interface
interface psb_gediv interface psb_gediv

@ -103,3 +103,96 @@ subroutine psb_cmlt_vect(x,y,desc_a,info)
return return
end subroutine psb_cmlt_vect end subroutine psb_cmlt_vect
!
! Subroutine: psb_cmlt_vect2
!
subroutine psb_cmlt_vect2(alpha,x,y,beta,z,desc_a,info,conjgx, conjgy)
use psb_base_mod, psb_protect_name => psb_cmlt_vect2
implicit none
complex(psb_spk_), intent(in) :: alpha,beta
type(psb_c_vect_type), intent (inout) :: x
type(psb_c_vect_type), intent (inout) :: y
type(psb_c_vect_type), intent (inout) :: z
type(psb_desc_type), intent (in) :: desc_a
integer(psb_ipk_), intent(out) :: info
character(len=1), intent(in), optional :: conjgx, conjgy
! locals
integer(psb_ipk_) :: ictxt, np, me,&
& err_act, iix, jjx, iiy, jjy, iiz, jjz
integer(psb_lpk_) :: ix, ijx, iy, ijy, iz, ijz, m
character(len=20) :: name, ch_err
name='psb_c_mlt_vect2'
if (psb_errstatus_fatal()) return
info=psb_success_
call psb_erractionsave(err_act)
ictxt=desc_a%get_context()
call psb_info(ictxt, me, np)
if (np == -ione) then
info = psb_err_context_error_
call psb_errpush(info,name)
goto 9999
endif
if (.not.allocated(x%v)) then
info = psb_err_invalid_vect_state_
call psb_errpush(info,name)
goto 9999
endif
if (.not.allocated(y%v)) then
info = psb_err_invalid_vect_state_
call psb_errpush(info,name)
goto 9999
endif
if (.not.allocated(z%v)) then
info = psb_err_invalid_vect_state_
call psb_errpush(info,name)
goto 9999
endif
ix = ione
iy = ione
iz = ione
m = desc_a%get_global_rows()
! check vector correctness
call psb_chkvect(m,lone,x%get_nrows(),ix,lone,desc_a,info,iix,jjx)
if(info /= psb_success_) then
info=psb_err_from_subroutine_
ch_err='psb_chkvect 1'
call psb_errpush(info,name,a_err=ch_err)
goto 9999
end if
call psb_chkvect(m,lone,y%get_nrows(),iy,lone,desc_a,info,iiy,jjy)
if(info /= psb_success_) then
info=psb_err_from_subroutine_
ch_err='psb_chkvect 2'
call psb_errpush(info,name,a_err=ch_err)
goto 9999
end if
call psb_chkvect(m,lone,z%get_nrows(),iz,lone,desc_a,info,iiz,jjz)
if(info /= psb_success_) then
info=psb_err_from_subroutine_
ch_err='psb_chkvect 3'
call psb_errpush(info,name,a_err=ch_err)
goto 9999
end if
if(desc_a%get_local_rows() > 0) then
call z%mlt(alpha,x,y,beta,info,conjgx,conjgy)
end if
call psb_erractionrestore(err_act)
return
9999 call psb_error_handler(ictxt,err_act)
return
end subroutine psb_cmlt_vect2

@ -103,3 +103,96 @@ subroutine psb_dmlt_vect(x,y,desc_a,info)
return return
end subroutine psb_dmlt_vect end subroutine psb_dmlt_vect
!
! Subroutine: psb_dmlt_vect2
!
subroutine psb_dmlt_vect2(alpha,x,y,beta,z,desc_a,info,conjgx, conjgy)
use psb_base_mod, psb_protect_name => psb_dmlt_vect2
implicit none
real(psb_dpk_), intent(in) :: alpha,beta
type(psb_d_vect_type), intent (inout) :: x
type(psb_d_vect_type), intent (inout) :: y
type(psb_d_vect_type), intent (inout) :: z
type(psb_desc_type), intent (in) :: desc_a
integer(psb_ipk_), intent(out) :: info
character(len=1), intent(in), optional :: conjgx, conjgy
! locals
integer(psb_ipk_) :: ictxt, np, me,&
& err_act, iix, jjx, iiy, jjy, iiz, jjz
integer(psb_lpk_) :: ix, ijx, iy, ijy, iz, ijz, m
character(len=20) :: name, ch_err
name='psb_d_mlt_vect2'
if (psb_errstatus_fatal()) return
info=psb_success_
call psb_erractionsave(err_act)
ictxt=desc_a%get_context()
call psb_info(ictxt, me, np)
if (np == -ione) then
info = psb_err_context_error_
call psb_errpush(info,name)
goto 9999
endif
if (.not.allocated(x%v)) then
info = psb_err_invalid_vect_state_
call psb_errpush(info,name)
goto 9999
endif
if (.not.allocated(y%v)) then
info = psb_err_invalid_vect_state_
call psb_errpush(info,name)
goto 9999
endif
if (.not.allocated(z%v)) then
info = psb_err_invalid_vect_state_
call psb_errpush(info,name)
goto 9999
endif
ix = ione
iy = ione
iz = ione
m = desc_a%get_global_rows()
! check vector correctness
call psb_chkvect(m,lone,x%get_nrows(),ix,lone,desc_a,info,iix,jjx)
if(info /= psb_success_) then
info=psb_err_from_subroutine_
ch_err='psb_chkvect 1'
call psb_errpush(info,name,a_err=ch_err)
goto 9999
end if
call psb_chkvect(m,lone,y%get_nrows(),iy,lone,desc_a,info,iiy,jjy)
if(info /= psb_success_) then
info=psb_err_from_subroutine_
ch_err='psb_chkvect 2'
call psb_errpush(info,name,a_err=ch_err)
goto 9999
end if
call psb_chkvect(m,lone,z%get_nrows(),iz,lone,desc_a,info,iiz,jjz)
if(info /= psb_success_) then
info=psb_err_from_subroutine_
ch_err='psb_chkvect 3'
call psb_errpush(info,name,a_err=ch_err)
goto 9999
end if
if(desc_a%get_local_rows() > 0) then
call z%mlt(alpha,x,y,beta,info,conjgx,conjgy)
end if
call psb_erractionrestore(err_act)
return
9999 call psb_error_handler(ictxt,err_act)
return
end subroutine psb_dmlt_vect2

@ -103,3 +103,96 @@ subroutine psb_smlt_vect(x,y,desc_a,info)
return return
end subroutine psb_smlt_vect end subroutine psb_smlt_vect
!
! Subroutine: psb_smlt_vect2
!
subroutine psb_smlt_vect2(alpha,x,y,beta,z,desc_a,info,conjgx, conjgy)
use psb_base_mod, psb_protect_name => psb_smlt_vect2
implicit none
real(psb_spk_), intent(in) :: alpha,beta
type(psb_s_vect_type), intent (inout) :: x
type(psb_s_vect_type), intent (inout) :: y
type(psb_s_vect_type), intent (inout) :: z
type(psb_desc_type), intent (in) :: desc_a
integer(psb_ipk_), intent(out) :: info
character(len=1), intent(in), optional :: conjgx, conjgy
! locals
integer(psb_ipk_) :: ictxt, np, me,&
& err_act, iix, jjx, iiy, jjy, iiz, jjz
integer(psb_lpk_) :: ix, ijx, iy, ijy, iz, ijz, m
character(len=20) :: name, ch_err
name='psb_s_mlt_vect2'
if (psb_errstatus_fatal()) return
info=psb_success_
call psb_erractionsave(err_act)
ictxt=desc_a%get_context()
call psb_info(ictxt, me, np)
if (np == -ione) then
info = psb_err_context_error_
call psb_errpush(info,name)
goto 9999
endif
if (.not.allocated(x%v)) then
info = psb_err_invalid_vect_state_
call psb_errpush(info,name)
goto 9999
endif
if (.not.allocated(y%v)) then
info = psb_err_invalid_vect_state_
call psb_errpush(info,name)
goto 9999
endif
if (.not.allocated(z%v)) then
info = psb_err_invalid_vect_state_
call psb_errpush(info,name)
goto 9999
endif
ix = ione
iy = ione
iz = ione
m = desc_a%get_global_rows()
! check vector correctness
call psb_chkvect(m,lone,x%get_nrows(),ix,lone,desc_a,info,iix,jjx)
if(info /= psb_success_) then
info=psb_err_from_subroutine_
ch_err='psb_chkvect 1'
call psb_errpush(info,name,a_err=ch_err)
goto 9999
end if
call psb_chkvect(m,lone,y%get_nrows(),iy,lone,desc_a,info,iiy,jjy)
if(info /= psb_success_) then
info=psb_err_from_subroutine_
ch_err='psb_chkvect 2'
call psb_errpush(info,name,a_err=ch_err)
goto 9999
end if
call psb_chkvect(m,lone,z%get_nrows(),iz,lone,desc_a,info,iiz,jjz)
if(info /= psb_success_) then
info=psb_err_from_subroutine_
ch_err='psb_chkvect 3'
call psb_errpush(info,name,a_err=ch_err)
goto 9999
end if
if(desc_a%get_local_rows() > 0) then
call z%mlt(alpha,x,y,beta,info,conjgx,conjgy)
end if
call psb_erractionrestore(err_act)
return
9999 call psb_error_handler(ictxt,err_act)
return
end subroutine psb_smlt_vect2

@ -103,3 +103,96 @@ subroutine psb_zmlt_vect(x,y,desc_a,info)
return return
end subroutine psb_zmlt_vect end subroutine psb_zmlt_vect
!
! Subroutine: psb_zmlt_vect2
!
subroutine psb_zmlt_vect2(alpha,x,y,beta,z,desc_a,info,conjgx, conjgy)
use psb_base_mod, psb_protect_name => psb_zmlt_vect2
implicit none
complex(psb_dpk_), intent(in) :: alpha,beta
type(psb_z_vect_type), intent (inout) :: x
type(psb_z_vect_type), intent (inout) :: y
type(psb_z_vect_type), intent (inout) :: z
type(psb_desc_type), intent (in) :: desc_a
integer(psb_ipk_), intent(out) :: info
character(len=1), intent(in), optional :: conjgx, conjgy
! locals
integer(psb_ipk_) :: ictxt, np, me,&
& err_act, iix, jjx, iiy, jjy, iiz, jjz
integer(psb_lpk_) :: ix, ijx, iy, ijy, iz, ijz, m
character(len=20) :: name, ch_err
name='psb_z_mlt_vect2'
if (psb_errstatus_fatal()) return
info=psb_success_
call psb_erractionsave(err_act)
ictxt=desc_a%get_context()
call psb_info(ictxt, me, np)
if (np == -ione) then
info = psb_err_context_error_
call psb_errpush(info,name)
goto 9999
endif
if (.not.allocated(x%v)) then
info = psb_err_invalid_vect_state_
call psb_errpush(info,name)
goto 9999
endif
if (.not.allocated(y%v)) then
info = psb_err_invalid_vect_state_
call psb_errpush(info,name)
goto 9999
endif
if (.not.allocated(z%v)) then
info = psb_err_invalid_vect_state_
call psb_errpush(info,name)
goto 9999
endif
ix = ione
iy = ione
iz = ione
m = desc_a%get_global_rows()
! check vector correctness
call psb_chkvect(m,lone,x%get_nrows(),ix,lone,desc_a,info,iix,jjx)
if(info /= psb_success_) then
info=psb_err_from_subroutine_
ch_err='psb_chkvect 1'
call psb_errpush(info,name,a_err=ch_err)
goto 9999
end if
call psb_chkvect(m,lone,y%get_nrows(),iy,lone,desc_a,info,iiy,jjy)
if(info /= psb_success_) then
info=psb_err_from_subroutine_
ch_err='psb_chkvect 2'
call psb_errpush(info,name,a_err=ch_err)
goto 9999
end if
call psb_chkvect(m,lone,z%get_nrows(),iz,lone,desc_a,info,iiz,jjz)
if(info /= psb_success_) then
info=psb_err_from_subroutine_
ch_err='psb_chkvect 3'
call psb_errpush(info,name,a_err=ch_err)
goto 9999
end if
if(desc_a%get_local_rows() > 0) then
call z%mlt(alpha,x,y,beta,info,conjgx,conjgy)
end if
call psb_erractionrestore(err_act)
return
9999 call psb_error_handler(ictxt,err_act)
return
end subroutine psb_zmlt_vect2

@ -62,6 +62,7 @@ psb_i_t psb_c_cspsm(psb_c_t alpha, psb_c_cspmat *th, psb_c_cvector *xh,
psb_c_t beta, psb_c_cvector *yh, psb_c_descriptor *cdh); psb_c_t beta, psb_c_cvector *yh, psb_c_descriptor *cdh);
/* Additional computational routines */ /* Additional computational routines */
psb_i_t psb_c_cgemlt(psb_c_cvector *xh,psb_c_cvector *yh,psb_c_descriptor *cdh); psb_i_t psb_c_cgemlt(psb_c_cvector *xh,psb_c_cvector *yh,psb_c_descriptor *cdh);
psb_i_t psb_c_cgemlt2(psb_c_t alpha, psb_c_cvector *xh, psb_c_cvector *yh, psb_c_t beta, psb_c_cvector *zh, psb_c_descriptor *cdh);
psb_i_t psb_c_cgediv(psb_c_cvector *xh,psb_c_cvector *yh,psb_c_descriptor *cdh); psb_i_t psb_c_cgediv(psb_c_cvector *xh,psb_c_cvector *yh,psb_c_descriptor *cdh);
psb_i_t psb_c_cgediv_check(psb_c_cvector *xh,psb_c_cvector *yh,psb_c_descriptor *cdh); psb_i_t psb_c_cgediv_check(psb_c_cvector *xh,psb_c_cvector *yh,psb_c_descriptor *cdh);
psb_i_t psb_c_cgeinv(psb_c_cvector *xh,psb_c_cvector *yh,psb_c_descriptor *cdh); psb_i_t psb_c_cgeinv(psb_c_cvector *xh,psb_c_cvector *yh,psb_c_descriptor *cdh);

@ -62,6 +62,7 @@ psb_i_t psb_c_dspsm(psb_d_t alpha, psb_c_dspmat *th, psb_c_dvector *xh,
psb_d_t beta, psb_c_dvector *yh, psb_c_descriptor *cdh); psb_d_t beta, psb_c_dvector *yh, psb_c_descriptor *cdh);
/* Additional computational routines */ /* Additional computational routines */
psb_i_t psb_c_dgemlt(psb_c_dvector *xh,psb_c_dvector *yh,psb_c_descriptor *cdh); psb_i_t psb_c_dgemlt(psb_c_dvector *xh,psb_c_dvector *yh,psb_c_descriptor *cdh);
psb_i_t psb_c_dgemlt2(psb_d_t alpha, psb_c_dvector *xh, psb_c_dvector *yh, psb_d_t beta, psb_c_dvector *zh, psb_c_descriptor *cdh);
psb_i_t psb_c_dgediv(psb_c_dvector *xh,psb_c_dvector *yh,psb_c_descriptor *cdh); psb_i_t psb_c_dgediv(psb_c_dvector *xh,psb_c_dvector *yh,psb_c_descriptor *cdh);
psb_i_t psb_c_dgediv_check(psb_c_dvector *xh,psb_c_dvector *yh,psb_c_descriptor *cdh); psb_i_t psb_c_dgediv_check(psb_c_dvector *xh,psb_c_dvector *yh,psb_c_descriptor *cdh);
psb_i_t psb_c_dgeinv(psb_c_dvector *xh,psb_c_dvector *yh,psb_c_descriptor *cdh); psb_i_t psb_c_dgeinv(psb_c_dvector *xh,psb_c_dvector *yh,psb_c_descriptor *cdh);

@ -78,6 +78,48 @@ contains
end function psb_c_cgemlt end function psb_c_cgemlt
function psb_c_cgemlt2(alpha,xh,yh,beta,zh,cdh) bind(c) result(res)
implicit none
integer(psb_c_ipk_) :: res
type(psb_c_cvector) :: xh,yh, zh
type(psb_c_descriptor) :: cdh
type(psb_desc_type), pointer :: descp
type(psb_c_vect_type), pointer :: xp,yp,zp
integer(psb_c_ipk_) :: info
complex(psb_spk_), intent(in) :: alpha,beta
res = -1
if (c_associated(cdh%item)) then
call c_f_pointer(cdh%item,descp)
else
return
end if
if (c_associated(xh%item)) then
call c_f_pointer(xh%item,xp)
else
return
end if
if (c_associated(yh%item)) then
call c_f_pointer(yh%item,yp)
else
return
end if
if (c_associated(zh%item)) then
call c_f_pointer(zh%item,zp)
else
return
end if
call psb_gemlt(alpha,xp,yp,beta,zp,descp,info)
res = info
end function psb_c_cgemlt2
function psb_c_cgediv(xh,yh,cdh) bind(c) result(res) function psb_c_cgediv(xh,yh,cdh) bind(c) result(res)
implicit none implicit none
integer(psb_c_ipk_) :: res integer(psb_c_ipk_) :: res

@ -62,6 +62,7 @@ psb_i_t psb_c_sspsm(psb_s_t alpha, psb_c_sspmat *th, psb_c_svector *xh,
psb_s_t beta, psb_c_svector *yh, psb_c_descriptor *cdh); psb_s_t beta, psb_c_svector *yh, psb_c_descriptor *cdh);
/* Additional computational routines */ /* Additional computational routines */
psb_i_t psb_c_sgemlt(psb_c_svector *xh,psb_c_svector *yh,psb_c_descriptor *cdh); psb_i_t psb_c_sgemlt(psb_c_svector *xh,psb_c_svector *yh,psb_c_descriptor *cdh);
psb_i_t psb_c_sgemlt2(psb_s_t alpha, psb_c_svector *xh, psb_c_svector *yh, psb_s_t beta, psb_c_svector *zh, psb_c_descriptor *cdh);
psb_i_t psb_c_sgediv(psb_c_svector *xh,psb_c_svector *yh,psb_c_descriptor *cdh); psb_i_t psb_c_sgediv(psb_c_svector *xh,psb_c_svector *yh,psb_c_descriptor *cdh);
psb_i_t psb_c_sgediv_check(psb_c_svector *xh,psb_c_svector *yh,psb_c_descriptor *cdh); psb_i_t psb_c_sgediv_check(psb_c_svector *xh,psb_c_svector *yh,psb_c_descriptor *cdh);
psb_i_t psb_c_sgeinv(psb_c_svector *xh,psb_c_svector *yh,psb_c_descriptor *cdh); psb_i_t psb_c_sgeinv(psb_c_svector *xh,psb_c_svector *yh,psb_c_descriptor *cdh);

@ -62,6 +62,7 @@ psb_i_t psb_c_zspsm(psb_z_t alpha, psb_c_zspmat *th, psb_c_zvector *xh,
psb_z_t beta, psb_c_zvector *yh, psb_c_descriptor *cdh); psb_z_t beta, psb_c_zvector *yh, psb_c_descriptor *cdh);
/* Additional computational routines */ /* Additional computational routines */
psb_i_t psb_c_zgemlt(psb_c_zvector *xh,psb_c_zvector *yh,psb_c_descriptor *cdh); psb_i_t psb_c_zgemlt(psb_c_zvector *xh,psb_c_zvector *yh,psb_c_descriptor *cdh);
psb_i_t psb_c_zgemlt2(psb_z_t alpha, psb_c_zvector *xh, psb_c_zvector *yh, psb_z_t beta, psb_c_zvector *zh, psb_c_descriptor *cdh);
psb_i_t psb_c_zgediv(psb_c_zvector *xh,psb_c_zvector *yh,psb_c_descriptor *cdh); psb_i_t psb_c_zgediv(psb_c_zvector *xh,psb_c_zvector *yh,psb_c_descriptor *cdh);
psb_i_t psb_c_zgediv_check(psb_c_zvector *xh,psb_c_zvector *yh,psb_c_descriptor *cdh); psb_i_t psb_c_zgediv_check(psb_c_zvector *xh,psb_c_zvector *yh,psb_c_descriptor *cdh);
psb_i_t psb_c_zgeinv(psb_c_zvector *xh,psb_c_zvector *yh,psb_c_descriptor *cdh); psb_i_t psb_c_zgeinv(psb_c_zvector *xh,psb_c_zvector *yh,psb_c_descriptor *cdh);

@ -78,6 +78,48 @@ contains
end function psb_c_dgemlt end function psb_c_dgemlt
function psb_c_dgemlt2(alpha,xh,yh,beta,zh,cdh) bind(c) result(res)
implicit none
integer(psb_c_ipk_) :: res
type(psb_c_dvector) :: xh,yh, zh
type(psb_c_descriptor) :: cdh
type(psb_desc_type), pointer :: descp
type(psb_d_vect_type), pointer :: xp,yp,zp
integer(psb_c_ipk_) :: info
real(psb_dpk_), intent(in) :: alpha,beta
res = -1
if (c_associated(cdh%item)) then
call c_f_pointer(cdh%item,descp)
else
return
end if
if (c_associated(xh%item)) then
call c_f_pointer(xh%item,xp)
else
return
end if
if (c_associated(yh%item)) then
call c_f_pointer(yh%item,yp)
else
return
end if
if (c_associated(zh%item)) then
call c_f_pointer(zh%item,zp)
else
return
end if
call psb_gemlt(alpha,xp,yp,beta,zp,descp,info)
res = info
end function psb_c_dgemlt2
function psb_c_dgediv(xh,yh,cdh) bind(c) result(res) function psb_c_dgediv(xh,yh,cdh) bind(c) result(res)
implicit none implicit none
integer(psb_c_ipk_) :: res integer(psb_c_ipk_) :: res

@ -78,6 +78,48 @@ contains
end function psb_c_sgemlt end function psb_c_sgemlt
function psb_c_sgemlt2(alpha,xh,yh,beta,zh,cdh) bind(c) result(res)
implicit none
integer(psb_c_ipk_) :: res
type(psb_c_svector) :: xh,yh, zh
type(psb_c_descriptor) :: cdh
type(psb_desc_type), pointer :: descp
type(psb_s_vect_type), pointer :: xp,yp,zp
integer(psb_c_ipk_) :: info
real(psb_spk_), intent(in) :: alpha,beta
res = -1
if (c_associated(cdh%item)) then
call c_f_pointer(cdh%item,descp)
else
return
end if
if (c_associated(xh%item)) then
call c_f_pointer(xh%item,xp)
else
return
end if
if (c_associated(yh%item)) then
call c_f_pointer(yh%item,yp)
else
return
end if
if (c_associated(zh%item)) then
call c_f_pointer(zh%item,zp)
else
return
end if
call psb_gemlt(alpha,xp,yp,beta,zp,descp,info)
res = info
end function psb_c_sgemlt2
function psb_c_sgediv(xh,yh,cdh) bind(c) result(res) function psb_c_sgediv(xh,yh,cdh) bind(c) result(res)
implicit none implicit none
integer(psb_c_ipk_) :: res integer(psb_c_ipk_) :: res

@ -78,6 +78,48 @@ contains
end function psb_c_zgemlt end function psb_c_zgemlt
function psb_c_zgemlt2(alpha,xh,yh,beta,zh,cdh) bind(c) result(res)
implicit none
integer(psb_c_ipk_) :: res
type(psb_c_zvector) :: xh,yh, zh
type(psb_c_descriptor) :: cdh
type(psb_desc_type), pointer :: descp
type(psb_z_vect_type), pointer :: xp,yp,zp
integer(psb_c_ipk_) :: info
complex(psb_dpk_), intent(in) :: alpha,beta
res = -1
if (c_associated(cdh%item)) then
call c_f_pointer(cdh%item,descp)
else
return
end if
if (c_associated(xh%item)) then
call c_f_pointer(xh%item,xp)
else
return
end if
if (c_associated(yh%item)) then
call c_f_pointer(yh%item,yp)
else
return
end if
if (c_associated(zh%item)) then
call c_f_pointer(zh%item,zp)
else
return
end if
call psb_gemlt(alpha,xp,yp,beta,zp,descp,info)
res = info
end function psb_c_zgemlt2
function psb_c_zgediv(xh,yh,cdh) bind(c) result(res) function psb_c_zgediv(xh,yh,cdh) bind(c) result(res)
implicit none implicit none
integer(psb_c_ipk_) :: res integer(psb_c_ipk_) :: res

Loading…
Cancel
Save