Merged minor typos from Daniela.

stopcriterion
Salvatore Filippone 17 years ago
parent b69cc135a9
commit acd870aa6e

@ -7,7 +7,7 @@
!!$ (C) Copyright 2007 Alfredo Buttari University of Rome Tor Vergata
!!$ Pasqua D'Ambra ICAR-CNR, Naples
!!$ Daniela di Serafino Second University of Naples
!!$ Salvatore Filippone University of Rome Tor Vergata
!!$ Salvatore Filippone University of Rome Tor Vergata
!!$
!!$ Redistribution and use in source and binary forms, with or without
!!$ modification, are permitted provided that the following conditions

@ -7,7 +7,7 @@
!!$ (C) Copyright 2007 Alfredo Buttari University of Rome Tor Vergata
!!$ Pasqua D'Ambra ICAR-CNR, Naples
!!$ Daniela di Serafino Second University of Naples
!!$ Salvatore Filippone University of Rome Tor Vergata
!!$ Salvatore Filippone University of Rome Tor Vergata
!!$
!!$ Redistribution and use in source and binary forms, with or without
!!$ modification, are permitted provided that the following conditions

@ -7,7 +7,7 @@
!!$ (C) Copyright 2007 Alfredo Buttari University of Rome Tor Vergata
!!$ Pasqua D'Ambra ICAR-CNR, Naples
!!$ Daniela di Serafino Second University of Naples
!!$ Salvatore Filippone University of Rome Tor Vergata
!!$ Salvatore Filippone University of Rome Tor Vergata
!!$
!!$ Redistribution and use in source and binary forms, with or without
!!$ modification, are permitted provided that the following conditions
@ -115,7 +115,7 @@ subroutine mld_das_aply(alpha,prec,x,beta,y,desc_data,trans,work,info)
if (prec%iprcparm(mld_n_ovr_)==0) then
!
! shortcut: this fixes performance for RAS(0) == BJA
! Shortcut: this fixes performance for RAS(0) == BJA
!
call mld_bjac_aply(alpha,prec,x,beta,y,desc_data,trans_,work,info)
if(info /= 0) then
@ -125,6 +125,9 @@ subroutine mld_das_aply(alpha,prec,x,beta,y,desc_data,trans,work,info)
end if
else
!
! Overlap > 0
!
n_row = psb_cd_get_local_rows(prec%desc_data)
n_col = psb_cd_get_local_cols(prec%desc_data)
@ -248,7 +251,6 @@ subroutine mld_das_aply(alpha,prec,x,beta,y,desc_data,trans,work,info)
end select
case('T','C')
!
! With transpose, we have to do it here
!
@ -261,7 +263,7 @@ subroutine mld_das_aply(alpha,prec,x,beta,y,desc_data,trans,work,info)
case(psb_sum_)
!
! Transpose of sum is halo
! The transpose of sum is halo
!
call psb_halo(tx,prec%desc_data,info,work=aux,data=psb_comm_ext_)
if(info /=0) then
@ -295,7 +297,6 @@ subroutine mld_das_aply(alpha,prec,x,beta,y,desc_data,trans,work,info)
goto 9999
end select
!
! If required, reorder tx according to the row/column permutation of the
! local extended matrix, stored into the permutation vector prec%perm

@ -7,7 +7,7 @@
!!$ (C) Copyright 2007 Alfredo Buttari University of Rome Tor Vergata
!!$ Pasqua D'Ambra ICAR-CNR, Naples
!!$ Daniela di Serafino Second University of Naples
!!$ Salvatore Filippone University of Rome Tor Vergata
!!$ Salvatore Filippone University of Rome Tor Vergata
!!$
!!$ Redistribution and use in source and binary forms, with or without
!!$ modification, are permitted provided that the following conditions

