Changed psb_const_mod to include psb_const.fh, to have constants

defined in just one place.
psblas3-type-indexed
Salvatore Filippone 19 years ago
parent 81f09ff266
commit 2becae4636

@ -33,6 +33,7 @@ subroutine psi_sort_dl(dep_list,l_dep_list,np,info)
! interface between former sort_dep_list subroutine ! interface between former sort_dep_list subroutine
! and new srtlist ! and new srtlist
! !
use psb_const_mod
use psb_error_mod use psb_error_mod
implicit none implicit none

@ -15,6 +15,8 @@ LIBDIR = ../../lib
psb_realloc_mod.o : psb_error_mod.o psb_realloc_mod.o : psb_error_mod.o
psb_spmat_type.o : psb_realloc_mod.o psb_const_mod.o psb_spmat_type.o : psb_realloc_mod.o psb_const_mod.o
psb_error_mod.o: psb_const_mod.o
psb_const_mod.f90: psb_const.fh
lib: $(MODULES) $(OBJS) lib: $(MODULES) $(OBJS)
$(AR) $(LIBDIR)/$(LIBNAME) $(MODULES) $(OBJS) $(AR) $(LIBDIR)/$(LIBNAME) $(MODULES) $(OBJS)

@ -1,33 +1,33 @@
C !
C Parallel Sparse BLAS v2.0 ! Parallel Sparse BLAS v2.0
C (C) Copyright 2006 Salvatore Filippone University of Rome Tor Vergata ! (C) Copyright 2006 Salvatore Filippone University of Rome Tor Vergata
C Alfredo Buttari University of Rome Tor Vergata ! Alfredo Buttari University of Rome Tor Vergata
C !
C Redistribution and use in source and binary forms, with or without ! Redistribution and use in source and binary forms, with or without
C modification, are permitted provided that the following conditions ! modification, are permitted provided that the following conditions
C are met: ! are met:
C 1. Redistributions of source code must retain the above copyright ! 1. Redistributions of source code must retain the above copyright
C notice, this list of conditions and the following disclaimer. ! notice, this list of conditions and the following disclaimer.
C 2. Redistributions in binary form must reproduce the above copyright ! 2. Redistributions in binary form must reproduce the above copyright
C notice, this list of conditions, and the following disclaimer in the ! notice, this list of conditions, and the following disclaimer in the
C documentation and/or other materials provided with the distribution. ! documentation and/or other materials provided with the distribution.
C 3. The name of the PSBLAS group or the names of its contributors may ! 3. The name of the PSBLAS group or the names of its contributors may
C not be used to endorse or promote products derived from this ! not be used to endorse or promote products derived from this
C software without specific written permission. ! software without specific written permission.
C !
C THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS ! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
C ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED ! ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED
C TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR ! TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR
C PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE PSBLAS GROUP OR ITS CONTRIBUTORS ! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE PSBLAS GROUP OR ITS CONTRIBUTORS
C BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR ! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR
C CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF ! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF
C SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS ! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS
C INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN ! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN
C CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ! CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE)
C ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE ! ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
C POSSIBILITY OF SUCH DAMAGE. ! POSSIBILITY OF SUCH DAMAGE.
C !
C !
integer, parameter :: psb_nohalo_=0, psb_halo_=4 integer, parameter :: psb_nohalo_=0, psb_halo_=4
integer, parameter :: psb_none_=0, psb_sum_=1 integer, parameter :: psb_none_=0, psb_sum_=1
integer, parameter :: psb_avg_=2, psb_square_root_=3 integer, parameter :: psb_avg_=2, psb_square_root_=3
@ -58,12 +58,12 @@ C
integer, parameter :: psb_elem_send_=3, psb_n_ovrlp_elem_=1 integer, parameter :: psb_elem_send_=3, psb_n_ovrlp_elem_=1
integer, parameter :: psb_ovrlp_elem_to_=2, psb_ovrlp_elem_=0 integer, parameter :: psb_ovrlp_elem_to_=2, psb_ovrlp_elem_=0
integer, parameter :: psb_n_dom_ovr_=1 integer, parameter :: psb_n_dom_ovr_=1
integer, parameter :: psb_nnz_=1
integer, parameter :: psb_no_comm_=-1 integer, parameter :: psb_no_comm_=-1
integer, parameter :: ione=1, izero=0 integer, parameter :: ione=1, izero=0
integer, parameter :: itwo=2, ithree=3,mone=-1, psb_root_=0 integer, parameter :: itwo=2, ithree=3,mone=-1, psb_root_=0
integer, parameter :: psb_nztotreq_=1, psb_nzrowreq_=2 integer, parameter :: psb_nztotreq_=1, psb_nzrowreq_=2
integer, parameter :: psb_nzsizereq_=3 integer, parameter :: psb_nzsizereq_=3
integer, parameter :: psb_nnz_=1
integer, parameter :: psb_del_bnd_=6, psb_srtd_=7 integer, parameter :: psb_del_bnd_=6, psb_srtd_=7
integer, parameter :: psb_state_=8, psb_upd_=9 integer, parameter :: psb_state_=8, psb_upd_=9
integer, parameter :: psb_upd_pnt_=10, psb_ifasize_=10 integer, parameter :: psb_upd_pnt_=10, psb_ifasize_=10
@ -82,6 +82,7 @@ C
real(kind(1.d0)), parameter :: dzero=0.d0, done=1.d0 real(kind(1.d0)), parameter :: dzero=0.d0, done=1.d0
complex(kind(1.d0)), parameter :: zzero=(0.d0,0.0d0) complex(kind(1.d0)), parameter :: zzero=(0.d0,0.0d0)
complex(kind(1.d0)), parameter :: zone=(1.d0,0.0d0) complex(kind(1.d0)), parameter :: zone=(1.d0,0.0d0)
real(kind(1.d0)), parameter :: epstol=1.d-32
character, parameter :: psb_all_='A', psb_topdef_=' ' character, parameter :: psb_all_='A', psb_topdef_=' '
character(len=5) :: psb_fidef_='CSR' character(len=5) :: psb_fidef_='CSR'

