Introduction

This is the fourth part of a series of articles that explore Object-Oriented Programming (OOP) in Fortran 2003 (F2003). The first installment introduced the OOP paradigm and three important features to OOP: inheritance, polymorphism, and information hiding. Part two covered data polymorphism, which deals with program variables that can store and operate on a variety of data types and values. Part three introduced parameterized derived types which allow the programmer to create derived types that take one or more values, known as parameters, to specify characteristics of the data encapsulated by the derived type.

In this installment, we discuss User-Defined Derived Type Input/Output (UDTIO). UDTIO allows the programmer to specify how a derived type is read (or written) from (or to) a file. One of the main purposes for providing UDTIO is so the user of an object can perform Input/Output (I/O) operations without any knowledge of the object's layout. For example, the derived type may have private components which are not directly accessible with traditional I/O operations:

module my_mod
type t
   integer :: x
   integer, private :: y
end type t
end module my_mod
program prg1
use my_mod
type(t) :: obj
write(*,*) obj   ! Illegal due to private y
end

Compiling the above example produces the following compilation error message:

		
% pgfortran -c prg1.f90
PGF90-S-0155-A derived type containing private components cannot be 
an I/O item  (prg1.f90: 12)
  0 inform,   0 warnings,   1 severes, 0 fatal for MAIN

F2003 also does not allow I/O operations on entire objects that have pointer components. For example,

module my_mod
type t
   integer :: x
   integer,pointer :: y
end type
end module my_mod
program prg2
use my_mod
type(t) :: obj
write(*,*) obj    ! Illegal due to pointer y
end

Compiling the above example produces the following compilation error message:

% pgfortran -c prg2.f90
PGF90-S-0453-Derived type variable with pointer member not allowed 
in IO - obj  (prg2.f90: 12)
  0 inform,   0 warnings,   1 severes, 0 fatal for MAIN

As we discussed in part one of this series, information hiding allows programmers to use an object without any knowledge of its implementation details. As illustrated in the previous examples, information hiding is not available when performing traditional I/O on objects (e.g., write(*,*) obj) that have private or pointer components. To make the first example legal, the user could replace write(*,*) obj with write(*,*) obj%x. In the second example, the user could replace write(*,*) obj with write(*,*) obj%x, obj%y. However, we lose information hiding if we require the user to specify the components of an object in their I/O statement. UDTIO was introduced in F2003 to permit information hiding with I/O as well as provide a way to perform special formatting and/or handling of objects involved in I/O operations.

UDTIO Syntax

The programmer specifies UDTIO as one or more subroutines and interfaces in their program. Each subroutine and interface operates on one or more derived types defined in the program. There are four basic types of UDTIO subroutines that a programmer can specify:

  1. Formatted READ
  2. Formatted WRITE
  3. Unformatted READ
  4. Unformatted WRITE

The Formatted/Unformatted UDTIO versions of READ/WRITE operate the same way as their Traditional I/O counterparts. That is, Formatted READ operations convert characters of data into their internal binary representation when they are read from a file. Formatted WRITE operations convert the internal binary representation of the data into characters before writing them to a file. Unformatted I/O performs no conversion between characters and their internal binary representation.

The Formatted READ and WRITE operations work with both explicit and implicit I/O formatting (i.e., I/O operations that use a dt edit descriptor, list-directed formatting, and namelist formatting). You can think of the dt edit descriptor as a way to pass in explicit formatting information to the UDTIO subroutine. The dt edit descriptor is a character object that takes the following form:

dt 'optional-string' (optional-comma-separated-list-of-integers)

An example of a dt edit descriptor used in formatting real numbers follows:

dt 'width.decimal-places' (0, 6)

The optional-string can be anything you want. The programmer may also omit the string and/or the integer list provided that the UDTIO subroutine knows what to do with it:

dt (0, 6)         ! omitted string
dt 'format-this'  ! omitted integer list
dt                ! omitted string and integer list