@ -7,7 +7,7 @@
!!$ (C) Copyright 2007 Alfredo Buttari University of Rome Tor Vergata
!!$ Pasqua D'Ambra ICAR-CNR, Naples
!!$ Daniela di Serafino Second University of Naples
!!$ Salvatore Filippone University of Rome Tor Vergata
!!$ Salvatore Filippone University of Rome Tor Vergata
!!$
!!$ Redistribution and use in source and binary forms, with or without
!!$ modification, are permitted provided that the following conditions
@ -150,6 +150,7 @@ subroutine mld_dbaseprc_bld(a,desc_a,p,info,upd)
end if
case(mld_bjac_)
! Block Jacobi preconditioner/smoother
call mld_check_def(p%iprcparm(mld_sub_ren_),'renumbering',&
& mld_renum_none_,is_legal_renum)
@ -164,7 +165,7 @@ subroutine mld_dbaseprc_bld(a,desc_a,p,info,upd)
goto 9999
end if
! Build the local part of the base preconditioner
! Build the local part of the base preconditioner/smoother
call mld_bjac_bld(a,p,iupd,info)
if(info /= 0) then
info=4010
@ -174,7 +175,7 @@ subroutine mld_dbaseprc_bld(a,desc_a,p,info,upd)
case(mld_as_)
! Block Jacobi and additive Schwarz preconditioners/smoothers
! Additive Schwarz preconditioners/smoothers
call mld_check_def(p%iprcparm(mld_n_ovr_),'overlap',&
& 0,is_legal_n_ovr)
@ -197,7 +198,7 @@ subroutine mld_dbaseprc_bld(a,desc_a,p,info,upd)
& write(debug_unit,*) me,' ',trim(name),&
& ': Calling mld_bjac_bld'
! Build the local part of the base preconditioner
! Build the local part of the base preconditioner/smoother
call mld_as_bld(a,desc_a,p,iupd,info)
if(info /= 0) then
info=4010

@ -7,7 +7,7 @@
!!$ (C) Copyright 2007 Alfredo Buttari University of Rome Tor Vergata
!!$ Pasqua D'Ambra ICAR-CNR, Naples
!!$ Daniela di Serafino Second University of Naples
!!$ Salvatore Filippone University of Rome Tor Vergata
!!$ Salvatore Filippone University of Rome Tor Vergata
!!$
!!$ Redistribution and use in source and binary forms, with or without
!!$ modification, are permitted provided that the following conditions
@ -143,7 +143,7 @@ subroutine mld_dbjac_aply(alpha,prec,x,beta,y,desc_data,trans,work,info)
real(kind(0.d0)),intent(in) :: x(:)
real(kind(0.d0)),intent(inout) :: y(:)
real(kind(0.d0)),intent(in) :: alpha,beta
character(len=1), intent(in) :: trans
character(len=1),intent(in) :: trans
real(kind(0.d0)),target, intent(inout) :: work(:)
integer, intent(out) :: info

