访问外部系统信息#
command_argument_count#
名称#
command_argument_count(3) - [SYSTEM:COMMAND LINE] 获取命令行参数的数量
语法#
result = command_argument_count()
integer function command_argument_count()
特性#
结果为默认整数标量。
描述#
command_argument_count(3) 返回包含程序被调用时传递到命令行的参数数量。
选项#
无
结果#
:返回值的类型为默认整数。它是程序被调用时传递到命令行的参数数量。
如果没有可用的命令参数,或者处理器不支持命令参数,则结果值为零。
如果处理器具有命令名称的概念,则命令名称不计为命令参数之一。
示例#
示例程序
program demo_command_argument_count
implicit none
integer :: count
count = command_argument_count()
print *, count
end program demo_command_argument_count
示例输出
# 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
标准#
Fortran 2003
参见#
get_command(3),get_command_argument(3)
fortran-lang 内在函数描述 (许可证:MIT) @urbanjost
get_command#
名称#
get_command(3) - [SYSTEM:COMMAND LINE] 获取整个命令行调用
语法#
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
特性#
指定为 ** 的种类可以是满足此处描述的条件的类型的任何受支持种类。
command 和 errmsg 是默认种类的标量字符变量。
length 和 status 是具有至少四位十进制指数范围的标量整数。
描述#
get_command(3) 检索用于调用程序的整个命令行。
请注意,在命令行上键入的内容通常由 shell 处理。shell 通常会在将命令行传递给程序之前处理特殊字符和空格。通常可以通过关闭通配符或引用命令行参数和/或更改默认字段分隔符来关闭处理,但这很少需要。
结果#
- command
如果存在command,则用于调用程序的整个命令行将存储到其中。如果无法确定命令,则command 将被分配所有空格。
- length
如果存在length,则将其分配为命令行的长度。是否计算尾随空格取决于系统。
如果无法确定命令长度,则分配长度 0。
- status
如果存在status,则在命令成功时将其分配为 0,如果command 太短而无法存储命令行,则分配-1,或者在发生错误时分配正值。
- errmsg
如果命令检索失败,则将其分配为处理器相关的解释性消息。否则,它保持不变。
示例#
示例程序
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
结果
# 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 *><`~[]!{}?"'|
标准#
Fortran 2003
参见#
get_command_argument(3),command_argument_count(3)
fortran-lang 内在函数描述 (许可证:MIT) @urbanjost
#
get_command_argument#
名称#
get_command_argument(3) - [SYSTEM:COMMAND LINE] 获取命令行参数
语法#
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
特性#
指定为 ** 的种类可以是满足此处描述的条件的类型的任何受支持种类。
number、length 和 status 是具有至少四位十进制指数范围的标量整数。
value 和 errmsg 是默认种类的标量字符变量。
描述#
get_command_argument(3) 检索或查询传递到当前程序执行的命令行的第 n 个参数。
没有明确说明参数是什么,但在实践中,参数是在空格上拆分的字符串,除非参数被引用。常见 shell 使用的 IFS 值(内部字段分隔符)通常会被忽略,并且未引用的空格几乎总是分隔符。
shell 通常会在将命令参数传递给程序之前扩展命令参数和拼写字符,因此读取的字符串通常与用户在命令行上键入的字符串不完全相同。
选项#
- number
是一个非负数,指示要检索或查询的当前程序命令行的哪个参数。
如果number = 0,则指向的参数将设置为程序的名称(在支持此功能的系统上)。
如果处理器没有命令名称这样的概念,则命令参数 0 的值取决于处理器。
对于从 1 到传递给程序的参数数量的值,将按处理器确定的顺序返回值。按照惯例,它们将按照从左到右在命令行中出现的顺序连续返回。
结果#
- value
value 参数包含命令行参数。如果value 无法容纳该参数,则将其截断以适合value 的长度。
如果命令行中指定的参数少于number 个,或者由于其他原因指定的参数不存在,则value 将填充空格。
- length
length 参数包含第 n 个命令行参数的长度。value 的长度对此值没有影响,它是保存参数所有有效字符所需的长度,无论value 提供多少存储空间。
- status
如果参数检索失败,则status 为正数;如果value 包含截断的命令行参数,则status 为-1;否则status 为零。
示例#
示例程序
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
结果
./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]
标准#
Fortran 2003
参见#
get_command(3),command_argument_count(3)
fortran-lang 内在函数描述 (许可证:MIT) @urbanjost
#
cpu_time#
名称#
cpu_time(3) - [SYSTEM:TIME] 返回以秒为单位的 CPU 处理器使用时间
语法#
call cpu_time(time)
subroutine cpu_time(time)
real,intent(out) :: time
特性#
time 是任何种类的实数
描述#
cpu_time(3) 返回一个表示以秒为单位的经过 CPU 时间的实数值。这对于测试代码段以确定执行时间很有用。
如果没有可用的时间源,则time 将设置为负值。
时间的精确定义是不精确的,因为不同处理器能够提供的内容存在差异。
请注意,time 可能包含系统相关的任意偏移量,并且可能不是从 0.0 开始。对于cpu_time(3),绝对值没有意义。仅应使用后续调用之间的差异,如下面的示例所示。
并行处理
分配的值是调用映像使用的时间量的近似值,还是整个程序使用的时间量的近似值,取决于处理器。
对于单个结果不足的处理器(例如,并行处理器),可能会选择提供一个额外的版本,其中time 为数组。
结果#
- 时间
被赋予一个处理器相关的近似值,表示处理器时间(以秒为单位)。如果处理器无法返回有意义的时间,则返回一个处理器相关的负值。
起始时间保持不精确,因为目的是对代码片段进行计时,如示例所示。这可能包括或可能不包括系统开销时间。
示例#
示例程序
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
结果
结果的精度、返回内容的某些方面以及并行应用程序的任何选项可能因系统而异。有关详细信息,请参阅特定编译器的文档。
Processor Time = 0.000 seconds.
Processor Time = .4000030E-05 seconds.
Processor Time = .2000000000000265E-05 seconds.
标准#
Fortran 95
另请参见#
system_clock(3),date_and_time(3)
fortran-lang 内在函数描述 (许可证:MIT) @urbanjost
date_and_time#
名称#
date_and_time(3) - [SYSTEM:TIME] 获取当前日期时间
概要#
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)
特征#
*date 是一个默认的 character 标量
*time 是一个默认的 character 标量
*zone 是一个默认的 character 标量
values 是一个秩为一的整数类型数组,其十进制指数范围至少为四。
描述#
date_and_time(3) 从实时系统时钟获取相应的日期和时间信息。
不可用的日期和时间 character 参数返回空格。
不可用的数值参数返回 -huge(value)。
这些格式与 ISO 8601:2004 中定义的表示形式兼容。UTC 由国际计量局 (BIPM,即国际计量局) 和国际地球自转服务 (IERS) 建立。
选项#
- date
一个默认类型的字符字符串,格式为 CCYYMMDD,长度为 8 或更大,其中
CCYY 是公历年份
MM 是年内的月份
DD 是月内的日期。
此值的字符均为十进制数字。
如果没有可用的日期,则 DATE 被赋予全部空格。
- 时间
一个默认类型的字符字符串,格式为 HHMMSS.SSS,长度为 10 或更大,其中
hh 是一天中的小时,
mm 是小时内的分钟,
ss.sss 是分钟内的秒和毫秒。
除了小数点,此值的字符均应为十进制数字。
如果没有可用的时钟,则 TIME 被赋予全部空格。
- zone
格式为 (+-)HHMM 的字符串,长度为 5 或更大,表示相对于协调世界时 (UTC) 的差异,其中
hh 和 mm 分别是相对于协调世界时 (UTC) 的时间差(以小时和分钟为单位)。
此值在符号字符之后的字符均为十进制数字。
如果此信息不可用,则 ZONE 被赋予全部空格。
- values
一个至少包含八个元素的数组。如果某个值没有可用的数据,则将其设置为 -huge(values)。否则,它包含
values(1) : 年份,包括世纪。
values(2) : 年份中的月份
values(3) : 月份中的日期
values(4) : 报告时间与 UTC 时间之间的时间差(以分钟为单位)。
values(5) : 一天中的小时,范围为 0 到 23。
values(6) : 小时内的分钟,范围为 0 到 59
values(7) : 分钟内的秒,范围为 0 到 60
values(8) : 秒内的毫秒,范围为 0 到 999。
日期、时钟和时区信息可能在某些镜像上可用,而在另一些镜像上不可用。如果日期、时钟或时区信息在多个镜像上可用,则这些镜像是否共享相同的信息取决于处理器。
示例#
示例程序
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
结果
> 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
标准#
Fortran 95
另请参见#
资源#
日期和时间转换、格式化和计算
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 内在函数描述 (许可证:MIT) @urbanjost
system_clock#
名称#
system_clock(3) - [SYSTEM:TIME] 查询系统时钟
概要#
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
特征#
count 是一个 integer 标量
count_rate 是一个 integer 或 real 标量
count_max 是一个 integer 标量
描述#
system_clock(3) 允许您以系统通常可用的最小时间增量精度来测量时间持续时间,方法是根据处理器时钟的当前值返回处理器相关的值。
system_clock 通常用于测量短时间间隔(例如,系统时钟可能是 24 小时时钟或测量自启动以来的处理器时钟滴答数)。它最常用于测量或跟踪代码块中花费的时间,而不是使用性能分析工具。
假设 count_rate 和 count_max 是常数(即使 CPU 速率在一个平台上可能会有所不同)。
镜像是否没有时钟、是否有自己的单个时钟或与其他镜像共享时钟,这取决于处理器。
如果没有时钟或查询时钟失败,则 count 设置为 -huge(count),count_rate 和 count_max 设置为零。
测量的准确性可能取决于参数的类型!
与时间相关的过程显然是处理器和系统相关的。更具体的信息通常可以在特定编译器的文档中找到。
选项#
count 如果没有时钟,则返回的 count 值为负值 -huge(count)。
否则,每次时钟计数 clock 值都会增加 1,直到达到值 count_max,然后在下次计数时重置为零。因此,clock 是一个位于 0 到 count_max 范围内的模值。
- count_rate
被赋予一个处理器相关的近似值,表示每秒的处理器时钟计数数,或者如果没有时钟则为零。count_rate 是系统相关的,并且会根据参数的类型而有所不同。通常,较大的 real 值可以生成更精确的时间间隔。
- count_max
被赋予 COUNT 可以具有的最大值,或者如果没有时钟则为零。
示例#
如果处理器时钟是一个 24 小时时钟,其时间注册速度约为每秒 18.20648193 个滴答,在上午 11:30,引用
call system_clock (count = c, count_rate = r, count_max = m)
定义
C = (11*3600+30*60)*18.20648193 = 753748,
R = 18.20648193, and
M = 24*3600*18.20648193-1 = 1573039.
示例程序
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
结果
> 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
标准#
Fortran 95
另请参见#
fortran-lang 内置描述
execute_command_line#
名称#
execute_command_line(3) - [SYSTEM:PROCESSES] 执行 shell 命令
概要#
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
特征#
command 是一个默认的 character 标量
wait 是一个默认的 logical 标量。如果 wait 与
exitstat 是一个默认类型的 integer。它必须与至少具有 9 个十进制指数范围的类型相同。
cmdstat 是一个默认类型的 integer。变量的类型必须至少支持 4 个十进制指数范围。
cmdmsg 是一个默认类型的 character 标量。
描述#
对于 execute_command_line(3),command 参数被传递给 shell 并执行。(shell 通常在 Unix 系统上为 sh(1),在 Windows 上为 cmd.exe。)如果 wait 存在且值为 .false.,则如果系统支持,则命令的执行是异步的;否则,命令是同步执行的。
最后三个参数允许用户获取状态信息。在同步执行之后,exitstat 包含命令的整数退出代码,由 system 返回。如果命令行被执行(无论其退出状态如何),则 cmdstat 设置为零。如果发生错误,则 cmdmsg 被赋予错误消息。
请注意,系统调用不一定是线程安全的。如果需要,用户有责任确保系统不被并发调用。
当命令同步执行时,execute_command_line 在命令行完成执行后返回。否则,execute_command_line 在不等待的情况下返回。
由于此内在函数正在进行系统调用,因此它非常依赖于系统。它在信号方面的行为取决于处理器。特别是,在符合 POSIX 的系统上,SIGINT 和 SIGQUIT 信号将被忽略,SIGCHLD 将被阻塞。因此,如果父进程终止,子进程可能不会随之终止。
选项#
- command
要执行的命令行。解释取决于编程环境。
- wait
如果 wait 存在且值为 .false.,并且处理器支持异步执行命令,则命令异步执行;否则同步执行。
当命令同步执行时,execute_command_line(3) 在命令行完成执行后返回。否则,execute_command_line(3) 在不等待的情况下返回。
- exitstat
如果命令同步执行,则将其赋予处理器相关的退出状态值。否则,exitstat 的值保持不变。
- cmdstat
如果发生错误条件且 cmdstat 不存在,则会启动镜像执行的错误终止。
如果处理器不支持命令行执行,则将其赋予值 -1;如果发生错误条件,则赋予处理器相关的正值;或者如果未发生错误条件但 wait 存在且值为 false 并且处理器不支持异步执行,则赋予值 -2。否则,将其赋予值 0。
- cmdmsg
如果发生错误情况,则会分配一个处理器相关的解释性消息。否则,它保持不变。
示例#
示例程序
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
标准#
Fortran 2008
另请参阅#
fortran-lang 内在函数描述 (许可证:MIT) @urbanjost
get_environment_variable#
名称#
get_environment_variable(3) - [SYSTEM:ENVIRONMENT] 获取环境变量的值
概要#
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
特征#
指定为 ** 的种类可以是满足此处描述的条件的类型的任何受支持种类。
name、value 和 errmsg 是默认类型的标量字符。
length 和 status 是整数标量,具有至少四位的十进制指数范围。
trim_name 是逻辑类型且为默认类型的标量。
描述#
get_environment_variable(3) 获取环境变量name的value。
请注意,get_environment_variable(3) 不必是线程安全的。用户有责任确保环境不会被并发更新。
如果并行运行,请注意,环境变量是否存在于一个映像上也存在于另一个映像上,以及如果它存在于两个映像上,其值是相同还是不同,这取决于处理器。
选项#
- name
要查询的环境变量的名称。大小写的解释取决于处理器。
结果#
- value
被查询的环境变量的值。如果value不足以容纳数据,则将其截断。如果变量name未设置或没有值,或者处理器不支持环境变量,则value将填充空格。
- length
参数length包含存储环境变量name所需的长度。如果环境变量未设置,则为零。
- status
如果value存在但对于环境变量来说太短,则status为-1;如果环境变量不存在,则为1;如果处理器不支持环境变量,则为2;在所有其他情况下,status为零。
- trim_name
如果trim_name存在且值为.false.,则name中的尾随空格具有意义;否则它们不是环境变量名称的一部分。
示例#
示例程序
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
典型结果
HOME="/home/urbanjs"
标准#
Fortran 2003
另请参阅#
get_command_argument(3),get_command(3)
fortran-lang 内在函数描述 (许可证:MIT) @urbanjost