@ -31,54 +31,6 @@
module psb_const_mod module psb_const_mod
integer, parameter :: psb_nohalo_=0, psb_halo_=4 include 'psb_const.fh'
integer, parameter :: psb_none_=0, psb_sum_=1
integer, parameter :: psb_avg_=2, psb_square_root_=3
integer, parameter :: psb_swap_send_=1, psb_swap_recv_=2
integer, parameter :: psb_swap_sync_=4, psb_swap_mpi_=8
integer, parameter :: psb_deadlock_check_=0, psb_local_mtrx_check_=1
integer, parameter :: psb_local_comm_check_=2, psb_consistency_check_=3
integer, parameter :: psb_global_check_=4, psb_order_communication_=5
integer, parameter :: psb_change_represent_=6, psb_loc_to_glob_check_=7
integer, parameter :: psb_convert_halo_=1, psb_convert_ovrlap_=2
integer, parameter :: psb_act_ret_=0, psb_act_abort_=1, no_err_=0
integer, parameter :: psb_dec_type_=1, psb_m_=2,psb_n_=3
integer, parameter :: psb_n_row_=4, psb_n_col_=5,psb_ctxt_=6
integer, parameter :: psb_loc_to_glob_=7, psb_mpi_c_=9,psb_mdata_size_=10
integer, parameter :: psb_desc_asb_=3099, psb_desc_bld_=psb_desc_asb_+1
integer, parameter :: psb_desc_repl_=3199
integer, parameter :: psb_desc_upd_=psb_desc_bld_+1, psb_desc_upd_asb_=psb_desc_upd_+1
integer, parameter :: psb_upd_glb_=998, psb_upd_loc_=997
integer, parameter :: psb_proc_id_=0, psb_n_elem_recv_=1
integer, parameter :: psb_elem_recv_=2, psb_n_elem_send_=2
integer, parameter :: psb_elem_send_=3, psb_n_ovrlp_elem_=1
integer, parameter :: psb_ovrlp_elem_to_=2, psb_ovrlp_elem_=0, psb_n_dom_ovr_=1
integer, parameter :: psb_nnz_=1
integer, parameter :: psb_no_comm_=-1
integer, parameter :: ione=1,izero=0,mone=-1
integer, parameter :: itwo=2, ithree=3, psb_root_=0
integer, parameter :: psb_nztotreq_=1, psb_nzrowreq_=2, psb_nzsizereq_=3
integer, parameter :: psb_del_bnd_=6, psb_srtd_=7
integer, parameter :: psb_state_=8, psb_upd_=9
integer, parameter :: psb_upd_pnt_=10, psb_ifasize_=10
integer, parameter :: psb_spmat_null_=0, psb_spmat_bld_=1
integer, parameter :: psb_spmat_asb_=2, psb_spmat_upd_=4
integer, parameter :: psb_ireg_flgs_=10, psb_ip2_=0
integer, parameter :: psb_iflag_=2, psb_ichk_=3
integer, parameter :: psb_nnzt_=4, psb_zero_=5,psb_ipc_=6
integer, parameter :: psb_perm_update_=98765, psb_isrtdcoo_=98764
integer, parameter :: psb_maxjdrows_=8, psb_minjdrows_=4
integer, parameter :: psb_dbleint_=2
integer, parameter :: psb_comm_halo_=0, psb_comm_ovr_=1
real(kind(1.d0)), parameter :: psb_colrow_=0.33, psb_percent_=0.7
real(kind(1.d0)), parameter :: dzero=0.d0, done=1.d0
complex(kind(1.d0)), parameter :: zzero=(0.d0,0.0d0), zone=(1.d0,0.0d0)
real(kind(1.d0)), parameter :: epstol=1.d-32
character, parameter :: psb_all_='A', psb_topdef_=' '
character(len=5) :: psb_fidef_='CSR'
end module psb_const_mod end module psb_const_mod

