File: MC01SY.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 (146 lines) | stat: -rw-r--r-- 4,015 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
      SUBROUTINE MC01SY( M, E, B, A, OVFLOW )
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 find a real number A from its mantissa M and its exponent E,
C     i.e.,
C        A = M * B**E.
C     M and E need not be the standard floating-point values.
C     If ABS(A) < B**(EMIN-1), i.e. the smallest positive model number,
C     then the routine returns A = 0.
C     If M = 0, then the routine returns A = 0 regardless of the value
C     of E.
C
C     ARGUMENTS
C
C     Input/Output Parameters
C
C     M       (input) DOUBLE PRECISION
C             The mantissa of the floating-point representation of A.
C
C     E       (input) INTEGER
C             The exponent of the floating-point representation of A.
C
C     B       (input) INTEGER
C             The base of the floating-point arithmetic.
C
C     A       (output) DOUBLE PRECISION
C             The value of M * B**E.
C
C     OVFLOW  (output) LOGICAL
C             The value .TRUE., if ABS(M) * B**E >= B**EMAX (where EMAX
C             is the largest possible exponent) and .FALSE. otherwise.
C             A is not defined if OVFLOW = .TRUE..
C
C     NUMERICAL ASPECTS
C
C     None.
C
C     CONTRIBUTOR
C
C     Release 3.0: V. Sima, Katholieke Univ. Leuven, Belgium, Mar. 1997.
C     Supersedes Release 2.0 routine MC01GY by A.J. Geurts.
C
C     REVISIONS
C
C     -
C
C     ******************************************************************
C
C     .. Parameters ..
      DOUBLE PRECISION  ZERO, ONE
      PARAMETER         ( ZERO = 0.0D0, ONE = 1.0D0 )
C     .. Scalar Arguments ..
      LOGICAL           OVFLOW
      INTEGER           B, E
      DOUBLE PRECISION  A, M
C     .. Local Scalars ..
      INTEGER           EMAX, EMIN, ET, EXPON
      DOUBLE PRECISION  BASE, MT
C     .. External Functions ..
      DOUBLE PRECISION  DLAMCH
      EXTERNAL          DLAMCH
C     .. Intrinsic Functions ..
      INTRINSIC         ABS, MOD
C     .. Executable Statements ..
C
      OVFLOW = .FALSE.
C
      IF ( ( M.EQ.ZERO ) .OR. ( E.EQ.0 ) ) THEN
         A = M
         RETURN
      END IF
C
C     Determination of the mantissa MT and the exponent ET of the
C     standard floating-point representation.
C
      EMIN = DLAMCH( 'Minimum exponent' )
      EMAX = DLAMCH( 'Largest exponent' )
      MT = M
      ET = E
C     WHILE ( ABS( MT ) >= B ) DO
   20 IF ( ABS( MT ).GE.B ) THEN
         MT = MT/B
         ET = ET + 1
         GO TO 20
      END IF
C     END WHILE 20
C     WHILE ( ABS( MT ) < 1 ) DO
   40 IF ( ABS( MT ).LT.ONE ) THEN
         MT = MT*B
         ET = ET - 1
         GO TO 40
      END IF
C     END WHILE 40
C
      IF ( ET.LT.EMIN ) THEN
         A = ZERO
         RETURN
      END IF
C
      IF ( ET.GE.EMAX ) THEN
         OVFLOW = .TRUE.
         RETURN
      END IF
C
C     Computation of the value of A by the relation
C     M * B**E = A * (BASE)**EXPON
C
      EXPON = ABS( ET )
      A = MT
      BASE = B
      IF ( ET.LT.0 ) BASE = ONE/BASE
C     WHILE ( not EXPON = 0 ) DO
   60 IF ( EXPON.NE.0 ) THEN
         IF ( MOD( EXPON, 2 ).EQ.0 ) THEN
            BASE = BASE*BASE
            EXPON = EXPON/2
         ELSE
            A = A*BASE
            EXPON = EXPON - 1
         END IF
         GO TO 60
      END IF
C     END WHILE 60
C
      RETURN
C *** Last line of MC01SY ***
      END