Accessing external system information#

command_argument_count#

Name#

command_argument_count(3) - [SYSTEM:COMMAND LINE] Get number of command line arguments

Syntax#

    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:

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 (license: MIT) @urbanjost

get_command#

Name#

get_command(3) - [SYSTEM:COMMAND LINE] 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

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 and later

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

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 number-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 :: args(:)
  !
  ! 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) :: args(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, args(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),args(i)(:ilen(i)),i=0,count)
end program demo_get_command_argument

Results:

/demo_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 (license: MIT) @urbanjost

cpu_time#

Name#

cpu_time(3) - [SYSTEM:TIME] return CPU processor time in seconds

Syntax#

     call cpu_time(time)
     real,intent(out) :: time

Description#

Returns a real value representing the elapsed CPU time in seconds. This is useful for testing segments of code to determine execution time.

The exact definition of time is left imprecise because of the variability in what different processors are able to provide.

If no time source is available, TIME is set to a negative value.

Note that TIME may contain a system dependent, arbitrary offset and may not start with 0.0. For cpu_time the absolute value is meaningless. Only differences between subsequent calls, as shown in the example below, should be used.

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.

Returns#

  • TIME

    The type shall be real with intent(out). It 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
implicit none
real :: start, finish
   !
   call cpu_time(start)
   ! put code to test here
   call cpu_time(finish)
   !
   ! writes processor time taken by the piece of code.
   print '("Processor Time = ",f6.3," seconds.")',finish-start
end program demo_cpu_time

Results:

   Processor Time =  0.000 seconds.

Standard#

Fortran 95 and later

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 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

    A character string of default kind of the form CCYYMMDD, of length 8 or larger.

  • time

    A character string of default kind of the form HHMMSS.SSS, of length 10 or larger.

  • zone

    A character string of default kind of the form (+-)HHMM, of length 5 or larger, representing the difference with respect to Coordinated Universal Time (UTC).

  • values

    An integer array of eight elements that contains:

    • 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

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 and later

See Also#

cpu_time(3), system_clock(3)

Resources#

date and time conversion, formatting and computation

####### fortran-lang intrinsic descriptions (license: MIT) @urbanjost

system_clock#

Name#

system_clock(3) - [SYSTEM:TIME] Return numeric data from a real-time clock.

Syntax#

subroutine system_clock(count, count_rate, count_max)

   integer,intent(out),optional  :: count
   integer,intent(out),optional  :: count_rate
    ! or !
   real,intent(out),optional     :: count_rate
   integer,intent(out),optional  :: count_max

Description#

system_clock 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. 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 and count_max are assumed constant (even though CPU rates can vary on a single platform).

count_rate is system dependent and can vary depending on the kind of the arguments.

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.

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.

Arguments#

  • count

    (optional) shall be an integer scalar. It is assigned a processor-dependent value based on the current value of the processor clock, or -huge(count) if there is no clock. The processor-dependent value is incremented by one for each clock count until the value count_max is reached and is reset to zero at the next count. It lies in the range 0 to count_max if there is a clock.

  • count_rate

    (optional) shall be an integer or real scalar. It is assigned a processor-dependent approximation to the number of processor clock counts per second, or zero if there is no clock.

  • count_max

    (optional) shall be an integer scalar. It is assigned the maximum value that COUNT can have, or zero if there is no clock.

Examples#

Sample program:

program demo_system_clock
implicit none
integer, parameter :: wp = kind(1.0d0)
integer :: count, count_rate, count_max
integer :: start, finish
real    :: time_read

   call system_clock(count, count_rate, count_max)
   write(*,*) count, count_rate, count_max

   call system_clock(start, count_rate)
   ! <<<< code to time
   call system_clock(finish)
   time_read=(finish-start)/real(count_rate,wp)
   write(*,'(a30,1x,f7.4,1x,a)') 'time * : ', time_read, ' seconds'

end program demo_system_clock

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.

Standard#

Fortran 95 and later

See Also#

date_and_time(3), cpu_time(3)

####### fortran-lang intrinsic descriptions

execute_command_line#

Name#

execute_command_line(3) - [SYSTEM:PROCESSES] Execute a shell command

Syntax#

   subroutine execute_command_line(command, wait, exitstat, cmdstat, cmdmsg)

    character(len=*),intent(in)  :: command
    logical,intent(in),optional  :: wait
    integer,intent(out),optional :: exitstat
    integer,intent(out),optional :: cmdstat
    character(len=*),intent(out),optional :: cmdmsg

Description#

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.

Arguments#

  • command

    a default character scalar containing the command line to be executed. The interpretation is programming-environment dependent.

  • wait

    (Optional) a default logical scalar. 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.

  • exitstat

    (Optional) an integer of the default kind with intent(inout). 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

    (Optional) an integer of default kind with intent(inout). 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

    (Optional) a character scalar of the default kind. It is an intent (inout) argument.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

Note#

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.

Standard#

Fortran 2008 and later

####### fortran-lang intrinsic descriptions

get_environment#

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 does not 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

####### fortran-lang intrinsic descriptions (license: MIT) @urbanjost