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

Functions

subroutine zaxpy (n, za, zx, incx, zy, incy)
 ZAXPY
subroutine zcopy (n, zx, incx, zy, incy)
 ZCOPY
complex *16 function zdotc (n, zx, incx, zy, incy)
 ZDOTC
complex *16 function zdotu (n, zx, incx, zy, incy)
 ZDOTU
subroutine zdrot (n, zx, incx, zy, incy, c, s)
 ZDROT
subroutine zdscal (n, da, zx, incx)
 ZDSCAL
subroutine zscal (n, za, zx, incx)
 ZSCAL
subroutine zswap (n, zx, incx, zy, incy)
 ZSWAP

Detailed Description

This is the group of complex16 LEVEL 1 BLAS routines.

Function Documentation

◆ zaxpy()

subroutine zaxpy ( integer n,
complex*16 za,
complex*16, dimension(*) zx,
integer incx,
complex*16, dimension(*) zy,
integer incy )

ZAXPY

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

Definition at line 87 of file zaxpy.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*16 ZA
95 INTEGER INCX,INCY,N
96* ..
97* .. Array Arguments ..
98 COMPLEX*16 ZX(*),ZY(*)
99* ..
100*
101* =====================================================================
102*
103* .. Local Scalars ..
104 INTEGER I,IX,IY
105* ..
106* .. External Functions ..
107 DOUBLE PRECISION DCABS1
108 EXTERNAL dcabs1
109* ..
110 IF (n.LE.0) RETURN
111 IF (dcabs1(za).EQ.0.0d0) 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 zy(i) = zy(i) + za*zx(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 zy(iy) = zy(iy) + za*zx(ix)
130 ix = ix + incx
131 iy = iy + incy
132 END DO
133 END IF
134*
135 RETURN
136*
137* End of ZAXPY
138*
double precision function dcabs1(z)
DCABS1
Definition dcabs1.f:47

◆ zcopy()

subroutine zcopy ( integer n,
complex*16, dimension(*) zx,
integer incx,
complex*16, dimension(*) zy,
integer incy )

ZCOPY

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

Definition at line 80 of file zcopy.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*16 ZX(*),ZY(*)
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 zy(i) = zx(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 zy(iy) = zx(ix)
117 ix = ix + incx
118 iy = iy + incy
119 END DO
120 END IF
121 RETURN
122*
123* End of ZCOPY
124*

◆ zdotc()

complex*16 function zdotc ( integer n,
complex*16, dimension(*) zx,
integer incx,
complex*16, dimension(*) zy,
integer incy )

ZDOTC

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

Definition at line 82 of file zdotc.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*16 ZX(*),ZY(*)
93* ..
94*
95* =====================================================================
96*
97* .. Local Scalars ..
98 COMPLEX*16 ZTEMP
99 INTEGER I,IX,IY
100* ..
101* .. Intrinsic Functions ..
102 INTRINSIC dconjg
103* ..
104 ztemp = (0.0d0,0.0d0)
105 zdotc = (0.0d0,0.0d0)
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 ztemp = ztemp + dconjg(zx(i))*zy(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 ztemp = ztemp + dconjg(zx(ix))*zy(iy)
125 ix = ix + incx
126 iy = iy + incy
127 END DO
128 END IF
129 zdotc = ztemp
130 RETURN
131*
132* End of ZDOTC
133*
complex *16 function zdotc(n, zx, incx, zy, incy)
ZDOTC
Definition zdotc.f:83

◆ zdotu()

complex*16 function zdotu ( integer n,
complex*16, dimension(*) zx,
integer incx,
complex*16, dimension(*) zy,
integer incy )

ZDOTU

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

Definition at line 82 of file zdotu.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*16 ZX(*),ZY(*)
93* ..
94*
95* =====================================================================
96*
97* .. Local Scalars ..
98 COMPLEX*16 ZTEMP
99 INTEGER I,IX,IY
100* ..
101 ztemp = (0.0d0,0.0d0)
102 zdotu = (0.0d0,0.0d0)
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 ztemp = ztemp + zx(i)*zy(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 ztemp = ztemp + zx(ix)*zy(iy)
122 ix = ix + incx
123 iy = iy + incy
124 END DO
125 END IF
126 zdotu = ztemp
127 RETURN
128*
129* End of ZDOTU
130*
complex *16 function zdotu(n, zx, incx, zy, incy)
ZDOTU
Definition zdotu.f:83

◆ zdrot()

subroutine zdrot ( integer n,
complex*16, dimension( * ) zx,
integer incx,
complex*16, dimension( * ) zy,
integer incy,
double precision c,
double precision s )

ZDROT

Purpose:
!>
!> 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]ZX
!>          ZX is COMPLEX*16 array, dimension at least
!>           ( 1 + ( N - 1 )*abs( INCX ) ).
!>           Before entry, the incremented array ZX must contain the n
!>           element vector cx. On exit, ZX is overwritten by the updated
!>           vector cx.
!> 
[in]INCX
!>          INCX is INTEGER
!>           On entry, INCX specifies the increment for the elements of
!>           ZX. INCX must not be zero.
!> 
[in,out]ZY
!>          ZY is COMPLEX*16 array, dimension at least
!>           ( 1 + ( N - 1 )*abs( INCY ) ).
!>           Before entry, the incremented array ZY must contain the n
!>           element vector cy. On exit, ZY is overwritten by the updated
!>           vector cy.
!> 
[in]INCY
!>          INCY is INTEGER
!>           On entry, INCY specifies the increment for the elements of
!>           ZY. INCY must not be zero.
!> 
[in]C
!>          C is DOUBLE PRECISION
!>           On entry, C specifies the cosine, cos.
!> 
[in]S
!>          S is DOUBLE PRECISION
!>           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 zdrot.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 DOUBLE PRECISION C, S
106* ..
107* .. Array Arguments ..
108 COMPLEX*16 ZX( * ), ZY( * )
109* ..
110*
111* =====================================================================
112*
113* .. Local Scalars ..
114 INTEGER I, IX, IY
115 COMPLEX*16 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*zx( i ) + s*zy( i )
127 zy( i ) = c*zy( i ) - s*zx( i )
128 zx( 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*zx( ix ) + s*zy( iy )
143 zy( iy ) = c*zy( iy ) - s*zx( ix )
144 zx( ix ) = ctemp
145 ix = ix + incx
146 iy = iy + incy
147 END DO
148 END IF
149 RETURN
150*
151* End of ZDROT
152*

◆ zdscal()

subroutine zdscal ( integer n,
double precision da,
complex*16, dimension(*) zx,
integer incx )

ZDSCAL

Purpose:
!>
!>    ZDSCAL scales a vector by a constant.
!> 
Parameters
[in]N
!>          N is INTEGER
!>         number of elements in input vector(s)
!> 
[in]DA
!>          DA is DOUBLE PRECISION
!>           On entry, DA specifies the scalar alpha.
!> 
[in,out]ZX
!>          ZX is COMPLEX*16 array, dimension ( 1 + ( N - 1 )*abs( INCX ) )
!> 
[in]INCX
!>          INCX is INTEGER
!>         storage spacing between elements of ZX
!> 
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Further Details:
!>
!>     jack dongarra, 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 zdscal.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 DOUBLE PRECISION DA
85 INTEGER INCX,N
86* ..
87* .. Array Arguments ..
88 COMPLEX*16 ZX(*)
89* ..
90*
91* =====================================================================
92*
93* .. Local Scalars ..
94 INTEGER I,NINCX
95* ..
96* .. Intrinsic Functions ..
97 INTRINSIC dcmplx
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 zx(i) = dcmplx(da,0.0d0)*zx(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 zx(i) = dcmplx(da,0.0d0)*zx(i)
114 END DO
115 END IF
116 RETURN
117*
118* End of ZDSCAL
119*

◆ zscal()

subroutine zscal ( integer n,
complex*16 za,
complex*16, dimension(*) zx,
integer incx )

ZSCAL

Purpose:
!>
!>    ZSCAL scales a vector by a constant.
!> 
Parameters
[in]N
!>          N is INTEGER
!>         number of elements in input vector(s)
!> 
[in]ZA
!>          ZA is COMPLEX*16
!>           On entry, ZA specifies the scalar alpha.
!> 
[in,out]ZX
!>          ZX is COMPLEX*16 array, dimension ( 1 + ( N - 1 )*abs( INCX ) )
!> 
[in]INCX
!>          INCX is INTEGER
!>         storage spacing between elements of ZX
!> 
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Further Details:
!>
!>     jack dongarra, 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 zscal.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*16 ZA
85 INTEGER INCX,N
86* ..
87* .. Array Arguments ..
88 COMPLEX*16 ZX(*)
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 zx(i) = za*zx(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 zx(i) = za*zx(i)
111 END DO
112 END IF
113 RETURN
114*
115* End of ZSCAL
116*

◆ zswap()

subroutine zswap ( integer n,
complex*16, dimension(*) zx,
integer incx,
complex*16, dimension(*) zy,
integer incy )

ZSWAP

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

Definition at line 80 of file zswap.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*16 ZX(*),ZY(*)
91* ..
92*
93* =====================================================================
94*
95* .. Local Scalars ..
96 COMPLEX*16 ZTEMP
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 ztemp = zx(i)
105 zx(i) = zy(i)
106 zy(i) = ztemp
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 ztemp = zx(ix)
119 zx(ix) = zy(iy)
120 zy(iy) = ztemp
121 ix = ix + incx
122 iy = iy + incy
123 END DO
124 END IF
125 RETURN
126*
127* End of ZSWAP
128*