AB07MD

Dual of a given state-space representation

[Specification] [Arguments] [Method] [References] [Comments] [Example]

Purpose

  To find the dual of a given state-space representation.

Specification
      SUBROUTINE AB07MD( JOBD, N, M, P, A, LDA, B, LDB, C, LDC, D, LDD,
     $                   INFO )
C     .. Scalar Arguments ..
      CHARACTER         JOBD
      INTEGER           INFO, LDA, LDB, LDC, LDD, M, N, P
C     .. Array Arguments ..
      DOUBLE PRECISION  A(LDA,*), B(LDB,*), C(LDC,*), D(LDD,*)

Arguments

Mode Parameters

  JOBD    CHARACTER*1
          Specifies whether or not a non-zero matrix D appears in
          the given state space model:
          = 'D':  D is present;
          = 'Z':  D is assumed a zero matrix.

Input/Output Parameters
  N       (input) INTEGER
          The order of the state-space representation.  N >= 0.

  M       (input) INTEGER
          The number of system inputs.  M >= 0.

  P       (input) INTEGER
          The number of system outputs.  P >= 0.

  A       (input/output) DOUBLE PRECISION array, dimension (LDA,N)
          On entry, the leading N-by-N part of this array must
          contain the original state dynamics matrix A.
          On exit, the leading N-by-N part of this array contains
          the dual state dynamics matrix A'.

  LDA     INTEGER
          The leading dimension of array A.  LDA >= MAX(1,N).

  B       (input/output) DOUBLE PRECISION array, dimension
          (LDB,MAX(M,P))
          On entry, the leading N-by-M part of this array must
          contain the original input/state matrix B.
          On exit, the leading N-by-P part of this array contains
          the dual input/state matrix C'.

  LDB     INTEGER
          The leading dimension of array B.  LDB >= MAX(1,N).

  C       (input/output) DOUBLE PRECISION array, dimension (LDC,N)
          On entry, the leading P-by-N part of this array must
          contain the original state/output matrix C.
          On exit, the leading M-by-N part of this array contains
          the dual state/output matrix B'.

  LDC     INTEGER
          The leading dimension of array C.
          LDC >= MAX(1,M,P) if N > 0.
          LDC >= 1 if N = 0.

  D       (input/output) DOUBLE PRECISION array, dimension
          (LDD,MAX(M,P))
          On entry, if JOBD = 'D', the leading P-by-M part of this
          array must contain the original direct transmission
          matrix D.
          On exit, if JOBD = 'D', the leading M-by-P part of this
          array contains the dual direct transmission matrix D'.
          The array D is not referenced if JOBD = 'Z'.

  LDD     INTEGER
          The leading dimension of array D.
          LDD >= MAX(1,M,P) if JOBD = 'D'.
          LDD >= 1 if JOBD = 'Z'.

Error Indicator
  INFO    INTEGER
          = 0:  successful exit;
          < 0:  if INFO = -i, the i-th argument had an illegal
                value.

Method
  If the given state-space representation is the M-input/P-output
  (A,B,C,D), its dual is simply the P-input/M-output (A',C',B',D').

References
  None

Numerical Aspects
  None

Further Comments
  None
Example

Program Text

*     AB07MD EXAMPLE PROGRAM TEXT
*     Copyright (c) 2002-2017 NICONET e.V.
*
*     .. Parameters ..
      INTEGER          NIN, NOUT
      PARAMETER        ( NIN = 5, NOUT = 6 )
      INTEGER          NMAX, MMAX, PMAX
      PARAMETER        ( NMAX = 20, MMAX = 20, PMAX = 20 )
      INTEGER          MAXMP
      PARAMETER        ( MAXMP = MAX( MMAX, PMAX ) )
      INTEGER          LDA, LDB, LDC, LDD
      PARAMETER        ( LDA = NMAX, LDB = NMAX, LDC = MAXMP,
     $                   LDD = MAXMP )
*     .. Local Scalars ..
      CHARACTER*1      JOBD
      INTEGER          I, INFO, J, M, N, P
*     .. Local Arrays ..
      DOUBLE PRECISION A(LDA,NMAX), B(LDB,MAXMP), C(LDC,NMAX),
     $                 D(LDD,MAXMP)
