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

explicit constructor with private components and implicit type casting --> non-meaningful error

Johannes_Rieke
New Contributor III
905 Views

I played around with OOP and got confused by a mis-leading error message (PSXE 2017u2, x64). Assume the following code:

module my_mod_type_short
  use, intrinsic :: ISO_FORTRAN_ENV, only : rk => real64
  implicit none
  
  private
  public  :: rk
  
  type, public :: my_type
    !real(rk), private :: x_  ! compile time error occurs here, if implicit type casting is happening in the constructor
    !real(rk), private :: y_  !
    real(rk) :: x_            ! this works with implicit type casting!!
    real(rk) :: y_
    
    !contains
    ! some procedures
  end type my_type   
    
    
  interface my_type
    module procedure my_type_constructor
  end interface  
  
  contains
  
  function my_type_constructor(x,y)
    implicit none
    !real(rk), intent (in) :: x    ! real should be used
    !real(rk), intent (in) :: y
    integer, intent (in) :: x      ! ERROR: this is not intended to be integer, but a coding error
    integer, intent (in) :: y      ! 
    type(my_type)         :: my_type_constructor
    my_type_constructor%x_ = x
    my_type_constructor%y_ = y
  end function my_type_constructor
  
end module my_mod_type_short
  
program OO_test_01
  use my_mod_type_short
  implicit none

  ! Variables
  type(my_type)  :: twoD_data
  real(rk)       :: my_x, my_y
  
  my_x = 5.0_rk
  my_y =10.0_rk  
  twoD_data = my_type(my_x, my_y)
  
end program OO_test_01

This runs fine, but contains a not intended implicit type casting in the constructor (my_type_constructor), where I accidently used integer instead of real. If I add the private attribute to x_ and y_ (line 09/10 instead of 11/12), I get this error message:

1>------ Build started: Project: OO_test_01, Configuration: Debug x64 ------
1>Compiling with Intel(R) Visual Fortran Compiler 17.0.2.187 [Intel(R) 64]...
1>my_mod_type_short.f90
1>D:\02_Fortran\99_test\OO_test_01\my_mod_type_short.f90(48): error #6053: Structure constructor may not have fields with the PRIVATE attribute   [MY_X]
1>D:\02_Fortran\99_test\OO_test_01\my_mod_type_short.f90(48): error #6053: Structure constructor may not have fields with the PRIVATE attribute   [MY_Y]
1>compilation aborted for D:\02_Fortran\99_test\OO_test_01\my_mod_type_short.f90 (code 1)
1>
1>Build log written to  "file://D:\02_Fortran\99_test\OO_test_01\x64\Debug\BuildLog.htm"
1>OO_test_01 - 3 error(s), 0 warning(s)
========== Build: 0 succeeded, 1 failed, 0 up-to-date, 0 skipped ==========

This message is not a help here and it took me some time to figure out, what is wrong. Makes the error message sense at all?

Switching in the constructor to real, everything works fine.

0 Kudos
1 Solution
FortranFan
Honored Contributor II
905 Views

Johannes wrote:

.. At the end, the error message I get, if I falsely use integer in the explicit constructor, is misleading, because it not mention the wrong data type, but complains about the private attribute. I assume that in case of non-matching interfaces, the implicit constructor is expected, which not works with private components. One can test this with commenting out the explicit constructor and its interface. With private components of my_type, I get the same error message like if the explicit contains wrong non-mating interface.

Or am I wrong? ..

When a GENERIC INTERFACE with the same name as a derived type is made PUBLIC, a specific procedure that is part of the interface will get invoked if the method signature matches with that employed with the "construction" statement in the caller.  If there is no match, the compiler will attempt the default structure constructor approach which can result in errors when PRIVATE components of the derived type are being assigned values.

First try this code:

module my_mod_type_short

   use, intrinsic :: ISO_FORTRAN_ENV, only : rk => real64

   implicit none

   private

   public :: rk

   type :: my_type
      private
      real(rk) :: x_
      real(rk) :: y_
   contains
      private
      procedure, pass(this), public :: x => get_x
      procedure, pass(this), public :: y => get_y
   end type my_type

   interface my_type
      module procedure my_type_constructor
      module procedure int_constructor
   end interface
   public :: my_type

