OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches

Functions

subroutine caxpy (n, ca, cx, incx, cy, incy)
 CAXPY
subroutine ccopy (n, cx, incx, cy, incy)
 CCOPY
complex function cdotc (n, cx, incx, cy, incy)
 CDOTC
complex function cdotu (n, cx, incx, cy, incy)
 CDOTU
subroutine cscal (n, ca, cx, incx)
 CSCAL
subroutine csrot (n, cx, incx, cy, incy, c, s)
 CSROT
subroutine csscal (n, sa, cx, incx)
 CSSCAL
subroutine cswap (n, cx, incx, cy, incy)
 CSWAP

Detailed Description

This is the group of complex LEVEL 1 BLAS routines.

Function Documentation

◆ caxpy()

subroutine caxpy ( integer n,
complex ca,
complex, dimension(*) cx,
integer incx,
complex, dimension(*) cy,
integer incy )

CAXPY

Purpose:
!>
!>    CAXPY constant times a vector plus a vector.
!> 
Parameters
[in]N
!>          N is INTEGER
!>         number of elements in input vector(s)
!> 
[in]CA
!>          CA is COMPLEX
!>           On entry, CA specifies the scalar alpha.
!> 
[in]CX
!>          CX is COMPLEX array, dimension ( 1 + ( N - 1 )*abs( INCX ) )
!> 
[in]INCX
!>          INCX is INTEGER
!>         storage spacing between elements of CX
!> 
[in,out]CY
!>          CY is COMPLEX array, dimension ( 1 + ( N - 1 )*abs( INCY ) )
!> 
[in]INCY
!>          INCY is INTEGER
!>         storage spacing between elements of CY
!> 
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Further Details:
!>
!>     jack dongarra, linpack, 3/11/78.
!>     modified 12/3/93, array(1) declarations changed to array(*)
!> 

Definition at line 87 of file caxpy.f.

88*
89* -- Reference BLAS level1 routine --
90* -- Reference BLAS is a software package provided by Univ. of Tennessee, --
91* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
92*
93* .. Scalar Arguments ..
94 COMPLEX CA
95 INTEGER INCX,INCY,N
96* ..
97* .. Array Arguments ..
98 COMPLEX CX(*),CY(*)
99* ..
100*
101* =====================================================================
102*
103* .. Local Scalars ..
104 INTEGER I,IX,IY
105* ..
106* .. External Functions ..
107 REAL SCABS1
108 EXTERNAL scabs1
109* ..
110 IF (n.LE.0) RETURN
111 IF (scabs1(ca).EQ.0.0e+0) RETURN
112 IF (incx.EQ.1 .AND. incy.EQ.1) THEN
113*
114* code for both increments equal to 1
115*
116 DO i = 1,n
117 cy(i) = cy(i) + ca*cx(i)
118 END DO
119 ELSE
120*
121* code for unequal increments or equal increments
122* not equal to 1
123*
124 ix = 1
125 iy = 1
126 IF (incx.LT.0) ix = (-n+1)*incx + 1
127 IF (incy.LT.0) iy = (-n+1)*incy + 1
128 DO i = 1,n
129 cy(iy) = cy(iy) + ca*cx(ix)
130 ix = ix + incx
131 iy = iy + incy
132 END DO
133 END IF
134*
135 RETURN
136*
137* End of CAXPY
138*
real function scabs1(z)
SCABS1
Definition scabs1.f:46

◆ ccopy()

subroutine ccopy ( integer n,
complex, dimension(*) cx,
integer incx,
complex, dimension(*) cy,
integer incy )

CCOPY

Purpose:
!>
!>    CCOPY copies a vector x to a vector y.
!> 
Parameters
[in]N
!>          N is INTEGER
!>         number of elements in input vector(s)
!> 
[in]CX
!>          CX is COMPLEX array, dimension ( 1 + ( N - 1 )*abs( INCX ) )
!> 
[in]INCX
!>          INCX is INTEGER
!>         storage spacing between elements of CX
!> 
[out]CY
!>          CY is COMPLEX array, dimension ( 1 + ( N - 1 )*abs( INCY ) )
!> 
[in]INCY
!>          INCY is INTEGER
!>         storage spacing between elements of CY
!> 
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Further Details:
!>
!>     jack dongarra, linpack, 3/11/78.
!>     modified 12/3/93, array(1) declarations changed to array(*)
!> 

