1<!--===- docs/Intrinsics.md
2
3   Part of the LLVM Project, under the Apache License v2.0 with LLVM Exceptions.
4   See https://llvm.org/LICENSE.txt for license information.
5   SPDX-License-Identifier: Apache-2.0 WITH LLVM-exception
6
7-->
8
9# A categorization of standard (2018) and extended Fortran intrinsic procedures
10
11```eval_rst
12.. contents::
13   :local:
14```
15
16This note attempts to group the intrinsic procedures of Fortran into categories
17of functions or subroutines with similar interfaces as an aid to
18comprehension beyond that which might be gained from the standard's
19alphabetical list.
20
21A brief status of intrinsic procedure support in f18 is also given at the end.
22
23Few procedures are actually described here apart from their interfaces; see the
24Fortran 2018 standard (section 16) for the complete story.
25
26Intrinsic modules are not covered here.
27
28## General rules
29
301. The value of any intrinsic function's `KIND` actual argument, if present,
31   must be a scalar constant integer expression, of any kind, whose value
32   resolves to some supported kind of the function's result type.
33   If optional and absent, the kind of the function's result is
34   either the default kind of that category or to the kind of an argument
35   (e.g., as in `AINT`).
361. Procedures are summarized with a non-Fortran syntax for brevity.
37   Wherever a function has a short definition, it appears after an
38   equal sign as if it were a statement function.  Any functions referenced
39   in these short summaries are intrinsic.
401. Unless stated otherwise, an actual argument may have any supported kind
41   of a particular intrinsic type.  Sometimes a pattern variable
42   can appear in a description (e.g., `REAL(k)`) when the kind of an
43   actual argument's type must match the kind of another argument, or
44   determines the kind type parameter of the function result.
451. When an intrinsic type name appears without a kind (e.g., `REAL`),
46   it refers to the default kind of that type.  Sometimes the word
47   `default` will appear for clarity.
481. The names of the dummy arguments actually matter because they can
49   be used as keywords for actual arguments.
501. All standard intrinsic functions are pure, even when not elemental.
511. Assumed-rank arguments may not appear as actual arguments unless
52   expressly permitted.
531. When an argument is described with a default value, e.g. `KIND=KIND(0)`,
54   it is an optional argument.  Optional arguments without defaults,
55   e.g. `DIM` on many transformationals, are wrapped in `[]` brackets
56   as in the Fortran standard.  When an intrinsic has optional arguments
57   with and without default values, the arguments with default values
58   may appear within the brackets to preserve the order of arguments
59   (e.g., `COUNT`).
60
61## Elemental intrinsic functions
62
63Pure elemental semantics apply to these functions, to wit: when one or more of
64the actual arguments are arrays, the arguments must be conformable, and
65the result is also an array.
66Scalar arguments are expanded when the arguments are not all scalars.
67
68### Elemental intrinsic functions that may have unrestricted specific procedures
69
70When an elemental intrinsic function is documented here as having an
71_unrestricted specific name_, that name may be passed as an actual
72argument, used as the target of a procedure pointer, appear in
73a generic interface, and be otherwise used as if it were an external
74procedure.
75An `INTRINSIC` statement or attribute may have to be applied to an
76unrestricted specific name to enable such usage.
77
78When a name is being used as a specific procedure for any purpose other
79than that of a called function, the specific instance of the function
80that accepts and returns values of the default kinds of the intrinsic
81types is used.
82A Fortran `INTERFACE` could be written to define each of
83these unrestricted specific intrinsic function names.
84
85Calls to dummy arguments and procedure pointers that correspond to these
86specific names must pass only scalar actual argument values.
87
88No other intrinsic function name can be passed as an actual argument,
89used as a pointer target, appear in a generic interface, or be otherwise
90used except as the name of a called function.
91Some of these _restricted specific intrinsic functions_, e.g. `FLOAT`,
92provide a means for invoking a corresponding generic (`REAL` in the case of `FLOAT`)
93with forced argument and result kinds.
94Others, viz. `CHAR`, `ICHAR`, `INT`, `REAL`, and the lexical comparisons like `LGE`,
95have the same name as their generic functions, and it is not clear what purpose
96is accomplished by the standard by defining them as specific functions.
97
98### Trigonometric elemental intrinsic functions, generic and (mostly) specific
99All of these functions can be used as unrestricted specific names.
100
101```
102ACOS(REAL(k) X) -> REAL(k)
103ASIN(REAL(k) X) -> REAL(k)
104ATAN(REAL(k) X) -> REAL(k)
105ATAN(REAL(k) Y, REAL(k) X) -> REAL(k) = ATAN2(Y, X)
106ATAN2(REAL(k) Y, REAL(k) X) -> REAL(k)
107COS(REAL(k) X) -> REAL(k)
108COSH(REAL(k) X) -> REAL(k)
109SIN(REAL(k) X) -> REAL(k)
110SINH(REAL(k) X) -> REAL(k)
111TAN(REAL(k) X) -> REAL(k)
112TANH(REAL(k) X) -> REAL(k)
113```
114
115These `COMPLEX` versions of some of those functions, and the
116inverse hyperbolic functions, cannot be used as specific names.
117```
118ACOS(COMPLEX(k) X) -> COMPLEX(k)
119ASIN(COMPLEX(k) X) -> COMPLEX(k)
120ATAN(COMPLEX(k) X) -> COMPLEX(k)
121ACOSH(REAL(k) X) -> REAL(k)
122ACOSH(COMPLEX(k) X) -> COMPLEX(k)
123ASINH(REAL(k) X) -> REAL(k)
124ASINH(COMPLEX(k) X) -> COMPLEX(k)
125ATANH(REAL(k) X) -> REAL(k)
126ATANH(COMPLEX(k) X) -> COMPLEX(k)
127COS(COMPLEX(k) X) -> COMPLEX(k)
128COSH(COMPLEX(k) X) -> COMPLEX(k)
129SIN(COMPLEX(k) X) -> COMPLEX(k)
130SINH(COMPLEX(k) X) -> COMPLEX(k)
131TAN(COMPLEX(k) X) -> COMPLEX(k)
132TANH(COMPLEX(k) X) -> COMPLEX(k)
133```
134
135### Non-trigonometric elemental intrinsic functions, generic and specific
136These functions *can* be used as unrestricted specific names.
137```
138ABS(REAL(k) A) -> REAL(k) = SIGN(A, 0.0)
139AIMAG(COMPLEX(k) Z) -> REAL(k) = Z%IM
140AINT(REAL(k) A, KIND=k) -> REAL(KIND)
141ANINT(REAL(k) A, KIND=k) -> REAL(KIND)
142CONJG(COMPLEX(k) Z) -> COMPLEX(k) = CMPLX(Z%RE, -Z%IM)
143DIM(REAL(k) X, REAL(k) Y) -> REAL(k) = X-MIN(X,Y)
144DPROD(default REAL X, default REAL Y) -> DOUBLE PRECISION = DBLE(X)*DBLE(Y)
145EXP(REAL(k) X) -> REAL(k)
146INDEX(CHARACTER(k) STRING, CHARACTER(k) SUBSTRING, LOGICAL(any) BACK=.FALSE., KIND=KIND(0)) -> INTEGER(KIND)
147LEN(CHARACTER(k,n) STRING, KIND=KIND(0)) -> INTEGER(KIND) = n
148LOG(REAL(k) X) -> REAL(k)
149LOG10(REAL(k) X) -> REAL(k)
150MOD(INTEGER(k) A, INTEGER(k) P) -> INTEGER(k) = A-P*INT(A/P)
151NINT(REAL(k) A, KIND=KIND(0)) -> INTEGER(KIND)
152SIGN(REAL(k) A, REAL(k) B) -> REAL(k)
153SQRT(REAL(k) X) -> REAL(k) = X ** 0.5
154```
155
156These variants, however *cannot* be used as specific names without recourse to an alias
157from the following section:
158```
159ABS(INTEGER(k) A) -> INTEGER(k) = SIGN(A, 0)
160ABS(COMPLEX(k) A) -> REAL(k) = HYPOT(A%RE, A%IM)
161DIM(INTEGER(k) X, INTEGER(k) Y) -> INTEGER(k) = X-MIN(X,Y)
162EXP(COMPLEX(k) X) -> COMPLEX(k)
163LOG(COMPLEX(k) X) -> COMPLEX(k)
164MOD(REAL(k) A, REAL(k) P) -> REAL(k) = A-P*INT(A/P)
165SIGN(INTEGER(k) A, INTEGER(k) B) -> INTEGER(k)
166SQRT(COMPLEX(k) X) -> COMPLEX(k)
167```
168
169### Unrestricted specific aliases for some elemental intrinsic functions with distinct names
170
171```
172ALOG(REAL X) -> REAL = LOG(X)
173ALOG10(REAL X) -> REAL = LOG10(X)
174AMOD(REAL A, REAL P) -> REAL = MOD(A, P)
175CABS(COMPLEX A) = ABS(A)
176CCOS(COMPLEX X) = COS(X)
177CEXP(COMPLEX A) -> COMPLEX = EXP(A)
178CLOG(COMPLEX X) -> COMPLEX = LOG(X)
179CSIN(COMPLEX X) -> COMPLEX = SIN(X)
180CSQRT(COMPLEX X) -> COMPLEX = SQRT(X)
181CTAN(COMPLEX X) -> COMPLEX = TAN(X)
182DABS(DOUBLE PRECISION A) -> DOUBLE PRECISION = ABS(A)
183DACOS(DOUBLE PRECISION X) -> DOUBLE PRECISION = ACOS(X)
184DASIN(DOUBLE PRECISION X) -> DOUBLE PRECISION = ASIN(X)
185DATAN(DOUBLE PRECISION X) -> DOUBLE PRECISION = ATAN(X)
186DATAN2(DOUBLE PRECISION Y, DOUBLE PRECISION X) -> DOUBLE PRECISION = ATAN2(Y, X)
187DCOS(DOUBLE PRECISION X) -> DOUBLE PRECISION = COS(X)
188DCOSH(DOUBLE PRECISION X) -> DOUBLE PRECISION = COSH(X)
189DDIM(DOUBLE PRECISION X, DOUBLE PRECISION Y) -> DOUBLE PRECISION = X-MIN(X,Y)
190DEXP(DOUBLE PRECISION X) -> DOUBLE PRECISION = EXP(X)
191DINT(DOUBLE PRECISION A) -> DOUBLE PRECISION = AINT(A)
192DLOG(DOUBLE PRECISION X) -> DOUBLE PRECISION = LOG(X)
193DLOG10(DOUBLE PRECISION X) -> DOUBLE PRECISION = LOG10(X)
194DMOD(DOUBLE PRECISION A, DOUBLE PRECISION P) -> DOUBLE PRECISION = MOD(A, P)
195DNINT(DOUBLE PRECISION A) -> DOUBLE PRECISION = ANINT(A)
196DSIGN(DOUBLE PRECISION A, DOUBLE PRECISION B) -> DOUBLE PRECISION = SIGN(A, B)
197DSIN(DOUBLE PRECISION X) -> DOUBLE PRECISION = SIN(X)
198DSINH(DOUBLE PRECISION X) -> DOUBLE PRECISION = SINH(X)
199DSQRT(DOUBLE PRECISION X) -> DOUBLE PRECISION = SQRT(X)
200DTAN(DOUBLE PRECISION X) -> DOUBLE PRECISION = TAN(X)
201DTANH(DOUBLE PRECISION X) -> DOUBLE PRECISION = TANH(X)
202IABS(INTEGER A) -> INTEGER = ABS(A)
203IDIM(INTEGER X, INTEGER Y) -> INTEGER = X-MIN(X,Y)
204IDNINT(DOUBLE PRECISION A) -> INTEGER = NINT(A)
205ISIGN(INTEGER A, INTEGER B) -> INTEGER = SIGN(A, B)
206```
207
208## Generic elemental intrinsic functions without specific names
209
210(No procedures after this point can be passed as actual arguments, used as
211pointer targets, or appear as specific procedures in generic interfaces.)
212
213### Elemental conversions
214
215```
216ACHAR(INTEGER(k) I, KIND=KIND('')) -> CHARACTER(KIND,LEN=1)
217CEILING(REAL() A, KIND=KIND(0)) -> INTEGER(KIND)
218CHAR(INTEGER(any) I, KIND=KIND('')) -> CHARACTER(KIND,LEN=1)
219CMPLX(COMPLEX(k) X, KIND=KIND(0.0D0)) -> COMPLEX(KIND)
220CMPLX(INTEGER or REAL or BOZ X, INTEGER or REAL or BOZ Y=0, KIND=KIND((0,0))) -> COMPLEX(KIND)
221DBLE(INTEGER or REAL or COMPLEX or BOZ A) = REAL(A, KIND=KIND(0.0D0))
222EXPONENT(REAL(any) X) -> default INTEGER
223FLOOR(REAL(any) A, KIND=KIND(0)) -> INTEGER(KIND)
224IACHAR(CHARACTER(KIND=k,LEN=1) C, KIND=KIND(0)) -> INTEGER(KIND)
225ICHAR(CHARACTER(KIND=k,LEN=1) C, KIND=KIND(0)) -> INTEGER(KIND)
226INT(INTEGER or REAL or COMPLEX or BOZ A, KIND=KIND(0)) -> INTEGER(KIND)
227LOGICAL(LOGICAL(any) L, KIND=KIND(.TRUE.)) -> LOGICAL(KIND)
228REAL(INTEGER or REAL or COMPLEX or BOZ A, KIND=KIND(0.0)) -> REAL(KIND)
229```
230
231### Other generic elemental intrinsic functions without specific names
232N.B. `BESSEL_JN(N1, N2, X)` and `BESSEL_YN(N1, N2, X)` are categorized
233below with the _transformational_ intrinsic functions.
234
235```
236BESSEL_J0(REAL(k) X) -> REAL(k)
237BESSEL_J1(REAL(k) X) -> REAL(k)
238BESSEL_JN(INTEGER(n) N, REAL(k) X) -> REAL(k)
239BESSEL_Y0(REAL(k) X) -> REAL(k)
240BESSEL_Y1(REAL(k) X) -> REAL(k)
241BESSEL_YN(INTEGER(n) N, REAL(k) X) -> REAL(k)
242ERF(REAL(k) X) -> REAL(k)
243ERFC(REAL(k) X) -> REAL(k)
244ERFC_SCALED(REAL(k) X) -> REAL(k)
245FRACTION(REAL(k) X) -> REAL(k)
246GAMMA(REAL(k) X) -> REAL(k)
247HYPOT(REAL(k) X, REAL(k) Y) -> REAL(k) = SQRT(X*X+Y*Y) without spurious overflow
248IMAGE_STATUS(INTEGER(any) IMAGE [, scalar TEAM_TYPE TEAM ]) -> default INTEGER
249IS_IOSTAT_END(INTEGER(any) I) -> default LOGICAL
250IS_IOSTAT_EOR(INTEGER(any) I) -> default LOGICAL
251LOG_GAMMA(REAL(k) X) -> REAL(k)
252MAX(INTEGER(k) ...) -> INTEGER(k)
253MAX(REAL(k) ...) -> REAL(k)
254MAX(CHARACTER(KIND=k) ...) -> CHARACTER(KIND=k,LEN=MAX(LEN(...)))
255MERGE(any type TSOURCE, same type FSOURCE, LOGICAL(any) MASK) -> type of FSOURCE
256MIN(INTEGER(k) ...) -> INTEGER(k)
257MIN(REAL(k) ...) -> REAL(k)
258MIN(CHARACTER(KIND=k) ...) -> CHARACTER(KIND=k,LEN=MAX(LEN(...)))
259MODULO(INTEGER(k) A, INTEGER(k) P) -> INTEGER(k); P*result >= 0
260MODULO(REAL(k) A, REAL(k) P) -> REAL(k) = A - P*FLOOR(A/P)
261NEAREST(REAL(k) X, REAL(any) S) -> REAL(k)
262OUT_OF_RANGE(INTEGER(any) X, scalar INTEGER or REAL(k) MOLD) -> default LOGICAL
263OUT_OF_RANGE(REAL(any) X, scalar REAL(k) MOLD) -> default LOGICAL
264OUT_OF_RANGE(REAL(any) X, scalar INTEGER(any) MOLD, scalar LOGICAL(any) ROUND=.FALSE.) -> default LOGICAL
265RRSPACING(REAL(k) X) -> REAL(k)
266SCALE(REAL(k) X, INTEGER(any) I) -> REAL(k)
267SET_EXPONENT(REAL(k) X, INTEGER(any) I) -> REAL(k)
268SPACING(REAL(k) X) -> REAL(k)
269```
270
271### Restricted specific aliases for elemental conversions &/or extrema with default intrinsic types
272
273```
274AMAX0(INTEGER ...) = REAL(MAX(...))
275AMAX1(REAL ...) = MAX(...)
276AMIN0(INTEGER...) = REAL(MIN(...))
277AMIN1(REAL ...) = MIN(...)
278DMAX1(DOUBLE PRECISION ...) = MAX(...)
279DMIN1(DOUBLE PRECISION ...) = MIN(...)
280FLOAT(INTEGER I) = REAL(I)
281IDINT(DOUBLE PRECISION A) = INT(A)
282IFIX(REAL A) = INT(A)
283MAX0(INTEGER ...) = MAX(...)
284MAX1(REAL ...) = INT(MAX(...))
285MIN0(INTEGER ...) = MIN(...)
286MIN1(REAL ...) = INT(MIN(...))
287SNGL(DOUBLE PRECISION A) = REAL(A)
288```
289
290### Generic elemental bit manipulation intrinsic functions
291Many of these accept a typeless "BOZ" literal as an actual argument.
292It is interpreted as having the kind of intrinsic `INTEGER` type
293as another argument, as if the typeless were implicitly wrapped
294in a call to `INT()`.
295When multiple arguments can be either `INTEGER` values or typeless
296constants, it is forbidden for *all* of them to be typeless
297constants if the result of the function is `INTEGER`
298(i.e., only `BGE`, `BGT`, `BLE`, and `BLT` can have multiple
299typeless arguments).
300
301```
302BGE(INTEGER(n1) or BOZ I, INTEGER(n2) or BOZ J) -> default LOGICAL
303BGT(INTEGER(n1) or BOZ I, INTEGER(n2) or BOZ J) -> default LOGICAL
304BLE(INTEGER(n1) or BOZ I, INTEGER(n2) or BOZ J) -> default LOGICAL
305BLT(INTEGER(n1) or BOZ I, INTEGER(n2) or BOZ J) -> default LOGICAL
306BTEST(INTEGER(n1) I, INTEGER(n2) POS) -> default LOGICAL
307DSHIFTL(INTEGER(k) I, INTEGER(k) or BOZ J, INTEGER(any) SHIFT) -> INTEGER(k)
308DSHIFTL(BOZ I, INTEGER(k), INTEGER(any) SHIFT) -> INTEGER(k)
309DSHIFTR(INTEGER(k) I, INTEGER(k) or BOZ J, INTEGER(any) SHIFT) -> INTEGER(k)
310DSHIFTR(BOZ I, INTEGER(k), INTEGER(any) SHIFT) -> INTEGER(k)
311IAND(INTEGER(k) I, INTEGER(k) or BOZ J) -> INTEGER(k)
312IAND(BOZ I, INTEGER(k) J) -> INTEGER(k)
313IBCLR(INTEGER(k) I, INTEGER(any) POS) -> INTEGER(k)
314IBITS(INTEGER(k) I, INTEGER(n1) POS, INTEGER(n2) LEN) -> INTEGER(k)
315IBSET(INTEGER(k) I, INTEGER(any) POS) -> INTEGER(k)
316IEOR(INTEGER(k) I, INTEGER(k) or BOZ J) -> INTEGER(k)
317IEOR(BOZ I, INTEGER(k) J) -> INTEGER(k)
318IOR(INTEGER(k) I, INTEGER(k) or BOZ J) -> INTEGER(k)
319IOR(BOZ I, INTEGER(k) J) -> INTEGER(k)
320ISHFT(INTEGER(k) I, INTEGER(any) SHIFT) -> INTEGER(k)
321ISHFTC(INTEGER(k) I, INTEGER(n1) SHIFT, INTEGER(n2) SIZE=BIT_SIZE(I)) -> INTEGER(k)
322LEADZ(INTEGER(any) I) -> default INTEGER
323MASKL(INTEGER(any) I, KIND=KIND(0)) -> INTEGER(KIND)
324MASKR(INTEGER(any) I, KIND=KIND(0)) -> INTEGER(KIND)
325MERGE_BITS(INTEGER(k) I, INTEGER(k) or BOZ J, INTEGER(k) or BOZ MASK) = IOR(IAND(I,MASK),IAND(J,NOT(MASK)))
326MERGE_BITS(BOZ I, INTEGER(k) J, INTEGER(k) or BOZ MASK) = IOR(IAND(I,MASK),IAND(J,NOT(MASK)))
327NOT(INTEGER(k) I) -> INTEGER(k)
328POPCNT(INTEGER(any) I) -> default INTEGER
329POPPAR(INTEGER(any) I) -> default INTEGER = IAND(POPCNT(I), Z'1')
330SHIFTA(INTEGER(k) I, INTEGER(any) SHIFT) -> INTEGER(k)
331SHIFTL(INTEGER(k) I, INTEGER(any) SHIFT) -> INTEGER(k)
332SHIFTR(INTEGER(k) I, INTEGER(any) SHIFT) -> INTEGER(k)
333TRAILZ(INTEGER(any) I) -> default INTEGER
334```
335
336### Character elemental intrinsic functions
337See also `INDEX` and `LEN` above among the elemental intrinsic functions with
338unrestricted specific names.
339```
340ADJUSTL(CHARACTER(k,LEN=n) STRING) -> CHARACTER(k,LEN=n)
341ADJUSTR(CHARACTER(k,LEN=n) STRING) -> CHARACTER(k,LEN=n)
342LEN_TRIM(CHARACTER(k,n) STRING, KIND=KIND(0)) -> INTEGER(KIND) = n
343LGE(CHARACTER(k,n1) STRING_A, CHARACTER(k,n2) STRING_B) -> default LOGICAL
344LGT(CHARACTER(k,n1) STRING_A, CHARACTER(k,n2) STRING_B) -> default LOGICAL
345LLE(CHARACTER(k,n1) STRING_A, CHARACTER(k,n2) STRING_B) -> default LOGICAL
346LLT(CHARACTER(k,n1) STRING_A, CHARACTER(k,n2) STRING_B) -> default LOGICAL
347SCAN(CHARACTER(k,n) STRING, CHARACTER(k,m) SET, LOGICAL(any) BACK=.FALSE., KIND=KIND(0)) -> INTEGER(KIND)
348VERIFY(CHARACTER(k,n) STRING, CHARACTER(k,m) SET, LOGICAL(any) BACK=.FALSE., KIND=KIND(0)) -> INTEGER(KIND)
349```
350
351`SCAN` returns the index of the first (or last, if `BACK=.TRUE.`) character in `STRING`
352that is present in `SET`, or zero if none is.
353
354`VERIFY` is essentially the opposite: it returns the index of the first (or last) character
355in `STRING` that is *not* present in `SET`, or zero if all are.
356
357## Transformational intrinsic functions
358
359This category comprises a large collection of intrinsic functions that
360are collected together because they somehow transform their arguments
361in a way that prevents them from being elemental.
362All of them are pure, however.
363
364Some general rules apply to the transformational intrinsic functions:
365
3661. `DIM` arguments are optional; if present, the actual argument must be
367   a scalar integer of any kind.
3681. When an optional `DIM` argument is absent, or an `ARRAY` or `MASK`
369   argument is a vector, the result of the function is scalar; otherwise,
370   the result is an array of the same shape as the `ARRAY` or `MASK`
371   argument with the dimension `DIM` removed from the shape.
3721. When a function takes an optional `MASK` argument, it must be conformable
373  with its `ARRAY` argument if it is present, and the mask can be any kind
374  of `LOGICAL`.  It can be scalar.
3751. The type `numeric` here can be any kind of `INTEGER`, `REAL`, or `COMPLEX`.
3761. The type `relational` here can be any kind of `INTEGER`, `REAL`, or `CHARACTER`.
3771. The type `any` here denotes any intrinsic or derived type.
3781. The notation `(..)` denotes an array of any rank (but not an assumed-rank array).
379
380### Logical reduction transformational intrinsic functions
381```
382ALL(LOGICAL(k) MASK(..) [, DIM ]) -> LOGICAL(k)
383ANY(LOGICAL(k) MASK(..) [, DIM ]) -> LOGICAL(k)
384COUNT(LOGICAL(any) MASK(..) [, DIM, KIND=KIND(0) ]) -> INTEGER(KIND)
385PARITY(LOGICAL(k) MASK(..) [, DIM ]) -> LOGICAL(k)
386```
387
388### Numeric reduction transformational intrinsic functions
389```
390IALL(INTEGER(k) ARRAY(..) [, DIM, MASK ]) -> INTEGER(k)
391IANY(INTEGER(k) ARRAY(..) [, DIM, MASK ]) -> INTEGER(k)
392IPARITY(INTEGER(k) ARRAY(..) [, DIM, MASK ]) -> INTEGER(k)
393NORM2(REAL(k) X(..) [, DIM ]) -> REAL(k)
394PRODUCT(numeric ARRAY(..) [, DIM, MASK ]) -> numeric
395SUM(numeric ARRAY(..) [, DIM, MASK ]) -> numeric
396```
397
398`NORM2` generalizes `HYPOT` by computing `SQRT(SUM(X*X))` while avoiding spurious overflows.
399
400### Extrema reduction transformational intrinsic functions
401```
402MAXVAL(relational(k) ARRAY(..) [, DIM, MASK ]) -> relational(k)
403MINVAL(relational(k) ARRAY(..) [, DIM, MASK ]) -> relational(k)
404```
405
406### Locational transformational intrinsic functions
407When the optional `DIM` argument is absent, the result is an `INTEGER(KIND)`
408vector whose length is the rank of `ARRAY`.
409When the optional `DIM` argument is present, the result is an `INTEGER(KIND)`
410array of rank `RANK(ARRAY)-1` and shape equal to that of `ARRAY` with
411the dimension `DIM` removed.
412
413The optional `BACK` argument is a scalar LOGICAL value of any kind.
414When present and `.TRUE.`, it causes the function to return the index
415of the *last* occurence of the target or extreme value.
416
417For `FINDLOC`, `ARRAY` may have any of the five intrinsic types, and `VALUE`
418must a scalar value of a type for which `ARRAY==VALUE` or `ARRAY .EQV. VALUE`
419is an acceptable expression.
420
421```
422FINDLOC(intrinsic ARRAY(..), scalar VALUE [, DIM, MASK, KIND=KIND(0), BACK=.FALSE. ])
423MAXLOC(relational ARRAY(..) [, DIM, MASK, KIND=KIND(0), BACK=.FALSE. ])
424MINLOC(relational ARRAY(..) [, DIM, MASK, KIND=KIND(0), BACK=.FALSE. ])
425```
426
427### Data rearrangement transformational intrinsic functions
428The optional `DIM` argument to these functions must be a scalar integer of
429any kind, and it takes a default value of 1 when absent.
430
431```
432CSHIFT(any ARRAY(..), INTEGER(any) SHIFT(..) [, DIM ]) -> same type/kind/shape as ARRAY
433```
434Either `SHIFT` is scalar or `RANK(SHIFT) == RANK(ARRAY) - 1` and `SHAPE(SHIFT)` is that of `SHAPE(ARRAY)` with element `DIM` removed.
435
436```
437EOSHIFT(any ARRAY(..), INTEGER(any) SHIFT(..) [, BOUNDARY, DIM ]) -> same type/kind/shape as ARRAY
438```
439* `SHIFT` is scalar or `RANK(SHIFT) == RANK(ARRAY) - 1` and `SHAPE(SHIFT)` is that of `SHAPE(ARRAY)` with element `DIM` removed.
440* If `BOUNDARY` is present, it must have the same type and parameters as `ARRAY`.
441* If `BOUNDARY` is absent, `ARRAY` must be of an intrinsic type, and the default `BOUNDARY` is the obvious `0`, `' '`, or `.FALSE.` value of `KIND(ARRAY)`.
442* If `BOUNDARY` is present, either it is scalar, or `RANK(BOUNDARY) == RANK(ARRAY) - 1` and `SHAPE(BOUNDARY)` is that of `SHAPE(ARRAY)` with element `DIM`
443  removed.
444
445```
446PACK(any ARRAY(..), LOGICAL(any) MASK(..)) -> vector of same type and kind as ARRAY
447```
448* `MASK` is conformable with `ARRAY` and may be scalar.
449* The length of the result vector is `COUNT(MASK)` if `MASK` is an array, else `SIZE(ARRAY)` if `MASK` is `.TRUE.`, else zero.
450
451```
452PACK(any ARRAY(..), LOGICAL(any) MASK(..), any VECTOR(n)) -> vector of same type, kind, and size as VECTOR
453```
454* `MASK` is conformable with `ARRAY` and may be scalar.
455* `VECTOR` has the same type and kind as `ARRAY`.
456* `VECTOR` must not be smaller than result of `PACK` with no `VECTOR` argument.
457* The leading elements of `VECTOR` are replaced with elements from `ARRAY` as
458  if `PACK` had been invoked without `VECTOR`.
459
460```
461RESHAPE(any SOURCE(..), INTEGER(k) SHAPE(n) [, PAD(..), INTEGER(k2) ORDER(n) ]) -> SOURCE array with shape SHAPE
462```
463* If `ORDER` is present, it is a vector of the same size as `SHAPE`, and
464  contains a permutation.
465* The element(s) of `PAD` are used to fill out the result once `SOURCE`
466  has been consumed.
467
468```
469SPREAD(any SOURCE, DIM, scalar INTEGER(any) NCOPIES) -> same type as SOURCE, rank=RANK(SOURCE)+1
470TRANSFER(any SOURCE, any MOLD) -> scalar if MOLD is scalar, else vector; same type and kind as MOLD
471TRANSFER(any SOURCE, any MOLD, scalar INTEGER(any) SIZE) -> vector(SIZE) of type and kind of MOLD
472TRANSPOSE(any MATRIX(n,m)) -> matrix(m,n) of same type and kind as MATRIX
473```
474
475The shape of the result of `SPREAD` is the same as that of `SOURCE`, with `NCOPIES` inserted
476at position `DIM`.
477
478```
479UNPACK(any VECTOR(n), LOGICAL(any) MASK(..), FIELD) -> type and kind of VECTOR, shape of MASK
480```
481`FIELD` has same type and kind as `VECTOR` and is conformable with `MASK`.
482
483### Other transformational intrinsic functions
484```
485BESSEL_JN(INTEGER(n1) N1, INTEGER(n2) N2, REAL(k) X) -> REAL(k) vector (MAX(N2-N1+1,0))
486BESSEL_YN(INTEGER(n1) N1, INTEGER(n2) N2, REAL(k) X) -> REAL(k) vector (MAX(N2-N1+1,0))
487COMMAND_ARGUMENT_COUNT() -> scalar default INTEGER
488DOT_PRODUCT(LOGICAL(k) VECTOR_A(n), LOGICAL(k) VECTOR_B(n)) -> LOGICAL(k) = ANY(VECTOR_A .AND. VECTOR_B)
489DOT_PRODUCT(COMPLEX(any) VECTOR_A(n), numeric VECTOR_B(n)) = SUM(CONJG(VECTOR_A) * VECTOR_B)
490DOT_PRODUCT(INTEGER(any) or REAL(any) VECTOR_A(n), numeric VECTOR_B(n)) = SUM(VECTOR_A * VECTOR_B)
491MATMUL(numeric ARRAY_A(j), numeric ARRAY_B(j,k)) -> numeric vector(k)
492MATMUL(numeric ARRAY_A(j,k), numeric ARRAY_B(k)) -> numeric vector(j)
493MATMUL(numeric ARRAY_A(j,k), numeric ARRAY_B(k,m)) -> numeric matrix(j,m)
494MATMUL(LOGICAL(n1) ARRAY_A(j), LOGICAL(n2) ARRAY_B(j,k)) -> LOGICAL vector(k)
495MATMUL(LOGICAL(n1) ARRAY_A(j,k), LOGICAL(n2) ARRAY_B(k)) -> LOGICAL vector(j)
496MATMUL(LOGICAL(n1) ARRAY_A(j,k), LOGICAL(n2) ARRAY_B(k,m)) -> LOGICAL matrix(j,m)
497NULL([POINTER/ALLOCATABLE MOLD]) -> POINTER
498REDUCE(any ARRAY(..), function OPERATION [, DIM, LOGICAL(any) MASK(..), IDENTITY, LOGICAL ORDERED=.FALSE. ])
499REPEAT(CHARACTER(k,n) STRING, INTEGER(any) NCOPIES) -> CHARACTER(k,n*NCOPIES)
500SELECTED_CHAR_KIND('DEFAULT' or 'ASCII' or 'ISO_10646' or ...) -> scalar default INTEGER
501SELECTED_INT_KIND(scalar INTEGER(any) R) -> scalar default INTEGER
502SELECTED_REAL_KIND([scalar INTEGER(any) P, scalar INTEGER(any) R, scalar INTEGER(any) RADIX]) -> scalar default INTEGER
503SHAPE(SOURCE, KIND=KIND(0)) -> INTEGER(KIND)(RANK(SOURCE))
504TRIM(CHARACTER(k,n) STRING) -> CHARACTER(k)
505```
506
507The type and kind of the result of a numeric `MATMUL` is the same as would result from
508a multiplication of an element of ARRAY_A and an element of ARRAY_B.
509
510The kind of the `LOGICAL` result of a `LOGICAL` `MATMUL` is the same as would result
511from an intrinsic `.AND.` operation between an element of `ARRAY_A` and an element
512of `ARRAY_B`.
513
514Note that `DOT_PRODUCT` with a `COMPLEX` first argument operates on its complex conjugate,
515but that `MATMUL` with a `COMPLEX` argument does not.
516
517The `MOLD` argument to `NULL` may be omitted only in a context where the type of the pointer is known,
518such as an initializer or pointer assignment statement.
519
520At least one argument must be present in a call to `SELECTED_REAL_KIND`.
521
522An assumed-rank array may be passed to `SHAPE`, and if it is associated with an assumed-size array,
523the last element of the result will be -1.
524
525### Coarray transformational intrinsic functions
526```
527FAILED_IMAGES([scalar TEAM_TYPE TEAM, KIND=KIND(0)]) -> INTEGER(KIND) vector
528GET_TEAM([scalar INTEGER(?) LEVEL]) -> scalar TEAM_TYPE
529IMAGE_INDEX(COARRAY, INTEGER(any) SUB(n) [, scalar TEAM_TYPE TEAM ]) -> scalar default INTEGER
530IMAGE_INDEX(COARRAY, INTEGER(any) SUB(n), scalar INTEGER(any) TEAM_NUMBER) -> scalar default INTEGER
531NUM_IMAGES([scalar TEAM_TYPE TEAM]) -> scalar default INTEGER
532NUM_IMAGES(scalar INTEGER(any) TEAM_NUMBER) -> scalar default INTEGER
533STOPPED_IMAGES([scalar TEAM_TYPE TEAM, KIND=KIND(0)]) -> INTEGER(KIND) vector
534TEAM_NUMBER([scalar TEAM_TYPE TEAM]) -> scalar default INTEGER
535THIS_IMAGE([COARRAY, DIM, scalar TEAM_TYPE TEAM]) -> default INTEGER
536```
537The result of `THIS_IMAGE` is a scalar if `DIM` is present or if `COARRAY` is absent,
538and a vector whose length is the corank of `COARRAY` otherwise.
539
540## Inquiry intrinsic functions
541These are neither elemental nor transformational; all are pure.
542
543### Type inquiry intrinsic functions
544All of these functions return constants.
545The value of the argument is not used, and may well be undefined.
546```
547BIT_SIZE(INTEGER(k) I(..)) -> INTEGER(k)
548DIGITS(INTEGER or REAL X(..)) -> scalar default INTEGER
549EPSILON(REAL(k) X(..)) -> scalar REAL(k)
550HUGE(INTEGER(k) X(..)) -> scalar INTEGER(k)
551HUGE(REAL(k) X(..)) -> scalar of REAL(k)
552KIND(intrinsic X(..)) -> scalar default INTEGER
553MAXEXPONENT(REAL(k) X(..)) -> scalar default INTEGER
554MINEXPONENT(REAL(k) X(..)) -> scalar default INTEGER
555NEW_LINE(CHARACTER(k,n) A(..)) -> scalar CHARACTER(k,1) = CHAR(10)
556PRECISION(REAL(k) or COMPLEX(k) X(..)) -> scalar default INTEGER
557RADIX(INTEGER(k) or REAL(k) X(..)) -> scalar default INTEGER, always 2
558RANGE(INTEGER(k) or REAL(k) or COMPLEX(k) X(..)) -> scalar default INTEGER
559TINY(REAL(k) X(..)) -> scalar REAL(k)
560```
561
562### Bound and size inquiry intrinsic functions
563The results are scalar when `DIM` is present, and a vector of length=(co)rank(`(CO)ARRAY`)
564when `DIM` is absent.
565```
566LBOUND(any ARRAY(..) [, DIM, KIND=KIND(0) ]) -> INTEGER(KIND)
567LCOBOUND(any COARRAY [, DIM, KIND=KIND(0) ]) -> INTEGER(KIND)
568SIZE(any ARRAY(..) [, DIM, KIND=KIND(0) ]) -> INTEGER(KIND)
569UBOUND(any ARRAY(..) [, DIM, KIND=KIND(0) ]) -> INTEGER(KIND)
570UCOBOUND(any COARRAY [, DIM, KIND=KIND(0) ]) -> INTEGER(KIND)
571```
572
573Assumed-rank arrays may be used with `LBOUND`, `SIZE`, and `UBOUND`.
574
575### Object characteristic inquiry intrinsic functions
576```
577ALLOCATED(any type ALLOCATABLE ARRAY) -> scalar default LOGICAL
578ALLOCATED(any type ALLOCATABLE SCALAR) -> scalar default LOGICAL
579ASSOCIATED(any type POINTER POINTER [, same type TARGET]) -> scalar default LOGICAL
580COSHAPE(COARRAY, KIND=KIND(0)) -> INTEGER(KIND) vector of length corank(COARRAY)
581EXTENDS_TYPE_OF(A, MOLD) -> default LOGICAL
582IS_CONTIGUOUS(any data ARRAY(..)) -> scalar default LOGICAL
583PRESENT(OPTIONAL A) -> scalar default LOGICAL
584RANK(any data A) -> scalar default INTEGER = 0 if A is scalar, SIZE(SHAPE(A)) if A is an array, rank if assumed-rank
585SAME_TYPE_AS(A, B) -> scalar default LOGICAL
586STORAGE_SIZE(any data A, KIND=KIND(0)) -> INTEGER(KIND)
587```
588The arguments to `EXTENDS_TYPE_OF` must be of extensible derived types or be unlimited polymorphic.
589
590An assumed-rank array may be used with `IS_CONTIGUOUS` and `RANK`.
591
592## Intrinsic subroutines
593
594(*TODO*: complete these descriptions)
595
596### One elemental intrinsic subroutine
597```
598INTERFACE
599  SUBROUTINE MVBITS(FROM, FROMPOS, LEN, TO, TOPOS)
600    INTEGER(k1) :: FROM, TO
601    INTENT(IN) :: FROM
602    INTENT(INOUT) :: TO
603    INTEGER(k2), INTENT(IN) :: FROMPOS
604    INTEGER(k3), INTENT(IN) :: LEN
605    INTEGER(k4), INTENT(IN) :: TOPOS
606  END SUBROUTINE
607END INTERFACE
608```
609
610### Non-elemental intrinsic subroutines
611```
612CALL CPU_TIME(REAL INTENT(OUT) TIME)
613```
614The kind of `TIME` is not specified in the standard.
615
616```
617CALL DATE_AND_TIME([DATE, TIME, ZONE, VALUES])
618```
619* All arguments are `OPTIONAL` and `INTENT(OUT)`.
620* `DATE`, `TIME`, and `ZONE` are scalar default `CHARACTER`.
621* `VALUES` is a vector of at least 8 elements of `INTEGER(KIND >= 2)`.
622```
623CALL EVENT_QUERY(EVENT, COUNT [, STAT])
624CALL EXECUTE_COMMAND_LINE(COMMAND [, WAIT, EXITSTAT, CMDSTAT, CMDMSG ])
625CALL GET_COMMAND([COMMAND, LENGTH, STATUS, ERRMSG ])
626CALL GET_COMMAND_ARGUMENT(NUMBER [, VALUE, LENGTH, STATUS, ERRMSG ])
627CALL GET_ENVIRONMENT_VARIABLE(NAME [, VALUE, LENGTH, STATUS, TRIM_NAME, ERRMSG ])
628CALL MOVE_ALLOC(ALLOCATABLE INTENT(INOUT) FROM, ALLOCATABLE INTENT(OUT) TO [, STAT, ERRMSG ])
629CALL RANDOM_INIT(LOGICAL(k1) INTENT(IN) REPEATABLE, LOGICAL(k2) INTENT(IN) IMAGE_DISTINCT)
630CALL RANDOM_NUMBER(REAL(k) INTENT(OUT) HARVEST(..))
631CALL RANDOM_SEED([SIZE, PUT, GET])
632CALL SYSTEM_CLOCK([COUNT, COUNT_RATE, COUNT_MAX])
633```
634
635### Atomic intrinsic subroutines
636```
637CALL ATOMIC_ADD(ATOM, VALUE [, STAT=])
638CALL ATOMIC_AND(ATOM, VALUE [, STAT=])
639CALL ATOMIC_CAS(ATOM, OLD, COMPARE, NEW [, STAT=])
640CALL ATOMIC_DEFINE(ATOM, VALUE [, STAT=])
641CALL ATOMIC_FETCH_ADD(ATOM, VALUE, OLD [, STAT=])
642CALL ATOMIC_FETCH_AND(ATOM, VALUE, OLD [, STAT=])
643CALL ATOMIC_FETCH_OR(ATOM, VALUE, OLD [, STAT=])
644CALL ATOMIC_FETCH_XOR(ATOM, VALUE, OLD [, STAT=])
645CALL ATOMIC_OR(ATOM, VALUE [, STAT=])
646CALL ATOMIC_REF(VALUE, ATOM [, STAT=])
647CALL ATOMIC_XOR(ATOM, VALUE [, STAT=])
648```
649
650### Collective intrinsic subroutines
651```
652CALL CO_BROADCAST
653CALL CO_MAX
654CALL CO_MIN
655CALL CO_REDUCE
656CALL CO_SUM
657```
658
659## Non-standard intrinsics
660### PGI
661```
662AND, OR, XOR
663LSHIFT, RSHIFT, SHIFT
664ZEXT, IZEXT
665COSD, SIND, TAND, ACOSD, ASIND, ATAND, ATAN2D
666COMPL
667DCMPLX
668EQV, NEQV
669INT8
670JINT, JNINT, KNINT
671LOC
672```
673
674### Intel
675```
676DCMPLX(X,Y), QCMPLX(X,Y)
677DREAL(DOUBLE COMPLEX A) -> DOUBLE PRECISION
678DFLOAT, DREAL
679QEXT, QFLOAT, QREAL
680DNUM, INUM, JNUM, KNUM, QNUM, RNUM - scan value from string
681ZEXT
682RAN, RANF
683ILEN(I) = BIT_SIZE(I)
684SIZEOF
685MCLOCK, SECNDS
686COTAN(X) = 1.0/TAN(X)
687COSD, SIND, TAND, ACOSD, ASIND, ATAND, ATAN2D, COTAND - degrees
688AND, OR, XOR
689LSHIFT, RSHIFT
690IBCHNG, ISHA, ISHC, ISHL, IXOR
691IARG, IARGC, NARGS, NUMARG
692BADDRESS, IADDR
693CACHESIZE, EOF, FP_CLASS, INT_PTR_KIND, ISNAN, LOC
694MALLOC
695```
696
697## Intrinsic Procedure Name Resolution
698
699When the name of a procedure in a program is the same as the one of an intrinsic
700procedure, and nothing other than its usage allows to decide whether the procedure
701is the intrinsic or not (i.e, it does not appear in an INTRINSIC or EXTERNAL attribute
702statement, is not an use/host associated procedure...), Fortran 2018 standard
703section 19.5.1.4 point 6 rules that the procedure is established to be intrinsic if it is
704invoked as an intrinsic procedure.
705
706In case the invocation would be an error if the procedure were the intrinsic
707(e.g. wrong argument number or type), the broad wording of the standard
708leaves two choices to the compiler: emit an error about the intrinsic invocation,
709or consider this is an external procedure and emit no error.
710
711f18 will always consider this case to be the intrinsic and emit errors, unless the procedure
712is used as a function (resp. subroutine) and the intrinsic is a subroutine (resp. function).
713The table below gives some examples of decisions made by Fortran compilers in such case.
714
715| What is ACOS ?     | Bad intrinsic call       | External with warning |  External no warning | Other error |
716| --- | --- | --- | --- | --- |
717| `print*, ACOS()`     | gfortran, nag, xlf, f18  |  ifort                |  nvfortran           | |
718| `print*, ACOS(I)`    | gfortran, nag, xlf, f18  |  ifort                |  nvfortran           | |
719| `print*, ACOS(X=I)`  | gfortran, nag, xlf, f18  |  ifort                |                      | nvfortran (keyword on implicit extrenal )|
720| `print*, ACOS(X, X)` | gfortran, nag, xlf, f18  |  ifort                |  nvfortran           | |
721| `CALL ACOS(X)`       |                          |                       |  gfortran, nag, xlf, nvfortran, ifort, f18  | |
722
723
724The rationale for f18 behavior is that when referring to a procedure with an
725argument number or type that does not match the intrinsic specification, it seems safer to block
726the rather likely case where the user is using the intrinsic the wrong way.
727In case the user wanted to refer to an external function, he can add an explicit EXTERNAL
728statement with no other consequences on the program.
729However, it seems rather unlikely that a user would confuse an intrinsic subroutine for a
730function and vice versa. Given no compiler is issuing an error here, changing the behavior might
731affect existing programs that omit the EXTERNAL attribute in such case.
732
733Also note that in general, the standard gives the compiler the right to consider
734any procedure that is not explicitly external as a non standard intrinsic (section 4.2 point 4).
735So it is highly advised for the programmer to use EXTERNAL statements to prevent any ambiguity.
736
737## Intrinsic Procedure Support in f18
738This section gives an overview of the support inside f18 libraries for the
739intrinsic procedures listed above.
740It may be outdated, refer to f18 code base for the actual support status.
741
742### Semantic Analysis
743F18 semantic expression analysis phase detects intrinsic procedure references,
744validates the argument types and deduces the return types.
745This phase currently supports all the intrinsic procedures listed above but the ones in the table below.
746
747| Intrinsic Category | Intrinsic Procedures Lacking Support |
748| --- | --- |
749| Coarray intrinsic functions | LCOBOUND, UCOBOUND, FAILED_IMAGES, GET_TEAM, IMAGE_INDEX, STOPPED_IMAGES, TEAM_NUMBER, THIS_IMAGE, COSHAPE |
750| Object characteristic inquiry functions | ALLOCATED, ASSOCIATED, EXTENDS_TYPE_OF, IS_CONTIGUOUS, PRESENT, RANK, SAME_TYPE, STORAGE_SIZE |
751| Type inquiry intrinsic functions | BIT_SIZE, DIGITS, EPSILON, HUGE, KIND, MAXEXPONENT, MINEXPONENT, NEW_LINE, PRECISION, RADIX, RANGE, TINY|
752| Non-standard intrinsic functions | AND, OR, XOR, LSHIFT, RSHIFT, SHIFT, ZEXT, IZEXT, COSD, SIND, TAND, ACOSD, ASIND, ATAND, ATAN2D, COMPL, DCMPLX, EQV, NEQV, INT8, JINT, JNINT, KNINT, LOC, QCMPLX, DREAL, DFLOAT, QEXT, QFLOAT, QREAL, DNUM, NUM, JNUM, KNUM, QNUM, RNUM, RAN, RANF, ILEN, SIZEOF, MCLOCK, SECNDS, COTAN, IBCHNG, ISHA, ISHC, ISHL, IXOR, IARG, IARGC, NARGS, NUMARG, BADDRESS, IADDR, CACHESIZE, EOF, FP_CLASS, INT_PTR_KIND, ISNAN, MALLOC |
753| Intrinsic subroutines |MVBITS (elemental), CPU_TIME, DATE_AND_TIME, EVENT_QUERY, EXECUTE_COMMAND_LINE, GET_COMMAND, GET_COMMAND_ARGUMENT, GET_ENVIRONMENT_VARIABLE, MOVE_ALLOC, RANDOM_INIT, RANDOM_NUMBER, RANDOM_SEED, SYSTEM_CLOCK |
754| Atomic intrinsic subroutines | ATOMIC_ADD &al. |
755| Collective intrinsic subroutines | CO_BROADCAST &al. |
756
757
758### Intrinsic Function Folding
759Fortran Constant Expressions can contain references to a certain number of
760intrinsic functions (see Fortran 2018 standard section 10.1.12 for more details).
761Constant Expressions may be used to define kind arguments. Therefore, the semantic
762expression analysis phase must be able to fold references to intrinsic functions
763listed in section 10.1.12.
764
765F18 intrinsic function folding is either performed by implementations directly
766operating on f18 scalar types or by using host runtime functions and
767host hardware types. F18 supports folding elemental intrinsic functions over
768arrays when an implementation is provided for the scalars (regardless of whether
769it is using host hardware types or not).
770The status of intrinsic function folding support is given in the sub-sections below.
771
772#### Intrinsic Functions with Host Independent Folding Support
773Implementations using f18 scalar types enables folding intrinsic functions
774on any host and with any possible type kind supported by f18. The intrinsic functions
775listed below are folded using host independent implementations.
776
777| Return Type | Intrinsic Functions with Host Independent Folding Support|
778| --- | --- |
779| INTEGER| ABS(INTEGER(k)), DIM(INTEGER(k), INTEGER(k)), DSHIFTL, DSHIFTR, IAND, IBCLR, IBSET, IEOR, INT, IOR, ISHFT, KIND, LEN, LEADZ, MASKL, MASKR, MERGE_BITS, POPCNT, POPPAR, SHIFTA, SHIFTL, SHIFTR, TRAILZ |
780| REAL | ABS(REAL(k)), ABS(COMPLEX(k)), AIMAG, AINT, DPROD, REAL |
781| COMPLEX | CMPLX, CONJG |
782| LOGICAL | BGE, BGT, BLE, BLT |
783
784#### Intrinsic Functions with Host Dependent Folding Support
785Implementations using the host runtime may not be available for all supported
786f18 types depending on the host hardware types and the libraries available on the host.
787The actual support on a host depends on what the host hardware types are.
788The list below gives the functions that are folded using host runtime and the related C/C++ types.
789F18 automatically detects if these types match an f18 scalar type. If so,
790folding of the intrinsic functions will be possible for the related f18 scalar type,
791otherwise an error message will be produced by f18 when attempting to fold related intrinsic functions.
792
793| C/C++ Host Type | Intrinsic Functions with Host Standard C++ Library Based Folding Support |
794| --- | --- |
795| float, double and long double | ACOS, ACOSH, ASINH, ATAN, ATAN2, ATANH, COS, COSH, ERF, ERFC, EXP, GAMMA, HYPOT, LOG, LOG10, LOG_GAMMA, MOD, SIN, SQRT, SINH, SQRT, TAN, TANH |
796| std::complex for float, double and long double| ACOS, ACOSH, ASIN, ASINH, ATAN, ATANH, COS, COSH, EXP, LOG, SIN, SINH, SQRT, TAN, TANH |
797
798On top of the default usage of C++ standard library functions for folding described
799in the table above, it is possible to compile f18 evaluate library with
800[libpgmath](https://github.com/flang-compiler/flang/tree/master/runtime/libpgmath)
801so that it can be used for folding. To do so, one must have a compiled version
802of the libpgmath library available on the host and add
803`-DLIBPGMATH_DIR=<path to the compiled shared libpgmath library>` to the f18 cmake command.
804
805Libpgmath comes with real and complex functions that replace C++ standard library
806float and double functions to fold all the intrinsic functions listed in the table above.
807It has no long double versions. If the host long double matches an f18 scalar type,
808C++ standard library functions will still be used for folding expressions with this scalar type.
809Libpgmath adds the possibility to fold the following functions for f18 real scalar
810types related to host float and double types.
811
812| C/C++ Host Type | Additional Intrinsic Function Folding Support with Libpgmath (Optional) |
813| --- | --- |
814|float and double| BESSEL_J0, BESSEL_J1, BESSEL_JN (elemental only), BESSEL_Y0, BESSEL_Y1, BESSEL_Yn (elemental only), ERFC_SCALED |
815
816Libpgmath comes in three variants (precise, relaxed and fast). So far, only the
817precise version is used for intrinsic function folding in f18. It guarantees the greatest numerical precision.
818
819### Intrinsic Functions with Missing Folding Support
820The following intrinsic functions are allowed in constant expressions but f18
821is not yet able to fold them. Note that there might be constraints on the arguments
822so that these intrinsics can be used in constant expressions (see section 10.1.12 of Fortran 2018 standard).
823
824ALL, ACHAR, ADJUSTL, ADJUSTR, ANINT, ANY, BESSEL_JN (transformational only),
825BESSEL_YN (transformational only), BTEST, CEILING, CHAR, COUNT, CSHIFT, DOT_PRODUCT,
826DIM (REAL only), DOT_PRODUCT, EOSHIFT, FINDLOC, FLOOR, FRACTION, HUGE, IACHAR, IALL,
827IANY, IPARITY, IBITS, ICHAR, IMAGE_STATUS, INDEX, ISHFTC, IS_IOSTAT_END,
828IS_IOSTAT_EOR, LBOUND, LEN_TRIM, LGE, LGT, LLE, LLT, LOGICAL, MATMUL, MAX, MAXLOC,
829MAXVAL, MERGE, MIN, MINLOC, MINVAL, MOD (INTEGER only), MODULO, NEAREST, NINT,
830NORM2, NOT, OUT_OF_RANGE, PACK, PARITY, PRODUCT, REPEAT, REDUCE, RESHAPE,
831RRSPACING, SCAN, SCALE, SELECTED_CHAR_KIND, SELECTED_INT_KIND, SELECTED_REAL_KIND,
832SET_EXPONENT, SHAPE, SIGN, SIZE, SPACING, SPREAD, SUM, TINY, TRANSFER, TRANSPOSE,
833TRIM, UBOUND, UNPACK, VERIFY.
834
835Coarray, non standard, IEEE and ISO_C_BINDINGS intrinsic functions that can be
836used in constant expressions have currently no folding support at all.
837