As its name implies, Unformatted I/O does not support any explicit or implicit I/O formatting. To add UDTIO to a derived type, the programmer first creates a UDTIO subroutine for one or more of the four basic types of I/O mentioned above. Each subroutine has a specific interface. Below summarizes each interface:

! Formatted READ:
subroutine read_formatted(dtv, unit, iotype, v_list, iostat, iomsg)   
! Formatted WRITE:
subroutine write_formatted(dtv, unit, iotype, v_list, iostat, iomsg)   
! Unformatted READ:
subroutine read_unformatted(dtv, unit, iotype, v_list, iostat, iomsg)  
! Unformatted WRITE:
subroutine write_unformatted(dtv, unit, iotype, v_list, iostat, iomsg) 

The subroutine name and dummy argument names can be any legal identifier. However, each dummy argument must be declared with the following characteristics:

TYPE or CLASS (derived-type-spec), INTENT(INOUT or IN) :: dtv

For a READ operation, dtv corresponds to the derived-type object that triggered execution of the UDTIO subroutine. For READ operations, the dtv argument must be declared INTENT(INOUT).

For WRITE operations, dtv holds the derived-type value to be written and must be declared INTENT(IN).

The programmer should also declare dtv with the CLASS keyword if dtv's type is extensible.

INTEGER, INTENT(IN) :: unit

I/O statements refer to a particular file by specifying an I/O unit. An I/O unit is either a positive integer to indicate an external file or a negative integer to indicate an internal file. The unit argument holds the value of the I/O unit for the file associated with our I/O operation.

CHARACTER(LEN=*), INTENT(IN) :: iotype

The iotype argument is used with Formatted I/O. It is a character object that is used to pass in the type of formatting associated with the I/O operation. The values of the object may be 'LISTDIRECTED' to indicate list-directed formatting, 'NAMELIST' to indicate namelist formatting, or 'DT'//string, where string is the optional-string associated with the dt edit descriptor.

INTEGER, INTENT(IN) :: v_list(:)

The v_list argument is used with Formatted I/O. It is a rank one assumed shape array that holds the integer values found in the integer list of the dt edit descriptor. The v_list array has zero size if the calling routine omits the integer list from the dt edit descriptor.

INTEGER, INTENT(OUT) :: iostat

The iostat argument is used to return a positive integer if an error condition occurs. If an end-of-file condition occurs, iostat should return the value iostat_end defined in the iso_fortran_env module. If an end-of-record condition occurs, then iostat should return the value iostat_eor defined in the iso_fortran_env module. If no error condition occurs, then iostat returns 0.

CHARACTER(LEN=*), INTENT(INOUT) :: iomsg

If an error condition occurs, then iomsg returns a descriptive error message string.

After creating the UDTIO subroutine(s), the programmer adds an interface for each UDTIO subroutine. The programmer may use generic interface blocks or generic type bound procedures for this step.

The following examples illustrate the use of generic interface blocks. Note that each procedure in the generic interface correspond to a UDTIO subroutine of one of the four basic types mentioned above.

interface write(formatted)
   module procedure write_fraction
   module procedure write_stack_top
end interface write(formatted)
interface read(formatted)
   module procedure read_fraction
   module procedure read_stack
end interface read(formatted)
interface write(unformatted)
   module procedure write_raw_data
end interface write(unformatted)
interface read(unformatted)
   module procedure read_raw_data
end interface read(unformatted)

The following examples illustrate the use of generic type bound procedures:

type :: fraction
   integer, private :: numerator, denominator
   contains
   procedure, private :: read_fraction
   procedure, private :: write_fraction
   procedure, private :: read_raw_data
   procedure, private :: write_raw_data
   generic :: read(formatted) => read_fraction
   generic :: write(formatted) => write_fraction
   generic :: read(unformatted) => read_raw_data
   generic :: write(unformatted) => write_raw_data
end type fraction

Similar to generic interfaces, the specific type bound procedures (e.g., read_fraction, write_fraction, read_raw_data, write_raw_data) are UDTIO subroutines.