contains

   function my_type_constructor( xy ) result( mt )

      real(rk), intent (in) :: xy
      ! Function result
      type(my_type)         :: mt

      print *, "enter my_type_constructor"
      mt%x_ = xy
      mt%y_ = xy

      return

   end function my_type_constructor

   function int_constructor(x,y) result( mt )

      integer, intent (in) :: x
      integer, intent (in) :: y
      ! Function result
      type(my_type)         :: mt

      print *, "enter int_constructor"
      mt%x_ = x
      mt%y_ = y

      return

   end function int_constructor

   function get_x( this ) result( x )

      class(my_type), intent (in) :: this
      ! Function result
      real(rk) :: x

      x = this%x_

      return

   end function get_x

   function get_y( this ) result( y )

      class(my_type), intent (in) :: this
      ! Function result
      real(rk) :: y

      y = this%y_

      return

   end function get_y

end module my_mod_type_short
program OO_test_01

   use my_mod_type_short, only : rk, my_type

   implicit none

   ! Variables
   type(my_type) :: mt1
   type(my_type) :: mt2
   type(my_type) :: mt3

   mt1 = my_type( xy=5.0_rk )
   print *, "mt1%x = ", mt1%x()
   print *, "mt1%y = ", mt1%y()

   mt2 = my_type( x=5, y=10 )
   print *, "mt2%x = ", mt2%x()
   print *, "mt3%y = ", mt2%y()

   !mt3 = my_type( 5.0_rk, 10.0_rk )

   stop

end program OO_test_01

Then try uncommenting the code on line #20 and retry to see what happens.

View solution in original post

0 Kudos
7 Replies
FortranFan
Honored Contributor II
905 Views

Seems like the root of your problem is the INTERFACE my_tape is not made public, only the derived type is.

Remove the ", public" attribute on the derived type definition for my_type and then add "public :: my_type" statement following the INTERFACE definition.

0 Kudos
Johannes_Rieke
New Contributor III
905 Views

Hi FortranFan,

I've tested your suggestion (removing public from line 8, adding public::mytype in line 22), but I receive now a different error:

error #6404: This name does not have a type, and must have an explicit type.   [MYTYPE]

Since the original code works, if the constructor contains the correct data type (real, line 27/28 instead of 29/30). I've a gut feeling, that I do something non-standard conforming or there might be a compiler bug.

What I'm wondering still, how the explicit constructor is found although I defined everything private (line 5) for the case, no error is thrown?

0 Kudos
andrew_4619
Honored Contributor II
905 Views

twoD_data = my_type(my_x, my_y) is standard fortran syntax you do not need a constructor routine for this to work and indeed maybe that is the cause of the problems.....

0 Kudos
Johannes_Rieke
New Contributor III
905 Views

Hi all,

the implicit standard constructor works fine as long the components of my_type are public. I wanted to hide them. If that is the case, I have to provide an explicit constructor as far as I understood. This works fine, if the correct data types (real) are written in the constructor (in debug, I can set a break point in the explicit constructor, where the code pauses, the code below works). At the end, the error message I get, if I falsely use integer in the explicit constructor, is misleading, because it not mention the wrong data type, but complains about the private attribute. I assume that in case of non-matching interfaces, the implicit constructor is expected, which not works with private components. One can test this with commenting out the explicit constructor and its interface. With private components of my_type, I get the same error message like if the explicit contains wrong non-mating interface.

Or am I wrong?

module my_mod_type_short
  use, intrinsic :: ISO_FORTRAN_ENV, only : rk => real64
  implicit none
  
  private
  public  :: rk
  
  type, public :: my_type
  !type :: my_type
    real(rk), private :: x_  ! 
    real(rk), private :: y_  !    
    !contains
    ! some procedures
  end type my_type 

  interface my_type
    module procedure my_type_constructor
  end interface  
  
  contains
  
  function my_type_constructor(x,y)
    implicit none
    real(rk), intent (in) :: x    ! real should be used
    real(rk), intent (in) :: y
    type(my_type)         :: my_type_constructor
    my_type_constructor%x_ = x
    my_type_constructor%y_ = y
  end function my_type_constructor   
end module my_mod_type_short
  
program OO_test_01
  use my_mod_type_short
  implicit none
  ! Variables
  type(my_type)  :: twoD_data
  real(rk)       :: my_x, my_y
  my_x = 5.0_rk
  my_y =10.0_rk  
  twoD_data = my_type(my_x, my_y)
  
end program OO_test_01

 

0 Kudos
FortranFan
Honored Contributor II
905 Views

Johannes wrote:

.. I've tested your suggestion (removing public from line 8, adding public::mytype in line 22), but I receive now a different error:

error #6404: This name does not have a type, and must have an explicit type.   [MYTYPE]

