Annotation of rpl/lapack/lapack/dla_wwaddw.f, revision 1.2

1.1       bertrand    1:       SUBROUTINE DLA_WWADDW( N, X, Y, W )
                      2: *
                      3: *     -- LAPACK routine (version 3.2.2)                                 --
                      4: *     -- Contributed by James Demmel, Deaglan Halligan, Yozo Hida and --
                      5: *     -- Jason Riedy of Univ. of California Berkeley.                 --
                      6: *     -- June 2010                                                    --
                      7: *
                      8: *     -- LAPACK is a software package provided by Univ. of Tennessee, --
                      9: *     -- Univ. of California Berkeley and NAG Ltd.                    --
                     10: *
                     11:       IMPLICIT NONE
                     12: *     ..
                     13: *     .. Scalar Arguments ..
                     14:       INTEGER            N
                     15: *     ..
                     16: *     .. Array Arguments ..
                     17:       DOUBLE PRECISION   X( * ), Y( * ), W( * )
                     18: *     ..
                     19: *
                     20: *     Purpose
                     21: *     =======
                     22: *
                     23: *     DLA_WWADDW adds a vector W into a doubled-single vector (X, Y).
                     24: *
                     25: *     This works for all extant IBM's hex and binary floating point
                     26: *     arithmetics, but not for decimal.
                     27: *
                     28: *     Arguments
                     29: *     =========
                     30: *
                     31: *     N      (input) INTEGER
                     32: *            The length of vectors X, Y, and W.
                     33: *
                     34: *     X      (input/output) DOUBLE PRECISION array, dimension (N)
                     35: *            The first part of the doubled-single accumulation vector.
                     36: *
                     37: *     Y      (input/output) DOUBLE PRECISION array, dimension (N)
                     38: *            The second part of the doubled-single accumulation vector.
                     39: *
                     40: *     W      (input) DOUBLE PRECISION array, dimension (N)
                     41: *            The vector to be added.
                     42: *
                     43: *  =====================================================================
                     44: *
                     45: *     .. Local Scalars ..
                     46:       DOUBLE PRECISION   S
                     47:       INTEGER            I
                     48: *     ..
                     49: *     .. Executable Statements ..
                     50: *
                     51:       DO 10 I = 1, N
                     52:         S = X(I) + W(I)
                     53:         S = (S + S) - S
                     54:         Y(I) = ((X(I) - S) + W(I)) + Y(I)
                     55:         X(I) = S
                     56:  10   CONTINUE
                     57:       RETURN
                     58:       END

CVSweb interface <joel.bertrand@systella.fr>