Case Study 1: Formatted I/O

We will now take a closer look at the fraction example introduced in the previous section. In particular, we will create a fraction object that can read and write formatted fractional values (we will look at unformatted I/O in the next section).

We will first create our UDTIO subroutines and enclose them in a module called fraction_mod. Below is our input subroutine:

 subroutine read_fraction(dtv, unit, iotype, v_list, iostat, iomsg)
	class(fraction), intent(inout) :: dtv
	integer, intent(in) :: unit
	character(len=*), intent(in) :: iotype
	integer, intent(in) :: v_list(:)
	integer, intent(out) :: iostat
	character(len=*), intent(inout) :: iomsg
	character(len=1024) ::buffer
	! Read numerator and denominator via list-directed input
	if (iotype .eq. 'LISTDIRECTED') then
	  read(unit,*,IOSTAT=iostat,IOMSG=iomsg) dtv%numerator
	  read(unit,*,IOSTAT=iostat,IOMSG=iomsg) dtv%denominator
	else
	   ! Error
	   iostat = 1
	   iomsg = 'read_fraction: Unsupported iotype'
	endif
  end subroutine read_fraction

The above input subroutine initializes the numerator and denominator private components in a fraction object. For simplicity, we assume list-directed input. If the caller of the subroutine attempts to use namelist input or explicit formatting, we issue an error. Note that information hiding is preserved for both numerator and denominator because they are not directly accessible by the user of the object.

Next, we add our write subroutine. For our write subroutine, we will support list-directed output, namelist output, and explicit formatted output. We will support two basic types of explicit formatting with the dt edit descriptor. The user can specify 'DTfraction' to print the number as a fraction (e.g., if numerator is 2 and denominator is 3, we print 2 / 3) or 'DTdecimal' to print the number as a decimal (e.g., if numerator is 2 and denominator is 3, we print 0.6666667). In addition to specifying fraction or decimal formatting, we can use the dt edit descriptor's integer-list to specify the output width and number of digits or decimal places. For example,

'DTfraction(w,d)'—The first integer, w, specifies the width of the number and the second integer, d, specifies the number of digits to print.

'DTdecimal(w,d)'—The first integer, w, specifies the width of the number and the second integer, d, specifies the number of decimal places to print.

'DT(w,d)'—Same as 'DTdecimal(w,d)'.

Below is our write subroutine:

  subroutine write_fraction(dtv, unit, iotype, v_list, iostat, iomsg)
    class(fraction), intent(in) :: dtv
    integer, intent(in) :: unit
    character(len=*), intent(in) :: iotype
    integer, intent(in) :: v_list(:)
    integer, intent(out) :: iostat
    character(len=*), intent(inout) :: iomsg
    character(len=80) :: buffer
    ! Write fraction using formatted output
    if (iotype .eq. 'LISTDIRECTED' .or. iotype .eq.&
        &'NAMELIST') then
       ! default formatting (list-directed or namelist)
       write(unit,'(I, A, I)',IOSTAT=iostat,IOMSG=iomsg)&
            &dtv%numerator,'/',dtv%denominator
    else if (iotype .eq. 'DT' .or. iotype .eq. 'DTdecimal') then
       if (size(v_list) .eq. 0) then
          ! default DT edit descriptor
          write(unit,'(F)',IOSTAT=iostat,IOMSG=iomsg)&
               &real(dtv%numerator)/real(dtv%denominator)
       else if (size(v_list) .eq. 2) then
          ! default DT/decimalDT edit descriptor formatted
          write(buffer,"(A2,I2,A1,I2,A1)") '(F',v_list(1),'.',&
               &v_list(2),")"
          write(unit,trim(buffer),IOSTAT=iostat,IOMSG=iomsg)&
               &real(dtv%numerator,kind=8)/real(dtv%denominator,kind=8)
       else
          ! Error
          iostat = 1
          iomsg = 'write_fraction: integer-list for DT edit'&
               &//'descriptor must contain two integers'
       endif
    else if (iotype .eq. 'DTfraction') then
       if (size(v_list) .eq. 0) then
          ! default DTfraction edit descriptor
          write(unit,'(I, A, I)',IOSTAT=iostat,IOMSG=iomsg)&
               &dtv%numerator,'/',dtv%denominator
       else if (size(v_list) .eq. 2) then
          ! default DT edit descriptor formatted
          write(buffer,"(A2,I2,A1,I2,A3,I2,A1,I2,A1)") &
               &'(I',v_list(1),'.',&
               &v_list(2),'A1I',v_list(1),'.',&
               &v_list(2),')'
          write(unit,trim(buffer),IOSTAT=iostat,IOMSG=iomsg)&
               dtv%numerator,'/',dtv%denominator
       else
          ! Error
          iostat = 1
          iomsg = 'write_fraction: integer-list for DT edit'&
               &//'descriptor must contain two integers'
       endif
    else
       ! Error
       iostat = 1
       iomsg = 'write_fraction: Unexpected iotype'
    endif
  end subroutine write_fraction

