stdlib_io Module

Provides a support for file handling (Specification)



Variables

Type Visibility Attributes Name Initial
character(len=*), public, parameter :: FMT_COMPLEX_DP = '(es24.16e3,1x,es24.16e3)'

Format strings with edit descriptors for each type and kind (Specification) Format string for integers Format string for single precision real numbers Format string for souble precision real numbers Format string for extended double precision real numbers Format string for quadruple precision real numbers Format string for single precision complex numbers Format string for double precision complex numbers Format string for extended double precision complex numbers Format string for quadruple precision complex numbers

character(len=*), public, parameter :: FMT_COMPLEX_QP = '(es44.35e4,1x,es44.35e4)'

Format strings with edit descriptors for each type and kind (Specification) Format string for integers Format string for single precision real numbers Format string for souble precision real numbers Format string for extended double precision real numbers Format string for quadruple precision real numbers Format string for single precision complex numbers Format string for double precision complex numbers Format string for extended double precision complex numbers Format string for quadruple precision complex numbers

character(len=*), public, parameter :: FMT_COMPLEX_SP = '(es15.8e2,1x,es15.8e2)'

Format strings with edit descriptors for each type and kind (Specification) Format string for integers Format string for single precision real numbers Format string for souble precision real numbers Format string for extended double precision real numbers Format string for quadruple precision real numbers Format string for single precision complex numbers Format string for double precision complex numbers Format string for extended double precision complex numbers Format string for quadruple precision complex numbers

character(len=*), public, parameter :: FMT_COMPLEX_XDP = '(es26.18e3,1x,es26.18e3)'

Format strings with edit descriptors for each type and kind (Specification) Format string for integers Format string for single precision real numbers Format string for souble precision real numbers Format string for extended double precision real numbers Format string for quadruple precision real numbers Format string for single precision complex numbers Format string for double precision complex numbers Format string for extended double precision complex numbers Format string for quadruple precision complex numbers

character(len=*), public, parameter :: FMT_INT = '(i0)'

Format strings with edit descriptors for each type and kind (Specification) Format string for integers Format string for single precision real numbers Format string for souble precision real numbers Format string for extended double precision real numbers Format string for quadruple precision real numbers Format string for single precision complex numbers Format string for double precision complex numbers Format string for extended double precision complex numbers Format string for quadruple precision complex numbers

character(len=*), public, parameter :: FMT_REAL_DP = '(es24.16e3)'

Format strings with edit descriptors for each type and kind (Specification) Format string for integers Format string for single precision real numbers Format string for souble precision real numbers Format string for extended double precision real numbers Format string for quadruple precision real numbers Format string for single precision complex numbers Format string for double precision complex numbers Format string for extended double precision complex numbers Format string for quadruple precision complex numbers

character(len=*), public, parameter :: FMT_REAL_QP = '(es44.35e4)'

Format strings with edit descriptors for each type and kind (Specification) Format string for integers Format string for single precision real numbers Format string for souble precision real numbers Format string for extended double precision real numbers Format string for quadruple precision real numbers Format string for single precision complex numbers Format string for double precision complex numbers Format string for extended double precision complex numbers Format string for quadruple precision complex numbers

character(len=*), public, parameter :: FMT_REAL_SP = '(es15.8e2)'

Format strings with edit descriptors for each type and kind (Specification) Format string for integers Format string for single precision real numbers Format string for souble precision real numbers Format string for extended double precision real numbers Format string for quadruple precision real numbers Format string for single precision complex numbers Format string for double precision complex numbers Format string for extended double precision complex numbers Format string for quadruple precision complex numbers

character(len=*), public, parameter :: FMT_REAL_XDP = '(es26.18e3)'

Format strings with edit descriptors for each type and kind (Specification) Format string for integers Format string for single precision real numbers Format string for souble precision real numbers Format string for extended double precision real numbers Format string for quadruple precision real numbers Format string for single precision complex numbers Format string for double precision complex numbers Format string for extended double precision complex numbers Format string for quadruple precision complex numbers


Interfaces

public interface getline

