Intel® Fortran Compiler
Build applications that can scale for the future with optimized code designed for Intel® Xeon® and compatible processors.

Abstract Derived Type I/O

Ian_P_
Beginner
405 Views

Is it not possible to write an abstract derived type I/O read and write procedure and then over-write it with an extension of the type? I'm running into error #8638: the type/rank signature for arguments of this specific subroutine is identical to another specific subroutine that shares the same defined I/O.

 

MODULE derived_io_test
    IMPLICIT NONE

    PRIVATE
    PUBLIC :: type1

    TYPE, ABSTRACT :: type1
        PRIVATE
        INTEGER, PUBLIC :: n_points = 1
    CONTAINS
        PROCEDURE(abs_read_form),  DEFERRED, PRIVATE :: read_form
        PROCEDURE(abs_write_form), DEFERRED, PRIVATE :: write_form
        GENERIC, PUBLIC :: READ  (FORMATTED) => read_form
        GENERIC, PUBLIC :: WRITE (FORMATTED) => write_form
    END TYPE type1

    CONTAINS

        SUBROUTINE abs_read_form (me, unit, iotype, v_list, iostat, iomsg)
        !>@brief
        !> Writes the dataset information from the .vtk file
        CLASS(type1),          INTENT(INOUT) :: me
        INTEGER,               INTENT(IN)    :: unit
        INTEGER,               INTENT(OUT)   :: iostat
        CHARACTER(LEN=*),      INTENT(IN)    :: iotype
        CHARACTER(LEN=*),      INTENT(INOUT) :: iomsg
        INTEGER, DIMENSION(:), INTENT(IN)    :: v_list

        END SUBROUTINE abs_read_form

        SUBROUTINE abs_write_form (me, unit, iotype, v_list, iostat, iomsg)
        !>@brief
        !> Writes the dataset information from the .vtk file
        CLASS(type1),          INTENT(IN)    :: me
        INTEGER,               INTENT(IN)    :: unit
        INTEGER,               INTENT(OUT)   :: iostat
        CHARACTER(LEN=*),      INTENT(IN)    :: iotype
        CHARACTER(LEN=*),      INTENT(INOUT) :: iomsg
        INTEGER, DIMENSION(:), INTENT(IN)    :: v_list

        END SUBROUTINE abs_write_form

    END MODULE derived_io_test

MODULE derived_io_extension
    USE derived_io_test, ONLY : type1

    TYPE, EXTENDS(type1) :: type2
        PRIVATE
    CONTAINS
        PROCEDURE, PRIVATE :: read_form   => type2_read_form
        PROCEDURE, PRIVATE :: write_form  => type2_write_form
        GENERIC, PUBLIC :: READ  (FORMATTED) => read_form
        GENERIC, PUBLIC :: WRITE (FORMATTED) => write_form
    END TYPE type2

    CONTAINS

        SUBROUTINE type2_read_form (me, unit, iotype, v_list, iostat, iomsg)
        !>@brief
        !> Writes the dataset information from the .vtk file
        CLASS(type2),          INTENT(INOUT) :: me
        INTEGER,               INTENT(IN)    :: unit
        INTEGER,               INTENT(OUT)   :: iostat
        CHARACTER(LEN=*),      INTENT(IN)    :: iotype
        CHARACTER(LEN=*),      INTENT(INOUT) :: iomsg
        INTEGER, DIMENSION(:), INTENT(IN)    :: v_list

        END SUBROUTINE type2_read_form

        SUBROUTINE type2_write_form (me, unit, iotype, v_list, iostat, iomsg)
        !>@brief
        !> Writes the dataset information from the .vtk file
        CLASS(type2),          INTENT(IN)    :: me
        INTEGER,               INTENT(IN)    :: unit
        INTEGER,               INTENT(OUT)   :: iostat
        CHARACTER(LEN=*),      INTENT(IN)    :: iotype
        CHARACTER(LEN=*),      INTENT(INOUT) :: iomsg
        INTEGER, DIMENSION(:), INTENT(IN)    :: v_list

        END SUBROUTINE type2_write_form
END MODULE derived_io_extension

 

0 Kudos
5 Replies
FortranFan
Honored Contributor II
405 Views

@Ian P.,

A couple of problems with the code you show:

1) Note the accessibility of derived type components and procedure bindings is with respect to the MODULE, not the derived type.  So you cannot provide a binding for DEFERRED procedure with PRIVATE attribute of an ABSTRACT type if the extended type is in another module,  In your example code,

  • you will need to either make the deferred defined I/O bindings have the PUBLIC attribute, or
  • make the extended types part of the same module as the abstract one.

2) Once you have established a GENERIC binding with a procedure in a type - deferred or otherwise - you don't need to repeat it in the extension of that type.  The GENERIC bindings on lines 53 and 54 are superfluous.

See a recent thread on a similar aspect where I have completely "lost my cool'" because of where things stand with support for OO based approaches in Fortran:

https://software.intel.com/en-us/forums/intel-visual-fortran-compiler-for-windows/topic/754000

0 Kudos
Ian_P_
Beginner
405 Views