Definition at line 80 of file ccopy.f.

81*
82* -- Reference BLAS level1 routine --
83* -- Reference BLAS is a software package provided by Univ. of Tennessee, --
84* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
85*
86* .. Scalar Arguments ..
87 INTEGER INCX,INCY,N
88* ..
89* .. Array Arguments ..
90 COMPLEX CX(*),CY(*)
91* ..
92*
93* =====================================================================
94*
95* .. Local Scalars ..
96 INTEGER I,IX,IY
97* ..
98 IF (n.LE.0) RETURN
99 IF (incx.EQ.1 .AND. incy.EQ.1) THEN
100*
101* code for both increments equal to 1
102*
103 DO i = 1,n
104 cy(i) = cx(i)
105 END DO
106 ELSE
107*
108* code for unequal increments or equal increments
109* not equal to 1
110*
111 ix = 1
112 iy = 1
113 IF (incx.LT.0) ix = (-n+1)*incx + 1
114 IF (incy.LT.0) iy = (-n+1)*incy + 1
115 DO i = 1,n
116 cy(iy) = cx(ix)
117 ix = ix + incx
118 iy = iy + incy
119 END DO
120 END IF
121 RETURN
122*
123* End of CCOPY
124*

◆ cdotc()

complex function cdotc ( integer n,
complex, dimension(*) cx,
integer incx,
complex, dimension(*) cy,
integer incy )

CDOTC

Purpose:
!>
!> CDOTC forms the dot product of two complex vectors
!>      CDOTC = X^H * Y
!>
!> 
Parameters
[in]N
!>          N is INTEGER
!>         number of elements in input vector(s)
!> 
[in]CX
!>          CX is COMPLEX array, dimension ( 1 + ( N - 1 )*abs( INCX ) )
!> 
[in]INCX
!>          INCX is INTEGER
!>         storage spacing between elements of CX
!> 
[in]CY
!>          CY is COMPLEX array, dimension ( 1 + ( N - 1 )*abs( INCY ) )
!> 
[in]INCY
!>          INCY is INTEGER
!>         storage spacing between elements of CY
!> 
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Further Details:
!>
!>     jack dongarra, linpack,  3/11/78.
!>     modified 12/3/93, array(1) declarations changed to array(*)
!> 

Definition at line 82 of file cdotc.f.

83*
84* -- Reference BLAS level1 routine --
85* -- Reference BLAS is a software package provided by Univ. of Tennessee, --
86* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
87*
88* .. Scalar Arguments ..
89 INTEGER INCX,INCY,N
90* ..
91* .. Array Arguments ..
92 COMPLEX CX(*),CY(*)
93* ..
94*
95* =====================================================================
96*
97* .. Local Scalars ..
98 COMPLEX CTEMP
99 INTEGER I,IX,IY
100* ..
101* .. Intrinsic Functions ..
102 INTRINSIC conjg
103* ..
104 ctemp = (0.0,0.0)
105 cdotc = (0.0,0.0)
106 IF (n.LE.0) RETURN
107 IF (incx.EQ.1 .AND. incy.EQ.1) THEN
108*
109* code for both increments equal to 1
110*
111 DO i = 1,n
112 ctemp = ctemp + conjg(cx(i))*cy(i)
113 END DO
114 ELSE
115*
116* code for unequal increments or equal increments
117* not equal to 1
118*
119 ix = 1
120 iy = 1
121 IF (incx.LT.0) ix = (-n+1)*incx + 1
122 IF (incy.LT.0) iy = (-n+1)*incy + 1
123 DO i = 1,n
124 ctemp = ctemp + conjg(cx(ix))*cy(iy)
125 ix = ix + incx
126 iy = iy + incy
127 END DO
128 END IF
129 cdotc = ctemp
130 RETURN
131*
132* End of CDOTC
133*
complex function cdotc(n, cx, incx, cy, incy)
CDOTC
Definition cdotc.f:83

