Intrinsic descriptions

I am proposing that we build a description of the Fortran intrinsics
as a MINIBOOK on the fortran-org.lang site that is community-developed.

The intrinsic descriptions available are often brief. These would be
extended cuts, so to speak. Each would have a working program example.
Vendor extensions would not be included.

If there is interest in this —

  1. is a MINIBOOK easy enough to contribute
    to, or is something more Wiki-like needed?

  2. How important is it that these be maintained in man-page-like format
    so they can easily be converted (perhaps with pandoc()) to actual
    man-pages?

  3. Would an on-line CLI text version be key? This and (2) would limit what types
    of mathmatical expressions and graphics could be included.

  4. As each description is fleshed out should there be an announcement
    or posting on this forum for review and/or should just a ‘intrinsic of the day’
    be announced where input is gathered before a description is begun?

  5. There are of course other approaches and formats for this, but
    weighing a lot of issues I think a MINIBOOK on fortran-lang.org
    primarily using markdown as the format is a good target.

Taking a simple intrinsic such as ABS() as an example:

ABS ### NAME

abs(3f) - [NUMERIC] Absolute value

SYNTAX

   result = ABS(A)

    TYPE(kind=KIND),elemental  :: abs
    TYPE(kind=KIND),intent(in) :: a

    where TYPE may be REAL, INTEGER, or COMPLEX
    and KIND may be any supported KIND for the
    associated TYPE.

DESCRIPTION

abs(A) computes the absolute value of numeric argument A.

In mathematics, the absolute value or modulus of a real number x,
denoted |x|, is the non-negative magnitude of x without regard to its sign.

The absolute value of a number may be thought of as its distance from zero,
which is the definition used by abs(1) when dealing with COMPLEX values.

ARGUMENTS

  • A
    the type of the argument shall be an INTEGER, REAL, or COMPLEX
    scalar or array.

RETURN VALUE

If A is of type INTEGER or REAL, the value of the result is |A| and of
the same type and kind as the input argument.

(Take particular note) if A is COMPLEX with value (X, Y), the result is
a REAL equal to a processor-dependent approximation to SQRT(X**2 +
Y**2) computed without undue overflow or underflow.

EXAMPLE

Sample program:

program demo_abs
integer         :: i = -1 
real            :: x = -1.e0 
complex         :: z = (-3.e0,-4.e0)
doubleprecision :: r8 = -45.78D+00 
character(len=*),parameter :: &
 frmt =  '(1x,a15,1x," In: ",g0,            T51," Out: ",g0)', &
 frmtc = '(1x,a15,1x," In: (",g0,",",g0,")",T51," Out: ",g0)'

    write(*, frmt)  'integer         ',  i, abs(i)
    write(*, frmt)  'real            ',  x, abs(x)
    write(*, frmt)  'doubleprecision ', r8, abs(r8)
    write(*, frmtc) 'complex         ',  z, abs(z)
    write(*, *)
    write(*, *)'abs is elemental: ', abs([20,  0,  -1,  -3,  100])
    write(*, *)
    write(*, *)'abs range test : ', abs(huge(0)), abs(-huge(0))
    write(*, *)'abs range test : ', abs(huge(0.0)), abs(-huge(0.0))
    write(*, *)'abs range test : ', abs(tiny(0.0)), abs(-tiny(0.0))

end program demo_abs

Results:

 integer          In: -1                        Out: 1
 real             In: -1.00000000               Out: 1.00000000
 doubleprecision  In: -45.780000000000001       Out: 45.780000000000001
 complex          In: (-3.00000000,-4.00000000) Out: 5.00000000

 abs is elemental: 20 0 1 3 100

 abs range test :  2147483647  2147483647
 abs range test :  3.40282347E+38   3.40282347E+38
 abs range test :  1.17549435E-38   1.17549435E-38

STANDARD

FORTRAN 77 and later

fortran-lang intrinsic descriptions
COMMAND_ARGUMENT_COUNT ## __Name__ __command\_argument\_count__(3) - \[SYSTEM ENVIRONMENT\] Get number of command line arguments ## __Syntax__ ```fortran result = command_argument_count()
 integer function command_argument_count() result(count)
 integer :: count
## __Description__
__command\_argument\_count()__ returns the number of arguments passed on the
command line when the containing program was invoked.
## __Arguments__
None
## __Returns__
  - __count__
    The return value is of type default _integer_. It is the number of
    arguments passed on the command line when the program was invoked.
