📄 fitabmon.gml
字号:
.if &e'&dohelp eq 0 .do begin
:set symbol="arrow" value=";.sf7;.ct ~L;.esf;.ct ".
:set symbol="dagref" value="a dagger".
:set symbol="generic" value="(generic)".
.dm nameuse begin
. .note Name:
. .bi Usage:
.dm nameuse end
.do end
.el .do begin
:set symbol="arrow" value="<-".
:set symbol="dagger" value="!".
:set symbol="dagref" value="an exclamation mark".
:set symbol="pi" value="pi".
:set symbol="generic" value="(g)".
.dm nameuse begin
. .note Name / Usage:
.dm nameuse end
.do end
:cmt. - is a minus
.np
The following sections present all generic and specific names of
intrinsic functions and describe how they are used.
The following is a guide to interpreting the information presented.
.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*1 is represented by I1.
.point
.xt INTEGER*2 is represented by I2.
.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
The "Definition" description gives the mathematical definition of the
function performed by the intrinsic function.
There are two fields for each intrinsic function.
The "Name" field lists the specific and generic names of the intrinsic
functions.
When the name of an intrinsic function is a generic name, it is
indicated by
.if &e'&dohelp eq 0 .do begin
the word "generic"
.do end
.el .do begin
the letter "g"
.do end
in parentheses;
all other names are specific names.
The "Usage" field describes how the intrinsic functions are used.
"R&arrow.ATAN2(R,R)" is a typical entry in this field.
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
&dagref. (&dagger.).
.*
.cp 18
.section Type Conversion: Conversion to integer
.*
.begnote $setptnt 12
.note Definition:
.mono int(a)
.nameuse
.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
.note INT &generic.
I&arrow.INT(I),
I&arrow.INT(R),
I&arrow.INT(D),
I&arrow.INT(C),
I&arrow.INT(Z) &dagger.
.note INT
I&arrow.INT(R)
.note HFIX
I2&arrow.HFIX(R) &dagger.
.note IFIX
I&arrow.IFIX(R)
.note IDINT
I&arrow.IDINT(D)
.note Notes:
.im finote1
.np
&dagger. is an extension to FORTRAN 77.
.endnote
.*
.cp 18
.section Type Conversion: Conversion to real
.*
.begnote $setptnt 12
.nameuse
.ix 'generic function' REAL
.ix 'intrinsic function' REAL
.ix 'intrinsic function' FLOAT
.ix 'intrinsic function' SNGL
.ix REAL
.ix FLOAT
.ix SNGL
.note REAL &generic.
R&arrow.REAL(I),
R&arrow.REAL(R),
R&arrow.REAL(D),
R&arrow.REAL(C),
R&arrow.REAL(Z) &dagger.
.note REAL
R&arrow.REAL(I)
.note FLOAT
R&arrow.FLOAT(I)
.note SNGL
R&arrow.SNGL(D)
.note Notes:
.im finote2
.np
&dagger. is an extension to FORTRAN 77.
.endnote
.*
.cp 18
.section Type Conversion: Conversion to double precision
.*
.begnote $setptnt 12
.nameuse
.ix 'generic function' DBLE
.ix 'intrinsic function' DBLE
.ix 'intrinsic function' DREAL
.ix 'intrinsic function' DFLOAT
.ix DBLE
.ix DREAL
.ix DFLOAT
.note DBLE &generic.
D&arrow.DBLE(I),
D&arrow.DBLE(R),
D&arrow.DBLE(D),
D&arrow.DBLE(C),
D&arrow.DBLE(Z) &dagger.
.note DREAL
D&arrow.DREAL(Z) &dagger.
.note DFLOAT
D&arrow.DFLOAT(I) &dagger.
.note Notes:
.im finote3
.np
&dagger. is an extension to FORTRAN 77.
.endnote
.*
.cp 18
.section Type Conversion: Conversion to complex
.*
.begnote $setptnt 12
.nameuse
.ix 'generic function' CMPLX
.ix 'intrinsic function' CMPLX
.ix CMPLX
.note 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.
.note Notes:
.im finote4a
.np
&dagger. is an extension to FORTRAN 77.
.endnote
.*
.cp 18
.section Type Conversion: Conversion to double complex
.*
.begnote $setptnt 12
.nameuse
.ix 'generic function' DCMPLX
.ix 'intrinsic function' DCMPLX
.ix DCMPLX
.note DCMPLX &generic. &dagger.
Z&arrow.DCMPLX(I), Z&arrow.DCMPLX(I,I),
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)
.note Notes:
.im finote4b
.np
&dagger. is an extension to FORTRAN 77.
.endnote
.*
.cp 18
.section Type Conversion: Character conversion to integer
.*
.begnote $setptnt 12
.nameuse
.ix 'intrinsic function' ICHAR
.ix ICHAR
.note ICHAR
I&arrow.ICHAR(CH)
.note Notes:
.im finote5a
.endnote
.*
.cp 18
.section Type Conversion: Conversion to character
.*
.begnote $setptnt 12
.nameuse
.ix 'intrinsic function' CHAR
.ix CHAR
.note CHAR
CH&arrow.CHAR(I)
.note Notes:
.im finote5b
.endnote
.*
.cp 18
.section Truncation
.*
.begnote $setptnt 12
.note Definition:
.mono int(a)
.nameuse
.ix 'generic function' AINT
.ix 'intrinsic function' AINT
.ix 'intrinsic function' DINT
.ix AINT
.ix DINT
.note AINT &generic.
R&arrow.AINT(R),
D&arrow.AINT(D)
.note AINT
R&arrow.AINT(R)
.note DINT
D&arrow.DINT(D)
.note Notes:
.im finote1
.endnote
.*
.cp 18
.section Nearest Whole Number
.*
.begnote $setptnt 12
.note Definition:
.mono int(a+.5)
if a>=0;
.mono int(a-.5)
if a<0
.nameuse
.ix 'generic function' ANINT
.ix 'intrinsic function' ANINT
.ix 'intrinsic function' DNINT
.ix ANINT
.ix DNINT
.note ANINT &generic.
R&arrow.ANINT(R),
D&arrow.ANINT(D)
.note ANINT
R&arrow.ANINT(R)
.note DNINT
D&arrow.DNINT(D)
.endnote
.*
.cp 18
.section Nearest Integer
.*
.begnote $setptnt 12
.note Definition:
.mono int(a+.5)
if a>=0;
.mono int(a-.5)
if a<0
.nameuse
.ix 'generic function' NINT
.ix 'intrinsic function' NINT
.ix 'intrinsic function' IDNINT
.ix NINT
.ix IDNINT
.note NINT &generic.
I&arrow.NINT(R),
I&arrow.NINT(D)
.note NINT
I&arrow.NINT(R)
.note IDNINT
I&arrow.IDNINT(D)
.endnote
.*
.cp 18
.section Absolute Value
.*
.begnote $setptnt 12
.note Definition:
.mono (ar**2+ai**2)**1/2
if a is complex;
.mono |a|
otherwise
.nameuse
.ix 'generic function' ABS
.ix 'intrinsic function' IABS
.ix 'intrinsic function' I1ABS
.ix 'intrinsic function' I2ABS
.ix 'intrinsic function' ABS
.ix 'intrinsic function' DABS
.ix 'intrinsic function' CABS
.ix 'intrinsic function' CDABS
.ix ABS
.ix IABS
.ix I1ABS
.ix I2ABS
.ix DABS
.ix CABS
.ix CDABS
.note ABS &generic.
I&arrow.ABS(I),
I1&arrow.ABS(I1) &dagger.,
I2&arrow.ABS(I2) &dagger.,
R&arrow.ABS(R),
D&arrow.ABS(D),
R&arrow.ABS(C),
D&arrow.ABS(Z) &dagger.
.note IABS
I&arrow.IABS(I)
.note I1ABS
I1&arrow.I1ABS(I1) &dagger.
.note I2ABS
I2&arrow.I2ABS(I2) &dagger.
.note ABS
R&arrow.ABS(R)
.note DABS
D&arrow.DABS(D)
.note CABS
R&arrow.CABS(C)
.note CDABS &dagger.
D&arrow.CDABS(Z)
.note Notes:
.im finote6
.np
&dagger. is an extension to FORTRAN 77.
.endnote
.*
.cp 18
.section Remainder
.*
.begnote $setptnt 12
.note Definition:
.mono mod(a1,a2) = a1-int(a1/a2)*a2
.nameuse
.ix 'generic function' MOD
.ix 'intrinsic function' MOD
.ix 'intrinsic function' I1MOD
.ix 'intrinsic function' I2MOD
.ix 'intrinsic function' AMOD
.ix 'intrinsic function' DMOD
.ix MOD
.ix I1MOD
.ix I2MOD
.ix AMOD
.ix DMOD
.note MOD &generic.
I&arrow.MOD(I,I),
I1&arrow.MOD(I1,I1) &dagger.,
I2&arrow.MOD(I2,I2) &dagger.,
R&arrow.MOD(R,R),
D&arrow.MOD(D,D),
.note MOD
I&arrow.MOD(I,I)
.note I1MOD
I1&arrow.I1MOD(I1,I1) &dagger.
.note I2MOD
I2&arrow.I2MOD(I2,I2) &dagger.
.note AMOD
R&arrow.AMOD(R,R)
.note DMOD
D&arrow.DMOD(D,D)
.note Notes:
.im finote1
.np
The value of MOD, I1MOD, I2MOD, AMOD or DMOD is undefined if the
value of a2 is 0.
.endnote
.*
.cp 18
.section Transfer of Sign
.*
.begnote $setptnt 12
.note Definition:
.mono sign(a1,a2) = |a1|
if a2>=0;
.mono -|a1|
if a2<0
.nameuse
.ix 'generic function' SIGN
.ix 'intrinsic function' ISIGN
.ix 'intrinsic function' I1SIGN
.ix 'intrinsic function' I2SIGN
.ix 'intrinsic function' SIGN
.ix 'intrinsic function' DSIGN
.ix ISIGN
.ix I1SIGN
.ix I2SIGN
.ix SIGN
.ix DSIGN
.note SIGN &generic.
I&arrow.SIGN(I,I),
I1&arrow.SIGN(I1,I1) &dagger.,
I2&arrow.SIGN(I2,I2) &dagger.,
R&arrow.SIGN(R,R),
D&arrow.SIGN(D,D)
.note ISIGN
I&arrow.ISIGN(I,I)
.note I1SIGN
I1&arrow.I1SIGN(I1,I1) &dagger.
.note I2SIGN
I2&arrow.I2SIGN(I2,I2) &dagger.
.note SIGN
R&arrow.SIGN(R,R)
.note DSIGN
D&arrow.DSIGN(D,D)
.note Notes:
If the value of a1 is 0, the result is 0 which has no sign.
.endnote
.*
.cp 18
.section Positive Difference
.*
.begnote $setptnt 12
.note Definition:
.mono a1-a2
if a1>a2;
.mono 0
if a1<=a2
.nameuse
.ix 'generic function' DIM
.ix 'intrinsic function' IDIM
.ix 'intrinsic function' I1DIM
.ix 'intrinsic function' I2DIM
.ix 'intrinsic function' DIM
.ix 'intrinsic function' DDIM
.ix IDIM
.ix I1DIM
.ix I2DIM
.ix DIM
.ix DDIM
.note DIM &generic.
I&arrow.DIM(I,I),
I1&arrow.DIM(I1,I1) &dagger.,
I2&arrow.DIM(I2,I2) &dagger.,
R&arrow.DIM(R,R),
D&arrow.DIM(D,D)
.note IDIM
I&arrow.IDIM(I,I)
.note I1IDIM
I1&arrow.I1DIM(I1,I1) &dagger.
.note I2IDIM
I2&arrow.I2DIM(I2,I2) &dagger.
.note DIM
R&arrow.DIM(R,R)
.note DDIM
D&arrow.DDIM(D,D)
.endnote
.*
.cp 18
.section Double Precision Product
.*
.begnote $setptnt 12
.note Definition:
.mono a1*a2
.nameuse
.ix 'intrinsic function' DPROD
.ix DPROD
.note DPROD
D&arrow.DPROD(R,R)
.endnote
.*
.cp 18
.section Choosing Largest Value
.*
.begnote $setptnt 12
.note Definition:
.mono max(a1,a2,...)
.nameuse
.ix 'generic function' MAX
.ix 'intrinsic function' MAX0
.ix 'intrinsic function' I1MAX0
.ix 'intrinsic function' I2MAX0
.ix 'intrinsic function' AMAX1
.ix 'intrinsic function' DMAX1
.ix 'intrinsic function' AMAX0
.ix 'intrinsic function' MAX1
.ix MAX0
.ix I1MAX0
.ix I2MAX0
.ix AMAX1
.ix DMAX1
.ix AMAX0
.ix MAX1
.note MAX &generic.
I&arrow.MAX(I,...),
I1&arrow.MAX(I1,...) &dagger.,
I2&arrow.MAX(I2,...) &dagger.,
R&arrow.MAX(R,...),
D&arrow.MAX(D,...)
.note MAX0
I&arrow.MAX0(I,...)
.note I1MAX0
I1&arrow.I1MAX0(I1,...) &dagger.
.note I2MAX0
I2&arrow.I2MAX0(I2,...) &dagger.
.note AMAX1
R&arrow.AMAX1(R,...)
.note DMAX1
D&arrow.DMAX1(D,...)
.note AMAX0
R&arrow.AMAX0(I,...)
.note MAX1
I&arrow.MAX1(R,...)
.endnote
.*
.cp 18
.section Choosing Smallest Value
.*
.begnote $setptnt 12
.note Definition:
.mono min(a1,a2,...)
.nameuse
.ix 'generic function' MIN
.ix 'intrinsic function' MIN0
.ix 'intrinsic function' I1MIN0
.ix 'intrinsic function' I2MIN0
.ix 'intrinsic function' AMIN1
.ix 'intrinsic function' DMIN1
.ix 'intrinsic function' AMIN0
.ix 'intrinsic function' MIN1
.ix MIN0
.ix I1MIN0
.ix I2MIN0
.ix AMIN1
.ix DMIN1
.ix AMIN0
.ix MIN1
.note MIN &generic.
I&arrow.MIN(I,...),
I1&arrow.MIN(I1,...) &dagger.,
I2&arrow.MIN(I2,...) &dagger.,
R&arrow.MIN(R,...),
D&arrow.MIN(D,...)
⌨️ 快捷键说明
复制代码
Ctrl + C
搜索代码
Ctrl + F
全屏模式
F11
切换主题
Ctrl + Shift + D
显示快捷键
?
增大字号
Ctrl + =
减小字号
Ctrl + -