..

It looks like you had a typo this time where you used "MYTYPE" in one place and "MY_TYPE" in another,

Anyways, try this:

module my_mod_type_short

   use, intrinsic :: ISO_FORTRAN_ENV, only : rk => real64

   implicit none

   private

   public :: rk

   type :: my_type
      private
      real(rk) :: x_
      real(rk) :: y_
   contains
      private
      procedure, pass(this), public :: x => get_x
      procedure, pass(this), public :: y => get_y
   end type my_type

   interface my_type
      module procedure my_type_constructor
   end interface
   public :: my_type

contains

   function my_type_constructor(x,y) result( mt )

      real(rk), intent (in) :: x
      real(rk), intent (in) :: y
      ! Function result
      type(my_type)         :: mt

      mt%x_ = x
      mt%y_ = y

      return

   end function my_type_constructor

   function get_x( this ) result( x )

      class(my_type), intent (in) :: this
      ! Function result
      real(rk) :: x

      x = this%x_

      return

   end function get_x

   function get_y( this ) result( y )

      class(my_type), intent (in) :: this
      ! Function result
      real(rk) :: y

      y = this%y_

      return

   end function get_y

end module my_mod_type_short
program OO_test_01

   use my_mod_type_short, only : rk, my_type

   implicit none

   ! Variables
   type(my_type)  :: twoD_data

   twoD_data = my_type( x=5.0_rk, y=10.0_rk )

   print *, "twoD_data%x = ", twoD_data%x()
   print *, "twoD_data%y = ", twoD_data%y()

   stop

end program OO_test_01

You should get no compilation warnings or errors and upon compilation, you should see the following:

 twoD_data%x =  5.00000000000000
 twoD_data%y =  10.0000000000000

 

So notice in this revised code the "data" for the class (derived type in Fortran) are PRIVATE, then using the facility introduced in Fortran 2003 that allows a GENERIC INTERFACE (that has PUBLIC attribute) to have the same name as the derived type a "constructor" option is introduced, and "setter" accessor methods (get_x, get_y) are added to the class to dispatch the requested "data" from the class to the caller.

0 Kudos
FortranFan
Honored Contributor II
906 Views

Johannes wrote:

.. At the end, the error message I get, if I falsely use integer in the explicit constructor, is misleading, because it not mention the wrong data type, but complains about the private attribute. I assume that in case of non-matching interfaces, the implicit constructor is expected, which not works with private components. One can test this with commenting out the explicit constructor and its interface. With private components of my_type, I get the same error message like if the explicit contains wrong non-mating interface.

Or am I wrong? ..

When a GENERIC INTERFACE with the same name as a derived type is made PUBLIC, a specific procedure that is part of the interface will get invoked if the method signature matches with that employed with the "construction" statement in the caller.  If there is no match, the compiler will attempt the default structure constructor approach which can result in errors when PRIVATE components of the derived type are being assigned values.

First try this code:

module my_mod_type_short

   use, intrinsic :: ISO_FORTRAN_ENV, only : rk => real64

   implicit none

   private

   public :: rk

   type :: my_type
      private
      real(rk) :: x_
      real(rk) :: y_
   contains
      private
      procedure, pass(this), public :: x => get_x
      procedure, pass(this), public :: y => get_y
   end type my_type

   interface my_type
      module procedure my_type_constructor
      module procedure int_constructor
   end interface
   public :: my_type

contains

   function my_type_constructor( xy ) result( mt )

      real(rk), intent (in) :: xy
      ! Function result
      type(my_type)         :: mt

      print *, "enter my_type_constructor"
      mt%x_ = xy
      mt%y_ = xy

      return

   end function my_type_constructor

   function int_constructor(x,y) result( mt )

      integer, intent (in) :: x
      integer, intent (in) :: y
      ! Function result
      type(my_type)         :: mt

      print *, "enter int_constructor"
      mt%x_ = x
      mt%y_ = y

      return

   end function int_constructor

   function get_x( this ) result( x )

      class(my_type), intent (in) :: this
      ! Function result
      real(rk) :: x

      x = this%x_

      return

   end function get_x

   function get_y( this ) result( y )

      class(my_type), intent (in) :: this
      ! Function result
      real(rk) :: y

      y = this%y_

      return

   end function get_y

