config/pac.m4
 configure
 docs/pdf/util.tex
 docs/userguide.pdf
 test/fileread/cf_sample.f90
 test/fileread/df_sample.f90
 test/fileread/getp.f90
 test/fileread/runs/cfs.inp
 test/fileread/runs/dfs.inp
 test/fileread/runs/sfs.inp
 test/fileread/runs/zfs.inp
 test/fileread/sf_sample.f90
 test/fileread/zf_sample.f90
 util/Makefile
 util/psb_hbio_mod.f90
 util/psb_mmio_mod.f90
 util/psb_read_mat_mod.f90
 util/psb_util_mod.f90

Fixed I/O for fileread samples.
psblas3-type-indexed
Salvatore Filippone 17 years ago
parent e8f6804783
commit a25813858e

@ -272,8 +272,8 @@ AC_DEFUN([PAC_ARG_WITH_LIBS],
AC_MSG_CHECKING([whether additional libraries are needed])
AC_ARG_WITH(libs,
AC_HELP_STRING([--with-libs],
[List additional libraries here. For example, --with-libs=-lsuperlu
or --with-libs=/path/libsuperlu.a]),
[List additional link flags here. For example, --with-libs=-lspecial_system_lib
or --with-libs=-L/path/to/libs]),
[
LIBS="${withval} ${LIBS}"
AC_MSG_RESULT([LIBS = ${LIBS}])

6
configure vendored

@ -1343,9 +1343,9 @@ Optional Packages:
to CFLAGS
--with-fflags additional FFLAGS flags to be added: will prepend
to FFLAGS
--with-libs List additional libraries here. For example,
--with-libs=-lsuperlu or
--with-libs=/path/libsuperlu.a
--with-libs List additional link flags here. For example,
--with-libs=-lspecial_system_lib or
--with-libs=-L/path/to/libs
--with-clibs additional CLIBS flags to be added: will prepend
to CLIBS
--with-flibs additional FLIBS flags to be added: will prepend

@ -31,11 +31,11 @@ Specified as: an integer value. Only meaningful if filename is not \verb|-|.
\item[a] the sparse matrix read from file.\\
Type:{\bf required}.\\
Specified as: a structured data of type \spdata.
\item[b] Rigth hand side.\\
\item[b] Rigth hand side(s).\\
Type: {\bf Optional} \\
An array of type real or complex, rank 1 and having the ALLOCATABLE
An array of type real or complex, rank 2 and having the ALLOCATABLE
attribute; will be allocated and filled in if the input file contains
a right hand side.
a right hand side, otherwise will be left in the UNALLOCATED state.
\item[mtitle] Matrix title.\\
Type: {\bf Optional} \\
A charachter variable of length 72 holding a copy of the
@ -122,6 +122,34 @@ Type: {\bf required} \\
An integer value; 0 means no error has been detected.
\end{description}
\subroutine{mm\_vet\_read}{Read a dense vector from a file in the MatrixMarket format}
\syntax{call mm\_vet\_read}{b, iret, iunit, filename}
\begin{description}
\item[Type:] Asynchronous.
\item[\bf On Entry ]
\item[filename] The name of the file to be read.\\
Type:{\bf optional}.\\
Specified as: a character variable containing a valid file name, or
\verb|-|, in which case the default input unit 5 (i.e. standard input
in Unix jargon) is used. Default: \verb|-|.
\item[iunit] The Fortran file unit number.\\
Type:{\bf optional}.\\
Specified as: an integer value. Only meaningful if filename is not \verb|-|.
\end{description}
\begin{description}
\item[\bf On Return]
\item[b] Rigth hand side(s).\\
Type: {\bf required} \\
An array of type real or complex, rank 2 and having the ALLOCATABLE
attribute; will be allocated and filled in if the input file contains
a right hand side, otherwise will be left in the UNALLOCATED state.
\item[iret] Error code.\\
Type: {\bf required} \\
An integer value; 0 means no error has been detected.
\end{description}
\subroutine{mm\_mat\_write}{Write a sparse matrix to a file in the MatrixMarket format}

File diff suppressed because one or more lines are too long

@ -64,6 +64,8 @@ program cf_sample
character(len=5) :: afmt
character(len=20) :: name
character(len=2) :: filefmt
integer, parameter :: iunit=12
integer :: iparm(20)
! other variables
@ -92,7 +94,7 @@ program cf_sample
!
! get parameters
!
call get_parms(ictxt,mtrx_file,rhs_file,kmethd,ptype,&
call get_parms(ictxt,mtrx_file,rhs_file,filefmt,kmethd,ptype,&
& ipart,afmt,istopc,itmax,itrace,irst,eps)
call psb_barrier(ictxt)
@ -101,16 +103,35 @@ program cf_sample
nrhs = 1
if (iam==psb_root_) then
call read_mat(mtrx_file, aux_a, ictxt)
select case(psb_toupper(filefmt))
case('MM')
! For Matrix Market we have an input file for the matrix
! and an (optional) second file for the RHS.
call mm_mat_read(aux_a,info,iunit=iunit,filename=mtrx_file)
if (info == 0) then
if (rhs_file /= 'NONE') then
call mm_vet_read(aux_b,info,iunit=iunit,filename=rhs_file)
end if
end if
case ('HB')
! For Harwell-Boeing we have a single file which may or may not
! contain an RHS.
call hb_read(aux_a,info,iunit=iunit,b=aux_b,filename=mtrx_file)
case default
info = -1
write(0,*) 'Wrong choice for fileformat ', filefmt
end select
if (info /= 0) then
write(0,*) 'Error while reading input matrix '
call psb_abort(ictxt)
end if
m_problem = aux_a%m
call psb_bcast(ictxt,m_problem)
if(rhs_file /= 'NONE') then
! reading an rhs
call read_rhs(rhs_file,aux_b,info,ictxt)
end if
! At this point aux_b may still be unallocated
if (psb_size(aux_b,dim=1)==m_problem) then
! if any rhs were present, broadcast the first one
write(0,'("Ok, got an rhs ")')

@ -64,6 +64,8 @@ program df_sample
character(len=5) :: afmt
character(len=20) :: name
character(len=2) :: filefmt
integer, parameter :: iunit=12
integer :: iparm(20)
! other variables
@ -92,7 +94,7 @@ program df_sample
!
! get parameters
!
call get_parms(ictxt,mtrx_file,rhs_file,kmethd,ptype,&
call get_parms(ictxt,mtrx_file,rhs_file,filefmt,kmethd,ptype,&
& ipart,afmt,istopc,itmax,itrace,irst,eps)
call psb_barrier(ictxt)
@ -101,16 +103,35 @@ program df_sample
nrhs = 1
if (iam==psb_root_) then
call read_mat(mtrx_file, aux_a, ictxt)
select case(psb_toupper(filefmt))
case('MM')
! For Matrix Market we have an input file for the matrix
! and an (optional) second file for the RHS.
call mm_mat_read(aux_a,info,iunit=iunit,filename=mtrx_file)
if (info == 0) then
if (rhs_file /= 'NONE') then
call mm_vet_read(aux_b,info,iunit=iunit,filename=rhs_file)
end if
end if
case ('HB')
! For Harwell-Boeing we have a single file which may or may not
! contain an RHS.
call hb_read(aux_a,info,iunit=iunit,b=aux_b,filename=mtrx_file)
case default
info = -1
write(0,*) 'Wrong choice for fileformat ', filefmt
end select
if (info /= 0) then
write(0,*) 'Error while reading input matrix '
call psb_abort(ictxt)
end if
m_problem = aux_a%m
call psb_bcast(ictxt,m_problem)
if(rhs_file /= 'NONE') then
! reading an rhs
call read_rhs(rhs_file,aux_b,info,ictxt)
end if
! At this point aux_b may still be unallocated
if (psb_size(aux_b,dim=1)==m_problem) then
! if any rhs were present, broadcast the first one
write(0,'("Ok, got an rhs ")')
@ -123,14 +144,16 @@ program df_sample
call psb_errpush(4000,name)
goto 9999
endif
b_col_glob => aux_b(:,1)
do i=1, m_problem
b_col_glob(i) = 1.d0
enddo
endif
call psb_bcast(ictxt,b_col_glob(1:m_problem))
else
call psb_bcast(ictxt,m_problem)
call psb_realloc(m_problem,1,aux_b,ircode)
if (ircode /= 0) then
@ -139,6 +162,7 @@ program df_sample
endif
b_col_glob =>aux_b(:,1)
call psb_bcast(ictxt,b_col_glob(1:m_problem))
end if
! switch over different partition types

@ -38,10 +38,11 @@ contains
!
! Get iteration parameters from the command line
!
subroutine get_dparms(ictxt,mtrx_file,rhs_file,kmethd,ptype,ipart,&
subroutine get_dparms(ictxt,mtrx_file,rhs_file,filefmt,kmethd,ptype,ipart,&
& afmt,istopc,itmax,itrace,irst,eps)
use psb_base_mod
integer :: ictxt
character(len=2) :: filefmt
character(len=40) :: kmethd, mtrx_file, rhs_file, ptype
integer :: iret, istopc,itmax,itrace,ipart,irst
character(len=40) :: charbuf
@ -57,6 +58,7 @@ contains
if (ip >= 5) then
read(*,*) mtrx_file
read(*,*) rhs_file
read(*,*) filefmt
read(*,*) kmethd
read(*,*) ptype
read(*,*) afmt
@ -64,6 +66,7 @@ contains
call psb_bcast(ictxt,mtrx_file)
call psb_bcast(ictxt,rhs_file)
call psb_bcast(ictxt,filefmt)
call psb_bcast(ictxt,kmethd)
call psb_bcast(ictxt,ptype)
call psb_bcast(ictxt,afmt)
@ -119,6 +122,7 @@ contains
! Receive Parameters
call psb_bcast(ictxt,mtrx_file)
call psb_bcast(ictxt,rhs_file)
call psb_bcast(ictxt,filefmt)
call psb_bcast(ictxt,kmethd)
call psb_bcast(ictxt,ptype)
call psb_bcast(ictxt,afmt)
@ -135,10 +139,11 @@ contains
end subroutine get_dparms
subroutine get_sparms(ictxt,mtrx_file,rhs_file,kmethd,ptype,ipart,&
subroutine get_sparms(ictxt,mtrx_file,rhs_file,filefmt,kmethd,ptype,ipart,&
& afmt,istopc,itmax,itrace,irst,eps)
use psb_base_mod
integer :: ictxt
character(len=2) :: filefmt
character(len=40) :: kmethd, mtrx_file, rhs_file, ptype
integer :: iret, istopc,itmax,itrace,ipart,irst
character(len=40) :: charbuf
@ -154,6 +159,7 @@ contains
if (ip >= 5) then
read(*,*) mtrx_file
read(*,*) rhs_file
read(*,*) filefmt
read(*,*) kmethd
read(*,*) ptype
read(*,*) afmt
@ -161,6 +167,7 @@ contains
call psb_bcast(ictxt,mtrx_file)
call psb_bcast(ictxt,rhs_file)
call psb_bcast(ictxt,filefmt)
call psb_bcast(ictxt,kmethd)
call psb_bcast(ictxt,ptype)
call psb_bcast(ictxt,afmt)
@ -216,6 +223,7 @@ contains
! Receive Parameters
call psb_bcast(ictxt,mtrx_file)
call psb_bcast(ictxt,rhs_file)
call psb_bcast(ictxt,filefmt)
call psb_bcast(ictxt,kmethd)
call psb_bcast(ictxt,ptype)
call psb_bcast(ictxt,afmt)

@ -1,7 +1,8 @@
11 Number of inputs
young1c.mtx waveguide3D.mtx This (and others) from: http://math.nist.gov/MatrixMarket/ or
young1c.mtx This (and others) from: http://math.nist.gov/MatrixMarket/ or
NONE http://www.cise.ufl.edu/research/sparse/matrices/index.html
BICGSTAB Iterative method: BiCGSTAB CGS RGMRES BiCGSTABL
MM File format: MM: Matrix Market HB: Harwell-Boeing.
BICGSTAB Iterative method: BiCGSTAB CGS RGMRES BiCGSTABL BICG CG
BJAC Preconditioner NONE DIAG BJAC
CSR Storage format CSR COO JAD
0 IPART: Partition method 0: BLK 2: graph (with Metis)

@ -1,12 +1,13 @@
11 Number of inputs
thm1000x600.mtx young1r.mtx This (and others) from: http://math.nist.gov/MatrixMarket/ or
NONE rhs.mtx NONE http://www.cise.ufl.edu/research/sparse/matrices/index.html
BICGSTAB Iterative method: BiCGSTAB CGS RGMRES BiCGSTABL
BJAC Preconditioner NONE DIAG BJAC
sherman3.mtx This (and others) from: http://math.nist.gov/MatrixMarket/ or
sherman3_rhs1.mtx http://www.cise.ufl.edu/research/sparse/matrices/index.html
MM File format: MM: Matrix Market HB: Harwell-Boeing.
BICGSTAB Iterative method: BiCGSTAB CGS RGMRES BiCGSTABL BICG CG
BJAC Preconditioner NONE DIAG BJAC
CSR Storage format CSR COO JAD
2 IPART: Partition method 0: BLK 2: graph (with Metis)
0 IPART: Partition method 0: BLK 2: graph (with Metis)
2 ISTOPC
01000 ITMAX
-1 ITRACE
01 ITRACE
30 IRST (restart for RGMRES and BiCGSTABL)
1.d-6 EPS

@ -1,7 +1,8 @@
11 Number of inputs
thm1000x600.mtx young1r.mtx This (and others) from: http://math.nist.gov/MatrixMarket/ or
young1r.mtx This (and others) from: http://math.nist.gov/MatrixMarket/ or
NONE http://www.cise.ufl.edu/research/sparse/matrices/index.html
BICGSTABL Iterative method: BiCGSTAB CGS RGMRES BiCGSTABL
MM File format: MM: Matrix Market HB: Harwell-Boeing.
BICGSTAB Iterative method: BiCGSTAB CGS RGMRES BiCGSTABL BICG CG
BJAC Preconditioner NONE DIAG BJAC
CSR Storage format CSR COO JAD
0 IPART: Partition method 0: BLK 2: graph (with Metis)

@ -1,7 +1,8 @@
11 Number of inputs
kim1.mtx aft02.mtx qc2534.mtx young1c.mtx waveguide3D.mtx This (and others) from: http://math.nist.gov/MatrixMarket/ or
NONE http://www.cise.ufl.edu/research/sparse/matrices/index.html
CGS Iterative method: BiCGSTAB CGS RGMRES BiCGSTABL
young1c.mtx This (and others) from: http://math.nist.gov/MatrixMarket/ or
NONE http://www.cise.ufl.edu/research/sparse/matrices/index.html
MM File format: MM: Matrix Market HB: Harwell-Boeing.
BICGSTAB Iterative method: BiCGSTAB CGS RGMRES BiCGSTABL BICG CG
BJAC Preconditioner NONE DIAG BJAC
CSR Storage format CSR COO JAD
0 IPART: Partition method 0: BLK 2: graph (with Metis)

@ -64,6 +64,8 @@ program sf_sample
character(len=5) :: afmt
character(len=20) :: name
character(len=2) :: filefmt
integer, parameter :: iunit=12
integer :: iparm(20)
! other variables
@ -92,7 +94,7 @@ program sf_sample
!
! get parameters
!
call get_parms(ictxt,mtrx_file,rhs_file,kmethd,ptype,&
call get_parms(ictxt,mtrx_file,rhs_file,filefmt,kmethd,ptype,&
& ipart,afmt,istopc,itmax,itrace,irst,eps)
call psb_barrier(ictxt)
@ -101,16 +103,35 @@ program sf_sample
nrhs = 1
if (iam==psb_root_) then
call read_mat(mtrx_file, aux_a, ictxt)
select case(psb_toupper(filefmt))
case('MM')
! For Matrix Market we have an input file for the matrix
! and an (optional) second file for the RHS.
call mm_mat_read(aux_a,info,iunit=iunit,filename=mtrx_file)
if (info == 0) then
if (rhs_file /= 'NONE') then
call mm_vet_read(aux_b,info,iunit=iunit,filename=rhs_file)
end if
end if
case ('HB')
! For Harwell-Boeing we have a single file which may or may not
! contain an RHS.
call hb_read(aux_a,info,iunit=iunit,b=aux_b,filename=mtrx_file)
case default
info = -1
write(0,*) 'Wrong choice for fileformat ', filefmt
end select
if (info /= 0) then
write(0,*) 'Error while reading input matrix '
call psb_abort(ictxt)
end if
m_problem = aux_a%m
call psb_bcast(ictxt,m_problem)
if(rhs_file /= 'NONE') then
! reading an rhs
call read_rhs(rhs_file,aux_b,info,ictxt)
end if
! At this point aux_b may still be unallocated
if (psb_size(aux_b,dim=1)==m_problem) then
! if any rhs were present, broadcast the first one
write(0,'("Ok, got an rhs ")')

@ -64,6 +64,8 @@ program zf_sample
character(len=5) :: afmt
character(len=20) :: name
character(len=2) :: filefmt
integer, parameter :: iunit=12
integer :: iparm(20)
! other variables
@ -92,7 +94,7 @@ program zf_sample
!
! get parameters
!
call get_parms(ictxt,mtrx_file,rhs_file,kmethd,ptype,&
call get_parms(ictxt,mtrx_file,rhs_file,filefmt,kmethd,ptype,&
& ipart,afmt,istopc,itmax,itrace,irst,eps)
call psb_barrier(ictxt)
@ -101,16 +103,35 @@ program zf_sample
nrhs = 1
if (iam==psb_root_) then
call read_mat(mtrx_file, aux_a, ictxt)
select case(psb_toupper(filefmt))
case('MM')
! For Matrix Market we have an input file for the matrix
! and an (optional) second file for the RHS.
call mm_mat_read(aux_a,info,iunit=iunit,filename=mtrx_file)
if (info == 0) then
if (rhs_file /= 'NONE') then
call mm_vet_read(aux_b,info,iunit=iunit,filename=rhs_file)
end if
end if
case ('HB')
! For Harwell-Boeing we have a single file which may or may not
! contain an RHS.
call hb_read(aux_a,info,iunit=iunit,b=aux_b,filename=mtrx_file)
case default
info = -1
write(0,*) 'Wrong choice for fileformat ', filefmt
end select
if (info /= 0) then
write(0,*) 'Error while reading input matrix '
call psb_abort(ictxt)
end if
m_problem = aux_a%m
call psb_bcast(ictxt,m_problem)
if(rhs_file /= 'NONE') then
! reading an rhs
call read_rhs(rhs_file,aux_b,info,ictxt)
end if
! At this point aux_b may still be unallocated
if (psb_size(aux_b,dim=1)==m_problem) then
! if any rhs were present, broadcast the first one
write(0,'("Ok, got an rhs ")')

@ -6,8 +6,7 @@ LIBDIR=../lib
HERE=.
BASEOBJS= psb_blockpart_mod.o psb_metispart_mod.o \
psb_hbio_mod.o psb_mmio_mod.o psb_mat_dist_mod.o \
psb_read_mat_mod.o
psb_hbio_mod.o psb_mmio_mod.o psb_mat_dist_mod.o
MODOBJ=psb_util_mod.o
OBJS=$(BASEOBJS) $(MODOBJ)
LIBMOD=psb_util_mod$(.mod)

@ -48,10 +48,11 @@ contains
integer, intent(out) :: iret
integer, optional, intent(in) :: iunit
character(len=*), optional, intent(in) :: filename
real(psb_spk_), optional, allocatable :: b(:), g(:), x(:)
real(psb_spk_), optional, allocatable, intent(out) :: b(:,:), g(:,:), x(:,:)
character(len=72), optional, intent(out) :: mtitle
character :: rhstype*3,type*3,key*8
character(len=72) :: mtitle_
character indfmt*16,ptrfmt*16,rhsfmt*20,valfmt*20
integer :: indcrd, ptrcrd, totcrd,&
& valcrd, rhscrd, nrow, ncol, nnzero, neltvl, nrhs, nrhsix
@ -81,7 +82,7 @@ contains
endif
endif
read (infile,fmt=fmt10) mtitle,key,totcrd,ptrcrd,indcrd,valcrd,rhscrd,&
read(infile,fmt=fmt10) mtitle_,key,totcrd,ptrcrd,indcrd,valcrd,rhscrd,&
& type,nrow,ncol,nnzero,neltvl,ptrfmt,indfmt,valfmt,rhsfmt
if (rhscrd > 0) read(infile,fmt=fmt11)rhstype,nrhs,nrhsix
@ -90,6 +91,7 @@ contains
write(0,*) 'Memory allocation failed'
goto 993
end if
if (present(mtitle)) mtitle=mtitle_
a%m = nrow
a%k = ncol
@ -107,20 +109,20 @@ contains
if (present(b)) then
if ((psb_toupper(rhstype(1:1)) == 'F').and.(rhscrd > 0)) then
call psb_ensure_size(nrow,b,info)
read (infile,fmt=rhsfmt) (b(i),i=1,nrow)
call psb_realloc(nrow,1,b,info)
read (infile,fmt=rhsfmt) (b(i,1),i=1,nrow)
endif
endif
if (present(g)) then
if ((psb_toupper(rhstype(2:2)) == 'G').and.(rhscrd > 0)) then
call psb_ensure_size(nrow,g,info)
read (infile,fmt=rhsfmt) (g(i),i=1,nrow)
call psb_realloc(nrow,1,g,info)
read (infile,fmt=rhsfmt) (g(i,1),i=1,nrow)
endif
endif
if (present(x)) then
if ((psb_toupper(rhstype(3:3)) == 'X').and.(rhscrd > 0)) then
call psb_ensure_size(nrow,x,info)
read (infile,fmt=rhsfmt) (x(i),i=1,nrow)
call psb_realloc(nrow,1,x,info)
read (infile,fmt=rhsfmt) (x(i,1),i=1,nrow)
endif
endif
@ -133,22 +135,23 @@ contains
read (infile,fmt=indfmt) (a%ia1(i),i=1,nnzero)
if (valcrd > 0) read (infile,fmt=valfmt) (a%aspk(i),i=1,nnzero)
if (present(b)) then
if ((psb_toupper(rhstype(1:1)) == 'F').and.(rhscrd > 0)) then
call psb_ensure_size(nrow,b,info)
read (infile,fmt=rhsfmt) (b(i),i=1,nrow)
call psb_realloc(nrow,1,b,info)
read (infile,fmt=rhsfmt) (b(i,1),i=1,nrow)
endif
endif
if (present(g)) then
if ((psb_toupper(rhstype(2:2)) == 'G').and.(rhscrd > 0)) then
call psb_ensure_size(nrow,g,info)
read (infile,fmt=rhsfmt) (g(i),i=1,nrow)
call psb_realloc(nrow,1,g,info)
read (infile,fmt=rhsfmt) (g(i,1),i=1,nrow)
endif
endif
if (present(x)) then
if ((psb_toupper(rhstype(3:3)) == 'X').and.(rhscrd > 0)) then
call psb_ensure_size(nrow,x,info)
read (infile,fmt=rhsfmt) (x(i),i=1,nrow)
call psb_realloc(nrow,1,x,info)
read (infile,fmt=rhsfmt) (x(i,1),i=1,nrow)
endif
endif
@ -187,10 +190,10 @@ contains
write(0,*) 'read_matrix: could not open file ',filename,' for input'
return
902 iret=902
write(0,*) 'DHB_READ: Unexpected end of file '
write(0,*) 'HB_READ: Unexpected end of file '
return
993 iret=993
write(0,*) 'DHB_READ: Memory allocation failure'
write(0,*) 'HB_READ: Memory allocation failure'
return
end subroutine shb_read
@ -329,10 +332,11 @@ contains
integer, intent(out) :: iret
integer, optional, intent(in) :: iunit
character(len=*), optional, intent(in) :: filename
real(psb_dpk_), optional, allocatable :: b(:), g(:), x(:)
real(psb_dpk_), optional, allocatable, intent(out) :: b(:,:), g(:,:), x(:,:)
character(len=72), optional, intent(out) :: mtitle
character :: rhstype*3,type*3,key*8
character(len=72) :: mtitle_
character indfmt*16,ptrfmt*16,rhsfmt*20,valfmt*20
integer :: indcrd, ptrcrd, totcrd,&
& valcrd, rhscrd, nrow, ncol, nnzero, neltvl, nrhs, nrhsix
@ -362,7 +366,7 @@ contains
endif
endif
read (infile,fmt=fmt10) mtitle,key,totcrd,ptrcrd,indcrd,valcrd,rhscrd,&
read (infile,fmt=fmt10) mtitle_,key,totcrd,ptrcrd,indcrd,valcrd,rhscrd,&
& type,nrow,ncol,nnzero,neltvl,ptrfmt,indfmt,valfmt,rhsfmt
if (rhscrd > 0) read(infile,fmt=fmt11)rhstype,nrhs,nrhsix
@ -371,7 +375,7 @@ contains
write(0,*) 'Memory allocation failed'
goto 993
end if
if (present(mtitle)) mtitle=mtitle_
a%m = nrow
a%k = ncol
a%fida = 'CSR'
@ -388,20 +392,20 @@ contains
if (present(b)) then
if ((psb_toupper(rhstype(1:1)) == 'F').and.(rhscrd > 0)) then
call psb_ensure_size(nrow,b,info)
read (infile,fmt=rhsfmt) (b(i),i=1,nrow)
call psb_realloc(nrow,1,b,info)
read (infile,fmt=rhsfmt) (b(i,1),i=1,nrow)
endif
endif
if (present(g)) then
if ((psb_toupper(rhstype(2:2)) == 'G').and.(rhscrd > 0)) then
call psb_ensure_size(nrow,g,info)
read (infile,fmt=rhsfmt) (g(i),i=1,nrow)
call psb_realloc(nrow,1,g,info)
read (infile,fmt=rhsfmt) (g(i,1),i=1,nrow)
endif
endif
if (present(x)) then
if ((psb_toupper(rhstype(3:3)) == 'X').and.(rhscrd > 0)) then
call psb_ensure_size(nrow,x,info)
read (infile,fmt=rhsfmt) (x(i),i=1,nrow)
call psb_realloc(nrow,1,x,info)
read (infile,fmt=rhsfmt) (x(i,1),i=1,nrow)
endif
endif
@ -417,24 +421,23 @@ contains
if (present(b)) then
if ((psb_toupper(rhstype(1:1)) == 'F').and.(rhscrd > 0)) then
call psb_ensure_size(nrow,b,info)
read (infile,fmt=rhsfmt) (b(i),i=1,nrow)
call psb_realloc(nrow,1,b,info)
read (infile,fmt=rhsfmt) (b(i,1),i=1,nrow)
endif
endif
if (present(g)) then
if ((psb_toupper(rhstype(2:2)) == 'G').and.(rhscrd > 0)) then
call psb_ensure_size(nrow,g,info)
read (infile,fmt=rhsfmt) (g(i),i=1,nrow)
call psb_realloc(nrow,1,g,info)
read (infile,fmt=rhsfmt) (g(i,1),i=1,nrow)
endif
endif
if (present(x)) then
if ((psb_toupper(rhstype(3:3)) == 'X').and.(rhscrd > 0)) then
call psb_ensure_size(nrow,x,info)
read (infile,fmt=rhsfmt) (x(i),i=1,nrow)
call psb_realloc(nrow,1,x,info)
read (infile,fmt=rhsfmt) (x(i,1),i=1,nrow)
endif
endif
call psb_spcnv(a,ircode,afmt='csr')
if (ircode /= 0) goto 993
@ -470,16 +473,13 @@ contains
write(0,*) 'read_matrix: could not open file ',filename,' for input'
return
902 iret=902
write(0,*) 'DHB_READ: Unexpected end of file '
write(0,*) 'HB_READ: Unexpected end of file '
return
993 iret=993
write(0,*) 'DHB_READ: Memory allocation failure'
write(0,*) 'HB_READ: Memory allocation failure'
return
end subroutine dhb_read
subroutine dhb_write(a,iret,iunit,filename,key,rhs,g,x,mtitle)
use psb_base_mod
implicit none
@ -615,14 +615,15 @@ contains
integer, intent(out) :: iret
integer, optional, intent(in) :: iunit
character(len=*), optional, intent(in) :: filename
complex(psb_spk_), optional, allocatable :: b(:), g(:), x(:)
complex(psb_spk_), optional, allocatable, intent(out) :: b(:,:), g(:,:), x(:,:)
character(len=72), optional, intent(out) :: mtitle
character :: rhstype*3,type*3,key*8
character(len=72) :: mtitle_
character indfmt*16,ptrfmt*16,rhsfmt*20,valfmt*20
integer :: indcrd, ptrcrd, totcrd,&
& valcrd, rhscrd, nrow, ncol, nnzero, neltvl, nrhs, nrhsix
integer :: ircode, i,nzr,infile,info
integer :: ircode, i,nzr,infile, info
character(len=*), parameter :: fmt10='(a72,a8,/,5i14,/,a3,11x,4i14,/,2a16,2a20)'
character(len=*), parameter :: fmt11='(a3,11x,2i14)'
character(len=*), parameter :: fmt111='(1x,a8,1x,i8,1x,a10)'
@ -648,25 +649,26 @@ contains
endif
endif
read (infile,fmt=fmt10) mtitle,key,totcrd,ptrcrd,indcrd,valcrd,rhscrd,&
read (infile,fmt=fmt10) mtitle_,key,totcrd,ptrcrd,indcrd,valcrd,rhscrd,&
& type,nrow,ncol,nnzero,neltvl,ptrfmt,indfmt,valfmt,rhsfmt
if (rhscrd > 0) read(infile,fmt=fmt11)rhstype,nrhs,nrhsix
call psb_sp_all(a,nnzero,nrow+1,nnzero,ircode)
if (ircode /= 0 ) then
write(0,*) 'Memory allocation failed'
goto 993
end if
if (present(mtitle)) mtitle=mtitle_
if (psb_tolower(type(1:1)) == 'c') then
a%m = nrow
a%k = ncol
a%fida = 'CSR'
a%descra='G'
if (psb_tolower(type(1:1)) == 'r') then
if (psb_tolower(type(2:2)) == 'u') then
call psb_sp_all(a,nnzero,nrow+1,nnzero,ircode)
if (ircode /= 0 ) then
write(0,*) 'Memory allocation failed'
goto 993
end if
a%m = nrow
a%k = ncol
a%fida = 'CSR'
a%descra='G'
read (infile,fmt=ptrfmt) (a%ia2(i),i=1,nrow+1)
read (infile,fmt=indfmt) (a%ia1(i),i=1,nnzero)
@ -674,20 +676,20 @@ contains
if (present(b)) then
if ((psb_toupper(rhstype(1:1)) == 'F').and.(rhscrd > 0)) then
call psb_ensure_size(nrow,b,info)
read (infile,fmt=rhsfmt) (b(i),i=1,nrow)
call psb_realloc(nrow,1,b,info)
read (infile,fmt=rhsfmt) (b(i,1),i=1,nrow)
endif
endif
if (present(g)) then
if ((psb_toupper(rhstype(2:2)) == 'G').and.(rhscrd > 0)) then
call psb_ensure_size(nrow,g,info)
read (infile,fmt=rhsfmt) (g(i),i=1,nrow)
call psb_realloc(nrow,1,g,info)
read (infile,fmt=rhsfmt) (g(i,1),i=1,nrow)
endif
endif
if (present(x)) then
if ((psb_toupper(rhstype(3:3)) == 'X').and.(rhscrd > 0)) then
call psb_ensure_size(nrow,x,info)
read (infile,fmt=rhsfmt) (x(i),i=1,nrow)
call psb_realloc(nrow,1,x,info)
read (infile,fmt=rhsfmt) (x(i,1),i=1,nrow)
endif
endif
@ -695,137 +697,48 @@ contains
! we are generally working with non-symmetric matrices, so
! we de-symmetrize what we are about to read
call psb_sp_all(nrow,ncol,a,nnzero,ircode)
if (ircode /= 0 ) then
write(0,*) 'Memory allocation failed'
goto 993
end if
a%fida = 'CSR'
a%descra='G'
read (infile,fmt=ptrfmt) (a%ia2(i),i=1,nrow+1)
read (infile,fmt=indfmt) (a%ia1(i),i=1,nnzero)
if (valcrd > 0) read (infile,fmt=valfmt) (a%aspk(i),i=1,nnzero)
if (present(b)) then
if ((psb_toupper(rhstype(1:1)) == 'F').and.(rhscrd > 0)) then
call psb_ensure_size(nrow,b,info)
read (infile,fmt=rhsfmt) (b(i),i=1,nrow)
call psb_realloc(nrow,1,b,info)
read (infile,fmt=rhsfmt) (b(i,1),i=1,nrow)
endif
endif
if (present(g)) then
if ((psb_toupper(rhstype(2:2)) == 'G').and.(rhscrd > 0)) then
call psb_ensure_size(nrow,g,info)
read (infile,fmt=rhsfmt) (g(i),i=1,nrow)
call psb_realloc(nrow,1,g,info)
read (infile,fmt=rhsfmt) (g(i,1),i=1,nrow)
endif
endif
if (present(x)) then
if ((psb_toupper(rhstype(3:3)) == 'X').and.(rhscrd > 0)) then
call psb_ensure_size(nrow,x,info)
read (infile,fmt=rhsfmt) (x(i),i=1,nrow)
call psb_realloc(nrow,1,x,info)
read (infile,fmt=rhsfmt) (x(i,1),i=1,nrow)
endif
endif
call psb_spcnv(a,ircode,afmt='coo')
if (ircode /= 0) then
write(0,*) 'ipcsr2coo ',ircode
goto 993
end if
call psb_sp_reall(a,2*nnzero,ircode)
if (ircode /= 0 ) then
write(0,*) 'Memory allocation failed'
goto 993
end if
! A is now in COO format
nzr = nnzero
do i=1,nnzero
if (a%ia1(i) /= a%ia2(i)) then
nzr = nzr + 1
a%aspk(nzr) = a%aspk(i)
a%ia1(nzr) = a%ia2(i)
a%ia2(nzr) = a%ia1(i)
end if
end do
a%infoa(psb_nnz_) = nzr
call psb_spcnv(a,ircode,afmt='csr')
if (ircode /= 0) then
write(0,*) 'ipcoo2csr ',ircode
goto 993
end if
else if (psb_tolower(type(2:2)) == 'h') then
! we are generally working with non-symmetric matrices, so
! we de-symmetrize what we are about to read
call psb_sp_all(nrow,ncol,a,2*nnzero,ircode)
if (ircode /= 0 ) then
write(0,*) 'Memory allocation failed'
goto 993
end if
a%fida = 'CSR'
a%descra='G'
read (infile,fmt=ptrfmt) (a%ia2(i),i=1,nrow+1)
read (infile,fmt=indfmt) (a%ia1(i),i=1,nnzero)
if (valcrd > 0) read (infile,fmt=valfmt) (a%aspk(i),i=1,nnzero)
if (ircode /= 0) goto 993
if (present(b)) then
if ((psb_toupper(rhstype(1:1)) == 'F').and.(rhscrd > 0)) then
call psb_ensure_size(nrow,b,info)
read (infile,fmt=rhsfmt) (b(i),i=1,nrow)
endif
endif
if (present(g)) then
if ((psb_toupper(rhstype(2:2)) == 'G').and.(rhscrd > 0)) then
call psb_ensure_size(nrow,g,info)
read (infile,fmt=rhsfmt) (g(i),i=1,nrow)
endif
endif
if (present(x)) then
if ((psb_toupper(rhstype(3:3)) == 'X').and.(rhscrd > 0)) then
call psb_ensure_size(nrow,x,info)
read (infile,fmt=rhsfmt) (x(i),i=1,nrow)
endif
endif
call psb_spcnv(a,ircode,afmt='coo')
if (ircode /= 0) then
write(0,*) 'ipcsr2coo ',ircode
goto 993
end if
call psb_sp_reall(a,2*nnzero,ircode)
if (ircode /= 0 ) then
write(0,*) 'Memory allocation failed'
goto 993
end if
! A is now in COO format
nzr = nnzero
do i=1,nnzero
if (a%ia1(i) /= a%ia2(i)) then
nzr = nzr + 1
a%aspk(nzr) = conjg(a%aspk(i))
a%aspk(nzr) = a%aspk(i)
a%ia1(nzr) = a%ia2(i)
a%ia2(nzr) = a%ia1(i)
end if
end do
a%infoa(psb_nnz_) = nzr
call psb_spcnv(a,ircode,afmt='csr')
if (ircode /= 0) then
write(0,*) 'ipcoo2csr ',ircode
goto 993
end if
if (ircode /= 0) goto 993
else
write(0,*) 'read_matrix: matrix type not yet supported'
@ -844,16 +757,14 @@ contains
write(0,*) 'read_matrix: could not open file ',filename,' for input'
return
902 iret=902
write(0,*) 'ZHB_READ: Unexpected end of file '
write(0,*) 'HB_READ: Unexpected end of file '
return
993 iret=993
write(0,*) 'ZHB_READ: Memory allocation failure'
write(0,*) 'HB_READ: Memory allocation failure'
return
end subroutine chb_read
subroutine chb_write(a,iret,iunit,filename,key,rhs,g,x,mtitle)
use psb_base_mod
implicit none
@ -985,14 +896,15 @@ contains
integer, intent(out) :: iret
integer, optional, intent(in) :: iunit
character(len=*), optional, intent(in) :: filename
complex(psb_dpk_), optional, allocatable :: b(:), g(:), x(:)
complex(psb_dpk_), optional, allocatable, intent(out) :: b(:,:), g(:,:), x(:,:)
character(len=72), optional, intent(out) :: mtitle
character :: rhstype*3,type*3,key*8
character(len=72) :: mtitle_
character indfmt*16,ptrfmt*16,rhsfmt*20,valfmt*20
integer :: indcrd, ptrcrd, totcrd,&
& valcrd, rhscrd, nrow, ncol, nnzero, neltvl, nrhs, nrhsix
integer :: ircode, i,nzr,infile,info
integer :: ircode, i,nzr,infile, info
character(len=*), parameter :: fmt10='(a72,a8,/,5i14,/,a3,11x,4i14,/,2a16,2a20)'
character(len=*), parameter :: fmt11='(a3,11x,2i14)'
character(len=*), parameter :: fmt111='(1x,a8,1x,i8,1x,a10)'
@ -1018,25 +930,26 @@ contains
endif
endif
read (infile,fmt=fmt10) mtitle,key,totcrd,ptrcrd,indcrd,valcrd,rhscrd,&
read (infile,fmt=fmt10) mtitle_,key,totcrd,ptrcrd,indcrd,valcrd,rhscrd,&
& type,nrow,ncol,nnzero,neltvl,ptrfmt,indfmt,valfmt,rhsfmt
if (rhscrd > 0) read(infile,fmt=fmt11)rhstype,nrhs,nrhsix
call psb_sp_all(a,nnzero,nrow+1,nnzero,ircode)
if (ircode /= 0 ) then
write(0,*) 'Memory allocation failed'
goto 993
end if
if (present(mtitle)) mtitle=mtitle_
a%m = nrow
a%k = ncol
a%fida = 'CSR'
a%descra='G'
if (psb_tolower(type(1:1)) == 'c') then
if (psb_tolower(type(1:1)) == 'r') then
if (psb_tolower(type(2:2)) == 'u') then
call psb_sp_all(a,nnzero,nrow+1,nnzero,ircode)
if (ircode /= 0 ) then
write(0,*) 'Memory allocation failed'
goto 993
end if
a%m = nrow
a%k = ncol
a%fida = 'CSR'
a%descra='G'
read (infile,fmt=ptrfmt) (a%ia2(i),i=1,nrow+1)
read (infile,fmt=indfmt) (a%ia1(i),i=1,nnzero)
@ -1044,20 +957,20 @@ contains
if (present(b)) then
if ((psb_toupper(rhstype(1:1)) == 'F').and.(rhscrd > 0)) then
call psb_ensure_size(nrow,b,info)
read (infile,fmt=rhsfmt) (b(i),i=1,nrow)
call psb_realloc(nrow,1,b,info)
read (infile,fmt=rhsfmt) (b(i,1),i=1,nrow)
endif
endif
if (present(g)) then
if ((psb_toupper(rhstype(2:2)) == 'G').and.(rhscrd > 0)) then
call psb_ensure_size(nrow,g,info)
read (infile,fmt=rhsfmt) (g(i),i=1,nrow)
call psb_realloc(nrow,1,g,info)
read (infile,fmt=rhsfmt) (g(i,1),i=1,nrow)
endif
endif
if (present(x)) then
if ((psb_toupper(rhstype(3:3)) == 'X').and.(rhscrd > 0)) then
call psb_ensure_size(nrow,x,info)
read (infile,fmt=rhsfmt) (x(i),i=1,nrow)
call psb_realloc(nrow,1,x,info)
read (infile,fmt=rhsfmt) (x(i,1),i=1,nrow)
endif
endif
@ -1065,136 +978,48 @@ contains
! we are generally working with non-symmetric matrices, so
! we de-symmetrize what we are about to read
call psb_sp_all(nrow,ncol,a,nnzero,ircode)
if (ircode /= 0 ) then
write(0,*) 'Memory allocation failed'
goto 993
end if
a%fida = 'CSR'
a%descra='G'
read (infile,fmt=ptrfmt) (a%ia2(i),i=1,nrow+1)
read (infile,fmt=indfmt) (a%ia1(i),i=1,nnzero)
if (valcrd > 0) read (infile,fmt=valfmt) (a%aspk(i),i=1,nnzero)
if (present(b)) then
if ((psb_toupper(rhstype(1:1)) == 'F').and.(rhscrd > 0)) then
call psb_ensure_size(nrow,b,info)
read (infile,fmt=rhsfmt) (b(i),i=1,nrow)
call psb_realloc(nrow,1,b,info)
read (infile,fmt=rhsfmt) (b(i,1),i=1,nrow)
endif
endif
if (present(g)) then
if ((psb_toupper(rhstype(2:2)) == 'G').and.(rhscrd > 0)) then
call psb_ensure_size(nrow,g,info)
read (infile,fmt=rhsfmt) (g(i),i=1,nrow)
call psb_realloc(nrow,1,g,info)
read (infile,fmt=rhsfmt) (g(i,1),i=1,nrow)
endif
endif
if (present(x)) then
if ((psb_toupper(rhstype(3:3)) == 'X').and.(rhscrd > 0)) then
call psb_ensure_size(nrow,x,info)
read (infile,fmt=rhsfmt) (x(i),i=1,nrow)
call psb_realloc(nrow,1,x,info)
read (infile,fmt=rhsfmt) (x(i,1),i=1,nrow)
endif
endif
call psb_spcnv(a,ircode,afmt='coo')
if (ircode /= 0) then
write(0,*) 'ipcsr2coo ',ircode
goto 993
end if
call psb_sp_reall(a,2*nnzero,ircode)
if (ircode /= 0 ) then
write(0,*) 'Memory allocation failed'
goto 993
end if
! A is now in COO format
nzr = nnzero
do i=1,nnzero
if (a%ia1(i) /= a%ia2(i)) then
nzr = nzr + 1
a%aspk(nzr) = a%aspk(i)
a%ia1(nzr) = a%ia2(i)
a%ia2(nzr) = a%ia1(i)
end if
end do
a%infoa(psb_nnz_) = nzr
call psb_spcnv(a,ircode,afmt='csr')
if (ircode /= 0) then
write(0,*) 'ipcoo2csr ',ircode
goto 993
end if
else if (psb_tolower(type(2:2)) == 'h') then
! we are generally working with non-symmetric matrices, so
! we de-symmetrize what we are about to read
call psb_sp_all(nrow,ncol,a,2*nnzero,ircode)
if (ircode /= 0 ) then
write(0,*) 'Memory allocation failed'
goto 993
end if
a%fida = 'CSR'
a%descra='G'
read (infile,fmt=ptrfmt) (a%ia2(i),i=1,nrow+1)
read (infile,fmt=indfmt) (a%ia1(i),i=1,nnzero)
if (valcrd > 0) read (infile,fmt=valfmt) (a%aspk(i),i=1,nnzero)
if (ircode /= 0) goto 993
if (present(b)) then
if ((psb_toupper(rhstype(1:1)) == 'F').and.(rhscrd > 0)) then
call psb_ensure_size(nrow,b,info)
read (infile,fmt=rhsfmt) (b(i),i=1,nrow)
endif
endif
if (present(g)) then
if ((psb_toupper(rhstype(2:2)) == 'G').and.(rhscrd > 0)) then
call psb_ensure_size(nrow,g,info)
read (infile,fmt=rhsfmt) (g(i),i=1,nrow)
endif
endif
if (present(x)) then
if ((psb_toupper(rhstype(3:3)) == 'X').and.(rhscrd > 0)) then
call psb_ensure_size(nrow,x,info)
read (infile,fmt=rhsfmt) (x(i),i=1,nrow)
endif
endif
call psb_spcnv(a,ircode,afmt='coo')
if (ircode /= 0) then
write(0,*) 'ipcsr2coo ',ircode
goto 993
end if
call psb_sp_reall(a,2*nnzero,ircode)
if (ircode /= 0 ) then
write(0,*) 'Memory allocation failed'
goto 993
end if
! A is now in COO format
nzr = nnzero
do i=1,nnzero
if (a%ia1(i) /= a%ia2(i)) then
nzr = nzr + 1
a%aspk(nzr) = conjg(a%aspk(i))
a%aspk(nzr) = a%aspk(i)
a%ia1(nzr) = a%ia2(i)
a%ia2(nzr) = a%ia1(i)
end if
end do
a%infoa(psb_nnz_) = nzr
call psb_spcnv(a,ircode,afmt='csr')
if (ircode /= 0) then
write(0,*) 'ipcoo2csr ',ircode
goto 993
end if
if (ircode /= 0) goto 993
else
write(0,*) 'read_matrix: matrix type not yet supported'
@ -1213,16 +1038,14 @@ contains
write(0,*) 'read_matrix: could not open file ',filename,' for input'
return
902 iret=902
write(0,*) 'ZHB_READ: Unexpected end of file '
write(0,*) 'HB_READ: Unexpected end of file '
return
993 iret=993
write(0,*) 'ZHB_READ: Memory allocation failure'
write(0,*) 'HB_READ: Memory allocation failure'
return
end subroutine zhb_read
subroutine zhb_write(a,iret,iunit,filename,key,rhs,g,x,mtitle)
use psb_base_mod
implicit none

@ -44,19 +44,37 @@ module psb_mmio_mod
contains
subroutine mm_svet_read(filename, b, info)
subroutine mm_svet_read(b, info, iunit, filename)
use psb_base_mod
implicit none
character :: filename*(*)
real(psb_spk_), allocatable, intent(out) :: b(:,:)
integer, intent(out) :: info
integer, parameter :: infile = 2
integer :: nrow, ncol, i,root, np, me, ircode, j
integer, intent(out) :: info
integer, optional, intent(in) :: iunit
character(len=*), optional, intent(in) :: filename
integer :: nrow, ncol, i,root, np, me, ircode, j,infile
character :: mmheader*15, fmt*15, object*10, type*10, sym*15,&
& line*1024
info = 0
open(infile,file=filename, status='old', err=901, action="read")
if (present(filename)) then
if (filename=='-') then
infile=5
else
if (present(iunit)) then
infile=iunit
else
infile=99
endif
open(infile,file=filename, status='OLD', err=901, action='READ')
endif
else
if (present(iunit)) then
infile=iunit
else
infile=5
endif
endif
read(infile,fmt=*, end=902) mmheader, object, fmt, type, sym
if ( (object /= 'matrix').or.(fmt /= 'array')) then
@ -79,6 +97,8 @@ contains
end if ! read right hand sides
if (infile/=5) close(infile)
return
! open failed
901 write(0,*) 'mm_vet_read: could not open file ',&
@ -96,19 +116,37 @@ contains
end subroutine mm_svet_read
subroutine mm_dvet_read(filename, b, info)
subroutine mm_dvet_read(b, info, iunit, filename)
use psb_base_mod
implicit none
character :: filename*(*)
real(psb_dpk_), allocatable, intent(out) :: b(:,:)
integer, intent(out) :: info
integer, parameter :: infile = 2
integer :: nrow, ncol, i,root, np, me, ircode, j
integer, intent(out) :: info
integer, optional, intent(in) :: iunit
character(len=*), optional, intent(in) :: filename
integer :: nrow, ncol, i,root, np, me, ircode, j, infile
character :: mmheader*15, fmt*15, object*10, type*10, sym*15,&
& line*1024
info = 0
open(infile,file=filename, status='old', err=901, action="read")
if (present(filename)) then
if (filename=='-') then
infile=5
else
if (present(iunit)) then
infile=iunit
else
infile=99
endif
open(infile,file=filename, status='OLD', err=901, action='READ')
endif
else
if (present(iunit)) then
infile=iunit
else
infile=5
endif
endif
read(infile,fmt=*, end=902) mmheader, object, fmt, type, sym
if ( (object /= 'matrix').or.(fmt /= 'array')) then
@ -130,6 +168,7 @@ contains
read(infile,fmt=*,end=902) ((b(i,j), i=1,nrow),j=1,ncol)
end if ! read right hand sides
if (infile/=5) close(infile)
return
! open failed
@ -148,20 +187,38 @@ contains
end subroutine mm_dvet_read
subroutine mm_cvet_read(filename, b, info)
subroutine mm_cvet_read(b, info, iunit, filename)
use psb_base_mod
implicit none
character :: filename*(*)
complex(psb_spk_), allocatable, intent(out) :: b(:,:)
integer, intent(out) :: info
integer, parameter :: infile = 2
integer :: nrow, ncol, i,root, np, me, ircode, j
integer, intent(out) :: info
integer, optional, intent(in) :: iunit
character(len=*), optional, intent(in) :: filename
integer :: nrow, ncol, i,root, np, me, ircode, j,infile
real(psb_spk_) :: bre, bim
character :: mmheader*15, fmt*15, object*10, type*10, sym*15,&
& line*1024
info = 0
open(infile,file=filename, status='old', err=901, action="read")
if (present(filename)) then
if (filename=='-') then
infile=5
else
if (present(iunit)) then
infile=iunit
else
infile=99
endif
open(infile,file=filename, status='OLD', err=901, action='READ')
endif
else
if (present(iunit)) then
infile=iunit
else
infile=5
endif
endif
read(infile,fmt=*, end=902) mmheader, object, fmt, type, sym
if ( (object /= 'matrix').or.(fmt /= 'array')) then
@ -188,6 +245,7 @@ contains
end do
end if ! read right hand sides
if (infile/=5) close(infile)
return
! open failed
@ -206,20 +264,38 @@ contains
end subroutine mm_cvet_read
subroutine mm_zvet_read(filename, b, info)
subroutine mm_zvet_read(b, info, iunit, filename)
use psb_base_mod
implicit none
character :: filename*(*)
complex(psb_dpk_), allocatable, intent(out) :: b(:,:)
integer, intent(out) :: info
integer, parameter :: infile = 2
integer :: nrow, ncol, i,root, np, me, ircode, j
integer, intent(out) :: info
integer, optional, intent(in) :: iunit
character(len=*), optional, intent(in) :: filename
integer :: nrow, ncol, i,root, np, me, ircode, j,infile
real(psb_dpk_) :: bre, bim
character :: mmheader*15, fmt*15, object*10, type*10, sym*15,&
& line*1024
info = 0
open(infile,file=filename, status='old', err=901, action="read")
if (present(filename)) then
if (filename=='-') then
infile=5
else
if (present(iunit)) then
infile=iunit
else
infile=99
endif
open(infile,file=filename, status='OLD', err=901, action='READ')
endif
else
if (present(iunit)) then
infile=iunit
else
infile=5
endif
endif
read(infile,fmt=*, end=902) mmheader, object, fmt, type, sym
if ( (object /= 'matrix').or.(fmt /= 'array')) then
@ -246,6 +322,7 @@ contains
end do
end if ! read right hand sides
if (infile/=5) close(infile)
return
! open failed
@ -265,11 +342,11 @@ contains
subroutine smm_mat_read(a, iret, iunit, filename)
subroutine smm_mat_read(a, info, iunit, filename)
use psb_base_mod
implicit none
type(psb_sspmat_type), intent(out) :: a
integer, intent(out) :: iret
integer, intent(out) :: info
integer, optional, intent(in) :: iunit
character(len=*), optional, intent(in) :: filename
character :: mmheader*15, fmt*15, object*10, type*10, sym*15
@ -277,7 +354,7 @@ contains
integer :: nrow, ncol, nnzero
integer :: ircode, i,nzr,infile
iret = 0
info = 0
if (present(filename)) then
if (filename=='-') then
@ -302,7 +379,7 @@ contains
if ( (psb_tolower(object) /= 'matrix').or.(psb_tolower(fmt)/='coordinate')) then
write(0,*) 'READ_MATRIX: input file type not yet supported'
iret=909
info=909
return
end if
@ -348,36 +425,36 @@ contains
else
write(0,*) 'read_matrix: matrix type not yet supported'
iret=904
info=904
end if
if (infile/=5) close(infile)
return
! open failed
901 iret=901
901 info=901
write(0,*) 'read_matrix: could not open file ',filename,' for input'
return
902 iret=902
902 info=902
write(0,*) 'READ_MATRIX: Unexpected end of file '
return
993 iret=993
993 info=993
write(0,*) 'READ_MATRIX: Memory allocation failure'
return
end subroutine smm_mat_read
subroutine smm_mat_write(a,mtitle,iret,iunit,filename)
subroutine smm_mat_write(a,mtitle,info,iunit,filename)
use psb_base_mod
implicit none
type(psb_sspmat_type), intent(in) :: a
integer, intent(out) :: iret
integer, intent(out) :: info
character(len=*), intent(in) :: mtitle
integer, optional, intent(in) :: iunit
character(len=*), optional, intent(in) :: filename
integer :: iout
iret = 0
info = 0
if (present(filename)) then
if (filename=='-') then
@ -406,16 +483,16 @@ contains
return
901 continue
iret=901
info=901
write(0,*) 'Error while opening ',filename
return
end subroutine smm_mat_write
subroutine dmm_mat_read(a, iret, iunit, filename)
subroutine dmm_mat_read(a, info, iunit, filename)
use psb_base_mod
implicit none
type(psb_dspmat_type), intent(out) :: a
integer, intent(out) :: iret
integer, intent(out) :: info
integer, optional, intent(in) :: iunit
character(len=*), optional, intent(in) :: filename
character :: mmheader*15, fmt*15, object*10, type*10, sym*15
@ -423,7 +500,7 @@ contains
integer :: nrow, ncol, nnzero
integer :: ircode, i,nzr,infile
iret = 0
info = 0
if (present(filename)) then
if (filename=='-') then
@ -448,7 +525,7 @@ contains
if ( (psb_tolower(object) /= 'matrix').or.(psb_tolower(fmt)/='coordinate')) then
write(0,*) 'READ_MATRIX: input file type not yet supported'
iret=909
info=909
return
end if
@ -494,36 +571,36 @@ contains
else
write(0,*) 'read_matrix: matrix type not yet supported'
iret=904
info=904
end if
if (infile/=5) close(infile)
return
! open failed
901 iret=901
901 info=901
write(0,*) 'read_matrix: could not open file ',filename,' for input'
return
902 iret=902
902 info=902
write(0,*) 'READ_MATRIX: Unexpected end of file '
return
993 iret=993
993 info=993
write(0,*) 'READ_MATRIX: Memory allocation failure'
return
end subroutine dmm_mat_read
subroutine dmm_mat_write(a,mtitle,iret,iunit,filename)
subroutine dmm_mat_write(a,mtitle,info,iunit,filename)
use psb_base_mod
implicit none
type(psb_dspmat_type), intent(in) :: a
integer, intent(out) :: iret
integer, intent(out) :: info
character(len=*), intent(in) :: mtitle
integer, optional, intent(in) :: iunit
character(len=*), optional, intent(in) :: filename
integer :: iout
iret = 0
info = 0
if (present(filename)) then
if (filename=='-') then
@ -552,16 +629,16 @@ contains
return
901 continue
iret=901
info=901
write(0,*) 'Error while opening ',filename
return
end subroutine dmm_mat_write
subroutine cmm_mat_read(a, iret, iunit, filename)
subroutine cmm_mat_read(a, info, iunit, filename)
use psb_base_mod
implicit none
type(psb_cspmat_type), intent(out) :: a
integer, intent(out) :: iret
integer, intent(out) :: info
integer, optional, intent(in) :: iunit
character(len=*), optional, intent(in) :: filename
character :: mmheader*15, fmt*15, object*10, type*10, sym*15
@ -570,7 +647,7 @@ contains
integer :: ircode, i,nzr,infile
real(psb_spk_) :: are, aim
iret = 0
info = 0
if (present(filename)) then
if (filename=='-') then
@ -595,7 +672,7 @@ contains
if ( (psb_tolower(object) /= 'matrix').or.(psb_tolower(fmt)/='coordinate')) then
write(0,*) 'READ_MATRIX: input file type not yet supported'
iret=909
info=909
return
end if
@ -668,37 +745,37 @@ contains
else
write(0,*) 'read_matrix: matrix type not yet supported'
iret=904
info=904
end if
if (infile/=5) close(infile)
return
! open failed
901 iret=901
901 info=901
write(0,*) 'read_matrix: could not open file ',filename,' for input'
return
902 iret=902
902 info=902
write(0,*) 'READ_MATRIX: Unexpected end of file '
return
993 iret=993
993 info=993
write(0,*) 'READ_MATRIX: Memory allocation failure'
return
end subroutine cmm_mat_read
subroutine cmm_mat_write(a,mtitle,iret,iunit,filename)
subroutine cmm_mat_write(a,mtitle,info,iunit,filename)
use psb_base_mod
implicit none
type(psb_cspmat_type), intent(in) :: a
integer, intent(out) :: iret
integer, intent(out) :: info
character(len=*), intent(in) :: mtitle
integer, optional, intent(in) :: iunit
character(len=*), optional, intent(in) :: filename
integer :: iout
iret = 0
info = 0
if (present(filename)) then
if (filename=='-') then
@ -727,16 +804,16 @@ contains
return
901 continue
iret=901
info=901
write(0,*) 'Error while opening ',filename
return
end subroutine cmm_mat_write
subroutine zmm_mat_read(a, iret, iunit, filename)
subroutine zmm_mat_read(a, info, iunit, filename)
use psb_base_mod
implicit none
type(psb_zspmat_type), intent(out) :: a
integer, intent(out) :: iret
integer, intent(out) :: info
integer, optional, intent(in) :: iunit
character(len=*), optional, intent(in) :: filename
character :: mmheader*15, fmt*15, object*10, type*10, sym*15
@ -745,7 +822,7 @@ contains
integer :: ircode, i,nzr,infile
real(psb_dpk_) :: are, aim
iret = 0
info = 0
if (present(filename)) then
if (filename=='-') then
@ -770,7 +847,7 @@ contains
if ( (psb_tolower(object) /= 'matrix').or.(psb_tolower(fmt)/='coordinate')) then
write(0,*) 'READ_MATRIX: input file type not yet supported'
iret=909
info=909
return
end if
@ -843,37 +920,37 @@ contains
else
write(0,*) 'read_matrix: matrix type not yet supported'
iret=904
info=904
end if
if (infile/=5) close(infile)
return
! open failed
901 iret=901
901 info=901
write(0,*) 'read_matrix: could not open file ',filename,' for input'
return
902 iret=902
902 info=902
write(0,*) 'READ_MATRIX: Unexpected end of file '
return
993 iret=993
993 info=993
write(0,*) 'READ_MATRIX: Memory allocation failure'
return
end subroutine zmm_mat_read
subroutine zmm_mat_write(a,mtitle,iret,iunit,filename)
subroutine zmm_mat_write(a,mtitle,info,iunit,filename)
use psb_base_mod
implicit none
type(psb_zspmat_type), intent(in) :: a
integer, intent(out) :: iret
integer, intent(out) :: info
character(len=*), intent(in) :: mtitle
integer, optional, intent(in) :: iunit
character(len=*), optional, intent(in) :: filename
integer :: iout
iret = 0
info = 0
if (present(filename)) then
if (filename=='-') then
@ -902,7 +979,7 @@ contains
return
901 continue
iret=901
info=901
write(0,*) 'Error while opening ',filename
return
end subroutine zmm_mat_write

@ -1,322 +0,0 @@
!!$
!!$ Parallel Sparse BLAS version 2.2
!!$ (C) Copyright 2006/2007/2008
!!$ Salvatore Filippone University of Rome Tor Vergata
!!$ Alfredo Buttari University of Rome Tor Vergata
!!$
!!$ Redistribution and use in source and binary forms, with or without
!!$ modification, are permitted provided that the following conditions
!!$ are met:
!!$ 1. Redistributions of source code must retain the above copyright
!!$ notice, this list of conditions and the following disclaimer.
!!$ 2. Redistributions in binary form must reproduce the above copyright
!!$ notice, this list of conditions, and the following disclaimer in the
!!$ documentation and/or other materials provided with the distribution.
!!$ 3. The name of the PSBLAS group or the names of its contributors may
!!$ not be used to endorse or promote products derived from this
!!$ software without specific written permission.
!!$
!!$ THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
!!$ ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED
!!$ TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR
!!$ PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE PSBLAS GROUP OR ITS CONTRIBUTORS
!!$ BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR
!!$ CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF
!!$ SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS
!!$ INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN
!!$ CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE)
!!$ ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
!!$ POSSIBILITY OF SUCH DAMAGE.
!!$
!!$
!
! READ_MAT subroutine reads a matrix and its right hand sides,
! all stored in Matrix Market format file. The B field is optional,.
!
! Character :: filename*20
! On Entry: name of file to be processed.
! On Exit : unchanged.
!
! Type(D_SPMAT) :: A
! On Entry: fresh variable.
! On Exit : will contain the global sparse matrix as follows:
! A%AS for coefficient values
! A%IA1 for column indices
! A%IA2 for row pointers
! A%M for number of global matrix rows
! A%K for number of global matrix columns
!
! Integer :: ICTXT
! On Entry: BLACS context.
! On Exit : unchanged.
!
! Real(psb_dpk_), Pointer, Optional :: B(:,:)
! On Entry: fresh variable.
! On Exit: will contain right hand side(s).
!
! Integer, Optional :: inroot
! On Entry: Index of root processor (default: 0)
! On Exit : unchanged.
!
module psb_read_mat_mod
interface read_mat
module procedure sreadmat, dreadmat, creadmat, zreadmat
end interface
interface read_rhs
module procedure sread_rhs, cread_rhs, dread_rhs, zread_rhs
end interface
contains
subroutine sreadmat (filename, a, ictxt, inroot)
use psb_base_mod
use psb_mmio_mod
implicit none
integer :: ictxt
type(psb_sspmat_type) :: a
character(len=*) :: filename
integer, optional :: inroot
integer, parameter :: infile = 2
integer :: info, root, np, me
if (present(inroot)) then
root = inroot
else
root = psb_root_
end if
call psb_info(ictxt, me, np)
if (me == root) then
write(*, '("Reading matrix...")') ! open input file
call mm_mat_read(a,info,infile,filename)
if (info /= 0) then
write(0,*) 'Error return from MM_MAT_READ ',info
call psb_abort(ictxt) ! Unexpected End of File
endif
end if
return
end subroutine sreadmat
subroutine sread_rhs (filename, b, info,ictxt, inroot)
use psb_base_mod
use psb_mmio_mod
implicit none
integer :: ictxt
character :: filename*(*)
real(psb_spk_), allocatable, intent(out) :: b(:,:)
integer, intent(out) :: info
integer, optional :: inroot
integer, parameter :: infile = 2
integer :: nrow, ncol, i,root, np, me, ircode, j
if (present(inroot)) then
root = inroot
else
root = psb_root_
end if
info = 0
call psb_info(ictxt, me, np)
if (me == root) then
write(*, '("Reading rhs...")') ! open input file
call mm_vet_read(filename,b,info)
if (info /= 0) then
write(0,*) 'read_rhs: something went wrong.'
return
end if ! read right hand sides
write(*,*) 'end read_rhs'
end if
return
end subroutine sread_rhs
subroutine dreadmat (filename, a, ictxt, inroot)
use psb_base_mod
use psb_mmio_mod
implicit none
integer :: ictxt
type(psb_dspmat_type) :: a
character(len=*) :: filename
integer, optional :: inroot
integer, parameter :: infile = 2
integer :: info, root, np, me
if (present(inroot)) then
root = inroot
else
root = psb_root_
end if
call psb_info(ictxt, me, np)
if (me == root) then
write(*, '("Reading matrix...")') ! open input file
call mm_mat_read(a,info,infile,filename)
if (info /= 0) then
write(0,*) 'Error return from MM_MAT_READ ',info
call psb_abort(ictxt) ! Unexpected End of File
endif
end if
return
end subroutine dreadmat
subroutine dread_rhs (filename, b, info,ictxt, inroot)
use psb_base_mod
use psb_mmio_mod
implicit none
integer :: ictxt
character :: filename*(*)
real(psb_dpk_), allocatable, intent(out) :: b(:,:)
integer, intent(out) :: info
integer, optional :: inroot
integer, parameter :: infile = 2
integer :: nrow, ncol, i,root, np, me, ircode, j
if (present(inroot)) then
root = inroot
else
root = psb_root_
end if
info = 0
call psb_info(ictxt, me, np)
if (me == root) then
write(*, '("Reading rhs...")') ! open input file
call mm_vet_read(filename,b,info)
if (info /= 0) then
write(0,*) 'read_rhs: something went wrong.'
return
end if ! read right hand sides
write(*,*) 'end read_rhs'
end if
return
end subroutine dread_rhs
subroutine creadmat (filename, a, ictxt, inroot)
use psb_base_mod
use psb_mmio_mod
implicit none
integer :: ictxt
type(psb_cspmat_type) :: a
character(len=*) :: filename
integer, optional :: inroot
integer, parameter :: infile = 2
integer :: info, root, np, me
if (present(inroot)) then
root = inroot
else
root = psb_root_
end if
call psb_info(ictxt, me, np)
if (me == root) then
write(*, '("Reading matrix...")') ! open input file
call mm_mat_read(a,info,infile,filename)
if (info /= 0) then
write(0,*) 'Error return from MM_MAT_READ ',info
call psb_abort(ictxt) ! Unexpected End of File
endif
end if
return
end subroutine creadmat
subroutine cread_rhs (filename, b, info,ictxt, inroot)
use psb_base_mod
use psb_mmio_mod
implicit none
integer :: ictxt
character :: filename*(*)
complex(psb_spk_), allocatable, intent(out) :: b(:,:)
integer, intent(out) :: info
integer, optional :: inroot
integer, parameter :: infile = 2
integer :: nrow, ncol, i,root, np, me, ircode, j
if (present(inroot)) then
root = inroot
else
root = psb_root_
end if
info = 0
call psb_info(ictxt, me, np)
if (me == root) then
write(*, '("Reading rhs...")') ! open input file
call mm_vet_read(filename,b,info)
if (info /= 0) then
write(0,*) 'read_rhs: something went wrong.'
return
end if ! read right hand sides
write(*,*) 'end read_rhs'
end if
return
end subroutine cread_rhs
subroutine zreadmat (filename, a, ictxt, inroot)
use psb_base_mod
use psb_mmio_mod
implicit none
integer :: ictxt
type(psb_zspmat_type) :: a
character(len=*) :: filename
integer, optional :: inroot
integer, parameter :: infile = 2
integer :: info, root, np, me
if (present(inroot)) then
root = inroot
else
root = psb_root_
end if
call psb_info(ictxt, me, np)
if (me == root) then
write(*, '("Reading matrix...")') ! open input file
call mm_mat_read(a,info,infile,filename)
if (info /= 0) then
write(0,*) 'Error return from MM_MAT_READ ',info
call psb_abort(ictxt) ! Unexpected End of File
endif
end if
return
end subroutine zreadmat
subroutine zread_rhs (filename, b, info,ictxt, inroot)
use psb_base_mod
use psb_mmio_mod
implicit none
integer :: ictxt
character :: filename*(*)
complex(psb_dpk_), allocatable, intent(out) :: b(:,:)
integer, intent(out) :: info
integer, optional :: inroot
integer, parameter :: infile = 2
integer :: nrow, ncol, i,root, np, me, ircode, j
if (present(inroot)) then
root = inroot
else
root = psb_root_
end if
info = 0
call psb_info(ictxt, me, np)
if (me == root) then
write(*, '("Reading rhs...")') ! open input file
call mm_vet_read(filename,b,info)
if (info /= 0) then
write(0,*) 'read_rhs: something went wrong.'
return
end if ! read right hand sides
write(*,*) 'end read_rhs'
end if
return
end subroutine zread_rhs
end module psb_read_mat_mod

@ -36,7 +36,6 @@ module psb_util_mod
use psb_metispart_mod
use psb_hbio_mod
use psb_mmio_mod
use psb_read_mat_mod
use psb_mat_dist_mod
end module psb_util_mod

Loading…
Cancel
Save