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

Information hiding in derived type

Blane_J_
New Contributor I
1,015 Views

Please take a look at the two simple module pairs as follows:

module test1
    implicit none
    
    private
    public :: tp1
    
    type, abstract :: tp1
        private
        ! <Nothing.>
    contains
        private
        procedure(isub), nopass, deferred :: sub
    end type tp1

    abstract interface
        subroutine isub(var)
            integer :: var
        end subroutine isub
    end interface
    
end module test1

module test2
    use test1, only: tp1
    implicit none
    
    private
    public :: tp2
    
    type, extends(tp1) :: tp2
        private
        integer :: t
    contains
        private
        procedure, nopass :: sub => mysub
    end type tp2
    
    contains

        subroutine mysub(var)
            integer :: var
            print*, var
        end subroutine mysub

end module test2

================================================

module test3
    implicit none
    
    private
    public :: tp3
    
    type, abstract :: tp3
        private
        ! <Nothing.>
    contains
        private
        procedure(ifunc), nopass, deferred :: ifunc
    end type tp3

    abstract interface
        function ifunc(var)
            integer :: ifunc
            integer :: var
        end function ifunc
    end interface
    
end module test3

module test4
    use test3, only: tp3
    implicit none
    
    private
    public :: tp4
    
    type, extends(tp3) :: tp4
        private
        integer :: t
    contains
        private
        procedure, nopass :: func => myfunc
    end type tp4
    
    contains

        function myfunc(var)
            integer :: myfunc
            integer :: var
            myfunc = var
        end function myfunc

end module test4

The only difference between the upper pair(test1 & test2) and the lower(test3 & test4) is the type-bound procedure: tp1 & tp2 has the subroutine while tp3 & tp4 has the function. The problem is the upper pair can be compiled without any warning or error but the lower cannot, the compiler says for the lower:

error #8322: A deferred binding is inherited by non-abstract type; It must be overridden.   [IFUNC]

Notice that PRIVATE statement is set for all the CONTAINS block of the derived types(tp1& tp2 & tp3 & tp4), so why subroutine can override while function cannot ?

0 Kudos
1 Solution
Blane_J_
New Contributor I
1,015 Views

FortranFan wrote:

Quote:

Blane J. wrote:

 

..The listdirected and DT-formed input and output (indicate by comment line 2,3,4,5 and 7.8.9.10) still generate the same error message I presented previously, but comment line 1 and 6 are just OK.

 

 

It looks to me like a bug in the Intel Fortran compiler, your code is alright.

Yes, I think so. I've reported this failure to OSC and wait for replies.

View solution in original post

0 Kudos
15 Replies
Arjen_Markus
Honored Contributor I
1,015 Views

I have not tried it, but in tp4 you define a function func, not ifunc. So the ifunc entry inherited from tp3 is not satisfied.

0 Kudos
IanH
Honored Contributor II
1,015 Views

Note also, that in the subroutine case (where the binding names are the same) an error should also be reported - a private binding effectively cannot be overridden outside of the module that defines the type with the private binding.  This behaviour has been discussed on the forums in the last year or two - the specified behaviour resulted in-part from a language interp, and it is possible compiler may not have caught up with the results of that interp and subsequent bug reports yet.
 

0 Kudos
Blane_J_
New Contributor I
1,015 Views

Arjen Markus wrote:

I have not tried it, but in tp4 you define a function func, not ifunc. So the ifunc entry inherited from tp3 is not satisfied.

The procedure name in tp3 is a mistake, it should be func, thanks Arjen Markus. correct it but the problem still exist...

0 Kudos
Blane_J_
New Contributor I
1,015 Views

ianh wrote:

Note also, that in the subroutine case (where the binding names are the same) an error should also be reported - a private binding effectively cannot be overridden outside of the module that defines the type with the private binding.  This behaviour has been discussed on the forums in the last year or two - the specified behaviour resulted in-part from a language interp, and it is possible compiler may not have caught up with the results of that interp and subsequent bug reports yet.
 

Yes, lanH, there's something more I would wonder. In the subroutine case, if the PRIVATE keyword in tp1 is an attribute as:

        procedure(isub), private, nopass, deferred :: sub

rather than a statement, the compiler can recognize the error and report:

error #8322: A deferred binding is inherited by non-abstract type; It must be overridden.  