@ -39,8 +39,8 @@
! Subroutine: mld_dbjac_bld
! Version: real
!
! This routine computes an LU or incomplete LU factorization
! of the input matrix, according to the value of p%iprcparm(iprcparm(sub_solve_),
! This routine computes an LU or incomplete LU factorization of the input
! matrix, according to the value of p%iprcparm(iprcparm(sub_solve_),
! set by the user through mld_dprecinit or mld_dprecset.
! It may also split the local matrix into its block-diagonal and
! off block-diagonal parts, for the future application of multiple
@ -51,6 +51,7 @@
! or a block-Jacobi or LU or ILU solver at the coarsest level of a multilevel
! preconditioner. For the Additive Schwarz, it is called from mld_as_bld,
! which prepares the overlap descriptor and retrieves the remote rows into blck.
!
! More precisely, the routine performs one of the following tasks:
!
! 1. construction of a block-Jacobi preconditioner associated
@ -87,14 +88,13 @@
! p - type(mld_dbaseprec_type), input/output.
! The 'base preconditioner' data structure containing the local
! part of the preconditioner or solver at the current level.
!
! info - integer, output.
! Error code.
! blck - type(psb_dspmat_type), input, optional.
! The sparse matrix structure containing the remote rows of the
! matrix to be factorized, that have been retrieved by mld_as_bld
! to build an Additive Schwarz base preconditioner with overlap
! greater than 0. If the overlap is 0 blck is empty.
! greater than 0. If the overlap is 0 blck is empty.
!
subroutine mld_dbjac_bld(a,p,upd,info,blck)
@ -110,7 +110,7 @@ subroutine mld_dbjac_bld(a,p,upd,info,blck)
character, intent(in) :: upd
type(psb_dspmat_type), intent(in), target, optional :: blck
! Local Variables
! Local Variables
integer :: i, k, m
integer :: int_err(5)
character :: trans, unitd

@ -7,7 +7,7 @@
!!$ (C) Copyright 2007 Alfredo Buttari University of Rome Tor Vergata
!!$ Pasqua D'Ambra ICAR-CNR, Naples
!!$ Daniela di Serafino Second University of Naples
!!$ Salvatore Filippone University of Rome Tor Vergata
!!$ Salvatore Filippone University of Rome Tor Vergata
!!$
!!$ Redistribution and use in source and binary forms, with or without
!!$ modification, are permitted provided that the following conditions

@ -7,7 +7,7 @@
!!$ (C) Copyright 2007 Alfredo Buttari University of Rome Tor Vergata
!!$ Pasqua D'Ambra ICAR-CNR, Naples
!!$ Daniela di Serafino Second University of Naples
!!$ Salvatore Filippone University of Rome Tor Vergata
!!$ Salvatore Filippone University of Rome Tor Vergata
!!$
!!$ Redistribution and use in source and binary forms, with or without
!!$ modification, are permitted provided that the following conditions

@ -7,7 +7,7 @@
!!$ (C) Copyright 2007 Alfredo Buttari University of Rome Tor Vergata
!!$ Pasqua D'Ambra ICAR-CNR, Naples
!!$ Daniela di Serafino Second University of Naples
!!$ Salvatore Filippone University of Rome Tor Vergata
!!$ Salvatore Filippone University of Rome Tor Vergata
!!$
!!$ Redistribution and use in source and binary forms, with or without
!!$ modification, are permitted provided that the following conditions
@ -223,8 +223,9 @@ contains
! Arguments:
! ialg - integer, input.
! The type of incomplete factorization to be performed.
! The MILU(0) factorization is computed if ialg = 2 (= mld_milu_n_);
! the ILU(0) factorization otherwise.
! The ILU(0) factorization is computed if ialg = 1 (= mld_ilu_n_),
! the MILU(0) one if ialg = 2 (= mld_milu_n_); other values
! are not allowed.
! m - integer, output.
! The total number of rows of the local matrix to be factorized,
! i.e. ma+mb.

@ -7,7 +7,7 @@
!!$ (C) Copyright 2007 Alfredo Buttari University of Rome Tor Vergata
!!$ Pasqua D'Ambra ICAR-CNR, Naples
!!$ Daniela di Serafino Second University of Naples
!!$ Salvatore Filippone University of Rome Tor Vergata
!!$ Salvatore Filippone University of Rome Tor Vergata
!!$
!!$ Redistribution and use in source and binary forms, with or without
!!$ modification, are permitted provided that the following conditions
@ -62,8 +62,9 @@
! The fill-in level k in ILU(k)/MILU(k).
! ialg - integer, input.
! The type of incomplete factorization to be performed.
! The MILU(k) factorization is computed if ialg = 2 (= mld_milu_n_);
! the ILU(k) factorization otherwise.
! The ILU(k) factorization is computed if ialg = 1 (= mld_ilu_n_);
! the MILU(k) one if ialg = 2 (= mld_milu_n_); other values are
! not allowed.
! a - type(psb_dspmat_type), input.
! The sparse matrix structure containing the local matrix to be
! factorized. Note that if the 'base' Additive Schwarz preconditioner

@ -7,7 +7,7 @@
!!$ (C) Copyright 2007 Alfredo Buttari University of Rome Tor Vergata
!!$ Pasqua D'Ambra ICAR-CNR, Naples
!!$ Daniela di Serafino Second University of Naples
!!$ Salvatore Filippone University of Rome Tor Vergata
!!$ Salvatore Filippone University of Rome Tor Vergata
!!$
!!$ Redistribution and use in source and binary forms, with or without
!!$ modification, are permitted provided that the following conditions

@ -7,7 +7,7 @@
!!$ (C) Copyright 2007 Alfredo Buttari University of Rome Tor Vergata
!!$ Pasqua D'Ambra ICAR-CNR, Naples
!!$ Daniela di Serafino Second University of Naples
!!$ Salvatore Filippone University of Rome Tor Vergata
!!$ Salvatore Filippone University of Rome Tor Vergata
!!$
!!$ Redistribution and use in source and binary forms, with or without
!!$ modification, are permitted provided that the following conditions

@ -7,7 +7,7 @@
!!$ (C) Copyright 2007 Alfredo Buttari University of Rome Tor Vergata
!!$ Pasqua D'Ambra ICAR-CNR, Naples
!!$ Daniela di Serafino Second University of Naples
!!$ Salvatore Filippone University of Rome Tor Vergata
!!$ Salvatore Filippone University of Rome Tor Vergata
!!$
!!$ Redistribution and use in source and binary forms, with or without
!!$ modification, are permitted provided that the following conditions

@ -7,7 +7,7 @@
!!$ (C) Copyright 2007 Alfredo Buttari University of Rome Tor Vergata
!!$ Pasqua D'Ambra ICAR-CNR, Naples
!!$ Daniela di Serafino Second University of Naples
!!$ Salvatore Filippone University of Rome Tor Vergata
!!$ Salvatore Filippone University of Rome Tor Vergata
!!$
!!$ Redistribution and use in source and binary forms, with or without
!!$ modification, are permitted provided that the following conditions

@ -7,7 +7,7 @@
!!$ (C) Copyright 2007 Alfredo Buttari University of Rome Tor Vergata
!!$ Pasqua D'Ambra ICAR-CNR, Naples
!!$ Daniela di Serafino Second University of Naples
!!$ Salvatore Filippone University of Rome Tor Vergata
!!$ Salvatore Filippone University of Rome Tor Vergata
!!$
!!$ Redistribution and use in source and binary forms, with or without
!!$ modification, are permitted provided that the following conditions

@ -7,7 +7,7 @@
!!$ (C) Copyright 2007 Alfredo Buttari University of Rome Tor Vergata
!!$ Pasqua D'Ambra ICAR-CNR, Naples
!!$ Daniela di Serafino Second University of Naples
!!$ Salvatore Filippone University of Rome Tor Vergata
!!$ Salvatore Filippone University of Rome Tor Vergata
!!$
!!$ Redistribution and use in source and binary forms, with or without
!!$ modification, are permitted provided that the following conditions

@ -7,7 +7,7 @@
!!$ (C) Copyright 2007 Alfredo Buttari University of Rome Tor Vergata
!!$ Pasqua D'Ambra ICAR-CNR, Naples
!!$ Daniela di Serafino Second University of Naples
!!$ Salvatore Filippone University of Rome Tor Vergata
!!$ Salvatore Filippone University of Rome Tor Vergata
!!$
!!$ Redistribution and use in source and binary forms, with or without
!!$ modification, are permitted provided that the following conditions

@ -7,7 +7,7 @@
!!$ (C) Copyright 2007 Alfredo Buttari University of Rome Tor Vergata
!!$ Pasqua D'Ambra ICAR-CNR, Naples
!!$ Daniela di Serafino Second University of Naples
!!$ Salvatore Filippone University of Rome Tor Vergata
!!$ Salvatore Filippone University of Rome Tor Vergata
!!$
!!$ Redistribution and use in source and binary forms, with or without
!!$ modification, are permitted provided that the following conditions

@ -7,7 +7,7 @@
!!$ (C) Copyright 2007 Alfredo Buttari University of Rome Tor Vergata
!!$ Pasqua D'Ambra ICAR-CNR, Naples
!!$ Daniela di Serafino Second University of Naples
!!$ Salvatore Filippone University of Rome Tor Vergata
!!$ Salvatore Filippone University of Rome Tor Vergata
!!$
!!$ Redistribution and use in source and binary forms, with or without
!!$ modification, are permitted provided that the following conditions

@ -7,7 +7,7 @@
!!$ (C) Copyright 2007 Alfredo Buttari University of Rome Tor Vergata
!!$ Pasqua D'Ambra ICAR-CNR, Naples
!!$ Daniela di Serafino Second University of Naples
!!$ Salvatore Filippone University of Rome Tor Vergata
!!$ Salvatore Filippone University of Rome Tor Vergata
!!$
!!$ Redistribution and use in source and binary forms, with or without
!!$ modification, are permitted provided that the following conditions

@ -7,7 +7,7 @@
!!$ (C) Copyright 2007 Alfredo Buttari University of Rome Tor Vergata
!!$ Pasqua D'Ambra ICAR-CNR, Naples
!!$ Daniela di Serafino Second University of Naples
!!$ Salvatore Filippone University of Rome Tor Vergata
!!$ Salvatore Filippone University of Rome Tor Vergata
!!$
!!$ Redistribution and use in source and binary forms, with or without
!!$ modification, are permitted provided that the following conditions

@ -7,7 +7,7 @@
!!$ (C) Copyright 2007 Alfredo Buttari University of Rome Tor Vergata
!!$ Pasqua D'Ambra ICAR-CNR, Naples
!!$ Daniela di Serafino Second University of Naples
!!$ Salvatore Filippone University of Rome Tor Vergata
!!$ Salvatore Filippone University of Rome Tor Vergata
!!$
!!$ Redistribution and use in source and binary forms, with or without
!!$ modification, are permitted provided that the following conditions

@ -7,7 +7,7 @@
!!$ (C) Copyright 2007 Alfredo Buttari University of Rome Tor Vergata
!!$ Pasqua D'Ambra ICAR-CNR, Naples
!!$ Daniela di Serafino Second University of Naples
!!$ Salvatore Filippone University of Rome Tor Vergata
!!$ Salvatore Filippone University of Rome Tor Vergata
!!$
!!$ Redistribution and use in source and binary forms, with or without
!!$ modification, are permitted provided that the following conditions

@ -7,7 +7,7 @@
!!$ (C) Copyright 2007 Alfredo Buttari University of Rome Tor Vergata
!!$ Pasqua D'Ambra ICAR-CNR, Naples
!!$ Daniela di Serafino Second University of Naples
!!$ Salvatore Filippone University of Rome Tor Vergata
!!$ Salvatore Filippone University of Rome Tor Vergata
!!$
!!$ Redistribution and use in source and binary forms, with or without
!!$ modification, are permitted provided that the following conditions

@ -7,7 +7,7 @@
!!$ (C) Copyright 2007 Alfredo Buttari University of Rome Tor Vergata
!!$ Pasqua D'Ambra ICAR-CNR, Naples
!!$ Daniela di Serafino Second University of Naples
!!$ Salvatore Filippone University of Rome Tor Vergata
!!$ Salvatore Filippone University of Rome Tor Vergata
!!$
!!$ Redistribution and use in source and binary forms, with or without
!!$ modification, are permitted provided that the following conditions

@ -7,7 +7,7 @@
!!$ (C) Copyright 2007 Alfredo Buttari University of Rome Tor Vergata
!!$ Pasqua D'Ambra ICAR-CNR, Naples
!!$ Daniela di Serafino Second University of Naples
!!$ Salvatore Filippone University of Rome Tor Vergata
!!$ Salvatore Filippone University of Rome Tor Vergata
!!$
!!$ Redistribution and use in source and binary forms, with or without
!!$ modification, are permitted provided that the following conditions

@ -7,7 +7,7 @@
!!$ (C) Copyright 2007 Alfredo Buttari University of Rome Tor Vergata
!!$ Pasqua D'Ambra ICAR-CNR, Naples
!!$ Daniela di Serafino Second University of Naples
!!$ Salvatore Filippone University of Rome Tor Vergata
!!$ Salvatore Filippone University of Rome Tor Vergata
!!$
!!$ Redistribution and use in source and binary forms, with or without
!!$ modification, are permitted provided that the following conditions

@ -7,7 +7,7 @@
!!$ (C) Copyright 2007 Alfredo Buttari University of Rome Tor Vergata
!!$ Pasqua D'Ambra ICAR-CNR, Naples
!!$ Daniela di Serafino Second University of Naples
!!$ Salvatore Filippone University of Rome Tor Vergata
!!$ Salvatore Filippone University of Rome Tor Vergata
!!$
!!$ Redistribution and use in source and binary forms, with or without
!!$ modification, are permitted provided that the following conditions

@ -7,7 +7,7 @@
!!$ (C) Copyright 2007 Alfredo Buttari University of Rome Tor Vergata
!!$ Pasqua D'Ambra ICAR-CNR, Naples
!!$ Daniela di Serafino Second University of Naples
!!$ Salvatore Filippone University of Rome Tor Vergata
!!$ Salvatore Filippone University of Rome Tor Vergata
!!$
!!$ Redistribution and use in source and binary forms, with or without
!!$ modification, are permitted provided that the following conditions

@ -7,7 +7,7 @@
!!$ (C) Copyright 2007 Alfredo Buttari University of Rome Tor Vergata
!!$ Pasqua D'Ambra ICAR-CNR, Naples
!!$ Daniela di Serafino Second University of Naples
!!$ Salvatore Filippone University of Rome Tor Vergata
!!$ Salvatore Filippone University of Rome Tor Vergata
!!$
!!$ Redistribution and use in source and binary forms, with or without
!!$ modification, are permitted provided that the following conditions

@ -7,7 +7,7 @@
!!$ (C) Copyright 2007 Alfredo Buttari University of Rome Tor Vergata
!!$ Pasqua D'Ambra ICAR-CNR, Naples
!!$ Daniela di Serafino Second University of Naples
!!$ Salvatore Filippone University of Rome Tor Vergata
!!$ Salvatore Filippone University of Rome Tor Vergata
!!$
!!$ Redistribution and use in source and binary forms, with or without
!!$ modification, are permitted provided that the following conditions

@ -7,7 +7,7 @@
!!$ (C) Copyright 2007 Alfredo Buttari University of Rome Tor Vergata
!!$ Pasqua D'Ambra ICAR-CNR, Naples
!!$ Daniela di Serafino Second University of Naples
!!$ Salvatore Filippone University of Rome Tor Vergata
!!$ Salvatore Filippone University of Rome Tor Vergata
!!$
!!$ Redistribution and use in source and binary forms, with or without
!!$ modification, are permitted provided that the following conditions

@ -7,7 +7,7 @@
!!$ (C) Copyright 2007 Alfredo Buttari University of Rome Tor Vergata
!!$ Pasqua D'Ambra ICAR-CNR, Naples
!!$ Daniela di Serafino Second University of Naples
!!$ Salvatore Filippone University of Rome Tor Vergata
!!$ Salvatore Filippone University of Rome Tor Vergata
!!$
!!$ Redistribution and use in source and binary forms, with or without
!!$ modification, are permitted provided that the following conditions

@ -7,7 +7,7 @@
!!$ (C) Copyright 2007 Alfredo Buttari University of Rome Tor Vergata
!!$ Pasqua D'Ambra ICAR-CNR, Naples
!!$ Daniela di Serafino Second University of Naples
!!$ Salvatore Filippone University of Rome Tor Vergata
!!$ Salvatore Filippone University of Rome Tor Vergata
!!$
!!$ Redistribution and use in source and binary forms, with or without
!!$ modification, are permitted provided that the following conditions

@ -7,7 +7,7 @@
!!$ (C) Copyright 2007 Alfredo Buttari University of Rome Tor Vergata
!!$ Pasqua D'Ambra ICAR-CNR, Naples
!!$ Daniela di Serafino Second University of Naples
!!$ Salvatore Filippone University of Rome Tor Vergata
!!$ Salvatore Filippone University of Rome Tor Vergata
!!$
!!$ Redistribution and use in source and binary forms, with or without
!!$ modification, are permitted provided that the following conditions

@ -7,7 +7,7 @@
!!$ (C) Copyright 2007 Alfredo Buttari University of Rome Tor Vergata
!!$ Pasqua D'Ambra ICAR-CNR, Naples
!!$ Daniela di Serafino Second University of Naples
!!$ Salvatore Filippone University of Rome Tor Vergata
!!$ Salvatore Filippone University of Rome Tor Vergata
!!$
!!$ Redistribution and use in source and binary forms, with or without
!!$ modification, are permitted provided that the following conditions

@ -7,7 +7,7 @@
!!$ (C) Copyright 2007 Alfredo Buttari University of Rome Tor Vergata
!!$ Pasqua D'Ambra ICAR-CNR, Naples
!!$ Daniela di Serafino Second University of Naples
!!$ Salvatore Filippone University of Rome Tor Vergata
!!$ Salvatore Filippone University of Rome Tor Vergata
!!$
!!$ Redistribution and use in source and binary forms, with or without
!!$ modification, are permitted provided that the following conditions

@ -5,7 +5,7 @@
# NUmber of attempts for each configuration
ntry=1
export GFORTRAN_UNBUFFERED_ALL=y
date=`date +%Y%m%d%H%M%S`

Loading…
Cancel
Save