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 —
-
is a MINIBOOK easy enough to contribute
to, or is something more Wiki-like needed? -
How important is it that these be maintained in man-page-like format
so they can easily be converted (perhaps withpandoc()
) to actual
man-pages? -
Would an on-line CLI text version be key? This and (2) would limit what types
of mathmatical expressions and graphics could be included. -
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? -
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
### NAMEabs(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