further more, If the PRIVATE statement in tp1 remains, but the PRIVATE in tp2 is omitted(which means all the type-bound procedures in tp2 is PUBLIC), the subroutine case can be compiled as well. Private bindings in abstract type would never be override, so I wonder if the DEFERRED attribute impilies PUBLIC attribute for the specified procedure regradless of PRIVATE statement ?

 

 

 

0 Kudos
IanH
Honored Contributor II
1,015 Views

Blane J. wrote:

Yes, lanH, there's something more I would wonder. In the subroutine case, if the PRIVATE keyword in tp1 is an attribute as:

        procedure(isub), private, nopass, deferred :: sub

rather than a statement, the compiler can recognize the error and report:

error #8322: A deferred binding is inherited by non-abstract type; It must be overridden.  

further more, If the PRIVATE statement in tp1 remains, but the PRIVATE in tp2 is omitted(which means all the type-bound procedures in tp2 is PUBLIC), the subroutine case can be compiled as well. Private bindings in abstract type would never be override, so I wonder if the DEFERRED attribute impilies PUBLIC attribute for the specified procedure regradless of PRIVATE statement ?

If you are seeing a difference based on whether PRIVATE for a bindings is explicitly specified for the binding or based on the default accessibility for bindings of the type, then that would be a compiler bug.

Private bindings can be overridden within the module (or its submodule descendants) that defines the type, they just cannot be overridden outside of the defining module.

0 Kudos
Blane_J_
New Contributor I
1,015 Views

I think so, may someone from Intel can see this.

0 Kudos
FortranFan
Honored Contributor II
1,015 Views

@Blane  J.,

I think there are one or more issues with Intel Fortran compiler for which you can submit incidents at the Intel's Online Service Center (OSC): https://supporttickets.intel.com/?lang=en-US in addition to a possible typo in one line of your code:

  • On line 12 of your second example involving a FUNCTION scenario, did you mean a DEFERRED PROCEDURE of 'func' instead of 'func' i.e., "procedure(ifunc), nopass, deferred :: func"?
  • See this thread: https://software.intel.com/en-us/forums/intel-fortran-compiler-for-linux-and-mac-os-x/topic/681705. 

Perhaps Intel Fortran team can update readers here on the status of the implementation of the findings from interp F08/0052

0 Kudos
Blane_J_
New Contributor I
1,015 Views

FortranFan wrote:

@Blane  J.,

I think there are one or more issues with Intel Fortran compiler for which you can submit incidents at the Intel's Online Service Center (OSC): https://supporttickets.intel.com/?lang=en-US in addition to a possible typo in one line of your code:

Perhaps Intel Fortran team can update readers here on the status of the implementation of the findings from interp F08/0052

For the first issue, yes, it is a mistake as I mentioned in Quote #4.

For the second, I have read about the thread and it has the question and discuession I'm just confusing. Unfortunately it seems the problem has not been fixed yet, thanks FortranFan.

0 Kudos
Blane_J_
New Contributor I
1,015 Views

In addition, I'd like to ask if the generic binding which bind user-defined I/O procedures cannot be inherited ?

module test1
    implicit none
    
    private
    public :: tp1
    
    type, abstract :: tp1
        private
        ! <Nothing.>
    contains
        private
        generic,                      public                 :: write(unformatted) => unformattedwrite
        procedure(iunformattedwrite), public, pass, deferred ::                       unformattedwrite
    end type tp1

    abstract interface
    
        subroutine iunformattedwrite (var,unit,iostat,iomsg)
            import tp1
            class(tp1),  intent(in)    :: var
            integer,     intent(in)    :: unit
            integer,     intent(out)   :: iostat
            character(*),intent(inout) :: iomsg
        end subroutine iunformattedwrite
    
    end interface

end module test1

module test2
    use test1, only: tp1
    implicit none
    
    private
    public :: tp2
    
    type, extends(tp1) :: tp2
        private
        integer :: t
    contains
        private
        procedure, public, pass :: unformattedwrite => output
    end type tp2
    
    contains

        subroutine output (var,unit,iostat,iomsg)
            implicit none

            class(tp2),  intent(in)    :: var
            integer,     intent(in)    :: unit
            integer,     intent(out)   :: iostat
            character(*),intent(inout) :: iomsg

            write(unit, IOSTAT=iostat, IOMSG=iomsg) var % t

        end subroutine output

