Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

zlanhf (3p)

Name

zlanhf - norm, or the Frobenius norm, or the infinity norm, or the element of largest absolute value of a Hermitian matrix in RFP format

Synopsis

DOUBLE PRECISION FUNCTION ZLANHF(NORM, TRANSR, UPLO, N, A, WORK)


CHARACTER*1 NORM, TRANSR, UPLO

INTEGER N

DOUBLE PRECISION WORK(0: *)

DOUBLE COMPLEX A(0: *)


DOUBLE PRECISION FUNCTION ZLANHF_64(NORM, TRANSR, UPLO, N, A, WORK)


CHARACTER*1 NORM, TRANSR, UPLO

INTEGER*8 N

DOUBLE PRECISION WORK(0: *)

DOUBLE COMPLEX A(0: *)


F95 INTERFACE
REAL(8) FUNCTION LANHF(NORM, TRANSR, UPLO, N, A, WORK)


INTEGER :: N

CHARACTER(LEN=1) :: NORM, TRANSR, UPLO

COMPLEX(8), DIMENSION(:) :: A

REAL(8), DIMENSION(:) :: WORK


REAL(8) FUNCTION LANHF_64(NORM, TRANSR, UPLO, N, A, WORK)


INTEGER(8) :: N

CHARACTER(LEN=1) :: NORM, TRANSR, UPLO

COMPLEX(8), DIMENSION(:) :: A

REAL(8), DIMENSION(:) :: WORK


C INTERFACE
#include <sunperf.h>

double  zlanhf (char norm, char transr, char uplo, int n, doublecomplex
*a);

double zlanhf_64 (char norm, char transr, char uplo, long n, doublecom-
plex *a);

Description

Oracle Solaris Studio Performance Library                           zlanhf(3P)



NAME
       zlanhf  - return the value of the 1-norm, or the Frobenius norm, or the
       infinity norm, or the element of largest absolute value of a  Hermitian
       matrix in RFP format


SYNOPSIS
       DOUBLE PRECISION FUNCTION ZLANHF(NORM, TRANSR, UPLO, N, A, WORK)


       CHARACTER*1 NORM, TRANSR, UPLO

       INTEGER N

       DOUBLE PRECISION WORK(0: *)

       DOUBLE COMPLEX A(0: *)


       DOUBLE PRECISION FUNCTION ZLANHF_64(NORM, TRANSR, UPLO, N, A, WORK)


       CHARACTER*1 NORM, TRANSR, UPLO

       INTEGER*8 N

       DOUBLE PRECISION WORK(0: *)

       DOUBLE COMPLEX A(0: *)


   F95 INTERFACE
       REAL(8) FUNCTION LANHF(NORM, TRANSR, UPLO, N, A, WORK)


       INTEGER :: N

       CHARACTER(LEN=1) :: NORM, TRANSR, UPLO

       COMPLEX(8), DIMENSION(:) :: A

       REAL(8), DIMENSION(:) :: WORK


       REAL(8) FUNCTION LANHF_64(NORM, TRANSR, UPLO, N, A, WORK)


       INTEGER(8) :: N

       CHARACTER(LEN=1) :: NORM, TRANSR, UPLO

       COMPLEX(8), DIMENSION(:) :: A

       REAL(8), DIMENSION(:) :: WORK


   C INTERFACE
       #include <sunperf.h>

       double  zlanhf (char norm, char transr, char uplo, int n, doublecomplex
                 *a);

       double zlanhf_64 (char norm, char transr, char uplo, long n, doublecom-
                 plex *a);