◆ cdotu()

complex function cdotu ( integer n,
complex, dimension(*) cx,
integer incx,
complex, dimension(*) cy,
integer incy )

CDOTU

Purpose:
!>
!> CDOTU forms the dot product of two complex vectors
!>      CDOTU = X^T * Y
!>
!> 
Parameters
[in]N
!>          N is INTEGER
!>         number of elements in input vector(s)
!> 
[in]CX
!>          CX is COMPLEX array, dimension ( 1 + ( N - 1 )*abs( INCX ) )
!> 
[in]INCX
!>          INCX is INTEGER
!>         storage spacing between elements of CX
!> 
[in]CY
!>          CY is COMPLEX array, dimension ( 1 + ( N - 1 )*abs( INCY ) )
!> 
[in]INCY
!>          INCY is INTEGER
!>         storage spacing between elements of CY
!> 
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Further Details:
!>
!>     jack dongarra, linpack, 3/11/78.
!>     modified 12/3/93, array(1) declarations changed to array(*)
!> 

Definition at line 82 of file cdotu.f.

83*
84* -- Reference BLAS level1 routine --
85* -- Reference BLAS is a software package provided by Univ. of Tennessee, --
86* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
87*
88* .. Scalar Arguments ..
89 INTEGER INCX,INCY,N
90* ..
91* .. Array Arguments ..
92 COMPLEX CX(*),CY(*)
93* ..
94*
95* =====================================================================
96*
97* .. Local Scalars ..
98 COMPLEX CTEMP
99 INTEGER I,IX,IY
100* ..
101 ctemp = (0.0,0.0)
102 cdotu = (0.0,0.0)
103 IF (n.LE.0) RETURN
104 IF (incx.EQ.1 .AND. incy.EQ.1) THEN
105*
106* code for both increments equal to 1
107*
108 DO i = 1,n
109 ctemp = ctemp + cx(i)*cy(i)
110 END DO
111 ELSE
112*
113* code for unequal increments or equal increments
114* not equal to 1
115*
116 ix = 1
117 iy = 1
118 IF (incx.LT.0) ix = (-n+1)*incx + 1
119 IF (incy.LT.0) iy = (-n+1)*incy + 1
120 DO i = 1,n
121 ctemp = ctemp + cx(ix)*cy(iy)
122 ix = ix + incx
123 iy = iy + incy
124 END DO
125 END IF
126 cdotu = ctemp
127 RETURN
128*
129* End of CDOTU
130*
complex function cdotu(n, cx, incx, cy, incy)
CDOTU
Definition cdotu.f:83

◆ cscal()

subroutine cscal ( integer n,
complex ca,
complex, dimension(*) cx,
integer incx )

CSCAL

Purpose:
!>
!>    CSCAL scales a vector by a constant.
!> 
Parameters
[in]N
!>          N is INTEGER
!>         number of elements in input vector(s)
!> 
[in]CA
!>          CA is COMPLEX
!>           On entry, CA specifies the scalar alpha.
!> 
[in,out]CX
!>          CX is COMPLEX array, dimension ( 1 + ( N - 1 )*abs( INCX ) )
!> 
[in]INCX
!>          INCX is INTEGER
!>         storage spacing between elements of CX
!> 
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Further Details:
!>
!>     jack dongarra, linpack,  3/11/78.
!>     modified 3/93 to return if incx .le. 0.
!>     modified 12/3/93, array(1) declarations changed to array(*)
!> 

Definition at line 77 of file cscal.f.

78*
79* -- Reference BLAS level1 routine --
80* -- Reference BLAS is a software package provided by Univ. of Tennessee, --
81* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
82*
83* .. Scalar Arguments ..
84 COMPLEX CA
85 INTEGER INCX,N
86* ..
87* .. Array Arguments ..
88 COMPLEX CX(*)
89* ..
90*
91* =====================================================================
92*
93* .. Local Scalars ..
94 INTEGER I,NINCX
95* ..
96 IF (n.LE.0 .OR. incx.LE.0) RETURN
97 IF (incx.EQ.1) THEN
98*
99* code for increment equal to 1
100*
101 DO i = 1,n
102 cx(i) = ca*cx(i)
103 END DO
104 ELSE
105*
106* code for increment not equal to 1
107*
108 nincx = n*incx
109 DO i = 1,nincx,incx
110 cx(i) = ca*cx(i)
111 END DO
112 END IF
113 RETURN
114*
115* End of CSCAL
116*

