⭐ 欢迎来到虫虫下载站! | 📦 资源下载 📁 资源专辑 ℹ️ 关于我们
⭐ 虫虫下载站

📄 fitab.gml

📁 开放源码的编译器open watcom 1.6.0版的源代码
💻 GML
📖 第 1 页 / 共 2 页
字号:
:set symbol="arrow"   value=";.sf7;.ct ~L;.esf;.ct ".
:cmt. - is a minus
.np
The following sections give tables of all generic and specific names of
intrinsic functions and describe how they are used.
The following is a guide to interpreting those tables.
.np
Data types are represented by letter codes.
.autopoint
.point
CHARACTER is represented by CH.
.point
LOGICAL is represented by L.
.point
INTEGER is represented by I.
.point
.xt INTEGER*2 is represented by H.
.point
REAL
.xt (REAL*4)
is represented by R.
.point
DOUBLE PRECISION
.xt (REAL*8)
is represented by D.
.point
Single precision COMPLEX
.xt (COMPLEX*8)
is represented by C.
.point
.xt Double precision COMPLEX (COMPLEX*16) is represented by Z.
.endpoint
.np
There are three columns to each table.
The "Definition" column gives the mathematical definition of the
function performed by the intrinsic function.
The "Name" column lists the specific and generic names of the intrinsic
functions.
The generic names are followed by the word "generic"; all other names
are specific names.
The "Usage" column describes how the intrinsic functions are used.
"R&arrow.ATAN2(R,R)" is a typical entry in this column.
The name of the intrinsic function always follows the "&arrow.".
In this example the name of the intrinsic function is ATAN2.
The data type of the arguments to the intrinsic function are enclosed
in parentheses,
are separated by commas and always follow the name of the intrinsic
function.
In this case, ATAN2 requires two arguments both of type REAL.
The type of the result of the intrinsic function is indicated by the
type preceding the "&arrow.".
In this case, the result of ATAN2 is of type REAL.
.np
&product extensions to the FORTRAN 77 language are flagged by
a dagger (&dagger).
.*
.cp 15
.section Type Conversion
.*
.ix 'generic function' INT
.ix 'intrinsic function' INT
.ix 'intrinsic function' IFIX
.ix 'intrinsic function' IDINT
.ix 'intrinsic function' HFIX
.ix INT
.ix IFIX
.ix IDINT
.ix HFIX
.sr c0=&INDlvl+1
.sr c1=&INDlvl+17
.sr c2=&INDlvl+30
.sr c3=&INDlvl+54
.* .box on 1 17 30 54
.box on &c0 &c1 &c2 &c3
\Definition\Name\Usage
.box
\Conversion to integer:\INT generic\I&arrow.INT(I)
\int(a)                \           \I&arrow.INT(R)
\                      \           \I&arrow.INT(D)
\                      \           \I&arrow.INT(C)
\                      \           \I&arrow.INT(Z) &dagger\
\                      \INT        \I&arrow.INT(R)
\                      \HFIX &dagger     \H&arrow.HFIX(R)
\                      \IFIX       \I&arrow.IFIX(R)
\                      \IDINT      \I&arrow.IDINT(D)
.box off
.im finote1
.ix 'generic function' REAL
.ix 'intrinsic function' REAL
.ix 'intrinsic function' FLOAT
.ix 'intrinsic function' SNGL
.ix REAL
.ix FLOAT
.ix SNGL
.cp 14
.box on &c0 &c1 &c2 &c3
\Definition\Name\Usage
.box
\Conversion to real\REAL generic\R&arrow.REAL(I)
\                  \            \R&arrow.REAL(R)
\                  \            \R&arrow.REAL(D)
\                  \            \R&arrow.REAL(C)
\                  \            \R&arrow.REAL(Z) &dagger\
\                  \REAL        \R&arrow.REAL(I)
\                  \FLOAT       \R&arrow.FLOAT(I)
\                  \SNGL        \R&arrow.SNGL(D)
.box off
.im finote2
.ix 'generic function' DBLE
.ix 'intrinsic function' DBLE
.ix 'intrinsic function' DREAL
.ix 'intrinsic function' DFLOAT
.ix DBLE
.ix DREAL
.ix DFLOAT
.cp 13
.box on &c0 &c1 &c2 &c3
\Definition\Name\Usage
.box
\Conversion to double \DBLE generic\D&arrow.DBLE(I)
\precision            \            \D&arrow.DBLE(R)
\                     \            \D&arrow.DBLE(D)
\                     \            \D&arrow.DBLE(C)
\                     \            \D&arrow.DBLE(Z) &dagger\
\                     \DREAL       \D&arrow.DREAL(Z) &dagger\
\                     \DFLOAT      \D&arrow.DFLOAT(I) &dagger\
.box off
.im finote3
.ix 'generic function' CMPLX
.ix 'intrinsic function' CMPLX
.ix CMPLX
.cp 11
.box on &c0 &c1 &c2 &c3
\Definition\Name\Usage
.box
\Conversion to complex \CMPLX generic \C&arrow.CMPLX(I)|C&arrow.CMPLX(I,I)
\                      \              \C&arrow.CMPLX(R)|C&arrow.CMPLX(R,R)
\                      \              \C&arrow.CMPLX(D)|C&arrow.CMPLX(D,D)
\                      \              \C&arrow.CMPLX(C)
\                      \              \C&arrow.CMPLX(Z) &dagger\
.box off
.im finote4a
.ix 'generic function' DCMPLX
.ix 'intrinsic function' DCMPLX
.ix DCMPLX
.cp 11
.box on &c0 &c1 &c2 &c3
\Definition\Name\Usage
.box
\Conversion to double \DCMPLX generic &dagger\Z&arrow.DCMPLX(I)|Z&arrow.DCMPLX(I,I)
\complex              \                \Z&arrow.DCMPLX(R)|Z&arrow.DCMPLX(R,R)
\                     \                \Z&arrow.DCMPLX(D)|Z&arrow.DCMPLX(D,D)
\                     \                \Z&arrow.DCMPLX(C)
\                     \                \Z&arrow.DCMPLX(Z)
.box off
.im finote4b
.ix 'intrinsic function' ICHAR
.ix ICHAR
.cp 7
.box on &c0 &c1 &c2 &c3
\Definition\Name\Usage
.box
\Conversion to integer \ICHAR \I&arrow.ICHAR(CH)
.box off
.im finote5a
.ix 'intrinsic function' CHAR
.ix CHAR
.cp 7
.box on &c0 &c1 &c2 &c3
\Definition\Name\Usage
.box
\Conversion to character \CHAR \CH&arrow.CHAR(I)
.box off
.im finote5b
.*
.cp 15
.section Truncation
.*
.ix 'generic function' AINT
.ix 'intrinsic function' AINT
.ix 'intrinsic function' DINT
.ix AINT
.ix DINT
.box on &c0 &c1 &c2 &c3
\Definition\Name\Usage
.box
\int(a)     \AINT generic \R&arrow.AINT(R)
\           \             \D&arrow.AINT(D)
\           \AINT         \R&arrow.AINT(R)
\           \DINT         \D&arrow.DINT(D)
.box off
.im finote1
.*
.cp 15
.section Nearest Whole Number
.*
.ix 'generic function' ANINT
.ix 'intrinsic function' ANINT
.ix 'intrinsic function' DNINT
.ix ANINT
.ix DNINT
.box on &c0 &c1 &c2 &c3
\Definition\Name\Usage
.box
\int(a+.5) if a>=0 \ANINT generic \R&arrow.ANINT(R)
\int(a-.5) if a<0  \              \D&arrow.ANINT(D)
\                  \ANINT         \R&arrow.ANINT(R)
\                  \DNINT         \D&arrow.DNINT(D)
.box off
.*
.cp 15
.section Nearest Integer
.*
.ix 'generic function' NINT
.ix 'intrinsic function' NINT
.ix 'intrinsic function' IDNINT
.ix NINT
.ix IDNINT
.box on &c0 &c1 &c2 &c3
\Definition\Name\Usage
.box
\int(a+.5) if a>=0 \NINT generic \I&arrow.NINT(R)
\int(a-.5) if a<0  \             \I&arrow.NINT(D)
\                  \NINT         \I&arrow.NINT(R)
\                  \IDNINT       \I&arrow.IDNINT(D)
.box off
.*
.cp 20
.section Absolute Value
.*
.ix 'generic function' ABS
.ix 'intrinsic function' IABS
.ix 'intrinsic function' ABS
.ix 'intrinsic function' DABS
.ix 'intrinsic function' CABS
.ix 'intrinsic function' CDABS
.ix ABS
.ix IABS
.ix DABS
.ix CABS
.ix CDABS
.box on &c0 &c1 &c2 &c3
\Definition\Name\Usage
.box
\(ar**2+ai**2)**1/2 \ABS generic \I&arrow.ABS(I)
\if a is complex;   \            \R&arrow.ABS(R)
\|a| otherwise      \            \D&arrow.ABS(D)
\                   \            \R&arrow.ABS(C)
\                   \            \D&arrow.ABS(Z) &dagger\
\                   \IABS        \I&arrow.IABS(I)
\                   \ABS         \R&arrow.ABS(R)
\                   \DABS        \D&arrow.DABS(D)
\                   \CABS        \R&arrow.CABS(C)
\                   \CDABS &dagger     \D&arrow.CDABS(Z)
.box off
.im finote6
.*
.cp 15
.section Remainder
.*
.ix 'generic function' MOD
.ix 'intrinsic function' MOD
.ix 'intrinsic function' AMOD
.ix 'intrinsic function' DMOD
.ix MOD
.ix AMOD
.ix DMOD
.box on &c0 &c1 &c2 &c3
\Definition\Name\Usage
.box
\a1-int(a1/a2)*a2 \MOD generic \I&arrow.MOD(I,I)
\                 \            \R&arrow.MOD(R,R)
\                 \            \D&arrow.MOD(D,D)
\                 \MOD         \I&arrow.MOD(I,I)
\                 \AMOD        \R&arrow.AMOD(R,R)
\                 \DMOD        \D&arrow.DMOD(D,D)
.box off
.im finote1
.np
The value of MOD, AMOD and DMOD is undefined if the value of a2 is 0.
.*
.cp 15
.section Transfer of Sign
.*
.ix 'generic function' SIGN
.ix 'intrinsic function' ISIGN
.ix 'intrinsic function' SIGN
.ix 'intrinsic function' DSIGN
.ix ISIGN
.ix SIGN
.ix DSIGN
.box on &c0 &c1 &c2 &c3
\Definition\Name\Usage
.box
\|a1| if a2>=0 \SIGN generic \I&arrow.SIGN(I,I)
\-|a1| if a2<0 \             \R&arrow.SIGN(R,R)
\              \             \D&arrow.SIGN(D,D)
\              \ISIGN        \I&arrow.ISIGN(I,I)
\              \SIGN         \R&arrow.SIGN(R,R)
\              \DSIGN        \D&arrow.DSIGN(D,D)
.box off
.np
If the value of a1 is 0, the result is 0 which has no sign.
.*
.cp 15
.section Positive Difference
.*
.ix 'generic function' DIM
.ix 'intrinsic function' IDIM
.ix 'intrinsic function' DIM
.ix 'intrinsic function' DDIM
.ix IDIM
.ix DIM
.ix DDIM
.box on &c0 &c1 &c2 &c3
\Definition\Name\Usage
.box
\a1-a2 if a1>a2 \DIM generic \I&arrow.DIM(I,I)
\0 if a1<=a2    \            \R&arrow.DIM(R,R)
\               \            \D&arrow.DIM(D,D)
\               \IDIM        \I&arrow.IDIM(I,I)
\               \DIM         \R&arrow.DIM(R,R)
\               \DDIM        \D&arrow.DDIM(D,D)
.box off
.*
.cp 10
.section Double Precision Product
.*
.ix 'intrinsic function' DPROD
.ix DPROD
.box on &c0 &c1 &c2 &c3
\Definition\Name\Usage
.box
\a1*a2 \DPROD \D&arrow.DPROD(R,R)
.box off
.*
.cp 15
.section Choosing Largest Value
.*
.ix 'generic function' MAX
.ix 'intrinsic function' MAX0
.ix 'intrinsic function' AMAX1
.ix 'intrinsic function' DMAX1
.ix 'intrinsic function' AMAX0
.ix 'intrinsic function' MAX1
.ix MAX0
.ix AMAX1
.ix DMAX1
.ix AMAX0
.ix MAX1
.box on &c0 &c1 &c2 &c3
\Definition\Name\Usage
.box
\max(a1,a2,...) \MAX generic \I&arrow.MAX(I,...)
\               \            \R&arrow.MAX(R,...)
\               \            \D&arrow.MAX(D,...)
\               \MAX0        \I&arrow.MAX0(I,...)
\               \AMAX1       \R&arrow.AMAX1(R,...)
\               \DMAX1       \D&arrow.DMAX1(D,...)
\               \AMAX0       \R&arrow.AMAX0(I,...)
\               \MAX1        \I&arrow.MAX1(R,...)
.box off
.*
.cp 15
.section Choosing Smallest Value
.*
.ix 'generic function' MIN
.ix 'intrinsic function' MIN0
.ix 'intrinsic function' AMIN1
.ix 'intrinsic function' DMIN1
.ix 'intrinsic function' AMIN0
.ix 'intrinsic function' MIN1
.ix MIN0
.ix AMIN1
.ix DMIN1
.ix AMIN0
.ix MIN1
.box on &c0 &c1 &c2 &c3
\Definition\Name\Usage
.box
\min(a1,a2,...) \MIN generic \I&arrow.MIN(I,...)
\               \            \R&arrow.MIN(R,...)
\               \            \D&arrow.MIN(D,...)
\               \MIN0        \I&arrow.MIN0(I,...)
\               \AMIN1       \R&arrow.AMIN1(R,...)
\               \DMIN1       \D&arrow.DMIN1(D,...)
\               \AMIN0       \R&arrow.AMIN0(I,...)
\               \MIN1        \I&arrow.MIN1(R,...)
.box off
.*
.cp 10
.section Length
.*
.ix 'intrinsic function' LEN
.ix LEN
.box on &c0 &c1 &c2 &c3
\Definition\Name\Usage
.box
\Length of character \LEN \I&arrow.LEN(CH)
\entity
.box off
.np
The argument to the LEN function need not be defined.
.*
.cp 10
.section Length Without Trailing Blanks
.*
.ix 'intrinsic function' LENTRIM
.ix LENTRIM
.bxt on &c0 &c3 &c1 &c2
\Definition\Name\Usage
.bxt
\Length of character \LENTRIM   \I&arrow.LENTRIM(CH)
\entity excluding    \          \
\trailing blanks     \
.bxt off
.*
.cp 10
.section Index of a Substring
.*
.ix 'intrinsic function' INDEX
.ix INDEX
.box on &c0 &c1 &c2 &c3
\Definition\Name\Usage
.box
\Location of substring \INDEX \I&arrow.INDEX(CH,CH)
\a2 in string a1
.box off
.np
INDEX(x,y) returns the starting position of a substring in x which is
identical to y.
The position of the first such substring is returned.
If y is not contained in x, zero is returned.
.*
.cp 15
.section Imaginary Part of Complex Number
.*
.ix 'generic function' IMAG
.ix 'intrinsic function' AIMAG
.ix 'intrinsic function' DIMAG
.ix AIMAG
.ix DIMAG
.box on &c0 &c1 &c2 &c3
\Definition\Name\Usage
.box
\ai         \IMAG generic &dagger \R&arrow.IMAG(C)
\           \               \D&arrow.IMAG(Z)
\           \AIMAG          \R&arrow.AIMAG(C)
\           \DIMAG &dagger        \D&arrow.DIMAG(Z)
.box off
.im finote6
.*
.cp 15
.section Conjugate of a Complex Number
.*
.ix 'generic function' CONJG
.ix 'intrinsic function' CONJG
.ix 'intrinsic function' DCONJG
.ix CONJG
.ix DCONJD
.box on &c0 &c1 &c2 &c3
\Definition\Name\Usage
.box
\(ar,-ai)   \CONJG generic &dagger \C&arrow.CONJG(C)
\           \                \Z&arrow.CONJG(Z)
\           \CONJG           \C&arrow.CONJG(C)
\           \DCONJG &dagger        \Z&arrow.DCONJG(Z)
.box off
.im finote6
.*
.cp 15
.section Square Root
.*
.ix 'generic function' SQRT
.ix 'intrinsic function' SQRT
.ix 'intrinsic function' DSQRT
.ix 'intrinsic function' CSQRT
.ix 'intrinsic function' CDSQRT
.ix SQRT
.ix DSQRT
.ix CSQRT
.ix CDSQRT
.box on &c0 &c1 &c2 &c3
\Definition\Name\Usage
.box
\a**1/2 \SQRT generic \R&arrow.SQRT(R)
\       \             \D&arrow.SQRT(D)
\       \             \C&arrow.SQRT(C)
\       \             \Z&arrow.SQRT(Z) &dagger\
\       \SQRT         \R&arrow.SQRT(R)
\       \DSQRT        \D&arrow.DSQRT(D)
\       \CSQRT        \C&arrow.CSQRT(C)
\       \CDSQRT &dagger     \Z&arrow.CDSQRT(Z)
.box off
The argument to SQRT must be >= 0.
The result of CSQRT and CDSQRT is the principal value with the
real part >= 0.
When the real part of the result is 0, the imaginary part is >= 0.
.*
.cp 15
.section Exponential
.*
.ix 'generic function' EXP
.ix 'intrinsic function' EXP
.ix 'intrinsic function' DEXP
.ix 'intrinsic function' CEXP
.ix 'intrinsic function' CDEXP
.ix EXP
.ix DEXP
.ix CEXP
.ix CDEXP
.box on &c0 &c1 &c2 &c3
\Definition\Name\Usage
.box
\e**a \EXP generic \R&arrow.EXP(R)
\     \            \D&arrow.EXP(D)
\     \            \C&arrow.EXP(C)
\     \            \Z&arrow.EXP(Z) &dagger\
\     \EXP         \R&arrow.EXP(R)
\     \DEXP        \D&arrow.DEXP(D)
\     \CEXP        \C&arrow.CEXP(C)
\     \CDEXP &dagger     \Z&arrow.CDEXP(Z)
.box off
.im finote8
.*
.cp 15
.section Natural Logarithm
.*
.ix 'generic function' LOG
.ix 'intrinsic function' ALOG
.ix 'intrinsic function' DLOG
.ix 'intrinsic function' CLOG
.ix 'intrinsic function' CDLOG
.ix ALOG
.ix DLOG
.ix CLOG
.ix CDLOG
.box on &c0 &c1 &c2 &c3
\Definition\Name\Usage
.box
\log (a) \LOG generic \R&arrow.LOG(R)
\    e   \            \D&arrow.LOG(D)

⌨️ 快捷键说明

复制代码 Ctrl + C
搜索代码 Ctrl + F
全屏模式 F11
切换主题 Ctrl + Shift + D
显示快捷键 ?
增大字号 Ctrl + =
减小字号 Ctrl + -