program main c*********************************************************************72 c cc blas3_z_test() tests blas3_z(). c c Licensing: c c This code is distributed under the MIT license. c c Modified: c c 18 January 2014 c c Author: c c John Burkardt c implicit none call timestamp ( ) write ( *, '(a)' ) ' ' write ( *, '(a)' ) 'blas3_z_test():' write ( *, '(a)' ) ' FORTRAN77 version' write ( *, '(a)' ) ' Test blas3_z().' call test01 ( ) c c Terminate. c write ( *, '(a)' ) ' ' write ( *, '(a)' ) 'blas3_z_test():' write ( *, '(a)' ) ' Normal end of execution.' write ( *, '(a)' ) ' ' call timestamp ( ) stop end subroutine test01 ( ) c*********************************************************************72 c cc TEST01 demonstrates the use of ZGEMM. c c Licensing: c c This code is distributed under the MIT license. c c Modified: c c 18 January 2014 c c Author: c c John Burkardt c implicit none integer k parameter ( k = 3 ) integer m parameter ( m = 3 ) integer n parameter ( n = 3 ) integer lda parameter ( lda = m ) integer ldb parameter ( ldb = k ) integer ldc parameter ( ldc = m ) double complex a(lda,k) double complex alpha double complex b(ldb,n) double complex beta double complex c(ldc,n) character transa character transb transa = 'N' transb = 'N' write ( *, '(a)' ) ' ' write ( *, '(a)' ) 'TEST01' write ( *, '(a)' ) & ' ZGEMM can combine scale, multiply and add matrices' write ( *, '(a)' ) & ' using single precision complex arithmetic.' write ( *, '(a)' ) ' ' write ( *, '(a)' ) ' Here, we simply compute C = A * B.' write ( *, '(a)' ) & ' Because B is inverse ( A ), C should be the identity.' call c8mat_test ( m, a ) call c8mat_print ( m, m, a, ' Matrix A:' ) call c8mat_test_inverse ( m, b ) call c8mat_print ( m, m, b, ' Matrix B:' ) alpha = ( 1.0D+00, 0.0D+00 ) beta = ( 0.0D+00, 0.0D+00 ) call zgemm ( transa, transb, m, n, k, alpha, a, lda, b, ldb, & beta, c, ldc ) call c8mat_print ( m, n, c, ' Product C = A * B:' ) return end subroutine c8mat_print ( m, n, a, title ) c*********************************************************************72 c cc c8mat_print() prints a C8MAT. c c Discussion: c c A C8MAT is a matrix of C8's. c c Licensing: c c This code is distributed under the MIT license. c c Modified: c c 07 December 2008 c c Author: c c John Burkardt c c Parameters: c c Input, integer M, N, the number of rows and columns c in the matrix. c c Input, double complex A(M,N), the matrix. c c Input, character * ( * ) TITLE, a title. c implicit none integer m integer n double complex a(m,n) character * ( * ) title call c8mat_print_some ( m, n, a, 1, 1, m, n, title ) return end subroutine c8mat_print_some ( m, n, a, ilo, jlo, ihi, jhi, & title ) c*********************************************************************72 c cc c8mat_print_some() prints some of a C8MAT. c c Discussion: c c A C8MAT is a matrix of C8's. c c Licensing: c c This code is distributed under the MIT license. c c Modified: c c 21 June 2010 c c Author: c c John Burkardt c c Parameters: c c Input, integer M, N, the number of rows and columns c in the matrix. c c Input, double complex A(M,N), the matrix. c c Input, integer ILO, JLO, IHI, JHI, the first row and c column, and the last row and column to be printed. c c Input, character * ( * ) TITLE, a title. c implicit none integer incx parameter ( incx = 4 ) integer m integer n double complex a(m,n) character * ( 20 ) ctemp(incx) integer i integer i2hi integer i2lo integer ihi integer ilo integer inc integer j integer j2 integer j2hi integer j2lo integer jhi integer jlo character * ( * ) title double complex zero zero = dcmplx ( 0.0D+00, 0.0D+00 ) write ( *, '(a)' ) ' ' write ( *, '(a)' ) trim ( title ) if ( m .le. 0 .or. n .le. 0 ) then write ( *, '(a)' ) ' ' write ( *, '(a)' ) ' (None)' return end if c c Print the columns of the matrix, in strips of INCX. c do j2lo = jlo, min ( jhi, n ), incx j2hi = j2lo + incx - 1 j2hi = min ( j2hi, n ) j2hi = min ( j2hi, jhi ) inc = j2hi + 1 - j2lo write ( *, '(a)' ) ' ' do j = j2lo, j2hi j2 = j + 1 - j2lo write ( ctemp(j2), '(i10,10x)' ) j end do write ( *, '(a,4a20)' ) ' Col: ', ( ctemp(j2), j2 = 1, inc ) write ( *, '(a)' ) ' Row' write ( *, '(a)' ) ' ---' c c Determine the range of the rows in this strip. c i2lo = max ( ilo, 1 ) i2hi = min ( ihi, m ) do i = i2lo, i2hi c c Print out (up to) INCX entries in row I, that lie in the current strip. c do j2 = 1, inc j = j2lo - 1 + j2 if ( dimag ( a(i,j) ) .eq. 0.0D+00 ) then write ( ctemp(j2), '(g10.3,10x)' ) dreal ( a(i,j) ) else write ( ctemp(j2), '(2g10.3)' ) a(i,j) end if end do write ( *, '(i5,a,4a20)' ) i, ':', ( ctemp(j2), j2 = 1, inc ) end do end do return end subroutine c8mat_test ( n, a ) c*********************************************************************72 c cc c8mat_test() sets up a test matrix. c c Licensing: c c This code is distributed under the MIT license. c c Modified: c c 03 April 2014 c c Author: c c John Burkardt c c Parameters: c c Input, integer N, the order of the matrix. c c Output, double complex A(N,N), the Fourier matrix. c implicit none integer n double complex a(n,n) double precision angle double complex c8_i integer i integer j double precision pi parameter ( pi = 3.141592653589793D+00 ) c8_i = dcmplx ( 0.0D+00, 1.0D+00 ) do i = 1, n do j = 1, n angle = 2.0D+00 * pi * dble ( ( i - 1 ) * ( j - 1 ) ) & / dble ( n ) a(i,j) = exp ( c8_i * angle ) / sqrt ( dble ( n ) ) end do end do return end subroutine c8mat_test_inverse ( n, a ) c*********************************************************************72 c cc c8mat_test_inverse() returns the inverse of the test matrix. c c Licensing: c c This code is distributed under the MIT license. c c Modified: c c 03 April 2014 c c Author: c c John Burkardt c c Parameters: c c Input, integer N, the order of the matrix. c c Output, double complex A(N,N), the matrix. c implicit none integer n double complex a(n,n) double complex b(n,n) integer i integer j call c8mat_test ( n, b ) do j = 1, n do i = 1, n a(i,j) = dconjg ( b(j,i) ) end do end do return end function lsame ( ca, cb ) c*********************************************************************72 c cc lsame() returns TRUE if CA is the same letter as CB regardless of case. c c Licensing: c c This code is distributed under the MIT license. c c Modified: c c 09 February 2014 c c Author: c c Original FORTRAN77 version by Jack Dongarra. c This version by John Burkardt. c c Reference: c c Jack Dongarra, Jim Bunch, Cleve Moler, Pete Stewart, c LINPACK User's Guide, c SIAM, 1979, c ISBN13: 978-0-898711-72-1, c LC: QA214.L56. c c Charles Lawson, Richard Hanson, David Kincaid, Fred Krogh, c Basic Linear Algebra Subprograms for FORTRAN usage, c ACM Transactions on Mathematical Software, c Volume 5, Number 3, pages 308-323, 1979. c c Parameters: c c Input, character CA, CB, the character to compare. c c Output, logical LSAME, is TRUE if the characters are equal, c disregarding case. c implicit none character ca character cb intrinsic ichar integer inta integer intb logical lsame integer zcode c c Test if the characters are equal. c lsame = ca .eq. cb if ( lsame ) then return end if c c Now test for equivalence if both characters are alphabetic. c zcode = ichar ( 'Z' ) c c Use 'Z' rather than 'A' so that ASCII can be detected on Prime c machines, on which ICHAR returns a value with bit 8 set. c ICHAR('A') on Prime machines returns 193 which is the same as c ICHAR('A') on an EBCDIC machine. c inta = ichar ( ca ) intb = ichar ( cb ) c c ASCII is assumed. c ZCODE is the ASCII code of either lower or upper case 'Z'. c if ( zcode .eq. 90 .or. zcode .eq. 122 ) then if ( inta .ge. 97 .and. inta .le. 122 ) then inta = inta - 32 end if if ( intb .ge. 97 .and. intb .le. 122 ) then intb = intb - 32 end if c c EBCDIC is assumed. c ZCODE is the EBCDIC code of either lower or upper case 'Z'. c else if ( zcode .eq. 233 .or. zcode .eq. 169 ) then if ( inta .ge. 129 .and. inta .le. 137 .or. & inta .ge. 145 .and. inta .le. 153 .or. & inta .ge. 162 .and. inta .le. 169 ) then inta = inta + 64 end if if ( intb .ge. 129 .and. intb .le. 137 .or. & intb .ge. 145 .and. intb .le. 153 .or. & intb .ge. 162 .and. intb .le. 169 ) then intb = intb + 64 end if c c ASCII is assumed, on Prime machines. c ZCODE is the ASCII code plus 128 of either lower or upper case 'Z'. c else if ( zcode .eq. 218 .or. zcode .eq. 250 ) then if ( inta .ge. 225 .and. inta .le. 250 ) then inta = inta - 32 end if if ( intb .ge. 225 .and. intb .le. 250 ) then intb = intb - 32 end if end if lsame = inta .eq. intb return end subroutine timestamp ( ) c*********************************************************************72 c cc timestamp() prints out the current YMDHMS date as a timestamp. c c Licensing: c c This code is distributed under the MIT license. c c Modified: c c 16 September 2005 c c Author: c c John Burkardt c c Parameters: c c None c implicit none character ( len = 8 ) date character ( len = 10 ) time call date_and_time ( date, time ) write ( *, '(a8,2x,a10)' ) date, time return end subroutine xerbla ( srname, info ) c*********************************************************************72 c cc xerbla() is an error handler. c c Discussion: c c XERBLA is called if an input parameter has an invalid value. c A message is printed and execution stops. c c Licensing: c c This code is distributed under the MIT license. c c Modified: c c 09 February 2014 c c Author: c c Original FORTRAN77 version by Jack Dongarra. c This version by John Burkardt. c c Reference: c c Jack Dongarra, Jim Bunch, Cleve Moler, Pete Stewart, c LINPACK User's Guide, c SIAM, 1979, c ISBN13: 978-0-898711-72-1, c LC: QA214.L56. c c Charles Lawson, Richard Hanson, David Kincaid, Fred Krogh, c Basic Linear Algebra Subprograms for FORTRAN usage, c ACM Transactions on Mathematical Software, c Volume 5, Number 3, pages 308-323, 1979. c c Parameters: c c Input, character * ( * ) SRNAME, the name of the routine c which called XERBLA. c c Input, integer INFO, the position of the invalid parameter in the c parameter list of the calling routine. c implicit none integer info character * ( * ) srname write ( *, '(a)' ) ' ' write ( *, '(a)' ) 'XERBLA - Fatal error!' write ( *, '(a)' ) ' On entry to routine ' // trim ( srname ) write ( *, '(a)' ) ' an illegal value was detected for' write ( *, '(a,i6)' ) ' parameter number ', info stop 1 end