◆ csrot()

subroutine csrot ( integer n,
complex, dimension( * ) cx,
integer incx,
complex, dimension( * ) cy,
integer incy,
real c,
real s )

CSROT

Purpose:
!>
!> CSROT applies a plane rotation, where the cos and sin (c and s) are real
!> and the vectors cx and cy are complex.
!> jack dongarra, linpack, 3/11/78.
!> 
Parameters
[in]N
!>          N is INTEGER
!>           On entry, N specifies the order of the vectors cx and cy.
!>           N must be at least zero.
!> 
[in,out]CX
!>          CX is COMPLEX array, dimension at least
!>           ( 1 + ( N - 1 )*abs( INCX ) ).
!>           Before entry, the incremented array CX must contain the n
!>           element vector cx. On exit, CX is overwritten by the updated
!>           vector cx.
!> 
[in]INCX
!>          INCX is INTEGER
!>           On entry, INCX specifies the increment for the elements of
!>           CX. INCX must not be zero.
!> 
[in,out]CY
!>          CY is COMPLEX array, dimension at least
!>           ( 1 + ( N - 1 )*abs( INCY ) ).
!>           Before entry, the incremented array CY must contain the n
!>           element vector cy. On exit, CY is overwritten by the updated
!>           vector cy.
!> 
[in]INCY
!>          INCY is INTEGER
!>           On entry, INCY specifies the increment for the elements of
!>           CY. INCY must not be zero.
!> 
[in]C
!>          C is REAL
!>           On entry, C specifies the cosine, cos.
!> 
[in]S
!>          S is REAL
!>           On entry, S specifies the sine, sin.
!> 
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.

Definition at line 97 of file csrot.f.

98*
99* -- Reference BLAS level1 routine --
100* -- Reference BLAS is a software package provided by Univ. of Tennessee, --
101* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
102*
103* .. Scalar Arguments ..
104 INTEGER INCX, INCY, N
105 REAL C, S
106* ..
107* .. Array Arguments ..
108 COMPLEX CX( * ), CY( * )
109* ..
110*
111* =====================================================================
112*
113* .. Local Scalars ..
114 INTEGER I, IX, IY
115 COMPLEX CTEMP
116* ..
117* .. Executable Statements ..
118*
119 IF( n.LE.0 )
120 $ RETURN
121 IF( incx.EQ.1 .AND. incy.EQ.1 ) THEN
122*
123* code for both increments equal to 1
124*
125 DO i = 1, n
126 ctemp = c*cx( i ) + s*cy( i )
127 cy( i ) = c*cy( i ) - s*cx( i )
128 cx( i ) = ctemp
129 END DO
130 ELSE
131*
132* code for unequal increments or equal increments not equal
133* to 1
134*
135 ix = 1
136 iy = 1
137 IF( incx.LT.0 )
138 $ ix = ( -n+1 )*incx + 1
139 IF( incy.LT.0 )
140 $ iy = ( -n+1 )*incy + 1
141 DO i = 1, n
142 ctemp = c*cx( ix ) + s*cy( iy )
143 cy( iy ) = c*cy( iy ) - s*cx( ix )
144 cx( ix ) = ctemp
145 ix = ix + incx
146 iy = iy + incy
147 END DO
148 END IF
149 RETURN
150*
151* End of CSROT
152*

◆ csscal()

subroutine csscal ( integer n,
real sa,
complex, dimension(*) cx,
integer incx )

CSSCAL