Our write subroutine supports all of the available formatting types (i.e., list-directed, namelist, and explicit formatting). If our subroutine is called with a 'DTfraction(w,d)' or 'DTdecimal(w,d)' edit descriptor, we build an appropriate format string using the v_list array argument and a write statement on a character object called buffer. Otherwise, the output uses default formatting for both integer and real numbers.

The next step is to add our UDTIO interfaces. For this example, we will use generic type bound procedures.

type :: fraction
   integer, private :: numerator, denominator
   contains
   procedure, private :: read_fraction
   procedure, private :: write_fraction
  generic :: read(formatted) => read_fraction
  generic :: write(formatted) => write_fraction
end type fraction

Below is a sample program that uses our fraction_mod module along with the output. You can also download the complete program from the PGI website.

program fractions
  use fraction_mod
  type(fraction) :: f
  character(len=80) :: iomsg
  integer :: iostat
  namelist /fraction_namelist/ f
  write(*,*) 'Please enter the numerator and denominator of the fraction'
  read(*,*,err=99,iomsg=iomsg,iostat=iostat) f
  write(*,*)
  write(*,"(A,DT)",err=99,iomsg=iomsg,iostat=iostat) 'The default DT: ',f
  write(*,"(A,DT(30,16))",err=99,iomsg=iomsg,iostat=iostat) &
	   &'The formatted DT(30,16): ',f
  write(*,"(A,DT'fraction')",err=99,iomsg=iomsg,iostat=iostat) &
	   &'The default fraction: ',f
  write(*,"(A,DT'fraction'(2,2))",err=99,iomsg=iomsg,iostat=iostat) &
	   &'The formatted fraction(2,2): ',f
  write(*,"(A,DT'decimal')",err=99,iomsg=iomsg,iostat=iostat) &
	   &'The default decimal: ',f
  write(*,"(A,DT'decimal'(10,4))",err=99,iomsg=iomsg,iostat=iostat) &
	   &'The formatted decimal(10,4): ',f
  write(*,*) 'The fraction namelist: '
  write(*,nml=fraction_namelist)
  ! Error Handling
99 if (iostat .eq. 0) then
	 continue
  else
	 write(*,*) iomsg
  endif
end program fractions

Below is the output from our program:

% pgfortran fraction.f90
% ./a.out
 Please enter the numerator and denominator of the fraction
2 3
The default DT:       0.6666667

The formatted DT(30,16):             0.6666666666666666

The default fraction:            2/           3

The formatted fraction(2,2): 02/03

The default decimal:       0.6666667

The formatted decimal(10,4):     0.6667

 The fraction namelist:
 &FRACTION_NAMELIST
 F =            2/           3

 /

Case Study 2: Unformatted I/O

For this case study, we will use a stack to demonstrate the Unformatted I/O variants of UDTIO. A stack is essentially a list of elements that are accessed in a last-in-first-out (LIFO) manner. Elements can only be added and removed from the front (or top) of the stack. Therefore, an element removed from a stack is the element held for the least amount of time.