@ -30,17 +30,18 @@
!!$ !!$
module psb_error_mod module psb_error_mod
use psb_const_mod
public psb_errpush, psb_error, psb_get_errstatus,& public psb_errpush, psb_error, psb_get_errstatus,&
& psb_get_errverbosity, psb_set_errverbosity,psb_errcomm, & & psb_get_errverbosity, psb_set_errverbosity,psb_errcomm, &
& psb_erractionsave, psb_erractionrestore, act_ret, act_abort, & & psb_erractionsave, psb_erractionrestore, &
& no_err, psb_get_erraction, psb_set_erraction & psb_get_erraction, psb_set_erraction
interface psb_error interface psb_error
module procedure psb_serror module procedure psb_serror
module procedure psb_perror module procedure psb_perror
end interface end interface
integer, parameter :: act_ret=0, act_abort=1, no_err=0 !!$ integer, parameter :: act_ret=0, act_abort=1, no_err=0
private private

@ -29,8 +29,9 @@
!!$ !!$
!!$ !!$
module psb_realloc_mod module psb_realloc_mod
use psb_const_mod
implicit none implicit none
Interface psb_realloc Interface psb_realloc
module procedure psb_dreallocate1i module procedure psb_dreallocate1i
module procedure psb_dreallocate2i module procedure psb_dreallocate2i

@ -44,6 +44,7 @@ subroutine psb_dilu_fct(a,l,u,d,info,blck)
use psb_serial_mod use psb_serial_mod
use psb_tools_mod use psb_tools_mod
use psb_error_mod use psb_error_mod
use psb_const_mod
implicit none implicit none
! .. Scalar Arguments .. ! .. Scalar Arguments ..
integer, intent(out) :: info integer, intent(out) :: info

@ -56,7 +56,6 @@ C .. Local scalars ..
INTEGER J, NNZ, IP1, NNZI INTEGER J, NNZ, IP1, NNZI
C .. Local arrays .. C .. Local arrays ..
IERROR = 0 IERROR = 0
c$$$ write(0,*) 'dcocrupd ',infoa(upd_),ibits(infoa(upd_),2,1)
IF (IBITS(INFOA(PSB_UPD_),2,1).EQ.1) THEN IF (IBITS(INFOA(PSB_UPD_),2,1).EQ.1) THEN
C C
C Smart update capability C Smart update capability

@ -57,7 +57,6 @@ C .. Local scalars ..
+ NRC, IPH, JPH, JPA, LPA, IRET, LNK, NNZ, IP1 + NRC, IPH, JPH, JPA, LPA, IRET, LNK, NNZ, IP1
C .. Local arrays .. C .. Local arrays ..
IERROR = 0 IERROR = 0
c$$$ write(0,*) 'dcrcrupd ',infoa(upd_),ibits(infoa(upd_),2,1)
IF (IBITS(INFOA(PSB_UPD_),2,1).EQ.1) THEN IF (IBITS(INFOA(PSB_UPD_),2,1).EQ.1) THEN
C C
C Smart update capability C Smart update capability

@ -108,7 +108,7 @@ subroutine psb_dcoins(nz,ia,ja,val,a,gtl,imin,imax,jmin,jmax,info)
endif endif
if ((nza+nz)>isza) then if ((nza+nz)>isza) then
call psb_sp_reall(a,nza+nz,info) call psb_sp_reall(a,max(nza+nz,int(1.5*isza)),info)
if(info.ne.izero) then if(info.ne.izero) then
info=4010 info=4010
ch_err='psb_sp_reall' ch_err='psb_sp_reall'

Loading…
Cancel
Save