PURPOSE
       zlanhf returns the value of the one norm, or the Frobenius norm, or the
       infinity norm, or the element of largest absolute value  of  a  complex
       Hermitian matrix A in RFP format.

       ZLANHF  =  (  max(abs(A(i,j))),  NORM  =  'M'  or  'm'  (  (  norm1(A),
       NORM = '1', 'O' or 'o' ( ( normI(A),         NORM =  'I'  or  'i'  (  (
       normF(A),         NORM = 'F', 'f', 'E' or 'e'

       where  norm1  denotes  the  one  norm of a matrix (maximum column sum),
       normI denotes the infinity norm of a matrix (maximum row sum) and normF
       denotes the Frobenius norm of a matrix (square root of sum of squares).
       Note that  max(abs(A(i,j))) is not a  matrix norm.


ARGUMENTS
       NORM (input)
                 NORM is CHARACTER
                 Specifies the value to be returned  in  ZLANHF  as  described
                 above.


       TRANSR (input)
                 TRANSR is CHARACTER
                 Specifies whether the RFP format of A is normal or conjugate-
                 transposed format.
                 = 'N':  RFP format is Normal
                 = 'C':  RFP format is Conjugate-transposed


       UPLO (input)
                 UPLO is CHARACTER
                 On entry, UPLO specifies whether the RFP matrix A  came  from
                 an upper or lower triangular matrix as follows:
                 UPLO = 'U' or 'u' RFP A came from an upper triangular matrix
                 UPLO = 'L' or 'l' RFP A came from a  lower triangular matrix


       N (input)
                 N is INTEGER
                 The  order of the matrix A. N >= 0. When N = 0, ZLANHF is set
                 to zero.


       A (input)
                 A is COMPLEX*16 array, dimension ( N*(N+1)/2 );
                 On entry,  the  matrix  A  in  RFP  Format.   RFP  Format  is
                 described  by  TRANSR,  UPLO  and N as follows: If TRANSR='N'
                 then RFP A is (0:N,0:K-1) when N is even;  K=N/2.  RFP  A  is
                 (0:N-1,0:K) when N is odd; K=N/2. If TRANSR = 'C' then RFP is
                 the Conjugate-transpose of RFP A as  defined  when  TRANSR  =
                 'N'. The contents of RFP A are defined by UPLO as follows: If
                 UPLO = 'U' the RFP A contains the ( N*(N+1)/2 )  elements  of
                 upper  packed  A either in normal or conjugate-transpose For-
                 mat. If UPLO = 'L' the RFP A contains the ( N*(N+1) /2 ) ele-
                 ments  of lower packed A either in normal or conjugate-trans-
                 pose Format. The LDA of RFP A is (N+1)/2 when TRANSR  =  'C'.
                 When  TRANSR  is  'N'  the LDA is N+1 when N is even and is N
                 when is odd. See the Note below for more details.   Unchanged
                 on exit.


       WORK (output)
                 WORK is DOUBLE PRECISION array, dimension (LWORK),
                 where  LWORK  >=  N when NORM = 'I' or '1' or 'O'; otherwise,
                 WORK is not referenced.


FURTHER DETAILS
         We first consider Standard Packed Format when N is even.
         We give an example where N = 6.

             AP is Upper             AP is Lower

          00 01 02 03 04 05       00
             11 12 13 14 15       10 11
                22 23 24 25       20 21 22
                   33 34 35       30 31 32 33
                      44 45       40 41 42 43 44
                         55       50 51 52 53 54 55

         Let TRANSR = 'N'. RFP holds AP as follows:
         For UPLO = 'U' the upper trapezoid A(0:5,0:2) consists of the last
         three columns of AP upper. The lower triangle A(4:6,0:2) consists of
         conjugate-transpose of the first three columns of AP upper.
         For UPLO = 'L' the lower trapezoid A(1:6,0:2) consists of the first
         three columns of AP lower. The upper triangle A(0:2,0:2) consists of
         conjugate-transpose of the last three columns of AP lower.
         To denote conjugate we place -- above the element. This covers the
         case N even and TRANSR = 'N'.

                RFP A                   RFP A

                                       -- -- --
               03 04 05                33 43 53
                                          -- --
               13 14 15                00 44 54
                                             --
               23 24 25                10 11 55

               33 34 35                20 21 22
               --
               00 44 45                30 31 32
               -- --
               01 11 55                40 41 42
               -- -- --
               02 12 22                50 51 52

         Now let TRANSR = 'C'. RFP A in both UPLO cases is just the conjugate-
         transpose of RFP A above. One therefore gets:

                  RFP A                   RFP A

            -- -- -- --                -- -- -- -- -- --
            03 13 23 33 00 01 02    33 00 10 20 30 40 50
            -- -- -- -- --                -- -- -- -- --
            04 14 24 34 44 11 12    43 44 11 21 31 41 51
            -- -- -- -- -- --                -- -- -- --
            05 15 25 35 45 55 22    53 54 55 22 32 42 52

         We next  consider Standard Packed Format when N is odd.
         We give an example where N = 5.

            AP is Upper                 AP is Lower

          00 01 02 03 04              00
             11 12 13 14              10 11
                22 23 24              20 21 22
                   33 34              30 31 32 33
                      44              40 41 42 43 44

         Let TRANSR = 'N'. RFP holds AP as follows:
         For UPLO = 'U' the upper trapezoid A(0:4,0:2) consists of the last
         three columns of AP upper. The lower triangle A(3:4,0:1) consists of
         conjugate-transpose of the first two   columns of AP upper.
         For UPLO = 'L' the lower trapezoid A(0:4,0:2) consists of the first
         three columns of AP lower. The upper triangle A(0:1,1:2) consists of
         conjugate-transpose of the last two   columns of AP lower.
         To denote conjugate we place -- above the element. This covers the
         case N odd  and TRANSR = 'N'.

                RFP A                   RFP A

                                          -- --
               02 03 04                00 33 43
                                             --
               12 13 14                10 11 44

               22 23 24                20 21 22
               --
               00 33 34                30 31 32
               -- --
               01 11 44                40 41 42

         Now let TRANSR = 'C'. RFP A in both UPLO cases is just the conjugate-
         transpose of RFP A above. One therefore gets:

                  RFP A                   RFP A

            -- -- --                   -- -- -- -- -- --
            02 12 22 00 01             00 10 20 30 40 50
            -- -- -- --                   -- -- -- -- --
            03 13 23 33 11             33 11 21 31 41 51
            -- -- -- -- --                   -- -- -- --
            04 14 24 34 44             43 44 22 32 42 52




                                  7 Nov 2015                        zlanhf(3P)