Our program will add ten integers, one through ten, to the stack. Using UDTIO, we will remove each number from the stack and write it to a file. Next, we will read all of the numbers from the file back into our stack before printing them out again.

The first step in our design is to create our stack object. We first begin with a base type called stack. We make stack an abstract type so we can specify basic requirements of any type extensions to stack. Below is our stack type definition:

  type, abstract :: stack
     private
     class(*), allocatable :: item           ! an item on the stack
     class(stack), pointer :: next=>null()   ! next item on the stack
   contains
     procedure :: empty                      ! returns true if stack is empty
  end type stack

The underlying data type for each item on our stack is unlimited polymorphic. This allows us to create stacks for any Fortran type. For this case study, we will create a type extension that operates on integers called integer_stack. Below is our integer_stack type definition:

type, extends(stack) :: integer_stack
contains
  procedure :: push => push_integer ! add integer item onto stack
  procedure :: pop => pop_integer  ! remove integer item from top of stack
end type integer_stack

The integer_stack inherits all of the components in stack and adds two type bound procedures: push and pop. The push type bound procedure is used to add an integer to the top of the stack and the pop type bound procedure is used to remove an integer from the top of the stack.

Next, we will create a type extension of integer_stack called io_stack:

type, extends(integer_stack) :: io_stack
contains
  procedure,private :: wio_stack
  procedure,private :: rio_stack
  procedure,private :: dump_stack
  generic :: write(unformatted) => wio_stack ! write stack item to file
  generic :: read(unformatted) => rio_stack  ! push item from file
  generic :: write(formatted) => dump_stack  ! print all items from stack
end type io_stack

The io_stack type inherits all components from stack and integer_stack. It also implements three UDTIO subroutines: write(unformatted), read(unformatted), and write(formatted).

Below is our write(unformatted) implementation:

  subroutine wio_stack(dtv, unit, iostat, iomsg)
    ! pop an item from stack and write it to file
    class(io_stack), intent(inout) :: dtv
    integer, intent(in) :: unit
    integer, intent(out) :: iostat
    character(len=*), intent(inout) :: iomsg
    integer :: item

    item = dtv%pop()
    write(unit,IOSTAT=iostat,IOMSG=iomsg), item
  end subroutine wio_stack

The wio_stack subroutine implements our unformatted write UDTIO subroutine. It removes the first integer item off the stack and writes it to the file associated with unit.

Below is our read(unformatted) implementation:

subroutine rio_stack (dtv, unit, iostat, iomsg)
    ! read item from file and add it to stack
    class(io_stack), intent(inout) :: dtv
    integer, intent(in) :: unit
    integer, intent(out) :: iostat
    character(len=*), intent(inout) :: iomsg
    integer :: item

    read(unit,IOSTAT=iostat,IOMSG=iomsg), item
    if (.not. iostat) then
      call dtv%push(item)
    endif
  end subroutine rio_stack

The rio_stack subroutine implements our unformatted read UDTIO subroutine. It reads an integer item from the file associated with unit and adds it to the top of the stack.

Below is our write(formatted) implementation:

subroutine dump_stack(dtv, unit, iotype, v_list, iostat, iomsg)
    ! Pop all items off stack and write them out to unit
    ! Assumes default LISTDIRECTED output
    class(io_stack), intent(in) :: dtv
    integer, intent(in) :: unit
    character(len=*), intent(in) :: iotype
    integer, intent(in) :: v_list(:)
    integer, intent(out) :: iostat
    character(len=*), intent(inout) :: iomsg
    character(len=80) :: buffer
    integer :: item

    if (iotype .ne. 'LISTDIRECTED') then
       ! Error
       iomsg = 'dump_stack: unsupported iotype'
       iostat = 1
    else
       iostat = 0
       do while( (.not. dtv%empty()) .and. (.not. iostat) )
          item = dtv%pop()
          write(unit, '(I)',IOSTAT=iostat,IOMSG=iomsg) item
       enddo
    endif
  end subroutine dump_stack