end module test2

program main
    use test2, only: tp2
    implicit none
    
    type(tp2) :: s
    
    write(*,*) s

end program main

tp1 has a generic unformatted output binding( write(unformatted) ), it refers to the public binding procedure(unformattedwrite) which is deferred and implemented concreate in the extended type tp2. Note tp1 and tp2 both have the unforamttedwrite procedure PUBLIC. If this is correct, tp2 should have inherited the generic binding from tp1 and output an instance of tp2 should be OK. but the compile time error message says:

error #5521: A derived-type object in an input/output list cannot have inaccessible components unless a suitable user-defined input/output procedure is available.

Is the generic binding not inherited or something else ?

0 Kudos
IanH
Honored Contributor II
1,015 Views

The list directed write statement in the main program is a formatted write statement.  The provided binding is only for unformatted writes.

("Formatted" means "formatted so humans can read it".  The format specification for the list directed write statement is `*`.  An unformatted write statement has no format specification, and produces "binary stuff" in the file that is generally not considered human readable.)

0 Kudos
jimdempseyatthecove
Honored Contributor III
1,015 Views

Try:

write(*,'(DT)') s

Jim Dempsey

0 Kudos
FortranFan
Honored Contributor II
1,015 Views

jimdempseyatthecove wrote:

Try:

write(*,'(DT)') s

Jim Dempsey

Jim,

What IanH in his own inimitable, cryptic style was informing the OP was to include a defined output procedure binding for WRITE(FORMATTED) that is missing in the derived type shown in Quote #10 and which will be needed whether it is "write(*,*) s" or "write(*,'(dt)') s" statements.

0 Kudos
Blane_J_
New Contributor I
1,015 Views

Thanks lanH, Jim and FortranFan. I see the clerical mistake. I then implemented all the input/output procedures in case of failure, show as below:

module test1
    implicit none
    
    private
    public :: tp1
    
    type, abstract :: tp1
        private
        ! <nothing.>
    contains
        private
        generic,                      public                 :: read(formatted)    => formattedread
        procedure(iformattedread),    public, pass, deferred ::                       formattedread
        
        generic,                      public                 :: read(unformatted)  => unformattedread
        procedure(iunformattedread),  public, pass, deferred ::                       unformattedread
                                                        
        generic,                      public                 :: write(formatted)   => formattedwrite
        procedure(iformattedwrite),   public, pass, deferred ::                       formattedwrite

        generic,                      public                 :: write(unformatted) => unformattedwrite
        procedure(iunformattedwrite), public, pass, deferred ::                       unformattedwrite
    end type tp1

    abstract interface

        subroutine iformattedread(var, unit, iotype, list, iostat, iomsg)
            import tp1
            class(tp1),                 intent(inout) :: var
            integer,                    intent(in)    :: unit
            character(*),               intent(in)    :: iotype
            integer,      dimension(:), intent(in)    :: list
            integer,                    intent(out)   :: iostat
            character(*),               intent(inout) :: iomsg
        end subroutine iformattedread

        subroutine iunformattedread(var, unit, iostat, iomsg)
            import tp1
            class(tp1),   intent(inout) :: var
            integer,      intent(in)    :: unit
            integer,      intent(out)   :: iostat
            character(*), intent(inout) :: iomsg
        end subroutine iunformattedread

        subroutine iformattedwrite(var, unit, iotype, list, iostat, iomsg)
            import tp1
            class(tp1),                 intent(in)    :: var
            integer,                    intent(in)    :: unit
            character(*),               intent(in)    :: iotype
            integer,      dimension(:), intent(in)    :: list
            integer,                    intent(out)   :: iostat
            character(*),               intent(inout) :: iomsg
        end subroutine iformattedwrite

        subroutine iunformattedwrite(var,unit,iostat,iomsg)
            import tp1
            class(tp1),   intent(in)    :: var
            integer,      intent(in)    :: unit
            integer,      intent(out)   :: iostat
            character(*), intent(inout) :: iomsg
        end subroutine iunformattedwrite
    
    end interface

end module test1

