Skip to content

Commit

Permalink
add declarations for external routines in QZ code
Browse files Browse the repository at this point in the history
  • Loading branch information
thijssteel committed Feb 15, 2021
1 parent 6166577 commit e9d5504
Show file tree
Hide file tree
Showing 16 changed files with 40 additions and 0 deletions.
2 changes: 2 additions & 0 deletions SRC/claqz0.f
Original file line number Diff line number Diff line change
Expand Up @@ -310,6 +310,8 @@ RECURSIVE SUBROUTINE CLAQZ0( WANTS, WANTQ, WANTZ, N, ILO, IHI, A,
CHARACTER :: JBCMPZ*3

* External Functions
EXTERNAL :: XERBLA, CHGEQZ, CLAQZ2, CLAQZ3, CLASET, SLABAD,
$ CLARTG, CROT
REAL, EXTERNAL :: SLAMCH
LOGICAL, EXTERNAL :: LSAME
INTEGER, EXTERNAL :: ILAENV
Expand Down
3 changes: 3 additions & 0 deletions SRC/claqz1.f
Original file line number Diff line number Diff line change
Expand Up @@ -187,6 +187,9 @@ SUBROUTINE CLAQZ1( ILQ, ILZ, K, ISTARTM, ISTOPM, IHI, A, LDA, B,
* Local variables
REAL :: C
COMPLEX :: S, TEMP
*
* External Functions
EXTERNAL :: CLARTG, CROT
*
IF( K+1 .EQ. IHI ) THEN
*
Expand Down
2 changes: 2 additions & 0 deletions SRC/claqz2.f
Original file line number Diff line number Diff line change
Expand Up @@ -257,6 +257,8 @@ RECURSIVE SUBROUTINE CLAQZ2( ILSCHUR, ILQ, ILZ, N, ILO, IHI, NW,
COMPLEX :: S, S1, TEMP

* External Functions
EXTERNAL :: XERBLA, CLAQZ0, CLAQZ1, SLABAD, CLACPY, CLASET, CGEMM,
$ CTGEXC, CLARTG, CROT
REAL, EXTERNAL :: SLAMCH

INFO = 0
Expand Down
2 changes: 2 additions & 0 deletions SRC/claqz3.f
Original file line number Diff line number Diff line change
Expand Up @@ -230,6 +230,8 @@ SUBROUTINE CLAQZ3( ILSCHUR, ILQ, ILZ, N, ILO, IHI, NSHIFTS,
COMPLEX :: TEMP, TEMP2, TEMP3, S

* External Functions
EXTERNAL :: XERBLA, SLABAD, CLASET, CLARTG, CROT, CLAQZ1, CGEMM,
$ CLACPY
REAL, EXTERNAL :: SLAMCH

INFO = 0
Expand Down
2 changes: 2 additions & 0 deletions SRC/dlaqz0.f
Original file line number Diff line number Diff line change
Expand Up @@ -332,6 +332,8 @@ RECURSIVE SUBROUTINE DLAQZ0( WANTS, WANTQ, WANTZ, N, ILO, IHI, A,
CHARACTER :: JBCMPZ*3

* External Functions
EXTERNAL :: XERBLA, DHGEQZ, DLASET, DLAQZ3, DLAQZ4, DLABAD,
$ DLARTG, DROT
DOUBLE PRECISION, EXTERNAL :: DLAMCH
LOGICAL, EXTERNAL :: LSAME
INTEGER, EXTERNAL :: ILAENV
Expand Down
3 changes: 3 additions & 0 deletions SRC/dlaqz2.f
Original file line number Diff line number Diff line change
Expand Up @@ -186,6 +186,9 @@ SUBROUTINE DLAQZ2( ILQ, ILZ, K, ISTARTM, ISTOPM, IHI, A, LDA, B,
*
* Local variables
DOUBLE PRECISION :: H( 2, 3 ), C1, S1, C2, S2, TEMP
*
* External functions
EXTERNAL :: DLARTG, DROT
*
IF( K+2 .EQ. IHI ) THEN
* Shift is located on the edge of the matrix, remove it
Expand Down
2 changes: 2 additions & 0 deletions SRC/dlaqz3.f
Original file line number Diff line number Diff line change
Expand Up @@ -260,6 +260,8 @@ RECURSIVE SUBROUTINE DLAQZ3( ILSCHUR, ILQ, ILZ, N, ILO, IHI, NW,
DOUBLE PRECISION :: S, SMLNUM, ULP, SAFMIN, SAFMAX, C1, S1, TEMP

* External Functions
EXTERNAL :: XERBLA, DTGEXC, DLABAD, DLAQZ0, DLACPY, DLASET,
$ DLAQZ2, DROT, DLARTG, DLAG2, DGEMM
DOUBLE PRECISION, EXTERNAL :: DLAMCH

INFO = 0
Expand Down
4 changes: 4 additions & 0 deletions SRC/dlaqz4.f
Original file line number Diff line number Diff line change
Expand Up @@ -232,6 +232,10 @@ SUBROUTINE DLAQZ4( ILSCHUR, ILQ, ILZ, N, ILO, IHI, NSHIFTS,
INTEGER :: I, J, NS, ISTARTM, ISTOPM, SHEIGHT, SWIDTH, K, NP,
$ ISTARTB, ISTOPB, ISHIFT, NBLOCK, NPOS
DOUBLE PRECISION :: TEMP, V( 3 ), C1, S1, C2, S2, SWAP
*
* External functions
EXTERNAL :: XERBLA, DGEMM, DLAQZ1, DLAQZ2, DLASET, DLARTG, DROT,
$ DLACPY

INFO = 0
IF ( NBLOCK_DESIRED .LT. NSHIFTS+1 ) THEN
Expand Down
2 changes: 2 additions & 0 deletions SRC/slaqz0.f
Original file line number Diff line number Diff line change
Expand Up @@ -328,6 +328,8 @@ RECURSIVE SUBROUTINE SLAQZ0( WANTS, WANTQ, WANTZ, N, ILO, IHI, A,
CHARACTER :: JBCMPZ*3

* External Functions
EXTERNAL :: XERBLA, SHGEQZ, SLAQZ3, SLAQZ4, SLASET, SLABAD,
$ SLARTG, SROT
REAL, EXTERNAL :: SLAMCH
LOGICAL, EXTERNAL :: LSAME
INTEGER, EXTERNAL :: ILAENV
Expand Down
3 changes: 3 additions & 0 deletions SRC/slaqz2.f
Original file line number Diff line number Diff line change
Expand Up @@ -184,6 +184,9 @@ SUBROUTINE SLAQZ2( ILQ, ILZ, K, ISTARTM, ISTOPM, IHI, A, LDA, B,
*
* Local variables
REAL :: H( 2, 3 ), C1, S1, C2, S2, TEMP
*
* External functions
EXTERNAL :: SLARTG, SROT
*
IF( K+2 .EQ. IHI ) THEN
* Shift is located on the edge of the matrix, remove it
Expand Down
2 changes: 2 additions & 0 deletions SRC/slaqz3.f
Original file line number Diff line number Diff line change
Expand Up @@ -258,6 +258,8 @@ RECURSIVE SUBROUTINE SLAQZ3( ILSCHUR, ILQ, ILZ, N, ILO, IHI, NW,
REAL :: S, SMLNUM, ULP, SAFMIN, SAFMAX, C1, S1, TEMP

* External Functions
EXTERNAL :: XERBLA, STGEXC, SLABAD, SLAQZ0, SLACPY, SLASET,
$ SLAQZ2, SROT, SLARTG, SLAG2, SGEMM
REAL, EXTERNAL :: SLAMCH

INFO = 0
Expand Down
4 changes: 4 additions & 0 deletions SRC/slaqz4.f
Original file line number Diff line number Diff line change
Expand Up @@ -232,6 +232,10 @@ SUBROUTINE SLAQZ4( ILSCHUR, ILQ, ILZ, N, ILO, IHI, NSHIFTS,
INTEGER :: I, J, NS, ISTARTM, ISTOPM, SHEIGHT, SWIDTH, K, NP,
$ ISTARTB, ISTOPB, ISHIFT, NBLOCK, NPOS
REAL :: TEMP, V( 3 ), C1, S1, C2, S2, SWAP
*
* External functions
EXTERNAL :: XERBLA, SGEMM, SLAQZ1, SLAQZ2, SLASET, SLARTG, SROT,
$ SLACPY

INFO = 0
IF ( NBLOCK_DESIRED .LT. NSHIFTS+1 ) THEN
Expand Down
2 changes: 2 additions & 0 deletions SRC/zlaqz0.f
Original file line number Diff line number Diff line change
Expand Up @@ -311,6 +311,8 @@ RECURSIVE SUBROUTINE ZLAQZ0( WANTS, WANTQ, WANTZ, N, ILO, IHI, A,
CHARACTER :: JBCMPZ*3

* External Functions
EXTERNAL :: XERBLA, ZHGEQZ, ZLAQZ2, ZLAQZ3, ZLASET, DLABAD,
$ ZLARTG, ZROT
DOUBLE PRECISION, EXTERNAL :: DLAMCH
LOGICAL, EXTERNAL :: LSAME
INTEGER, EXTERNAL :: ILAENV
Expand Down
3 changes: 3 additions & 0 deletions SRC/zlaqz1.f
Original file line number Diff line number Diff line change
Expand Up @@ -188,6 +188,9 @@ SUBROUTINE ZLAQZ1( ILQ, ILZ, K, ISTARTM, ISTOPM, IHI, A, LDA, B,
* Local variables
DOUBLE PRECISION :: C
COMPLEX*16 :: S, TEMP
*
* External Functions
EXTERNAL :: ZLARTG, ZROT
*
IF( K+1 .EQ. IHI ) THEN
*
Expand Down
2 changes: 2 additions & 0 deletions SRC/zlaqz2.f
Original file line number Diff line number Diff line change
Expand Up @@ -258,6 +258,8 @@ RECURSIVE SUBROUTINE ZLAQZ2( ILSCHUR, ILQ, ILZ, N, ILO, IHI, NW,
COMPLEX*16 :: S, S1, TEMP

* External Functions
EXTERNAL :: XERBLA, ZLAQZ0, ZLAQZ1, DLABAD, ZLACPY, ZLASET, ZGEMM,
$ ZTGEXC, ZLARTG, ZROT
DOUBLE PRECISION, EXTERNAL :: DLAMCH

INFO = 0
Expand Down
2 changes: 2 additions & 0 deletions SRC/zlaqz3.f
Original file line number Diff line number Diff line change
Expand Up @@ -232,6 +232,8 @@ SUBROUTINE ZLAQZ3( ILSCHUR, ILQ, ILZ, N, ILO, IHI, NSHIFTS,
COMPLEX*16 :: TEMP, TEMP2, TEMP3, S

* External Functions
EXTERNAL :: XERBLA, DLABAD, ZLASET, ZLARTG, ZROT, ZLAQZ1, ZGEMM,
$ ZLACPY
DOUBLE PRECISION, EXTERNAL :: DLAMCH

INFO = 0
Expand Down

0 comments on commit e9d5504

Please sign in to comment.