Accessing external system information#
command_argument_count#
Name#
command_argument_count(3) - [SYSTEM:COMMAND LINE] Get number of command line arguments
Synopsis#
result = command_argument_count()
integer function command_argument_count()
Characteristics#
the result is of default integer scalar.
Description#
command_argument_count(3) returns the number of arguments passed on the command line when the containing program was invoked.
Options#
None
Result#
: The return value is of type default integer. It is the number of arguments passed on the command line when the program was invoked.
If there are no command arguments available or if the processor does not support command arguments, then the result has the value zero.
If the processor has a concept of a command name, the command name does not count as one of the command arguments.
Examples#
Sample program:
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
See Also#
get_command(3), get_command_argument(3)
fortran-lang intrinsic descriptions (license: MIT) @urbanjost
get_command#
Name#
get_command(3) - [SYSTEM:COMMAND LINE] Get the entire command line invocation
Synopsis#
call get_command([command] [,length] [,status] [,errmsg])
subroutine get_command( command ,length ,status, errmsg )
character(len=*),intent(out),optional :: command
integer(kind=**),intent(out),optional :: length
integer(kind=**),intent(out),optional :: status
character(len=*),intent(inout),optional :: errmsg
Characteristics#
a kind designated as ** may be any supported kind for the type meeting the conditions described herein.
command and errmsg are scalar character variables of default kind.
length and status are scalar integer with a decimal exponent range of at least four.
Description#
get_command(3) retrieves 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.
Result#
- command
If command is present, the entire command line that was used to invoke the program is stored into it. If the command cannot be determined, command is assigned all blanks.
- length
If length is present, it is assigned the length of the command line. It is system-dependent as to whether trailing blanks will be counted.
If the command length cannot be determined, a length of 0 is assigned.
- status
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.
- errmsg
It is assigned a processor-dependent explanatory message if the command retrieval fails. Otherwise, it is unchanged.
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
Results:
# note that shell expansion removes some of the whitespace
# without quotes
./test_get_command arguments on command line to echo
OUTPUT:./test_get_command arguments on command line to echo
# using the bash shell with single quotes
./test_get_command 'arguments *><`~[]!{}?"\'| '
OUTPUT:./test_get_command arguments *><`~[]!{}?"'|
Standard#
Fortran 2003
See Also#
get_command_argument(3), command_argument_count(3)
fortran-lang intrinsic descriptions (license: MIT) @urbanjost
#
get_command_argument#
Name#
get_command_argument(3) - [SYSTEM:COMMAND LINE] Get command line arguments
Synopsis#
call get_command_argument(number [,value] [,length] &
& [,status] [,errmsg])
subroutine get_command_argument( number, value, length, &
& status ,errmsg)
integer(kind=**),intent(in) :: number
character(len=*),intent(out),optional :: value
integer(kind=**),intent(out),optional :: length
integer(kind=**),intent(out),optional :: status
character(len=*),intent(inout),optional :: errmsg
Characteristics#
a kind designated as ** may be any supported kind for the type meeting the conditions described herein.
number, length, and status are scalar integer with a decimal exponent range of at least four.
value and errmsg are scalar character variables of default kind.
Description#
get_command_argument(3) retrieves or queries the n-th argument that was passed on the command line to the current program execution.
There is not anything specifically stated about what an argument is but in practice the arguments are strings split on whitespace unless the arguments are quoted. IFS values (Internal Field Separators) used by common shells are typically ignored and unquoted whitespace is almost always the separator.
Shells have often expanded command arguments and spell characters before passing them to the program, so the strings read are often not exactly what the user typed on the command line.
Options#
- number
is a non-negative number indicating which argument of the current program command line is to be retrieved or queried.
If number = 0, the argument pointed to is set to the name of the program (on systems that support this feature).
if the processor does not have such a concept as a command name the value of command argument 0 is processor dependent.
For values from 1 to the number of arguments passed to the program a value is returned in an order determined by the processor. Conventionally they are returned consecutively as they appear on the command line from left to right.
Result#
- value
The value argument holds the 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 or if the argument specified does not exist for other reasons, value will be filled with blanks.
- length
The length argument contains the length of the n-th command line argument. The length of value has no effect on this value, It is the length required to hold all the significant characters of the argument regardless of how much storage is provided by value.
- status
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 :: count, i, argument_length, istat
character(len=:),allocatable :: arg
! command name assuming it is less than 255 characters in length
call get_command_argument (0, progname, status=istat)
if (istat == 0) then
print *, "The program's name is " // trim (progname)
else
print *, "Could not get the program's name " // trim (progname)
endif
! get number of arguments
count = command_argument_count()
write(*,*)'The number of arguments is ',count
!
! allocate string array big enough to hold command line
! argument strings and related information
!
do i=1,count
call get_command_argument(number=i,length=argument_length)
if(allocated(arg))deallocate(arg)
allocate(character(len=argument_length) :: arg)
call get_command_argument(i, arg,status=istat)
! show the results
write (*,'(i3.3,1x,i0.5,1x,i0.5,1x,"[",a,"]")') &
& i,istat,argument_length,arg
enddo
end program demo_get_command_argument
Results:
./demo_get_command_argument a test 'of getting arguments ' " leading"
The program's name is ./demo_get_command_argument
The number of arguments is 4
001 00000 00001 [a]
002 00000 00004 [test]
003 00000 00022 [of getting arguments ]
004 00000 00008 [ leading]
Standard#
Fortran 2003
See Also#
get_command(3), command_argument_count(3)
fortran-lang intrinsic descriptions (license: MIT) @urbanjost
#
cpu_time#
Name#
cpu_time(3) - [SYSTEM:TIME] Return CPU processor time used in seconds
Synopsis#
call cpu_time(time)
subroutine cpu_time(time)
real,intent(out) :: time
Characteristics#
time is a real of any kind
Description#
cpu_time(3) returns a real value representing the elapsed CPU time in seconds. This is useful for testing segments of code to determine execution time.
If no time source is available, time is set to a negative value.
The exact definition of time is left imprecise because of the variability in what different processors are able to provide.
Note that time may contain a system dependent, arbitrary offset and may not start with 0.0. For cpu_time(3) the absolute value is meaningless. Only differences between subsequent calls, as shown in the example below, should be used.
PARALLEL PROCESSING
Whether the value assigned is an approximation to the amount of time used by the invoking image, or the amount of time used by the whole program, is processor dependent.
A processor for which a single result is inadequate (for example, a parallel processor) might choose to provide an additional version for which time is an array.
Result#
- time
is assigned a processor-dependent approximation to the processor time in seconds. If the processor cannot return a meaningful time, a processor-dependent negative value is returned.
The start time is left imprecise because the purpose is to time sections of code, as in the example. This might or might not include system overhead time.
Examples#
Sample program:
program demo_cpu_time
use, intrinsic :: iso_fortran_env, only : real_kinds,real32,real64,real128
implicit none
real :: start, finish
real(kind=real64) :: startd, finishd
!
call cpu_time(start)
call cpu_time(startd)
! put code to time here
call cpu_time(finish)
call cpu_time(finishd)
!
! writes processor time taken by the piece of code.
! the accuracy of the clock and whether it includes system time
! as well as user time is processor dependent. Accuracy up to
! milliseconds is common but not guaranteed, and may be much
! higher or lower
print '("Processor Time = ",f6.3," seconds.")',finish-start
! see your specific compiler documentation for how to measure
! parallel jobs and for the precision of the time returned
print '("Processor Time = ",g0," seconds.")',finish-start
print '("Processor Time = ",g0," seconds.")',finishd-startd
end program demo_cpu_time
Results:
The precision of the result, some aspects of what is returned, and what if any options there are for parallel applications may very from system to system. See compiler-specific for details.
Processor Time = 0.000 seconds.
Processor Time = .4000030E-05 seconds.
Processor Time = .2000000000000265E-05 seconds.
Standard#
Fortran 95
See Also#
system_clock(3), date_and_time(3)
fortran-lang intrinsic descriptions (license: MIT) @urbanjost
date_and_time#
Name#
date_and_time(3) - [SYSTEM:TIME] Gets current date time
Synopsis#
call date_and_time( [date] [,time] [,zone] [,values] )
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)
Characteristics#
*date is a default character scalar
*time is a default character scalar
*zone is a default character scalar
values is a rank-one array of type integer with a decimal exponent range of at least four.
Description#
date_and_time(3) gets the corresponding date and time information from the real-time system clock.
Unavailable time and date character parameters return blanks.
Unavailable numeric parameters return -huge(value).
These forms are compatible with the representations defined in ISO 8601:2004. UTC is established by the International Bureau of Weights and Measures (BIPM, i.e. Bureau International des Poids et Mesures) and the International Earth Rotation Service (IERS).
Options#
- date
A character string of default kind of the form CCYYMMDD, of length 8 or larger, where
CCYY is the year in the Gregorian calendar
MM is the month within the year
DD is the day within the month.
The characters of this value are all decimal digits.
If there is no date available, DATE is assigned all blanks.
- time
A character string of default kind of the form HHMMSS.SSS, of length 10 or larger, where
hh is the hour of the day,
mm is the minutes of the hour,
and ss.sss is the seconds and milliseconds of the minute.
Except for the decimal point, the characters of this value shall all be decimal digits.
If there is no clock available, TIME is assigned all blanks.
- zone
A string of the form (+-)HHMM, of length 5 or larger, representing the difference with respect to Coordinated Universal Time (UTC), where
hh and mm are the time difference with respect to Coordinated Universal Time (UTC) in hours and minutes, respectively.
The characters of this value following the sign character are all decimal digits.
If this information is not available, ZONE is assigned all blanks.
- values
An array of at least eight elements. If there is no data available for a value it is set to -huge(values). Otherwise, it contains:
values(1) : The year, including the century.
values(2) : The month of the year
values(3) : The day of the month
values(4) : Time difference in minutes between the reported time and UTC time.
values(5) : The hour of the day, in the range 0 to 23.
values(6) : The minutes of the hour, in the range 0 to 59
values(7) : The seconds of the minute, in the range 0 to 60
values(8) : The milliseconds of the second, in the range 0 to 999.
The date, clock, and time zone information might be available on some images and not others. If the date, clock, or time zone information is available on more than one image, it is processor dependent whether or not those images share the same information.
Examples#
Sample program:
program demo_date_and_time
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)
print '(*(g0))','DATE="',date,'" TIME="',time,'" ZONE="',zone,'"'
call date_and_time(VALUES=values)
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_date_and_time
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
See Also#
Resources#
date and time conversion, formatting and computation
M_time - https://github.com/urbanjost/M_time
fortran-datetime https://github.com/dongli/fortran-datetime
datetime-fortran - https://github.com/wavebitscientific/datetime-fortran
fortran-lang intrinsic descriptions (license: MIT) @urbanjost
system_clock#
Name#
system_clock(3) - [SYSTEM:TIME] Query system clock
Synopsis#
call system_clock([count] [,count_rate] [,count_max] )
subroutine system_clock(count, count_rate, count_max)
integer(kind=**),intent(out),optional :: count
type(TYPE(kind=**),intent(out),optional :: count_rate
integer(kind=**),intent(out),optional :: count_max
Characteristics#
count is an integer scalar
count_rate is an integer or real scalar
count_max is an integer scalar
Description#
system_clock(3) lets you measure durations of time with the precision of the smallest time increment generally available on a system by returning processor-dependent values based on the current value of the processor clock.
system_clock is typically used to measure short time intervals (system clocks may be 24-hour clocks or measure processor clock ticks since boot, for example). It is most often used for measuring or tracking the time spent in code blocks in lieu of using profiling tools.
count_rate and count_max are assumed constant (even though CPU rates can vary on a single platform).
Whether an image has no clock, has a single clock of its own, or shares a clock with another image, is processor dependent.
If there is no clock, or querying the clock fails, count is set to -huge(count), and count_rate and count_max are set to zero.
The accuracy of the measurements may depend on the kind of the arguments!
Timing-related procedures are obviously processor and system-dependent. More specific information may generally be found in compiler-specific documentation.
Options#
count If there is no clock, the returned value for count is the negative value -huge(count).
Otherwise, the clock value is incremented by one for each clock count until the value count_max is reached and is then reset to zero at the next count. clock therefore is a modulo value that lies in the range 0 to count_max.
- count_rate
is assigned a processor-dependent approximation to the number of processor clock counts per second, or zero if there is no clock. count_rate is system dependent and can vary depending on the kind of the arguments. Generally, a large real may generate a more precise interval.
- count_max
is assigned the maximum value that COUNT can have, or zero if there is no clock.
Examples#
If the processor clock is a 24-hour clock that registers time at approximately 18.20648193 ticks per second, at 11:30 A.M. the reference
call system_clock (count = c, count_rate = r, count_max = m)
defines
C = (11*3600+30*60)*18.20648193 = 753748,
R = 18.20648193, and
M = 24*3600*18.20648193-1 = 1573039.
Sample program:
program demo_system_clock
use, intrinsic :: iso_fortran_env, only: wp => real64, int32, int64
implicit none
character(len=*), parameter :: g = '(1x,*(g0,1x))'
integer(kind=int64) :: count64, count_rate64, count_max64
integer(kind=int64) :: start64, finish64
integer(kind=int32) :: count32, count_rate32, count_max32
integer(kind=int32) :: start32, finish32
real(kind=wp) :: time_read
real(kind=wp) :: sum
integer :: i
print g, 'accuracy may vary with argument type!'
print g, 'query all arguments'
call system_clock(count64, count_rate64, count_max64)
print g, 'COUNT_MAX(64bit)=', count_max64
print g, 'COUNT_RATE(64bit)=', count_rate64
print g, 'CURRENT COUNT(64bit)=', count64
call system_clock(count32, count_rate32, count_max32)
print g, 'COUNT_MAX(32bit)=', count_max32
print g, 'COUNT_RATE(32bit)=', count_rate32
print g, 'CURRENT COUNT(32bit)=', count32
print g, 'time some computation'
call system_clock(start64)
! some code to time
sum = 0.0_wp
do i = -0, huge(0) - 1
sum = sum + sqrt(real(i))
end do
print g, 'SUM=', sum
call system_clock(finish64)
time_read = (finish64 - start64)/real(count_rate64, wp)
write (*, '(1x,a,1x,g0,1x,a)') 'time : ', time_read, ' seconds'
end program demo_system_clock
Results:
> accuracy may vary with argument type!
> query all arguments
> COUNT_MAX(64bit)= 9223372036854775807
> COUNT_RATE(64bit)= 1000000000
> CURRENT COUNT(64bit)= 1105422387865806
> COUNT_MAX(32bit)= 2147483647
> COUNT_RATE(32bit)= 1000
> CURRENT COUNT(32bit)= 1105422387
> time some computation
> SUM= 66344288183024.266
> time : 6.1341038460000004 seconds
Standard#
Fortran 95
See Also#
fortran-lang intrinsic descriptions
execute_command_line#
Name#
execute_command_line(3) - [SYSTEM:PROCESSES] Execute a shell command
Synopsis#
call execute_command_line( &
& command [,wait] [,exitstat] [,cmdstat] [,cmdmsg] )
subroutine execute_command_line(command,wait,exitstat,cmdstat,cmdmsg)
character(len=*),intent(in) :: command
logical,intent(in),optional :: wait
integer,intent(inout),optional :: exitstat
integer,intent(inout),optional :: cmdstat
character(len=*),intent(inout),optional :: cmdmsg
Characteristics#
command is a default character scalar
wait is a default logical scalar. If wait is present with the
exitstat is an integer of the default kind. It must be of a kind with at least a decimal exponent range of 9.
cmdstat is an integer of default kind The kind of the variable must support at least a decimal exponent range of four.
cmdmsg is a character scalar of the default kind.
Description#
For execute_command_line(3) the command argument is passed to the shell and executed. (The shell is generally sh(1) on Unix systems, and cmd.exe on Windows.) If wait is present and has the value .false., the execution of the command is asynchronous if the system supports it; otherwise, the command is executed synchronously.
The three last arguments allow the user to get status information. After synchronous execution, exitstat contains the integer exit code of the command, as returned by system. cmdstat is set to zero if the command line was executed (whatever its exit status was). cmdmsg is assigned an error message if an error has occurred.
Note that the system call need not be thread-safe. It is the responsibility of the user to ensure that the system is not called concurrently if required.
When the command is executed synchronously, execute_command_line returns after the command line has completed execution. Otherwise, execute_command_line returns without waiting.
Because this intrinsic is making a system call, it is very system dependent. Its behavior with respect to signaling is processor dependent. In particular, on POSIX-compliant systems, the SIGINT and SIGQUIT signals will be ignored, and the SIGCHLD will be blocked. As such, if the parent process is terminated, the child process might not be terminated alongside.
Options#
- command
the command line to be executed. The interpretation is programming-environment dependent.
- wait
If wait is present with the value .false., and the processor supports asynchronous execution of the command, the command is executed asynchronously; otherwise it is executed synchronously.
When the command is executed synchronously, execute_command_line(3) returns after the command line has completed execution. Otherwise, execute_command_line(3) returns without waiting.
- exitstat
If the command is executed synchronously, it is assigned the value of the processor-dependent exit status. Otherwise, the value of exitstat is unchanged.
- cmdstat
If an error condition occurs and cmdstat is not present, error termination of execution of the image is initiated.
It is assigned the value -1 if the processor does not support command line execution, a processor-dependent positive value if an error condition occurs, or the value -2 if no error condition occurs but wait is present with the value false and the processor does not support asynchronous execution. Otherwise it is assigned the value 0.
- cmdmsg
If an error condition occurs, it is assigned a processor-dependent explanatory message. Otherwise, it is unchanged.
Examples#
Sample program:
program demo_exec
implicit none
integer :: i
call execute_command_line("external_prog.exe", exitstat=i)
print *, "Exit status of external_prog.exe was ", i
call execute_command_line("reindex_files.exe", wait=.false.)
print *, "Now reindexing files in the background"
end program demo_exec
Standard#
Fortran 2008
See also#
fortran-lang intrinsic descriptions (license: MIT) @urbanjost
get_environment_variable#
Name#
get_environment_variable(3) - [SYSTEM:ENVIRONMENT] Get value of an environment variable
Synopsis#
call get_environment_variable(name [,value] [,length] &
& [,status] [,trim_name] [,errmsg] )
subroutine character(len=*) get_environment_variable( &
& name, value, length, status, trim_name, errmsg )
character(len=*),intent(in) :: name
character(len=*),intent(out),optional :: value
integer(kind=**),intent(out),optional :: length
integer(kind=**),intent(out),optional :: status
logical,intent(out),optional :: trim_name
character(len=*),intent(inout),optional :: errmsg
Characteristics#
a kind designated as ** may be any supported kind for the type meeting the conditions described herein.
name, value, and errmsg are a scalar character of default kind.
length and status are integer scalars with a decimal exponent range of at least four.
trim_name is a scalar of type logical and of default kind.
Description#
get_environment_variable(3) gets the value of the environment 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.
If running in parallel be aware It is processor dependent whether an environment variable that exists on an image also exists on another image, and if it does exist on both images whether the values are the same or different.
Options#
- name
The name of the environment variable to query. The interpretation of case is processor dependent.
Result#
- value
The value of the environment variable being queried. If value is not large enough to hold the data, it is truncated. If the variable name is not set or has no value, or the processor does not support environment variables value will be filled with blanks.
- length
Argument length contains the length needed for storing the environment variable name. It is zero if the environment variable is not set.
- 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.
- 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.
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
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 does not support environment variables. Boooh!"
value=''
case default
! make string of sufficient size to hold value
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
See also#
get_command_argument(3), get_command(3)
fortran-lang intrinsic descriptions (license: MIT) @urbanjost