## __Examples__
Sample program:

```fortran
program demo_command_argument_count
implicit none
integer :: count
   count = command_argument_count()
   print *, count
end program demo_command_argument_count

Sample output:

   # the command verb does not count
   ./test_command_argument_count
       0
   # quoted strings may count as one argument
   ./test_command_argument_count count arguments
       2
   ./test_command_argument_count 'count arguments'
       1

Standard

Fortran 2003 and later

See Also

get_command(3),
get_command_argument(3)

fortran-lang intrinsic descriptions (@urbanjost)
GET_COMMAND_ARGUMENT ## __Name__

get_command_argument(3) - [SYSTEM ENVIRONMENT] Get command line arguments

Syntax

     call get_command_argument(number, value, length, status)

     subroutine get_command_argument(number,value,length.status)
     integer,intent(in)                    :: number
     character(len=*),intent(out),optional :: value
     integer,intent(out),optional          :: length
     integer,intent(out),optional          :: status

Description

Retrieve the n-th argument that was passed on the command line when
the containing program was invoked.

There is not anything specifically stated about what an argument is but
in practice the arguments are split on whitespace unless the arguments
are quoted and IFS values (Internal Field Separators) used by common
shells are ignored.

Options

  • number
    Shall be a scalar of type integer, number >= 0. If number =
    0
    , value is set to the name of the program (on systems that support
    this feature).

Returns

  • value
    Shall be a scalar of type character and of default kind. After
    get_command_argument returns, the value argument holds the
    number-th command line argument. If value can not hold the argument,
    it is truncated to fit the length of value. If there are less than
    number arguments specified at the command line, value will be filled
    with blanks.

  • length
    (Optional) Shall be a scalar of type integer. The length
    argument contains the length of the number-th command line argument.

  • status
    (Optional) Shall be a scalar of type integer. If the argument
    retrieval fails, status is a positive number; if value contains a
    truncated command line argument, status is -1; and otherwise the
    status is zero.

Examples

Sample program:

   program demo_get_command_argument
   implicit none
   character(len=255)           :: progname
   integer                      :: stat
   integer                      :: count,i, longest, argument_length
   integer,allocatable          :: istat(:), ilen(:)
   character(len=:),allocatable :: arguments(:)
     !
     ! get number of arguments
     count = command_argument_count()
     write(*,*)'The number of arguments is ',count
     !
     ! simple usage
     !
     call get_command_argument (0, progname, status=stat)
     if (stat == 0) then
        print *, "The program's name is " // trim (progname)
     endif
     !
     ! showing how to make an array to hold any argument list
     !
     ! find longest argument
     !
     longest=0
     do i=0,count
        call get_command_argument(number=i,length=argument_length)
        longest=max(longest,argument_length)
     enddo
     !
     ! allocate string array big enough to hold command line argument strings
     ! and related information
     !
     allocate(character(len=longest) :: arguments(0:count))
     allocate(istat(0:count))
     allocate(ilen(0:count))
     !
     ! read the arguments into the array
     !
     do i=0,count
       call get_command_argument(i, arguments(i),status=istat(i),length=ilen(i))
     enddo
     !
     ! show the results
     !
     write (*,'(i3.3,1x,i0.5,1x,i0.5,1x,"[",a,"]")') &
     & (i,istat(i),ilen(i),arguments(i)(:ilen(i)),i=0,count)
   end program demo_get_command_argument

Sample output:

   ./test_get_command_argument a    test  'of getting   arguments  ' "  leading"

   > The number of arguments is            5
   > The program's name is xxx
   >000 00000 00003 [./test_get_command_argument]
   >001 00000 00001 [a]
   >003 00000 00004 [test]
   >004 00000 00024 [of getting   arguments  ]
   >005 00000 00018 [  leading]

Standard

Fortran 2003 and later

See Also

get_command(3),
command_argument_count(3)

fortran-lang intrinsic descriptions (@urbanjost)
GET_COMMAND ## __Name__

get_command(3) - [SYSTEM ENVIRONMENT] Get the entire command line

Syntax

   call get_command(command, length, status)

    subroutine get_command(command,length,status)
    character(len=*),intent(out),optional :: command
    integer,intent(out),optional :: length
    integer,intent(out),optional :: status

Description

Retrieve the entire command line that was used to invoke the program.

Note that what is typed on the command line is often processed by
a shell. The shell typically processes special characters and white
space before passing it to the program. The processing can typically be
turned off by turning off globbing or quoting the command line arguments
and/or changing the default field separators, but this should rarely
be necessary.

Returns

  • command
    Shall be of type character and of default kind. If
    command is present, stores the entire command line that was used to
    invoke the program in command.

  • length
    Shall be of type integer and of default kind. If length
    is present, it is assigned the length of the command line.

  • status
    Shall be of type integer and of default kind. If status
    is present, it is assigned 0 upon success of the command, -1 if
    command is too short to store the command line, or a positive value
    in case of an error.

Examples

Sample program:

   program demo_get_command
   implicit none
   integer                      :: COMMAND_LINE_LENGTH
   character(len=:),allocatable :: COMMAND_LINE
      ! get command line length
      call get_command(length=COMMAND_LINE_LENGTH)
      ! allocate string big enough to hold command line
      allocate(character(len=COMMAND_LINE_LENGTH) :: COMMAND_LINE)
      ! get command line as a string
      call get_command(command=COMMAND_LINE)
      ! trim leading spaces just in case
      COMMAND_LINE=adjustl(COMMAND_LINE)
      write(*,'("OUTPUT:",a)')COMMAND_LINE
   end program demo_get_command

Sample execution:

     # note that shell expansion removes some of the whitespace
     # without quotes
     ./test_get_command  arguments    on the    command   line to   echo

     OUTPUT:./test_get_command arguments on the command line to echo

     # using the bash shell with single quotes
     ./test_get_command  'arguments  *><`~[]!{}?"\'| on the    command   line '

     OUTPUT:./test_get_command arguments  *><`~[]!{}?"'| on the   command   line

Standard

Fortran 2003 and later

See Also

get_command_argument(3),
command_argument_count(3)

fortran-lang intrinsic descriptions (@urbanjost)
HYPOT

Name

hypot(3) - [MATHEMATICS] returns the distance between the point and the origin.

Syntax

result = hypot(x, y)

   real(kind=KIND) elemental function hypot(x,y) result(value)
   real(kind=KIND),intent(in) :: x, y

where x,y,value shall all be of the same kind.

Description

hypot(x,y) is referred to as the Euclidean distance function. It is equal to
sqrt(x2 + y2), without undue underflow or overflow.

In mathematics, the Euclidean distance between two points in Euclidean
space is the length of a line segment between two points.

hypot(x,y) returns the distance between the point <x,y> and the origin.

Arguments

  • x
    The type shall be real.

  • y
    The type and kind type parameter shall be the same as x.

Returns

The return value has the same type and kind type parameter as x.

The result is the positive magnitude of the distance of the point <x,y> from the
origin <0.0,0.0> .

Examples

Sample program:

program demo_hypot
use, intrinsic :: iso_fortran_env, only : &
 & real_kinds, real32, real64, real128
implicit none
real(kind=real32) :: x, y 
real(kind=real32),allocatable :: xs(:), ys(:)
integer :: i
character(len=*),parameter :: f='(a,/,SP,*(3x,g0,1x,g0:,/))'

   x = 1.e0_real32
   y = 0.5e0_real32

   write(*,*)
   write(*,'(*(g0))')'point <',x,',',y,'> is ',hypot(x,y)
   write(*,'(*(g0))')'units away from the origin'
   write(*,*)

   ! elemental
   xs=[  x,  x**2,  x*10.0,  x*15.0, -x**2  ]
   ys=[  y,  y**2, -y*20.0,  y**2,   -y**2  ]

   write(*,f)"the points",(xs(i),ys(i),i=1,size(xs))
   write(*,f)"have distances from the origin of ",hypot(xs,ys)
   write(*,f)"the closest is",minval(hypot(xs,ys))

end program demo_hypot

Results:

   point <1.00000000,0.500000000> is 1.11803401
   units away from the origin
   
   the points
      +1.00000000 +0.500000000
      +1.00000000 +0.250000000
      +10.0000000 -10.0000000
      +15.0000000 +0.250000000
      -1.00000000 -0.250000000
   have distances from the origin of 
      +1.11803401 +1.03077638
      +14.1421356 +15.0020828
      +1.03077638
   the closest is
      +1.03077638

Standard

Fortran 2008 and later

fortran-lang intrinsic descriptions (@urbanjost)
9 Likes

I would say let’s implement this in whatever format, as long as the format is machine readable, so that we can write a Python script that loads it and converts it to whatever form we want, whether man pages, html, terminal text (with and without colors), etc. This approach allows to change later how section names appear (upper case / lower case, which color, etc.)

So whichever format we end up using, it needs to have sections like name of the subroutine, arguments and types, one line description, a paragraph description, examples, etc.

The only big issue to figure out is how to handle math. I would like math. One option is to use sympy to represent math. Then it can be converted to any representation we want, so latex for web, and plain ascii for a terminal. There are other ways to represent math, as long as it is possible to load it into symbolic form. I would not recommend using latex, as it is very hard to load it (yes, sympy can parse latex, but it’s not a good format for that).

Today’s entry (looking for more items for the resource list)

DATE_AND_TIME

Name

date_and_time(3) - [SYSTEM ENVIRONMENT] gets current time

Syntax

    subroutine date_and_time(date, time, zone, values)

     character(len=8),intent(out),optional :: date
     character(len=10),intent(out),optional :: time
     character(len=5),intent(out),optional :: zone
     integer,intent(out),optional :: values(8)

Description

date_and_time(date, time, zone, values) gets the corresponding
date and time information from the real-time system clock.

Unavailable time and date character parameters return blanks.

Arguments

  • date
    The type shall be character(len=8) or larger, and of default
    kind. date has the form ccyymmdd.

  • time
    The type shall be character(len=10) or larger, and of default
    kind. time has the form hhmmss.sss.

  • zone
    The type shall be character(len=5) or larger, and of default
    kind. zone has form (±)hhmm, representing the difference with
    respect to Coordinated Universal Time (UTC).

  • values
    An integer array of eight elements. On return values contains:

    • value(1): - The year

    • value(2): - The month

    • value(3): - The day of the month

    • value(4): - Time difference with UTC in minutes

    • value(5): - The hour of the day

    • value(6): - The minutes of the hour

    • value(7): - The seconds of the minute

    • value(8): - The milliseconds of the second

Examples

Sample program:

program demo_time_and_date
implicit none
character(len=8)     :: date
character(len=10)    :: time
character(len=5)     :: zone
integer,dimension(8) :: values
    call date_and_time(date,time,zone,values)
    ! using keyword arguments
    call date_and_time(DATE=date,TIME=time,ZONE=zone)
    call date_and_time(VALUES=values)
    print '(*(g0))','DATE="',date,'" TIME="',time,'" ZONE="',zone,'"'
    write(*,'(i5,a)') &
     & values(1),' - The year', &
     & values(2),' - The month', &
     & values(3),' - The day of the month', &
     & values(4),' - Time difference with UTC in minutes', &
     & values(5),' - The hour of the day', &
     & values(6),' - The minutes of the hour', &
     & values(7),' - The seconds of the minute', &
     & values(8),' - The milliseconds of the second'
end program demo_time_and_date

Results:

   DATE="20201222" TIME="165738.779" ZONE="-0500"
    2020 - The year
      12 - The month
      22 - The day of the month
    -300 - Time difference with UTC in minutes
      16 - The hour of the day
      57 - The minutes of the hour
      38 - The seconds of the minute
     779 - The milliseconds of the second

Standard

Fortran 95 and later

See Also

cpu_time(3),
system_clock(3)

Resources

date and time conversion, formatting and computation

fortran-lang intrinsic descriptions (@urbanjost)
1 Like

A skeleton of the
Proposed Document
has been recently built for comment.

Good example cases for the procedures or recommendations for links to examples; or contributions of minibooks on atomic routines, co-arrays, … would help. Expect this to be a WIP (Work In Progress) for quite some time.

GET_ENVIRONMENT_VARIABLE

Name

get_environment_variable(3) - [SYSTEM ENVIRONMENT] Get an environmental variable

Syntax

  call get_environment_variable(name, value, length, status, trim_name)

   character(len=*),intent(in) :: name
   character(len=*),intent(out),optional :: value
   integer,intent(out),optional :: length
   integer,intent(out),optional :: status
   logical,intent(out),optional :: trim_name

Description

Get the value of the environmental variable name.

Note that get_environment_variable(3) need not be thread-safe. It
is the responsibility of the user to ensure that the environment is not
being updated concurrently.

Options

  • name
    The name of the environment variable to query.

    Shall be a scalar of type character and of default kind.

Returns

  • value
    The value of the environment variable being queried.

    Shall be a scalar of type character and of default kind.
    The value of NAME is stored in value. If value is not large enough
    to hold the data, it is truncated. If name is not set, value will be
    filled with blanks.

  • length
    Argument length contains the length needed for storing the
    environment variable name or zero if it is not present.

    Shall be a scalar of type integer and of default kind.

  • status
    status is -1 if value is present but too short for the
    environment variable; it is 1 if the environment variable does not
    exist and 2 if the processor does not support environment variables;
    in all other cases status is zero.

    Shall be a scalar of type integer and of default kind.

  • trim_name
    If trim_name is present with the value .false., the trailing blanks in
    name are significant; otherwise they are not part of the environment
    variable name.

    Shall be a scalar of type logical and of default kind.

Examples

Sample program:

program demo_getenv
implicit none
character(len=:),allocatable :: homedir
character(len=:),allocatable :: var
     var='HOME'
     homedir=get_env(var)
     write (*,'(a,"=""",a,"""")')var,homedir

contains

function get_env(NAME,DEFAULT) result(VALUE)
! a function that makes calling get_environment_variable(3) simple
implicit none
character(len=*),intent(in)          :: NAME
character(len=*),intent(in),optional :: DEFAULT
character(len=:),allocatable         :: VALUE
integer                              :: howbig
integer                              :: stat
integer                              :: length
   ! get length required to hold value
   length=0
   VALUE=''
   if(NAME.ne.'')then
      call get_environment_variable(NAME, length=howbig,status=stat,trim_name=.true.)
      select case (stat)
      case (1)
         !*!print *, NAME, " is not defined in the environment. Strange..."
         VALUE=''
      case (2)
         !*!print *, "This processor doesn't support environment variables. Boooh!"
         VALUE=''
      case default
         ! make string to hold value of sufficient size
         if(allocated(VALUE))deallocate(VALUE)
         allocate(character(len=max(howbig,1)) :: VALUE)
         ! get value
         call get_environment_variable(NAME,VALUE,status=stat,trim_name=.true.)
         if(stat.ne.0)VALUE=''
      end select
   endif
   if(VALUE.eq.''.and.present(DEFAULT))VALUE=DEFAULT
end function get_env

end program demo_getenv

Typical Results:

   HOME="/home/urbanjs"

Standard

Fortran 2003 and later

EPSILON

Name

epsilon(3) - [NUMERIC MODEL] Epsilon function

Syntax

result = __epsilon__(x)

Description

epsilon(x) returns the floating point relative accuracy.
It is the nearly negligible number relative to 1
such that 1+ little_number is not equal to 1; or more
precisely

   real( 1.0, kind(x)) + epsilon(x) /=  real( 1.0, kind(x))

It may be thought of as the distance from 1.0 to the next largest
floating point number.

One use of epsilon(3) is to select a delta value for algorithms that
search until the calculation is within delta of an estimate.

If delta is too small the algorithm might never halt, as a computation
summing values smaller than the decimal resolution of the data type does
not change.

Arguments

  • x
    : The type shall be real.

Returns

The return value is of the same type as the argument.

Examples

Sample program:

program demo_epsilon
use,intrinsic :: iso_fortran_env, only : dp=>real64,sp=>real32
implicit none
real(kind=sp) :: x = 3.143
real(kind=dp) :: y = 2.33d0

   ! so if x is of type real32, epsilon(x) has the value 2**-23
   print *, epsilon(x) ! note just the type and kind of x matter, not the value
   print *, epsilon(huge(x)) 
   print *, epsilon(tiny(x)) 

   ! the value changes with the kind of the real value though
   print *, epsilon(y)

   ! adding and subtracing epsilon(x) changes x
   write(*,*)x == x + epsilon(x)
   write(*,*)x == x - epsilon(x)

   ! these next two comparisons will be .true. !
   write(*,*)x == x + epsilon(x) * 0.999999
   write(*,*)x == x - epsilon(x) * 0.999999

   ! you can calculate epsilon(1.0d0)
   write(*,*)my_dp_eps()

contains

function my_dp_eps()
! calculate the epsilon value of a machine the hard way
real(kind=dp) :: t
real(kind=dp) :: my_dp_eps

   ! starting with a value of 1, keep dividing the value
   ! by 2 until no change is detected. Note that with
   ! infinite precision this would be an infinite loop,
   ! but floating point values in Fortran have a defined
   ! and limited precision.
   my_dp_eps = 1.0d0
   SET_ST: do
      my_dp_eps = my_dp_eps/2.0d0
      t = 1.0d0 + my_dp_eps
      if (t <= 1.0d0) exit
   enddo SET_ST
   my_dp_eps = 2.0d0*my_dp_eps

end function my_dp_eps

end program demo_epsilon

Results:

  1.1920929E-07
  1.1920929E-07
  1.1920929E-07
  2.220446049250313E-016
 F
 F
 T
 T
  2.220446049250313E-016

Standard

Fortran 95 and later

See Also

digits(3),
exponent(3),
fraction(3),
huge(3),
maxexponent(3),
minexponent(3),
nearest(3),
precision(3),
radix(3),
range(3),
rrspacing(3),
scale(3),
set_exponent(3),
spacing(3),
tiny(3)

fortran-lang intrinsic descriptions (@urbanjost)

Use cases and/or links to external references welcome!

So far … Intrinsics

These are beautiful. Great job!

One question: what are all the “(3)s” for?

Thanks. I am hoping this will be the beginning of a useful resource for Fortran programmers.

A convention on Unix and subsequently GNU/Linux systems in man-pages (one of the main on-line tools for reading documentation in a terminal) is to use a numeric
suffix to distinguish between English, command, procedure and other uses of the same name by using a numeric suffix. man-pages were once limited to the ASCII character set (then extended ASCII, and now often UTF-8) but when documentation is limited to just plain characters there is no easy way to distinguish between things like unlink (the English word) unlink (the command) and unlink (the C procedure). The convention became to use (3) for procedures, (1) for commands, (5) for configuration file descriptions and so on. These documents (so far, the pros and cons of this are being weighed) can be converted to actual man-pages for direct use on GNU/Linux and Linux using utilities like pandoc(1); so at least for the time being I need to use the suffixes so they still work with man(1). On-line as kramdown (the markdown variant being used on fortran-lang.org) I can use high-lighting or italics for pretty much the same purpose, but so far I am still following that convention, as that gets lost when going to plain text. If you use a Linux or Unix box the meanings are described by entering “man man”.

The number is also used by the man(1) command itself. If I want to read about the C routine unlink I would enter “man 3 unlink”; for the command I would enter “man 1 unlink”; although when there is no conflict or you do not mind seeing all of them you can enter “man unlink”.

There is also the issue of name conflicts between languages, so some platforms use something like (3c) for C routines, (3X11) for X11 WIndows procedures and commands, and so on. When I convert these to man-pages I use (3fortran), but again just a 3 or no number will work as well, and just show you all matches. But that lets you say things like “man -S 3fortran .” and list all
fortran-related documents, and so on. There are all kinds of options on man(1) to let you select just certain sections.

The most commonly used basic numbers are

   1   Executable programs or shell commands
   2   System calls (functions provided by the kernel)
   3   Library calls (functions within program libraries)
   4   Special files (usually found in /dev)
   5   File formats and conventions, e.g. /etc/passwd
   6   Games
   7   Miscellaneous (including macro packages and conventions), e.g. man(7), groff(7)
   8   System administration commands (usually only for root)
   9   Kernel routines [Non standard]
EXP ## __Name__

exp(3) - [MATHEMATICS] Exponential function

Syntax

result = exp(x)

Description

exp(x) computes the base “e” exponential of x where “e” is
Euler’s constant.

If x is of type complex, its imaginary part is regarded as a value
in radians such that (see Euler’s formula):

if
cx=(re,im)
then
exp(cx)=exp(re)*cmplx(cos(im),sin(im))

Since exp(3) is the inverse function of log(3) the maximum valid magnitude
of the real component of x is log(huge(x)).

Arguments

  • x
    : The type shall be real or complex.

Returns

The value of the result is e**x where e is Euler’s constant.

The return value has the same type and kind as x.

Examples

Sample program:

program demo_exp
implicit none
real :: x , re, im
complex :: cx

   x = 1.0
   write(*,*)"Euler's constant is approximately",exp(x)

   !! complex values
   ! given
   re=3.0
   im=4.0
   cx=cmplx(re,im)

   ! complex results from complex arguments are Related to Euler's formula
   write(*,*)'given the complex value ',cx
   write(*,*)'exp(x) is',exp(cx)
   write(*,*)'is the same as',exp(re)*cmplx(cos(im),sin(im))

   ! exp(3) is the inverse function of log(3) so
   ! the real compoenent of the input must be less than or equal to 
   write(*,*)'maximum real real component',log(huge(0.0)) 
   ! or for double precision
   write(*,*)'maximum doubleprecision real component',log(huge(0.0d0)) 

   ! but since the imaginary component is passed to the cos(3) and sin(3)
   ! functions the imaginary component can be any real value

end program demo_exp

Results

 Euler's constant is approximately   2.718282    
 given the complex value  (3.000000,4.000000)
 exp(x) is (-13.12878,-15.20078)
 is the same as (-13.12878,-15.20078)
 maximum real real component   88.72284    
 maximum doubleprecision real component   709.782712893384     

Standard

FORTRAN 77 and later

See Also

fortran-lang intrinsic descriptions (@urbanjost)

The standard seems oddly vague about exp. I added some details for context, but I think the explanation is better served with some Wikipedia links so I added those instead of re-inventing the wheel, so to speak.

Thank you very much for your efforts! This will be very valuable to Fortran users and learners.

When coding in Fortran, I try to use as few capital letters as possible. It seems to me that coding in capitals is a stereotype about the “old-fashion” of Fortran (just like how we typed the name of the language in the old days). Thus I try to break/stay away from this stereotype. Maybe it is also a good idea to use as few capital letters as possible in documents. Just a personal and minor suggestion for your consideration.

Actually have been doing just that; although I have been starting with files that had a lot of uppercase in them, especially some of the example programs, but I ran all or virtually all of them
through flower so there should only be a few uppercase characters, mostly in comments and quoted strings. Any files in particular you see this in? I still have a few to go; there are a lot of them.

1 Like

Thank you @urbanjost for the reply and again for the efforts! It is great that we see this aspect similarly. It was just a general suggestion without a particular file in mind.

Many thanks again!

great job!
cppreference.com offers great documentation for C++ intrinsic functions and data structures. its style seems a good one to follow.

That does look like a great model; and a complete User manual ( with pointers to the stdlib and fpm registry too) is an ideal end goal; but for now just doing justice to the intrinsics is a daunting task.

Luckily, there are good Fortran references available. However, they and the standard itself are concentrated on other aspects of Fortran, and typically give just a brie f description of the intrinsics, often just a few pages (even in its current state this description would probably push 200 pages if printed!) So an extended description of the intrinsics seems not only a good start at a general user guide but something lacking in other venues, so I think it will remain focused on (primarily) the intrinsics for now; but contributions towards a true Fortran reference would be an exciting turn of events!

There are a lot of related issues even with something as simple as len(3). Do detailed example
programs help or hinder the descriptions? Here is a rather lengthy example program as an example:

LEN

Name

len(3) - [CHARACTER] Length of a character entity

Syntax

   l = len(string, kind)

    integer(kind=KIND) function len(string,kind) result(value)
    character(len=*),intent(in) :: string
    integer,optional,intent(in) :: kind
    integer :: value

Description

len(3) Returns the length of a character string.

If string is an array, the length of an element of string
is returned.

Note that string need not be defined when this intrinsic is invoked,
as only the length (not the content) of string is needed.

Arguments

  • string
    : Shall be a scalar or array of type character, with intent(in)

  • kind
    : An integer initialization expression indicating the kind
    parameter of the result.

Returns

The return value is of type integer and of kind kind. If kind is absent,
the return value is of default integer kind.

Standard

FORTRAN 77 and later, with kind argument - Fortran 2003 and later

Examples

Sample program

program demo_len
use,intrinsic :: iso_fortran_env, only : stdout=>output_unit
implicit none
character(len=:),allocatable :: string
character(len=:),allocatable :: many_strings(:)
integer :: ii

   string=' How long is this string?     '
   ii=len(string)
   ! note when adjacent strings are printed no space is inserted between them
   write(*,*)'['//string//']',' length=',ii

   ! Related Matters:

   write(*,*)
   ! you can also query the length (and other attributes) of a string using a 
   write(*,*) "type parameter inquiry:"
   write(*,*)'length=',string%len,'kind=',string%kind
   ! note a type parameter inquiry of an intrinsic requires Fortran 2018+ 

   ! note that all that is required is an A descriptor in a format, a numeric
   ! length is not required. If a length IS provided the string will be trimmed
   ! or blank padded ON THE LEFT to the specified length
   write(*,*)
   write(*,'(" ",a," ")')repeat('=',ii)
   write(*,'("[",a,"]")')string
   write(*,'(" ",a," ")')repeat('=',ii)

   write(*,'("[",a10,"]")')string  ! TRUNCATED!
   write(*,'("[",a40,"]")')string  ! PADDED!

   ! a scalar is returned for an array, as all values in a Fortran
   ! character array must be of the same length:

   ! stepping aside to define an allocatable array with a constructor ...
   ! (that MUST specify a LEN= length type parameter if all values are
   ! not the same length):
     many_strings = [ character(len=7) :: 'Takata', 'Tanaka', 'Hayashi' ]
   ! if the length specified is too short the strings will be truncated

   ! In that constructor, without the LEN= type specification, it would
   ! have been necessary to specify all of the constants with the same
   ! character length.

   write(*,*)
   write(*,*)'length of ALL elements of array=',len(many_strings)
   write(*,'("[",a,"]")')many_strings

   ! Note in the following the result is always scalar, even if the
   ! object is an array.

   write(*,*) &
   & 'length=', many_strings%len, &
   & 'kind=', many_strings%kind
   ! which is the same as
   write(*,*) &
   & 'length=', len(many_strings), &
   & 'kind=', kind(many_strings)

   ! you should also be careful when printing strings that they do not
   ! exceed the current record length of your output file, although that
   ! usually is very large
   inquire(unit=stdout,recl=ii)
   write(*,*)'line length=',ii

end program demo_len

Results:

 [ How long is this string?     ] length=          30
 
 type parameter inquiry:
 length=          30 kind=           1
 
 ============================== 
[ How long is this string?     ]
 ============================== 
[ How long ]
[           How long is this string?     ]
 
 length of ALL elements of array=           7
[Takata ]
[Tanaka ]
[Hayashi]
 length=           7 kind=           1
 length=           7 kind=           1
 line length=         132

See Also

Functions that perform operations on character strings, return lengths
of arguments, and search for certain arguments:

I would say that the sample program tries to show too many things at once. At least if it is intended as a demonstration of LEN(). Rather than trying to encompass all aspects, such a sample program should focus on the typical use of an intrinsic routine. In this case, I’d say:

  • len() on a variable that is declared with a specific length
  • len() on a dummy argument, declared with character(len=*)
  • Perhaps contrast it with len_trim()
  • Show the output
3 Likes

The one I have in there is relatively close to the shorter version, but I am trying to think of a good way to work in things like the extended version here contains, as I often see people bitten by such things; or making elaborate mechanisms to do something there is sometimes a simple solution to. Perhaps extended examples programs as a “See Also” or sections more like an actual user guide about strings in general later.

I added links to a Fortran program and a tar(1) file that contain a line-mode program called “fman” and a tar(1) file containing man-pages directly generated from the intrinsics descriptions.
Some might be familiar with the fpm-man utility which this is basically the same as except the documentation is created via pandoc(1) from the web site; whereas fpm-man used descriptions that start as plain text. Installing man-pages can get a little compicated but for those that know how to add or directly use a directory of man-pages they are in good enough shape to experiment with.

  • Is a web description of Fortran intrinsics preferable? It can contain mathematical expressions, graphics, and links.
  • is a platform-portable CLI interface, limited to just ASCII text preferred?
  • are GNU/Linux Unix man-pages the best solution?
  • Is a single document (from text to Adobe PDF) the best delivery method for the documentation?

0 voters

  • fman(1) A self-contained Fortran program that displays the documentation as text
  • man pages A gzipped tar(1) file containing GNU/Linux or Unix man-pages
  • on-line pages

Tried a utility called slidy for making an HTML document that lets one review the state of the
the intrinsics quickly:
slides
which is interesting. Do not overlook the index and help selections in the lower left corner.

The survey will close 2021-12-20

So it looks like the on-line documentation is a strong favorite, with a significant desire for a CLI interface so lets do both. The main pages will retain a man-page-like format that can be rended as ASCII text for the CLI interfaces with links where appropriate to supplemental examples and references that are long, contain graphics, or mathematical expressions that cannot be represented well with ASCII or Fortran expressions. As the learning curve and infrastructure can be a bit much for first contributors for setting up a functioning clone of the fortran-lang.org minibooks you can contribute by downloading the markdown from a secondary site and editing it and contributing it (preferably as a PR request to the github site but using the issues or wiki pages on the following site are also supported. See the WIP (Work in progress) at GitHub - urbanjost/fortran-intrinsic-descriptions: A snapshot of the markdown source for Fortran intrinsics as well as the fman(1) program for where this
stands.

2 Likes

I still use an old version of fman. In fact, I never upgraded it, because the old version just works. Thanks for developing fman and I’d like to wish you a happy new year.

Great to hear; but I hope we keep it evolving (I still have the old one as fpm-man on my machine too as it has a bit more than the intrinisics :slight_smile: ). Happy New Year!