*     .. External functions ..
      LOGICAL          LSAME
      EXTERNAL         LSAME
*     .. External Subroutines ..
      EXTERNAL         AB07MD
*     .. Intrinsic Functions ..
      INTRINSIC        MAX
*     .. Executable Statements ..
*
      WRITE ( NOUT, FMT = 99999 )
*     Skip the heading in the data file and read in the data.
      READ ( NIN, FMT = '()' )
      READ ( NIN, FMT = * ) N, M, P, JOBD
      IF ( N.LE.0 .OR. N.GT.NMAX ) THEN
         WRITE ( NOUT, FMT = 99992 ) N
      ELSE
         READ ( NIN, FMT = * ) ( ( A(I,J), J = 1,N ), I = 1,N )
         IF ( M.LE.0 .OR. M.GT.MMAX ) THEN
            WRITE ( NOUT, FMT = 99991 ) M
         ELSE
            READ ( NIN, FMT = * ) ( ( B(I,J), J = 1,M ), I = 1,N )
            IF ( P.LE.0 .OR. P.GT.PMAX ) THEN
               WRITE ( NOUT, FMT = 99990 ) P
            ELSE
               READ ( NIN, FMT = * ) ( ( C(I,J), J = 1,N ), I = 1,P )
               READ ( NIN, FMT = * ) ( ( D(I,J), J = 1,M ), I = 1,P )
*              Find the dual of the ssr (A,B,C,D).
               CALL AB07MD( JOBD, N, M, P, A, LDA, B, LDB, C, LDC, D,
     $                      LDD, INFO )
*
               IF ( INFO.NE.0 ) THEN
                  WRITE ( NOUT, FMT = 99998 ) INFO
               ELSE
                  WRITE ( NOUT, FMT = 99997 )
                  DO 20 I = 1, N
                     WRITE ( NOUT, FMT = 99996 ) ( A(I,J), J = 1,N )
   20             CONTINUE
                  WRITE ( NOUT, FMT = 99995 )
                  DO 40 I = 1, N
                     WRITE ( NOUT, FMT = 99996 ) ( B(I,J), J = 1,P )
   40             CONTINUE
                  WRITE ( NOUT, FMT = 99994 )
                  DO 60 I = 1, M
                     WRITE ( NOUT, FMT = 99996 ) ( C(I,J), J = 1,N )
   60             CONTINUE
                  IF ( LSAME( JOBD, 'D' ) ) THEN
                     WRITE ( NOUT, FMT = 99993 )
                     DO 80 I = 1, M
                        WRITE ( NOUT, FMT = 99996 ) ( D(I,J), J = 1,P )
   80                CONTINUE
                  END IF
               END IF
            END IF
         END IF
      END IF
      STOP
*
99999 FORMAT (' AB07MD EXAMPLE PROGRAM RESULTS',/1X)
99998 FORMAT (' INFO on exit from AB07MD = ',I2)
99997 FORMAT (' The dual state dynamics matrix is ')
99996 FORMAT (20(1X,F8.4))
99995 FORMAT (/' The dual input/state matrix is ')
99994 FORMAT (/' The dual state/output matrix is ')
99993 FORMAT (/' The dual direct transmission matrix is ')
99992 FORMAT (/' N is out of range.',/' N = ',I5)
99991 FORMAT (/' M is out of range.',/' M = ',I5)
99990 FORMAT (/' P is out of range.',/' P = ',I5)
      END
Program Data
 AB07MD EXAMPLE PROGRAM DATA
   3     1     2     D
   1.0   2.0   0.0
   4.0  -1.0   0.0
   0.0   0.0   1.0
   1.0   0.0   1.0
   0.0   1.0  -1.0
   0.0   0.0   1.0
   0.0   1.0
Program Results
 AB07MD EXAMPLE PROGRAM RESULTS

 The dual state dynamics matrix is 
   1.0000   4.0000   0.0000
   2.0000  -1.0000   0.0000
   0.0000   0.0000   1.0000

 The dual input/state matrix is 
   0.0000   0.0000
   1.0000   0.0000
  -1.0000   1.0000

 The dual state/output matrix is 
   1.0000   0.0000   1.0000

 The dual direct transmission matrix is 
   0.0000   1.0000

Return to index