end module my_mod_type_short
program OO_test_01

   use my_mod_type_short, only : rk, my_type

   implicit none

   ! Variables
   type(my_type) :: mt1
   type(my_type) :: mt2
   type(my_type) :: mt3

   mt1 = my_type( xy=5.0_rk )
   print *, "mt1%x = ", mt1%x()
   print *, "mt1%y = ", mt1%y()

   mt2 = my_type( x=5, y=10 )
   print *, "mt2%x = ", mt2%x()
   print *, "mt3%y = ", mt2%y()

   !mt3 = my_type( 5.0_rk, 10.0_rk )

   stop

end program OO_test_01

Then try uncommenting the code on line #20 and retry to see what happens.

0 Kudos
Johannes_Rieke
New Contributor III
905 Views

Hi FortranFan,

many thanks for your help! Eureka.

So, if no matching procedure is found in the generic interface, the known error message occurs. It's the same for non OO generic interfaces. The only point, I miss from the user perspective is a meaningful error message, which is different to non OO generic interfaces.

The OO message is:

error #6053: Structure constructor may not have fields with the PRIVATE attribute

The non OO non-matching generic interface is:

error #6284: There is no matching specific function for this generic function reference.   [DUMMY]

It would be nice to have a better error message for non-matching generic function references for the OO case, if it is possible. The working solution is shown below.

module my_mod_type_short 
   use, intrinsic :: ISO_FORTRAN_ENV, only : rk => real64 
   implicit none 
   private 
   public :: rk
 
   type :: my_type
      private
      real(rk) :: x_
      real(rk) :: y_
   contains
      private
      procedure, pass(this), public :: x => get_x
      procedure, pass(this), public :: y => get_y
   end type my_type
 
   interface my_type
      module procedure my_type_constructor
      module procedure my_type_constructor_xy
      module procedure int_constructor
   end interface
   public :: my_type
   
   interface dummy
     module procedure dummy_int
     module procedure dummy_real
   end interface dummy
   public :: dummy
 
contains
 
   function my_type_constructor( x, y ) result( mt )
 
      real(rk), intent (in) :: x
      real(rk), intent (in) :: y
      ! Function result
      type(my_type)         :: mt
 
      print *, "enter my_type_constructor"
      mt%x_ = x
      mt%y_ = y
 
      return
 
   end function my_type_constructor
 
   function my_type_constructor_xy( xy ) result( mt )
 
      real(rk), intent (in) :: xy
      ! Function result
      type(my_type)         :: mt
 
      print *, "enter my_type_constructor_xy"
      mt%x_ = xy
      mt%y_ = xy
 
      return
 
   end function my_type_constructor_xy
 
   function int_constructor(x,y) result( mt )
 
      integer, intent (in) :: x
      integer, intent (in) :: y
      ! Function result
      type(my_type)         :: mt
 
      print *, "enter int_constructor"
      mt%x_ = x
      mt%y_ = y
 
      return
 
   end function int_constructor
 
   function get_x( this ) result( x )
 
      class(my_type), intent (in) :: this
      ! Function result
      real(rk) :: x
 
      x = this%x_
 
      return
 
   end function get_x
 
   function get_y( this ) result( y )
 
      class(my_type), intent (in) :: this
      ! Function result
      real(rk) :: y
 
      y = this%y_
 
      return
 
   end function get_y
   
   function dummy_int ( input )
     implicit none
     integer, intent(in) :: input
     integer             :: dummy_int
     
     write(*,'(i8)') input
     dummy_int = input * 2
     return
   end function dummy_int 
   
   function dummy_real ( input )
     implicit none
     real(rk), intent(in) :: input
     real(rk)             :: dummy_real
     
     write(*,'(f8.2)') input
     dummy_real = input * 2.0_rk
     return
   end function dummy_real
 
  end module my_mod_type_short
program OO_test_01
 
   use my_mod_type_short, only : rk, my_type, dummy
 
   implicit none
 
   ! Variables
   type(my_type) :: mt1
   type(my_type) :: mt2
   type(my_type) :: mt3
   integer       :: i_value
   real(rk)      :: r_value
 
   mt1 = my_type( xy=5.0_rk )
   print *, "mt1%x = ", mt1%x()
   print *, "mt1%y = ", mt1%y()
 
   mt2 = my_type( x=5, y=10 )
   print *, "mt2%x = ", mt2%x()
   print *, "mt3%y = ", mt2%y()
 
   mt3 = my_type( 5.0_rk, 10.0_rk )
   
   i_value = dummy( input = 1      )
   r_value = dummy( input = 1.0_rk )
 
   stop
 
end program OO_test_01

 

0 Kudos
Reply