File: sset.f

package info (click to toggle)
scalapack 1.7.4-2
  • links: PTS
  • area: main
  • in suites: etch, etch-m68k
  • size: 34,004 kB
  • ctags: 30,444
  • sloc: fortran: 310,201; ansic: 64,027; makefile: 1,838; sh: 4
file content (123 lines) | stat: -rw-r--r-- 2,677 bytes parent folder | download | duplicates (12)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
      SUBROUTINE SSET( N, ALPHA, X, INCX )
*
*  -- PBLAS auxiliary routine (version 2.0) --
*     University of Tennessee, Knoxville, Oak Ridge National Laboratory,
*     and University of California, Berkeley.
*     April 1, 1998
*
*     .. Scalar Arguments ..
      INTEGER            INCX, N
      REAL               ALPHA
*     ..
*     .. Array Arguments ..
      REAL               X( * )
*     ..
*
*  Purpose
*  =======
*
*  SSET sets the entries of an n vector x to the scalar alpha.
*
*  Arguments
*  =========
*
*  N       (input) INTEGER
*          On entry, N specifies the length of the vector x. N  must  be
*          at least zero.
*
*  ALPHA   (input) REAL
*          On entry, ALPHA specifies the scalar alpha.
*
*  X       (input/output) REAL array of dimension at least
*          ( 1 + ( n - 1 )*abs( INCX ) ). Before entry,  the incremented
*          array  X  must  contain the vector x. On exit, entries of the
*          incremented array X are set to alpha.
*
*  INCX    (input) INTEGER
*          On entry, INCX specifies the increment for the elements of X.
*          INCX must not be zero.
*
*  -- Written on April 1, 1998 by
*     Antoine Petitet, University  of  Tennessee, Knoxville 37996, USA.
*
*  =====================================================================
*
*     .. Local Scalars ..
      INTEGER            I, INFO, IX, M, MP1
*     ..
*     .. External Subroutines ..
      EXTERNAL           XERBLA
*     ..
*     .. Intrinsic Functions ..
      INTRINSIC          MOD
*     ..
*     .. Executable Statements ..
*
*     Test the input parameters.
*
      INFO = 0
      IF( N.LT.0 ) THEN
         INFO = 1
      ELSE IF( INCX.EQ.0 ) THEN
         INFO = 4
      END IF
      IF( INFO.NE.0 ) THEN
         CALL XERBLA( 'SSET', INFO )
         RETURN
      END IF
*
*     Quick return if possible.
*
      IF( N.LE.0 )
     $   RETURN
*
*     Form  x := alpha
*
      IF( INCX.EQ.1 )
     $   GO TO 20
*
*     code for increments not equal to 1
*
*     Set up the start point in  X.
*
      IF( INCX.GT.0 ) THEN
         IX = 1
      ELSE
         IX = 1 - ( N - 1 ) * INCX
      END IF
*
      DO 10 I = 1, N
        X( IX ) = ALPHA
        IX = IX + INCX
   10 CONTINUE
*
      RETURN
*
*     code for increment equal to 1
*
*     clean-up loop
*
   20 M = MOD( N, 4 )
*
      IF( M.EQ.0 )
     $   GO TO 40
*
      DO 30 I = 1, M
        X( I ) = ALPHA
   30 CONTINUE
      IF( N.LT.4 )
     $   RETURN
*
   40 MP1 = M + 1
      DO 50 I = MP1, N, 4
         X( I     ) = ALPHA
         X( I + 1 ) = ALPHA
         X( I + 2 ) = ALPHA
         X( I + 3 ) = ALPHA
   50 CONTINUE
*
      RETURN
*
*     End of SSET
*
      END