Purpose:
!>
!>    CSSCAL scales a complex vector by a real constant.
!> 
Parameters
[in]N
!>          N is INTEGER
!>         number of elements in input vector(s)
!> 
[in]SA
!>          SA is REAL
!>           On entry, SA specifies the scalar alpha.
!> 
[in,out]CX
!>          CX is COMPLEX array, dimension ( 1 + ( N - 1 )*abs( INCX ) )
!> 
[in]INCX
!>          INCX is INTEGER
!>         storage spacing between elements of CX
!> 
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Further Details:
!>
!>     jack dongarra, linpack, 3/11/78.
!>     modified 3/93 to return if incx .le. 0.
!>     modified 12/3/93, array(1) declarations changed to array(*)
!> 

Definition at line 77 of file csscal.f.

78*
79* -- Reference BLAS level1 routine --
80* -- Reference BLAS is a software package provided by Univ. of Tennessee, --
81* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
82*
83* .. Scalar Arguments ..
84 REAL SA
85 INTEGER INCX,N
86* ..
87* .. Array Arguments ..
88 COMPLEX CX(*)
89* ..
90*
91* =====================================================================
92*
93* .. Local Scalars ..
94 INTEGER I,NINCX
95* ..
96* .. Intrinsic Functions ..
97 INTRINSIC aimag,cmplx,real
98* ..
99 IF (n.LE.0 .OR. incx.LE.0) RETURN
100 IF (incx.EQ.1) THEN
101*
102* code for increment equal to 1
103*
104 DO i = 1,n
105 cx(i) = cmplx(sa*real(cx(i)),sa*aimag(cx(i)))
106 END DO
107 ELSE
108*
109* code for increment not equal to 1
110*
111 nincx = n*incx
112 DO i = 1,nincx,incx
113 cx(i) = cmplx(sa*real(cx(i)),sa*aimag(cx(i)))
114 END DO
115 END IF
116 RETURN
117*
118* End of CSSCAL
119*
float cmplx[2]
Definition pblas.h:136

◆ cswap()

subroutine cswap ( integer n,
complex, dimension(*) cx,
integer incx,
complex, dimension(*) cy,
integer incy )

CSWAP

Purpose:
!>
!>   CSWAP interchanges two vectors.
!> 
Parameters
[in]N
!>          N is INTEGER
!>         number of elements in input vector(s)
!> 
[in,out]CX
!>          CX is COMPLEX array, dimension ( 1 + ( N - 1 )*abs( INCX ) )
!> 
[in]INCX
!>          INCX is INTEGER
!>         storage spacing between elements of CX
!> 
[in,out]CY
!>          CY is COMPLEX array, dimension ( 1 + ( N - 1 )*abs( INCY ) )
!> 
[in]INCY
!>          INCY is INTEGER
!>         storage spacing between elements of CY
!> 
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Further Details:
!>
!>     jack dongarra, linpack, 3/11/78.
!>     modified 12/3/93, array(1) declarations changed to array(*)
!> 

Definition at line 80 of file cswap.f.

81*
82* -- Reference BLAS level1 routine --
83* -- Reference BLAS is a software package provided by Univ. of Tennessee, --
84* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
85*
86* .. Scalar Arguments ..
87 INTEGER INCX,INCY,N
88* ..
89* .. Array Arguments ..
90 COMPLEX CX(*),CY(*)
91* ..
92*
93* =====================================================================
94*
95* .. Local Scalars ..
96 COMPLEX CTEMP
97 INTEGER I,IX,IY
98* ..
99 IF (n.LE.0) RETURN
100 IF (incx.EQ.1 .AND. incy.EQ.1) THEN
101*
102* code for both increments equal to 1
103 DO i = 1,n
104 ctemp = cx(i)
105 cx(i) = cy(i)
106 cy(i) = ctemp
107 END DO
108 ELSE
109*
110* code for unequal increments or equal increments not equal
111* to 1
112*
113 ix = 1
114 iy = 1
115 IF (incx.LT.0) ix = (-n+1)*incx + 1
116 IF (incy.LT.0) iy = (-n+1)*incy + 1
117 DO i = 1,n
118 ctemp = cx(ix)
119 cx(ix) = cy(iy)
120 cy(iy) = ctemp
121 ix = ix + incx
122 iy = iy + incy
123 END DO
124 END IF
125 RETURN
126*
127* End of CSWAP
128*