Read a whole line from a formatted unit into a string variable

  • private subroutine getline_char(unit, line, iostat, iomsg)

    Read a whole line from a formatted unit into a deferred length character variable

    Arguments

    Type IntentOptional Attributes Name
    integer, intent(in) :: unit

    Formatted IO unit

    character(len=:), intent(out), allocatable :: line

    Line to read

    integer, intent(out), optional :: iostat

    Status of operation

    character(len=:), optional, allocatable :: iomsg

    Error message

  • private subroutine getline_string(unit, line, iostat, iomsg)

    Read a whole line from a formatted unit into a string variable

    Arguments

    Type IntentOptional Attributes Name
    integer, intent(in) :: unit

    Formatted IO unit

    type(string_type), intent(out) :: line

    Line to read

    integer, intent(out), optional :: iostat

    Status of operation

    character(len=:), optional, allocatable :: iomsg

    Error message

  • private subroutine getline_input_char(line, iostat, iomsg)

    Read a whole line from the standard input into a deferred length character variable

    Arguments

    Type IntentOptional Attributes Name
    character(len=:), intent(out), allocatable :: line

    Line to read

    integer, intent(out), optional :: iostat

    Status of operation

    character(len=:), optional, allocatable :: iomsg

    Error message

  • private subroutine getline_input_string(line, iostat, iomsg)

    Read a whole line from the standard input into a string variable

    Arguments

    Type IntentOptional Attributes Name
    type(string_type), intent(out) :: line

    Line to read

    integer, intent(out), optional :: iostat

    Status of operation

    character(len=:), optional, allocatable :: iomsg

    Error message

public interface loadtxt

