Fixed allocatable, and i/o of complex RHS.

psblas3-type-indexed
Salvatore Filippone 18 years ago
parent 3093612a31
commit 1ac9dae334

@ -95,7 +95,7 @@ program df_sample
real(kind(1.d0)) :: t1, t2, tprec, r_amax, b_amax,&
&scale,resmx,resmxp
integer :: nrhs, nrow, n_row, dim, nv, ne
integer, pointer :: ivg(:), ipv(:), neigh(:)
integer, allocatable :: ivg(:), ipv(:)
call psb_init(ictxt)

@ -55,7 +55,7 @@ MODULE PARTGRAPH
public part_graph, build_grppart, distr_grppart,&
& getv_grppart, build_usrpart, free_part
private
integer, pointer, save :: graph_vect(:)
integer, allocatable, save :: graph_vect(:)
CONTAINS
@ -65,7 +65,7 @@ CONTAINS
integer, intent(out) :: nv
integer, intent(out) :: pv(*)
IF (.not.associated(graph_vect)) then
IF (.not.allocated(graph_vect)) then
write(0,*) 'Fatal error in PART_GRAPH: vector GRAPH_VECT ',&
& 'not initialized'
return
@ -96,7 +96,7 @@ CONTAINS
endif
if (me == root) then
if (.not.associated(graph_vect)) then
if (.not.allocated(graph_vect)) then
write(0,*) 'Fatal error in DISTR_GRPPART: vector GRAPH_VECT ',&
& 'not initialized'
call psb_abort(ictxt)
@ -121,12 +121,10 @@ CONTAINS
end subroutine distr_grppart
subroutine getv_grppart(ivg)
integer, pointer :: ivg(:)
if (associated(graph_vect)) then
integer, allocatable, intent(out) :: ivg(:)
if (allocated(graph_vect)) then
allocate(ivg(size(graph_vect)))
ivg(:) = graph_vect(:)
else
ivg => null()
end if
end subroutine getv_grppart

@ -196,6 +196,7 @@ contains
integer :: nrow, ncol, i,root, nprow, npcol, myprow, mypcol, ircode, j
character :: mmheader*15, fmt*15, object*10, type*10, sym*15,&
& line*1024
real(kind(1.d0)) :: bre, bim
complex(kind(1.0d0)), allocatable :: b(:,:)
if (present(inroot)) then
root = inroot
@ -223,8 +224,12 @@ contains
if ((tolower(type) == 'complex').and.(tolower(sym) == 'general')) then
allocate(b(nrow,ncol),stat = ircode)
if (ircode /= 0) goto 993
read(infile,fmt=*,end=902) ((b(i,j), i=1,nrow),j=1,ncol)
do j=1, ncol
do i=1, nrow
read(infile,fmt=*,end=902) bre,bim
b(i,j) = cmplx(bre,bim)
end do
end do
else
write(0,*) 'read_rhs: rhs type not yet supported'
call psb_abort(ictxt)

@ -95,7 +95,7 @@ program zf_sample
real(kind(1.d0)) :: t1, t2, tprec, r_amax, b_amax,&
&scale,resmx,resmxp
integer :: nrhs, nrow, n_row, dim, nv, ne
integer, pointer :: ivg(:), ipv(:), neigh(:)
integer, allocatable :: ivg(:), ipv(:)

Loading…
Cancel
Save