@FortranFan, Thanks! The code now compiles but I'm running into an issue regardless of how I implement your changes outlined in #1 (making PUBLIC or put into same module). It will only call the abstract's READ/WRITE statements, not the extended type's read/write statements(I put in a simple print statement to check which one it was calling). I don't have this problem with user-defined operators (Such as:

GENERIC, PUBLIC :: OPERATOR(+) => add_two_vals

I only have this issue with read/write statements. Any further suggestions?

Updated code:

MODULE derived_io
    IMPLICIT NONE

    PRIVATE
    PUBLIC :: type1, type2

    TYPE, ABSTRACT :: type1
        PRIVATE
        INTEGER, PUBLIC :: n_points = 1
    CONTAINS
        PROCEDURE(abs_read_form),  DEFERRED, PRIVATE :: read_form
        PROCEDURE(abs_write_form), DEFERRED, PRIVATE :: write_form
        GENERIC, PUBLIC :: READ  (FORMATTED) => read_form
        GENERIC, PUBLIC :: WRITE (FORMATTED) => write_form
    END TYPE type1

    TYPE, EXTENDS(type1) :: type2
        PRIVATE
    CONTAINS
        PROCEDURE, PRIVATE :: read_form  => type2_read_form
        PROCEDURE, PRIVATE :: write_form => type2_write_form
!        GENERIC, PUBLIC :: READ  (FORMATTED) => read_form
!        GENERIC, PUBLIC :: WRITE (FORMATTED) => write_form
    END TYPE type2

    CONTAINS

        SUBROUTINE abs_read_form (me, unit, iotype, v_list, iostat, iomsg)
        !>@brief
        !> Writes the dataset information from the .vtk file
        CLASS(type1),          INTENT(INOUT) :: me
        INTEGER,               INTENT(IN)    :: unit
        INTEGER,               INTENT(OUT)   :: iostat
        CHARACTER(LEN=*),      INTENT(IN)    :: iotype
        CHARACTER(LEN=*),      INTENT(INOUT) :: iomsg
        INTEGER, DIMENSION(:), INTENT(IN)    :: v_list

        END SUBROUTINE abs_read_form

        SUBROUTINE abs_write_form (me, unit, iotype, v_list, iostat, iomsg)
        !>@brief
        !> Writes the dataset information from the .vtk file
        CLASS(type1),          INTENT(IN)    :: me
        INTEGER,               INTENT(IN)    :: unit
        INTEGER,               INTENT(OUT)   :: iostat
        CHARACTER(LEN=*),      INTENT(IN)    :: iotype
        CHARACTER(LEN=*),      INTENT(INOUT) :: iomsg
        INTEGER, DIMENSION(:), INTENT(IN)    :: v_list

        PRINT *, 'HI FROM ABS_WRITE_FORM'

        END SUBROUTINE abs_write_form

        SUBROUTINE type2_read_form (me, unit, iotype, v_list, iostat, iomsg)
        !>@brief
        !> Writes the dataset information from the .vtk file
        CLASS(type2),          INTENT(INOUT) :: me
        INTEGER,               INTENT(IN)    :: unit
        INTEGER,               INTENT(OUT)   :: iostat
        CHARACTER(LEN=*),      INTENT(IN)    :: iotype
        CHARACTER(LEN=*),      INTENT(INOUT) :: iomsg
        INTEGER, DIMENSION(:), INTENT(IN)    :: v_list

        END SUBROUTINE type2_read_form

        SUBROUTINE type2_write_form (me, unit, iotype, v_list, iostat, iomsg)
        !>@brief
        !> Writes the dataset information from the .vtk file
        CLASS(type2),          INTENT(IN)    :: me
        INTEGER,               INTENT(IN)    :: unit
        INTEGER,               INTENT(OUT)   :: iostat
        CHARACTER(LEN=*),      INTENT(IN)    :: iotype
        CHARACTER(LEN=*),      INTENT(INOUT) :: iomsg
        INTEGER, DIMENSION(:), INTENT(IN)    :: v_list

        print *, 'HI FROM TYPE2_WRITE_FORM'

        END SUBROUTINE type2_write_form
END MODULE derived_io

PROGRAM scratch
    USE derived_io, ONLY : type1, type2
    IMPLICIT NONE

    CLASS(type1), ALLOCATABLE :: test_abs
    TYPE(type2) :: test_type_2

    ALLOCATE(type2::test_abs)

    OPEN(unit=8,file='test.txt',form='formatted')

    WRITE(unit=8,FMT='(DT)') test_abs
    WRITE(unit=8,FMT='(DT)') test_type_2

END PROGRAM scratch

 

0 Kudos
FortranFan
Honored Contributor II
405 Views

Ian P. wrote:

.. I only have this issue with read/write statements. Any further suggestions? ..

@Ian P.,

You're now running into a bug in Intel Fortran, I suggest you submit a support incident at the Intel Online Service Center:

https://supporttickets.intel.com/?lang=en-US 

0 Kudos
FortranFan
Honored Contributor II
405 Views

By the way, there is another bug in Intel Fortran where your need to include defined I/O in an ABSTRACT type does NOT work, unfortunately.

Also, I assume you're using Intel Fortran 18.0 compiler (otherwise PUBLIC attribute on a GENERIC binding for defined I/O won't work either).

Under the circumstances, it appears the best you can do with Intel Fortran is defined I/O with a derived type that is not an extension type of an type with the ABSTRACT attribute.

 

 

0 Kudos
Ian_P_
Beginner
405 Views

@FortranFan,

Thanks for your help - I submitted (or at least hope I did) this as a bug with Intel Fortran 2018 Patch 1.

Note: I tested this with Intel 2018 Patch 1 for Windows & Linux and they both provide the error. I tested with gfortran 8.0.0 20171020(experimental) and it produces the correct result.

0 Kudos
Reply