Loads a 2D array from a text file (Specification)

  • private subroutine loadtxt_rsp(filename, d, skiprows, max_rows)

    Loads a 2D array from a text file.

    Arguments

    Filename to load the array from

    Arguments

    Type IntentOptional Attributes Name
    character(len=*), intent(in) :: filename

    The array 'd' will be automatically allocated with the correct dimensions

    real(kind=sp), intent(out), allocatable :: d(:,:)

    Skip the first skiprows lines. If skipping more rows than present, a 0-sized array will be returned. The default is 0.

    integer, intent(in), optional :: skiprows

    Read max_rows lines of content after skiprows lines. A negative value results in reading all lines. A value of zero results in no lines to be read. The default value is -1.

    integer, intent(in), optional :: max_rows

    Example


     real(sp), allocatable :: data(:, :)
     call loadtxt("log.txt", data)  ! 'data' will be automatically allocated
    

    Where 'log.txt' contains for example::

     1 2 3
     2 4 6
     8 9 10
     11 12 13
     ...
    
  • private subroutine loadtxt_rdp(filename, d, skiprows, max_rows)

    Loads a 2D array from a text file.

    Arguments

    Filename to load the array from

    Arguments

    Type IntentOptional Attributes Name
    character(len=*), intent(in) :: filename

    The array 'd' will be automatically allocated with the correct dimensions

    real(kind=dp), intent(out), allocatable :: d(:,:)

    Skip the first skiprows lines. If skipping more rows than present, a 0-sized array will be returned. The default is 0.

    integer, intent(in), optional :: skiprows

    Read max_rows lines of content after skiprows lines. A negative value results in reading all lines. A value of zero results in no lines to be read. The default value is -1.

    integer, intent(in), optional :: max_rows

    Example


     real(dp), allocatable :: data(:, :)
     call loadtxt("log.txt", data)  ! 'data' will be automatically allocated
    

    Where 'log.txt' contains for example::

     1 2 3
     2 4 6
     8 9 10
     11 12 13
     ...
    
  • private subroutine loadtxt_iint8(filename, d, skiprows, max_rows)

    Loads a 2D array from a text file.

    Arguments

    Filename to load the array from

    Arguments

    Type IntentOptional Attributes Name
    character(len=*), intent(in) :: filename

    The array 'd' will be automatically allocated with the correct dimensions

    integer(kind=int8), intent(out), allocatable :: d(:,:)

    Skip the first skiprows lines. If skipping more rows than present, a 0-sized array will be returned. The default is 0.

    integer, intent(in), optional :: skiprows

    Read max_rows lines of content after skiprows lines. A negative value results in reading all lines. A value of zero results in no lines to be read. The default value is -1.

    integer, intent(in), optional :: max_rows

    Example


     integer(int8), allocatable :: data(:, :)
     call loadtxt("log.txt", data)  ! 'data' will be automatically allocated
    

    Where 'log.txt' contains for example::

     1 2 3
     2 4 6
     8 9 10
     11 12 13
     ...
    
  • private subroutine loadtxt_iint16(filename, d, skiprows, max_rows)

    Loads a 2D array from a text file.

    Arguments

    Filename to load the array from

    Arguments

    Type IntentOptional Attributes Name
    character(len=*), intent(in) :: filename

    The array 'd' will be automatically allocated with the correct dimensions

    integer(kind=int16), intent(out), allocatable :: d(:,:)

    Skip the first skiprows lines. If skipping more rows than present, a 0-sized array will be returned. The default is 0.

    integer, intent(in), optional :: skiprows

    Read max_rows lines of content after skiprows lines. A negative value results in reading all lines. A value of zero results in no lines to be read. The default value is -1.

    integer, intent(in), optional :: max_rows

    Example


     integer(int16), allocatable :: data(:, :)
     call loadtxt("log.txt", data)  ! 'data' will be automatically allocated
    

    Where 'log.txt' contains for example::

     1 2 3
     2 4 6
     8 9 10
     11 12 13
     ...
    
  • private subroutine loadtxt_iint32(filename, d, skiprows, max_rows)

    Loads a 2D array from a text file.

    Arguments

    Filename to load the array from

    Arguments

    Type IntentOptional Attributes Name
    character(len=*), intent(in) :: filename

    The array 'd' will be automatically allocated with the correct dimensions

    integer(kind=int32), intent(out), allocatable :: d(:,:)

    Skip the first skiprows lines. If skipping more rows than present, a 0-sized array will be returned. The default is 0.

    integer, intent(in), optional :: skiprows

    Read max_rows lines of content after skiprows lines. A negative value results in reading all lines. A value of zero results in no lines to be read. The default value is -1.

    integer, intent(in), optional :: max_rows

    Example


     integer(int32), allocatable :: data(:, :)
     call loadtxt("log.txt", data)  ! 'data' will be automatically allocated
    

    Where 'log.txt' contains for example::

     1 2 3
     2 4 6
     8 9 10
     11 12 13
     ...
    
  • private subroutine loadtxt_iint64(filename, d, skiprows, max_rows)

    Loads a 2D array from a text file.

    Arguments

    Filename to load the array from

    Arguments

    Type IntentOptional Attributes Name
    character(len=*), intent(in) :: filename

    The array 'd' will be automatically allocated with the correct dimensions

    integer(kind=int64), intent(out), allocatable :: d(:,:)

    Skip the first skiprows lines. If skipping more rows than present, a 0-sized array will be returned. The default is 0.

    integer, intent(in), optional :: skiprows

    Read max_rows lines of content after skiprows lines. A negative value results in reading all lines. A value of zero results in no lines to be read. The default value is -1.

    integer, intent(in), optional :: max_rows

    Example


     integer(int64), allocatable :: data(:, :)
     call loadtxt("log.txt", data)  ! 'data' will be automatically allocated
    

    Where 'log.txt' contains for example::

     1 2 3
     2 4 6
     8 9 10
     11 12 13
     ...
    
  • private subroutine loadtxt_csp(filename, d, skiprows, max_rows)

    Loads a 2D array from a text file.

    Arguments

    Filename to load the array from

    Arguments

    Type IntentOptional Attributes Name
    character(len=*), intent(in) :: filename

    The array 'd' will be automatically allocated with the correct dimensions

    complex(kind=sp), intent(out), allocatable :: d(:,:)

    Skip the first skiprows lines. If skipping more rows than present, a 0-sized array will be returned. The default is 0.

    integer, intent(in), optional :: skiprows

    Read max_rows lines of content after skiprows lines. A negative value results in reading all lines. A value of zero results in no lines to be read. The default value is -1.

    integer, intent(in), optional :: max_rows

    Example


     complex(sp), allocatable :: data(:, :)
     call loadtxt("log.txt", data)  ! 'data' will be automatically allocated
    

    Where 'log.txt' contains for example::

     1 2 3
     2 4 6
     8 9 10
     11 12 13
     ...
    
  • private subroutine loadtxt_cdp(filename, d, skiprows, max_rows)

    Loads a 2D array from a text file.

    Arguments

    Filename to load the array from

    Arguments

    Type IntentOptional Attributes Name
    character(len=*), intent(in) :: filename

    The array 'd' will be automatically allocated with the correct dimensions

    complex(kind=dp), intent(out), allocatable :: d(:,:)

    Skip the first skiprows lines. If skipping more rows than present, a 0-sized array will be returned. The default is 0.

    integer, intent(in), optional :: skiprows

    Read max_rows lines of content after skiprows lines. A negative value results in reading all lines. A value of zero results in no lines to be read. The default value is -1.

    integer, intent(in), optional :: max_rows

    Example


     complex(dp), allocatable :: data(:, :)
     call loadtxt("log.txt", data)  ! 'data' will be automatically allocated
    

    Where 'log.txt' contains for example::

     1 2 3
     2 4 6
     8 9 10
     11 12 13
     ...
    