The dump_stack subroutine implements our formatted write UDTIO subroutine. It removes each integer item off the stack and prints them to the file associated with unit.

Below is an example program that uses our io_stack type defined above. You can download this complete program from the PGI website as well.

program stack_demo
  use stack_mod
  implicit none
  integer i
  type(io_stack) :: stk

  ! step 1: set up an 'output' file
  open(10, file='stack.dat', status='replace', form='unformatted')
  ! step 2: add values to stack
  do i=1,10
     write(*,*) 'Adding ',i,' to the stack'
     call stk%push(i)
  enddo
  ! step 3: pop values from stack and write them to file
  write(*,*)
  write(*,*) 'Removing each item from stack and writing it to file.'
  write(*,*)
  do while(.not.stk%empty())
     write(10), stk
  enddo
  ! step 4: close file and reopen it for read
  close(10)
  open(10, file='stack.dat', status='old', form='unformatted')
  ! step 5: read values back into stack
  write(*,*) 'Reading each value from file and adding it to stack:'
  do while(.true.)
     read(10,END=9999) i
     write(*,*), 'Reading ',i,' from file. Adding it to stack'
     call stk%push(i)
  enddo
9999 continue
  ! step 6: Dump stack to standard out

  write(*,*)
  write(*,*), 'Removing every element from stack and writing it to screen:'
  write(*,*) stk
  close(10)
end program stack_demo

Below is an example compile and run of our stack_demo program:

% pgfortran stack.f90
% ./a.out
 Adding             1  to the stack
 Adding             2  to the stack
 Adding             3  to the stack
 Adding             4  to the stack
 Adding             5  to the stack
 Adding             6  to the stack
 Adding             7  to the stack
 Adding             8  to the stack
 Adding             9  to the stack
 Adding            10  to the stack
 
 Removing each item from stack and writing it to file.
 
 Reading each value from file and adding it to stack:
 Reading            10  from file. Adding it to stack
 Reading             9  from file. Adding it to stack
 Reading             8  from file. Adding it to stack
 Reading             7  from file. Adding it to stack
 Reading             6  from file. Adding it to stack
 Reading             5  from file. Adding it to stack
 Reading             4  from file. Adding it to stack
 Reading             3  from file. Adding it to stack
 Reading             2  from file. Adding it to stack
 Reading             1  from file. Adding it to stack
 
 Removing every element from stack and writing it to screen:
           1
           2
           3
           4
           5
           6
           7
           8
           9
          10

The above program first adds integers one through ten to our stack. Next, it invokes our unformatted write UDTIO subroutine to write each item to the stack.dat file until the stack is empty. The integers are written to the file in descending order due to the last-in-first-out behavior of a stack. We see this when we read the integers from the stack.dat file using our unformatted read UDTIO subroutine. Finally, we remove and print every integer item in our stack using our formatted write UDTIO subroutine.

Conclusion

User-Defined Derived Type Input/Output, or UDTIO, allows the programmer to specify how a derived type is read (or written) from (or to) a file. F2003 provides four basic types of UDTIO: formatted read, formatted write, unformatted read, and unformatted write.

One of the motivations for providing UDTIO in F2003 is to allow a user to perform Input/Output (I/O) operations on an object without any knowledge of the object's layout. In other words, UDTIO is required when we desire information hiding for derived types involved with I/O.

UDTIO also allows the implementer to add special processing of data during I/O operations. We demonstrated this in the first case study where we created UDTIO subroutines that support custom formatting of fractional numbers. We also demonstrated this in our second case study where we used read/write UDTIO subroutines to push/pop values onto/from a stack.

Acknowledgement

The author would like to thank Jerry DeLisle and Paul Richard Thomas for submitting corrections to the code examples in earlier versions of this article.

Click me
Cookie Consent

This site uses cookies to store information on your computer. See our cookie policy for further details on how to block cookies.

X