module test2
    use test1, only: tp1
    implicit none
    
    private
    public :: tp2
    
    type, extends(tp1) :: tp2
        private
        integer :: t
    contains
        private
        procedure, public, pass ::   formattedread  =>   formattedreadsub
        procedure, public, pass :: unformattedread  => unformattedreadsub
        procedure, public, pass ::   formattedwrite =>   formattedwritesub
        procedure, public, pass :: unformattedwrite => unformattedwritesub
    end type tp2
    
    contains

        subroutine formattedreadsub(var, unit, iotype, list, iostat, iomsg)
            implicit none

            class(tp2),                 intent(inout) :: var
            integer,                    intent(in)    :: unit
            character(*),               intent(in)    :: iotype
            integer,      dimension(:), intent(in)    :: list
            integer,                    intent(out)   :: iostat
            character(*),               intent(inout) :: iomsg

            if(iotype == 'listdirected' .or. iotype == 'dt')then
                read(unit, *, IOSTAT=iostat, IOMSG=iomsg) var % t
            end if

        end subroutine formattedreadsub

        subroutine unformattedreadsub(var, unit, iostat, iomsg)
            implicit none

            class(tp2),   intent(inout) :: var
            integer,      intent(in)    :: unit
            integer,      intent(out)   :: iostat
            character(*), intent(inout) :: iomsg

            read(unit, IOSTAT=iostat, IOMSG=iomsg) var % t

        end subroutine unformattedreadsub

        subroutine formattedwritesub(var, unit, iotype, list, iostat, iomsg)
            implicit none

            class(tp2),                 intent(in)    :: var
            integer,                    intent(in)    :: unit
            character(*),               intent(in)    :: iotype
            integer,      dimension(:), intent(in)    :: list
            integer,                    intent(out)   :: iostat
            character(*),               intent(inout) :: iomsg

            if(iotype == 'listdirected' .or. iotype == 'dt')then
                write(unit, *, IOSTAT=iostat, IOMSG=iomsg) var % t
            end if

        end subroutine formattedwritesub

        subroutine unformattedwritesub(var,unit,iostat,iomsg)
            implicit none

            class(tp2),   intent(in)    :: var
            integer,      intent(in)    :: unit
            integer,      intent(out)   :: iostat
            character(*), intent(inout) :: iomsg

            write(unit, IOSTAT=iostat, IOMSG=iomsg) var % t
        end subroutine unformattedwritesub

end module test2

program main
    use test2, only: tp2
    implicit none
    
    type(tp2) :: s
    
    open(unit=100, file="100.txt", form="unformatted", status = "replace")
    open(unit=101, file="101.txt", form="formatted",   status = "replace")
    write(100)        s ! <-- 1.

    write(*,*)        s ! <-- 2.
    write(*,"(DT)")   s ! <-- 3.
    write(101,*)      s ! <-- 4.
    write(101,"(DT)") s ! <-- 5.

    close(100)
    close(101)

    open(unit=100, file="100.txt", form="unformatted", status = "old")
    open(unit=101, file="101.txt", form="formatted",   status = "old")
    read(100)         s ! <-- 6.

    read(*,*)         s ! <-- 7.
    read(*,"(DT)")    s ! <-- 8.
    read(101,*)       s ! <-- 9.
    read(101,"(DT)")  s ! <-- 10.

    close(100)
    close(101)

end program main

Point me out if I'm wrong. The listdirected and DT-formed input and output (indicate by comment line 2,3,4,5 and 7.8.9.10) still generate the same error message I presented previously, but comment line 1 and 6 are just OK.

0 Kudos
FortranFan
Honored Contributor II
1,015 Views

Blane J. wrote:

..The listdirected and DT-formed input and output (indicate by comment line 2,3,4,5 and 7.8.9.10) still generate the same error message I presented previously, but comment line 1 and 6 are just OK.

It looks to me like a bug in the Intel Fortran compiler, your code is alright.

0 Kudos
Blane_J_
New Contributor I
1,016 Views

FortranFan wrote:

Quote:

Blane J. wrote:

 

..The listdirected and DT-formed input and output (indicate by comment line 2,3,4,5 and 7.8.9.10) still generate the same error message I presented previously, but comment line 1 and 6 are just OK.

 

 

It looks to me like a bug in the Intel Fortran compiler, your code is alright.

Yes, I think so. I've reported this failure to OSC and wait for replies.

0 Kudos
Reply