public interface savetxt

Saves a 2D array into a text file (Specification)

  • private subroutine savetxt_rsp(filename, d)

    Saves a 2D array into a text file.

    Arguments

    Arguments

    Type IntentOptional Attributes Name
    character(len=*), intent(in) :: filename
    real(kind=sp), intent(in) :: d(:,:)

    Example


     real(sp) :: data(3, 2)
     call savetxt("log.txt", data)
    
  • private subroutine savetxt_rdp(filename, d)

    Saves a 2D array into a text file.

    Arguments

    Arguments

    Type IntentOptional Attributes Name
    character(len=*), intent(in) :: filename
    real(kind=dp), intent(in) :: d(:,:)

    Example


     real(dp) :: data(3, 2)
     call savetxt("log.txt", data)
    
  • private subroutine savetxt_iint8(filename, d)

    Saves a 2D array into a text file.

    Arguments

    Arguments

    Type IntentOptional Attributes Name
    character(len=*), intent(in) :: filename
    integer(kind=int8), intent(in) :: d(:,:)

    Example


     integer(int8) :: data(3, 2)
     call savetxt("log.txt", data)
    
  • private subroutine savetxt_iint16(filename, d)

    Saves a 2D array into a text file.

    Arguments

    Arguments

    Type IntentOptional Attributes Name
    character(len=*), intent(in) :: filename
    integer(kind=int16), intent(in) :: d(:,:)

    Example


     integer(int16) :: data(3, 2)
     call savetxt("log.txt", data)
    
  • private subroutine savetxt_iint32(filename, d)

    Saves a 2D array into a text file.

    Arguments

    Arguments

    Type IntentOptional Attributes Name
    character(len=*), intent(in) :: filename
    integer(kind=int32), intent(in) :: d(:,:)

    Example


     integer(int32) :: data(3, 2)
     call savetxt("log.txt", data)
    
  • private subroutine savetxt_iint64(filename, d)

    Saves a 2D array into a text file.

    Arguments

    Arguments

    Type IntentOptional Attributes Name
    character(len=*), intent(in) :: filename
    integer(kind=int64), intent(in) :: d(:,:)

    Example


     integer(int64) :: data(3, 2)
     call savetxt("log.txt", data)
    
  • private subroutine savetxt_csp(filename, d)

    Saves a 2D array into a text file.

    Arguments

    Arguments

    Type IntentOptional Attributes Name
    character(len=*), intent(in) :: filename
    complex(kind=sp), intent(in) :: d(:,:)

    Example


     complex(sp) :: data(3, 2)
     call savetxt("log.txt", data)
    
  • private subroutine savetxt_cdp(filename, d)

    Saves a 2D array into a text file.

    Arguments

    Arguments

    Type IntentOptional Attributes Name
    character(len=*), intent(in) :: filename
    complex(kind=dp), intent(in) :: d(:,:)

    Example


     complex(dp) :: data(3, 2)
     call savetxt("log.txt", data)
    

Functions

public function open(filename, mode, iostat) result(u)

License
Creative Commons License
Version
experimental

Opens a file (Specification)

Read more…

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: filename
character(len=*), intent(in), optional :: mode
integer, intent(out), optional :: iostat

Return Value integer

public function parse_mode(mode) result(mode_)

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: mode

Return Value character(len=3)