@ignore Copyright (C) 2005 Free Software Foundation, Inc. This is part of the GFORTRAN manual. For copying conditions, see the file gfortran.texi. Permission is granted to copy, distribute and/or modify this document under the terms of the GNU Free Documentation License, Version 1.2 or any later version published by the Free Software Foundation; with the Invariant Sections being ``GNU General Public License'' and ``Funding Free Software'', the Front-Cover texts being (a) (see below), and with the Back-Cover Texts being (b) (see below). A copy of the license is included in the gfdl(7) man page. Some basic guidelines for editing this document: (1) The intrinsic procedures are to be listed in alphabetical order. (2) The generic name is to be use. (3) The specific names are included in the function index and in a table at the end of the node (See ABS entry). (4) Try to maintain the same style for each entry. @end ignore @node Intrinsic Procedures @chapter Intrinsic Procedures @cindex Intrinsic Procedures This portion of the document is incomplete and undergoing massive expansion and editing. All contributions and corrections are strongly encouraged. @menu * Introduction: Introduction * @code{ABORT}: ABORT, Abort the program * @code{ABS}: ABS, Absolute value * @code{ACHAR}: ACHAR, Character in @acronym{ASCII} collating sequence * @code{ACOS}: ACOS, Arccosine function * @code{ADJUSTL}: ADJUSTL, Left adjust a string * @code{ADJUSTR}: ADJUSTR, Right adjust a string * @code{AIMAG}: AIMAG, Imaginary part of complex number * @code{AINT}: AINT, Truncate to a whole number * @code{ALL}: ALL, Determine all values are true @end menu @node Introduction @section Introduction to intrinsic procedures Gfortran provides a rich set of intrinsic procedures that includes all the intrinsic procedures required by the Fortran 95 standard, a set of intrinsic procedures for backwards compatibility with Gnu Fortran 77 (i.e., @command{g77}), and a small selection of intrinsic procedures from the Fortran 2003 standard. Any description here, which conflicts with a description in either the Fortran 95 standard or the Fortran 2003 standard, is unintentional and the standard(s) should be considered authoritative. The enumeration of the @code{KIND} type parameter is processor defined in the Fortran 95 standard. Gfortran defines the default integer type and default real type by @code{INTEGER(KIND=4)} and @code{REAL(KIND=4)}, respectively. The standard mandates that both data types shall have another kind, which have more precision. On typical target architectures supports by @command{gfortran}, this kind type parameter is @code{KIND=8}. Hence, @code{REAL(KIND=8)} and @code{DOUBLE PRECISION} are equivalent. In the description of generic intrinsic procedures, the kind type parameter will be specified by @code{KIND=*}, and in the description of specific names for an intrinsic procedure the kind type parameter will be explicitly given (e.g., @code{REAL(KIND=4)} or @code{REAL(KIND=8)}). Finally, for brevity the optional @code{KIND=} syntax will be omitted. Many of the intrinsics procedures take one or more optional arguments. This document follows the convention used in the Fortran 95 standard, and denotes such arguments by square brackets. @command{Gfortran} offers the @option{-std=f95} and @option{-std=gnu} options, which can be used to restrict the set of intrinsic procedures to a given standard. By default, @command{gfortran} sets the @option{-std=gnu} option, and so all intrinsic procedures describe here are accepted. There is one caveat. For a select group of intrinsic procedures, @command{g77} implemented both a function and a subroutine. Both classes have been implemented in @command{gfortran} for backwards compatibility with @command{g77}. It is noted here that these functions and subroutines cannot be intermixed in a given subprogram. In the descriptions that follow, the applicable option(s) is noted. @node ABORT @section @code{ABORT} --- Abort the program @findex @code{ABORT} @cindex abort @table @asis @item @emph{Description}: @code{ABORT} causes immediate termination of the program. On operating systems that support a core dump, @code{ABORT} will produce a core dump, which is suitable for debugging purposes. @item @emph{Option}: gnu @item @emph{Type}: non-elemental subroutine @item @emph{Syntax}: @code{CALL ABORT} @item @emph{Return value}: Does not return. @item @emph{Example}: @smallexample program test_abort integer :: i = 1, j = 2 if (i /= j) call abort end program test_abort @end smallexample @end table @node ABS @section @code{ABS} --- Absolute value @findex @code{ABS} intrinsic @findex @code{CABS} intrinsic @findex @code{DABS} intrinsic @findex @code{IABS} intrinsic @findex @code{ZABS} intrinsic @findex @code{CDABS} intrinsic @cindex absolute value @table @asis @item @emph{Description}: @code{ABS(X)} computes the absolute value of @code{X}. @item @emph{Option}: f95, gnu @item @emph{Type}: elemental function @item @emph{Syntax}: @code{X = ABS(X)} @item @emph{Arguments}: @multitable @columnfractions .15 .80 @item @var{X} @tab The type of the argument shall be an @code{INTEGER(*)}, @code{REAL(*)}, or @code{COMPLEX(*)}. @end multitable @item @emph{Return value}: The return value is of the same type and kind as the argument except the return value is @code{REAL(*)} for a @code{COMPLEX(*)} argument. @item @emph{Example}: @smallexample program test_abort integer :: i = -1 real :: x = -1.e0 complex :: z = (-1.e0,0.e0) i = abs(i) x = abs(x) x = abs(z) end program test_abort @end smallexample @item @emph{Specific names}: @multitable @columnfractions .24 .24 .24 .24 @item Name @tab Argument @tab Return type @tab Option @item @code{CABS(Z)} @tab @code{COMPLEX(4) Z} @tab @code{REAL(4)} @tab f95, gnu @item @code{DABS(X)} @tab @code{REAL(8) X} @tab @code{REAL(8)} @tab f95, gnu @item @code{IABS(I)} @tab @code{INTEGER(4) I} @tab @code{INTEGER(4)} @tab f95, gnu @item @code{ZABS(Z)} @tab @code{COMPLEX(8) Z} @tab @code{COMPLEX(8)} @tab gnu @item @code{CDABS(Z)} @tab @code{COMPLEX(8) Z} @tab @code{COMPLEX(8)} @tab gnu @end multitable @end table @node ACHAR @section @code{ACHAR} --- Character in @acronym{ASCII} collating sequence @findex @code{ACHAR} intrinsic @cindex @acronym{ASCII} collating sequence @table @asis @item @emph{Description}: @code{ACHAR(I)} returns the character located at position @code{I} in the @acronym{ASCII} collating sequence. @item @emph{Option}: f95, gnu @item @emph{Type}: elemental function @item @emph{Syntax}: @code{C = ACHAR(I)} @item @emph{Arguments}: @multitable @columnfractions .15 .80 @item @var{I} @tab The type shall be an @code{INTEGER(*)}. @end multitable @item @emph{Return value}: The return value is of type @code{CHARACTER} with a length of one. The kind type parameter is the same as @code{KIND('A')}. @item @emph{Example}: @smallexample program test_achar character c c = achar(32) end program test_abort @end smallexample @end table @node ACOS @section @code{ACOS} --- Arccosine function @findex @code{ACOS} intrinsic @findex @code{DACOS} intrinsic @cindex arccosine @table @asis @item @emph{Description}: @code{ACOS(X)} computes the arccosine of its @var{X}. @item @emph{Option}: f95, gnu @item @emph{Type}: elemental function @item @emph{Syntax}: @code{X = ACOS(X)} @item @emph{Arguments}: @multitable @columnfractions .15 .80 @item @var{X} @tab The type shall be an @code{REAL(*)}. @end multitable @item @emph{Return value}: The return value is of type @code{REAL(*)} and it lies in the range @math{ 0 \leq \arccos (x) \leq \pi}. @item @emph{Example}: @smallexample program test_acos real(8) :: x = 0.866_8 x = achar(x) end program test_acos @end smallexample @item @emph{Specific names}: @multitable @columnfractions .24 .24 .24 .24 @item Name @tab Argument @tab Return type @tab Option @item @code{DACOS(X)} @tab @code{REAL(8) X} @tab @code{REAL(8)} @tab f95, gnu @end multitable @end table @node ADJUSTL @section @code{ADJUSTL} --- Left adjust a string @findex @code{ADJUSTL} intrinsic @cindex adjust string @table @asis @item @emph{Description}: @code{ADJUSTL(STR)} will left adjust a string by removing leading spaces. Spaces are inserted at the end of the string as needed. @item @emph{Option}: f95, gnu @item @emph{Type}: elemental function @item @emph{Syntax}: @code{STR = ADJUSTL(STR)} @item @emph{Arguments}: @multitable @columnfractions .15 .80 @item @var{STR} @tab The type shall be @code{CHARACTER}. @end multitable @item @emph{Return value}: The return value is of type @code{CHARACTER} where leading spaces are removed and the same number of spaces are inserted on the end of @var{STR}. @item @emph{Example}: @smallexample program test_adjustl character(len=20) :: str = ' gfortran' str = adjustl(str) print *, str end program test_adjustl @end smallexample @end table @node ADJUSTR @section @code{ADJUSTR} --- Right adjust a string @findex @code{ADJUSTR} intrinsic @cindex adjust string @table @asis @item @emph{Description}: @code{ADJUSTR(STR)} will right adjust a string by removing trailing spaces. Spaces are inserted at the start of the string as needed. @item @emph{Option}: f95, gnu @item @emph{Type}: elemental function @item @emph{Syntax}: @code{STR = ADJUSTR(STR)} @item @emph{Arguments}: @multitable @columnfractions .15 .80 @item @var{STR} @tab The type shall be @code{CHARACTER}. @end multitable @item @emph{Return value}: The return value is of type @code{CHARACTER} where trailing spaces are removed and the same number of spaces are inserted at the start of @var{STR}. @item @emph{Example}: @smallexample program test_adjustr character(len=20) :: str = 'gfortran' str = adjustr(str) print *, str end program test_adjustr @end smallexample @end table @node AIMAG @section @code{AIMAG} --- Imaginary part of complex number @findex @code{AIMAG} intrinsic @findex @code{DIMAG} intrinsic @cindex Imaginary part @table @asis @item @emph{Description}: @code{AIMAG(Z)} yields the imaginary part of complex argument @code{Z}. @item @emph{Option}: f95, gnu @item @emph{Type}: elemental function @item @emph{Syntax}: @code{X = AIMAG(Z)} @item @emph{Arguments}: @multitable @columnfractions .15 .80 @item @var{Z} @tab The type of the argument shall be @code{COMPLEX(*)}. @end multitable @item @emph{Return value}: The return value is of type real with the kind type parameter of the argument. @item @emph{Example}: @smallexample program test_aimag complex(4) z4 complex(8) z8 z4 = cmplx(1.e0_4, 0.e0_4) z8 = cmplx(0.e0_8, 1.e0_8) print *, aimag(z4), dimag(z8) end program test_aimag @end smallexample @item @emph{Specific names}: @multitable @columnfractions .24 .24 .24 .24 @item Name @tab Argument @tab Return type @tab Option @item @code{DIMAG(Z)} @tab @code{COMPLEX(8) Z} @tab @code{REAL(8)} @tab f95, gnu @end multitable @end table @node AINT @section @code{AINT} --- Imaginary part of complex number @findex @code{AINT} intrinsic @findex @code{DINT} intrinsic @cindex whole number @table @asis @item @emph{Description}: @code{AINT(X [, KIND])} truncates its argument to a whole number. @item @emph{Option}: f95, gnu @item @emph{Type}: elemental function @item @emph{Syntax}: @code{X = AINT(X)} @* @code{X = AINT(X, KIND)} @item @emph{Arguments}: @multitable @columnfractions .15 .80 @item @var{X} @tab The type of the argument shall be @code{REAL(*)}. @item @var{KIND} @tab (Optional) @var{KIND} shall be a scalar integer initialization expression. @end multitable @item @emph{Return value}: The return value is of type real with the kind type parameter of the argument if the optional @var{KIND} is absence; otherwise, the kind type parameter will be given by @var{KIND}. If the magnitude of @var{X} is less than one, then @code{AINT(X)} returns zero. If the magnitude is equal to or greater than one, then it returns the largest whole number that does not exceed its magnitude. The sign is the same as the sign of @var{X}. @item @emph{Example}: @smallexample program test_aint real(4) x4 real(8) x8 x4 = 1.234E0_4 x8 = 4.321_8 print *, aint(x4), dint(x8) x8 = aint(x4,8) end program test_aint @end smallexample @item @emph{Specific names}: @multitable @columnfractions .24 .24 .24 .24 @item Name @tab Argument @tab Return type @tab Option @item @code{DINT(X)} @tab @code{REAL(8) X} @tab @code{REAL(8)} @tab f95, gnu @end multitable @end table @node ALL @section @code{ALL} --- All values in @var{MASK} along @var{DIM} are true @findex @code{ALL} intrinsic @cindex true values @table @asis @item @emph{Description}: @code{ALL(MASK [, DIM])} determines if all the values are true in @var{MASK} in the array along dimension @var{DIM}. @item @emph{Option}: f95, gnu @item @emph{Type}: transformational function @item @emph{Syntax}: @code{L = ALL(MASK)} @* @code{L = ALL(MASK, DIM)} @item @emph{Arguments}: @multitable @columnfractions .15 .80 @item @var{MASK} @tab The type of the argument shall be @code{LOGICAL(*)} and it shall not be scalar. @item @var{DIM} @tab (Optional) @var{DIM} shall be a scalar integer with a value that lies between one and the rank of @var{MASK}. @end multitable @item @emph{Return value}: @code{ALL(MASK)} returns a scalar value of type @code{LOGICAL(*)} where the kind type parameter is the same as the kind type parameter of @var{MASK}. If @var{DIM} is present, then @code{ALL(MASK, DIM)} returns an array with the rank of @var{MASK} minus 1. The shape is determined from the shape of @var{MASK} where the @var{DIM} dimension is elided. @table @asis @item (A) @code{ALL(MASK)} is true if all elements of @var{MASK} are true. It also is true if @var{MASK} has zero size; otherwise, it is false. @item (B) If the rank of @var{MASK} is one, then @code{ALL(MASK,DIM)} is equivalent to @code{ALL(MASK)}. If the rank is greater than one, then @code{ALL(MASK,DIM)} is determined by applying @code{ALL} to the array sections. @end table @item @emph{Example}: @smallexample program test_all logical l l = all((/.true., .true., .true./)) print *, l call section contains subroutine section integer a(2,3), b(2,3) a = 1 b = 1 b(2,2) = 2 print *, all(a .eq. b, 1) print *, all(a .eq. b, 2) end subroutine section end program test_all @end smallexample @end table @comment gen allocated @comment @comment gen anint @comment dnint @comment @comment gen any @comment @comment gen asin @comment dasin @comment @comment gen associated @comment @comment gen atan @comment datan @comment @comment gen atan2 @comment datan2 @comment @comment gen besj0 @comment dbesj0 @comment @comment gen besj1 @comment dbesj1 @comment @comment gen besjn @comment dbesjn @comment @comment gen besy0 @comment dbesy0 @comment @comment gen besy1 @comment dbesy1 @comment @comment gen besyn @comment dbesyn @comment @comment gen bit_size @comment @comment gen btest @comment @comment gen ceiling @comment @comment gen char @comment @comment gen cmplx @comment @comment gen command_argument_count @comment @comment gen conjg @comment dconjg @comment @comment gen cos @comment dcos @comment ccos @comment zcos,cdcos @comment @comment gen cosh @comment dcosh @comment @comment gen count @comment @comment sub cpu_time @comment @comment gen cshift @comment @comment sub date_and_time @comment @comment gen dble @comment dfloat @comment @comment gen dcmplx @comment @comment gen digits @comment @comment gen dim @comment idim @comment ddim @comment @comment gen dot_product @comment @comment gen dprod @comment @comment gen dreal @comment @comment sub dtime @comment @comment gen eoshift @comment @comment gen epsilon @comment @comment gen erf @comment derf @comment @comment gen erfc @comment derfc @comment @comment gen etime @comment sub etime @comment @comment sub exit @comment @comment gen exp @comment dexp @comment cexp @comment zexp,cdexp @comment @comment gen exponent @comment @comment gen floor @comment @comment sub flush @comment @comment gen fnum @comment @comment gen fraction @comment @comment gen fstat @comment sub fstat @comment @comment sub getarg @comment @comment gen getcwd @comment sub getcwd @comment @comment sub getenv @comment @comment gen getgid @comment @comment gen getpid @comment @comment gen getuid @comment @comment sub get_command @comment @comment sub get_command_argument @comment @comment sub get_environment_variable @comment @comment gen huge @comment @comment gen iachar @comment @comment gen iand @comment @comment gen iargc @comment @comment gen ibclr @comment @comment gen ibits @comment @comment gen ibset @comment @comment gen ichar @comment @comment gen ieor @comment @comment gen index @comment @comment gen int @comment ifix @comment idint @comment @comment gen ior @comment @comment gen irand @comment @comment gen ishft @comment @comment gen ishftc @comment @comment gen kind @comment @comment gen lbound @comment @comment gen len @comment @comment gen len_trim @comment @comment gen lge @comment @comment gen lgt @comment @comment gen lle @comment @comment gen llt @comment @comment gen log @comment alog @comment dlog @comment clog @comment zlog, cdlog @comment @comment gen log10 @comment alog10 @comment dlog10 @comment @comment gen logical @comment @comment gen matmul @comment @comment gen max @comment max0 @comment amax0 @comment amax1 @comment max1 @comment dmax1 @comment @comment gen maxexponent @comment @comment gen maxloc @comment @comment gen maxval @comment @comment gen merge @comment @comment gen min @comment min0 @comment amin0 @comment amin1 @comment min1 @comment dmin1 @comment @comment gen minexponent @comment @comment gen minloc @comment @comment gen minval @comment @comment gen mod @comment amod @comment dmod @comment @comment gen modulo @comment @comment sub mvbits @comment @comment gen nearest @comment @comment gen nint @comment idnint @comment @comment gen not @comment @comment gen null @comment @comment gen pack @comment @comment gen precision @comment @comment gen present @comment @comment gen product @comment @comment gen radix @comment @comment gen rand @comment ran @comment @comment sub random_number @comment @comment sub random_seed @comment @comment gen range @comment @comment gen real @comment float @comment sngl @comment @comment gen repeat @comment @comment gen reshape @comment @comment gen rrspacing @comment @comment gen scale @comment @comment gen scan @comment @comment gen second @comment sub second @comment @comment gen selected_int_kind @comment @comment gen selected_real_kind @comment @comment gen set_exponent @comment @comment gen shape @comment @comment gen sign @comment isign @comment dsign @comment @comment gen sin @comment dsin @comment csin @comment zsin,cdsin @comment @comment gen sinh @comment dsinh @comment @comment gen size @comment @comment gen spacing @comment @comment gen spread @comment @comment gen sqrt @comment dsqrt @comment csqrt @comment zsqrt,cdsqrt @comment @comment sub srand @comment @comment gen stat @comment sub stat @comment @comment gen sum @comment @comment gen system @comment sub system @comment @comment sub system_clock @comment @comment gen tan @comment dtan @comment @comment gen tanh @comment dtanh @comment @comment gen tiny @comment @comment gen transfer @comment @comment gen transpose @comment @comment gen trim @comment @comment gen ubound @comment @comment gen umask @comment sub umask @comment @comment gen unlink @comment sub unlink @comment @comment gen unpack @comment @comment gen verify