File: IB01OY.f

package info (click to toggle)
dynare 4.3.0-2
  • links: PTS, VCS
  • area: main
  • in suites: wheezy
  • size: 40,640 kB
  • sloc: fortran: 82,231; cpp: 72,734; ansic: 28,874; pascal: 13,241; sh: 4,300; objc: 3,281; yacc: 2,833; makefile: 1,288; lex: 1,162; python: 162; lisp: 54; xml: 8
file content (175 lines) | stat: -rw-r--r-- 5,346 bytes parent folder | download
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
      SUBROUTINE IB01OY( NS, NMAX, N, SV, INFO )
C
C     SLICOT RELEASE 5.0.
C
C     Copyright (c) 2002-2009 NICONET e.V.
C
C     This program is free software: you can redistribute it and/or
C     modify it under the terms of the GNU General Public License as
C     published by the Free Software Foundation, either version 2 of
C     the License, or (at your option) any later version.
C
C     This program is distributed in the hope that it will be useful,
C     but WITHOUT ANY WARRANTY; without even the implied warranty of
C     MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
C     GNU General Public License for more details.
C
C     You should have received a copy of the GNU General Public License
C     along with this program.  If not, see
C     <http://www.gnu.org/licenses/>.
C
C     PURPOSE
C
C     To ask for user's confirmation of the system order found by
C     SLICOT Library routine IB01OD. This routine may be modified,
C     but its interface must be preserved.
C
C     ARGUMENTS
C
C     Input/Output Parameters
C
C     NS      (input) INTEGER
C             The number of singular values.  NS > 0.
C
C     NMAX    (input) INTEGER
C             The maximum value of the system order.  0 <= NMAX <= NS.
C
C     N       (input/output) INTEGER
C             On entry, the estimate of the system order computed by
C             IB01OD routine.  0 <= N <= NS.
C             On exit, the user's estimate of the system order, which
C             could be identical with the input value of  N.
C             Note that the output value of  N  should be less than
C             or equal to  NMAX.
C
C     SV      (input) DOUBLE PRECISION array, dimension ( NS )
C             The singular values, in descending order, used for
C             determining the system order.
C
C     Error Indicator
C
C     INFO    INTEGER
C             = 0:  successful exit;
C             < 0:  if INFO = -i, the i-th argument had an illegal
C                   value.
C
C     CONTRIBUTORS
C
C     V. Sima, Research Institute for Informatics, Bucharest, Aug. 1999.
C
C     REVISIONS
C
C     -
C
C     KEYWORDS
C
C     Identification, parameter estimation, singular values, structure
C     identification.
C
C  *********************************************************************
C
C     .. Parameters ..
      INTEGER            INTRMN, OUTRMN
      PARAMETER          ( INTRMN = 5, OUTRMN = 6 )
C        INTRMN is the unit number for the (terminal) input device.
C        OUTRMN is the unit number for the (terminal) output device.
C     ..
C     .. Scalar Arguments ..
      INTEGER            INFO, N, NMAX, NS
C     ..
C     .. Array Arguments ..
      DOUBLE PRECISION   SV( * )
C     ..
C     .. Local Scalars ..
      LOGICAL            YES
      INTEGER            I
      CHARACTER          ANS
C     ..
C     .. External Functions ..
      LOGICAL            LSAME
      EXTERNAL           LSAME
C     ..
C     .. External Subroutines ..
      EXTERNAL           XERBLA
C
C     .. Executable Statements ..
C
C     Check the scalar input parameters.
C
      INFO = 0
      IF( NS.LE.0 ) THEN
         INFO = -1
      ELSE IF( NMAX.LT.0 .OR. NMAX.GT.NS ) THEN
         INFO = -2
      ELSE IF( N.LT.0 .OR. N.GT.NS ) THEN
         INFO = -3
      END IF
C
      IF( INFO.NE.0 ) THEN
         CALL XERBLA( 'IB01OY', -INFO )
         RETURN
      END IF
C
      WRITE( OUTRMN, '(/'' Singular values (in descending order) used'',
     $                  '' to estimate the system order:'', //
     $                     (5D15.8) )' ) ( SV(I), I = 1, NS )
      WRITE( OUTRMN, '(/'' Estimated order of the system,  n = '', I5 )'
     $     )               N
      WRITE( OUTRMN, '(/'' Do you want this value of  n  to be used'',
     $                  '' to determine the system matrices?'' )' )
C
   10 CONTINUE
         WRITE( OUTRMN, '(/''  Type "yes" or "no":  '' )' )
         READ ( INTRMN,  '( A )' ) ANS
         YES = LSAME( ANS, 'Y' )
         IF( YES ) THEN
            IF( N.LE.NMAX ) THEN
C
C              The value of n is adequate and has been confirmed.
C
               RETURN
            ELSE
C
C              The estimated value of n is not acceptable.
C
               WRITE( OUTRMN, '(/'' n  should be less than or equal'',
     $                           '' to '', I5 )' ) NMAX
               WRITE( OUTRMN, '( '' (It may be useful to restart'',
     $                           '' with a larger tolerance.)'' )' )
               GO TO 20
            END IF
C
         ELSE IF( LSAME( ANS, 'N' ) ) THEN
            GO TO 20
         ELSE
C
C           Wrong answer should be re-entered.
C
            GO TO 10
         END IF
C
C     Enter the desired value of n.
C
   20 CONTINUE
         WRITE( OUTRMN,'(/'' Enter the desired value of n (n <= '', I5,
     $                    '');  n = '' )' ) NMAX
         READ ( INTRMN, * ) N
         IF ( N.LT.0 ) THEN
C
C           The specified value of n is not acceptable.
C
            WRITE( OUTRMN, '(/'' n  should be larger than zero.'' )' )
            GO TO 20
         ELSE IF ( N.GT.NMAX ) THEN
C
C           The specified value of n is not acceptable.
C
            WRITE( OUTRMN, '(/'' n  should be less than or equal to '',
     $                   I5 )' ) NMAX
            GO TO 20
         END IF
C
      RETURN
C
C *** Last line of IB01OY ***
      END