source: LMDZ5/trunk/libf/bibio/i1mach.F @ 2197

Last change on this file since 2197 was 2197, checked in by Ehouarn Millour, 9 years ago

Added 'implicit none' statements and proper variable definitions where they were missing.
EM

  • Property copyright set to
    Name of program: LMDZ
    Creation date: 1984
    Version: LMDZ5
    License: CeCILL version 2
    Holder: Laboratoire de m\'et\'eorologie dynamique, CNRS, UMR 8539
    See the license file in the root directory
File size: 4.5 KB
Line 
1*DECK I1MACH
2      INTEGER FUNCTION I1MACH (I)
3      IMPLICIT NONE
4C***BEGIN PROLOGUE  I1MACH
5C***PURPOSE  Return integer machine dependent constants.
6C***LIBRARY   SLATEC
7C***CATEGORY  R1
8C***TYPE      INTEGER (I1MACH-I)
9C***KEYWORDS  MACHINE CONSTANTS
10C***AUTHOR  Fox, P. A., (Bell Labs)
11C           Hall, A. D., (Bell Labs)
12C           Schryer, N. L., (Bell Labs)
13C***DESCRIPTION
14C
15C   I1MACH can be used to obtain machine-dependent parameters for the
16C   local machine environment.  It is a function subprogram with one
17C   (input) argument and can be referenced as follows:
18C
19C        K = I1MACH(I)
20C
21C   where I=1,...,16.  The (output) value of K above is determined by
22C   the (input) value of I.  The results for various values of I are
23C   discussed below.
24C
25C   I/O unit numbers:
26C     I1MACH( 1) = the standard input unit.
27C     I1MACH( 2) = the standard output unit.
28C     I1MACH( 3) = the standard punch unit.
29C     I1MACH( 4) = the standard error message unit.
30C
31C   Words:
32C     I1MACH( 5) = the number of bits per integer storage unit.
33C     I1MACH( 6) = the number of characters per integer storage unit.
34C
35C   Integers:
36C     assume integers are represented in the S-digit, base-A form
37C
38C                sign ( X(S-1)*A**(S-1) + ... + X(1)*A + X(0) )
39C
40C                where 0 .LE. X(I) .LT. A for I=0,...,S-1.
41C     I1MACH( 7) = A, the base.
42C     I1MACH( 8) = S, the number of base-A digits.
43C     I1MACH( 9) = A**S - 1, the largest magnitude.
44C
45C   Floating-Point Numbers:
46C     Assume floating-point numbers are represented in the T-digit,
47C     base-B form
48C                sign (B**E)*( (X(1)/B) + ... + (X(T)/B**T) )
49C
50C                where 0 .LE. X(I) .LT. B for I=1,...,T,
51C                0 .LT. X(1), and EMIN .LE. E .LE. EMAX.
52C     I1MACH(10) = B, the base.
53C
54C   Single-Precision:
55C     I1MACH(11) = T, the number of base-B digits.
56C     I1MACH(12) = EMIN, the smallest exponent E.
57C     I1MACH(13) = EMAX, the largest exponent E.
58C
59C   Double-Precision:
60C     I1MACH(14) = T, the number of base-B digits.
61C     I1MACH(15) = EMIN, the smallest exponent E.
62C     I1MACH(16) = EMAX, the largest exponent E.
63C
64C   To alter this function for a particular environment, the desired
65C   set of DATA statements should be activated by removing the C from
66C   column 1.  Also, the values of I1MACH(1) - I1MACH(4) should be
67C   checked for consistency with the local operating system.
68C
69C***REFERENCES  P. A. Fox, A. D. Hall and N. L. Schryer, Framework for
70C                 a portable library, ACM Transactions on Mathematical
71C                 Software 4, 2 (June 1978), pp. 177-188.
72C***ROUTINES CALLED  (NONE)
73C***REVISION HISTORY  (YYMMDD)
74C   750101  DATE WRITTEN
75C   891012  Added VAX G-floating constants.  (WRB)
76C   891012  REVISION DATE from Version 3.2
77C   891214  Prologue converted to Version 4.0 format.  (BAB)
78C   900618  Added DEC RISC constants.  (WRB)
79C   900723  Added IBM RS 6000 constants.  (WRB)
80C   901009  Correct I1MACH(7) for IBM Mainframes. Should be 2 not 16.
81C           (RWC)
82C   910710  Added HP 730 constants.  (SMR)
83C   911114  Added Convex IEEE constants.  (WRB)
84C   920121  Added SUN -r8 compiler option constants.  (WRB)
85C   920229  Added Touchstone Delta i860 constants.  (WRB)
86C   920501  Reformatted the REFERENCES section.  (WRB)
87C   920625  Added Convex -p8 and -pd8 compiler option constants.
88C           (BKS, WRB)
89C   930201  Added DEC Alpha and SGI constants.  (RWC and WRB)
90C   930618  Corrected I1MACH(5) for Convex -p8 and -pd8 compiler
91C           options.  (DWL, RWC and WRB).
92C   100623  Use Fortran 95 intrinsic functions (Lionel GUEZ)
93C***END PROLOGUE  I1MACH
94C
95      INTEGER IMACH(16),OUTPUT
96      SAVE IMACH
97      EQUIVALENCE (IMACH(4),OUTPUT)
98      INTEGER I
99C***FIRST EXECUTABLE STATEMENT  I1MACH
100      IMACH( 1) =         5
101      IMACH( 2) =         6
102      IMACH( 3) =         6
103      IMACH( 4) =         6
104      IMACH( 5) =        bit_size(0)
105      IMACH( 6) =         IMACH( 5) / 8
106      IMACH( 7) =         radix(0)
107      IMACH( 8) =        digits(0)
108      IMACH( 9) =     huge(0)
109      IMACH(10) =         radix(0.)
110      IMACH(11) =        digits(0.)
111      IMACH(12) =      minexponent(0.)
112      IMACH(13) =       maxexponent(0.)
113      IMACH(14) =        digits(0d0)
114      IMACH(15) =      minexponent(0d0)
115      IMACH(16) =       maxexponent(0d0)
116      IF (I .LT. 1  .OR.  I .GT. 16) GO TO 10
117C
118      I1MACH = IMACH(I)
119      RETURN
120C
121   10 CONTINUE
122      WRITE (UNIT = OUTPUT, FMT = 9000)
123 9000 FORMAT ('1ERROR    1 IN I1MACH - I OUT OF BOUNDS')
124C
125C     CALL FDUMP
126C
127      STOP
128      END
Note: See TracBrowser for help on using the repository browser.