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

PROTECTED within Class

holysword
Novice
1,986 Views
Hi there,

I am trying to write a simple class but I would like some of its members to be PROTECTED. For instance

TYPE, ABSTRACT :: my_class
INTEGER :: Int1, Int2, Int 3
PROTECTED LOGICAL :: Logical1,Logical2
END TYPEmy_class

The reason is that I don't want the user to try to change the values of Logical1 and Logical2 manually (they are internal flags, let's say), but they should be setted by using the classes's procedures. I have been trying to google anything regarding this, but I was unable to find any answer.
Thanks in advance!!
0 Kudos
1 Solution
IanH
Honored Contributor II
1,986 Views
The protected attribute is only for module variables, not for components of a derived type.

You can achieve a similar concept to protected (but with different syntax at the point of use) by writing "set and get" procedures for the component.

[fortran]TYPE :: the_type  
  PRIVATE
  INTEGER :: the_component
CONTAINS
  PROCEDURE :: Get
  PROCEDURE :: Set
END TYPE the_type

...

FUNCTION Get(the_object) RESULT(the_value)
  TYPE(the_type), INTENT(IN) :: the_object
  INTEGER :: the_value
  the_value = the_object%the_component
END FUNCTION Get

! If you don't provide this procedure and binding then the value 
! would be "read-only" outside its module.
SUBROUTINE Set(the_object, new_value)
  TYPE(the_type), INTENT(INOUT) :: the_object
  INTEGER, INTENT(IN) :: new_value
  !***
  the_object%the_component = new_value
  ! ... other stuff that must happen when the_component changes
END SUBROUTINE Set

...

PROGRAM TypicalUsage
  USE the_module
  ...
  TYPE(the_type) :: a
  ...
  a%the_component = ...   ! This would be an error.
  CALL a%Set(1)           ! Ok if the Set procedure is provided.
  PRINT "('The value of the component is:',I0)", a%Get()  ! Ok.
[/fortran]

View solution in original post

11 Replies
Steven_L_Intel1
Employee
1,986 Views
Do you want the user to even read the values? If so, then you want PRIVATE, not PROTECTED. The syntax would be:

TYPE, ABSTRACT :: my_class
PRIVATE ! Change default accessibility of components
INTEGER, PUBLIC :: Int1, Int2, Int3
LOGICAL :: Logical1, Logical2
END TYPE my_class

PROTECTED is for variables that can be read but should not be written to.
0 Kudos
IDZ_A_Intel
Employee
1,986 Views
Note that the PRIVATE statement, if present, has to go before the first component and, if it's present, then all components are private by default. If you just want to make one or two components private, but leave the rest public, then just put the private attribute in the component definitions.

[fortran]ABSTRACT TYPE my_class
  INTEGER :: Int1, Int2, Int3
  LOGICAL, PRIVATE :: Logical1, Logical2
END TYPE my_class[/fortran]
Steven_L_Intel1
Employee
1,986 Views
Argh - yes, the standard does indeed require that PRIVATE go before the components. The compiler doesn't catch this, however. Fortran 2003 added the ability to define a private type with public components or vice-versa.

Also, I had an error in the first line - it is "TYPE, ABSTRACT :: my_class" not "ABSTRACT TYPE". I corrected my post with both fixes - apologies for the error.
holysword
Novice
1,986 Views
Thanks for answering.
Yes, I want the user to read but not to change the value, so its PROTECTED and not PRIVATE.
The version of the compiler in my university doesn't allow me to compile using the same syntax (just changing PRIVATE by PROTECTED). If it is possible at all to set the variable to PROTECTED, which is the oldest version of ifc that allows that?
0 Kudos
IanH
Honored Contributor II
1,987 Views
The protected attribute is only for module variables, not for components of a derived type.

You can achieve a similar concept to protected (but with different syntax at the point of use) by writing "set and get" procedures for the component.

[fortran]TYPE :: the_type  
  PRIVATE
  INTEGER :: the_component
CONTAINS
  PROCEDURE :: Get
  PROCEDURE :: Set
END TYPE the_type

...

FUNCTION Get(the_object) RESULT(the_value)
  TYPE(the_type), INTENT(IN) :: the_object
  INTEGER :: the_value
  the_value = the_object%the_component
END FUNCTION Get

! If you don't provide this procedure and binding then the value 
! would be "read-only" outside its module.
SUBROUTINE Set(the_object, new_value)
  TYPE(the_type), INTENT(INOUT) :: the_object
  INTEGER, INTENT(IN) :: new_value
  !***
  the_object%the_component = new_value
  ! ... other stuff that must happen when the_component changes
END SUBROUTINE Set

...

PROGRAM TypicalUsage
  USE the_module
  ...
  TYPE(the_type) :: a
  ...
  a%the_component = ...   ! This would be an error.
  CALL a%Set(1)           ! Ok if the Set procedure is provided.
  PRINT "('The value of the component is:',I0)", a%Get()  ! Ok.
[/fortran]
holysword
Novice
1,986 Views
Yes, I know the idea of get and set methods, but I was trying to avoid it.
Thakn you very much anyway.
0 Kudos
holysword
Novice
1,986 Views
Sorry for ressurrecting the thread, but I have an additional point.
I have the following type
[fortran]TYPE, ABSTRACT :: FATHER_TYPE
  LOGICAL, PRIVATE :: Initialized
CONTAINS  
  PROCEDURE :: GetInitialize()
END TYPE FATHER_TYPE[/fortran]
I am using polymorphism and I don't want the routines which use FATHER_TYPE to be able to modify Initialized (I think that the names suggests a lot...).
[fortran]TYPE EXTENDS(FATHER_TYPE) :: CHILD_TYPE
  ...
CONTAINS  
  PROCEDURE :: Initialize()
END TYPE FATHER_TYPE[/fortran]
I want to be able to set Initialized flag inside Initialize(), but it won't allow me because its a private attribute. If I create a set method inside FATHER_TYPE, then everybody will be able to change it - not much different from having it PUBLIC.
Any idea on how to workaround?
0 Kudos
John4
Valued Contributor I
1,986 Views

Since nobody has replied to your new post, I guess I'll try to help by pointing out (again) how Fortran ins NOT C/C++:

  1. Fortran accessibility is tied to the module, not to the derived type ---I guess you already noticed that.
  2. Type-bound procedures are overridable by default, unless you use the NON_OVERRIDABLE attribute.
  3. Abstract derived types let you have deferred type-bound procedures ---well, C++ also lets you do that.
  4. Type-bound procedures are, in a certain way, just syntactic sugar (with the notable exception of generic TBP).

Combining 2 and 3, you can apply as many "abstract levels" as you want, and that could solve your problem.

Combining 1 and 4, certainly solves your problem, but only if you're willing/allowed to hide certain implementation details. For example:

[fortran]module mod1
    use iso_fortran_env

    implicit none

    type, abstract :: t1
        logical, private :: read_only = .TRUE.
        logical, private :: flag = .FALSE.
    contains
        procedure :: set
    end type

contains
    subroutine set(this, flag)
        class(t1), intent(INOUT) :: this
        logical, intent(IN) :: flag

    continue
        if (this%read_only) then
            write(ERROR_UNIT, '("this%set is for internal use only")')
        else
            this%flag = flag
        endif
    end subroutine

    subroutine toggle_read_only(this)
        class(t1), intent(INOUT) :: this

    continue
        this%read_only = .NOT. this%read_only
    end subroutine
end module mod1

module mod2
    use mod1

    implicit none

    type, extends(t1) :: t2
    contains
        procedure :: initialize
    end type

contains
    subroutine initialize(this, flag)
        class(t2), intent(INOUT) :: this
        logical, intent(IN) :: flag

    continue
        call toggle_read_only(this)
        call this%set(flag)
        call toggle_read_only(this)
    end subroutine
end module mod2
[/fortran]
If toggle_read_only is not documented (or only documented in an advanced section), then any call to the set TBP will trigger an error... And of course, read_only should also be excluded from the documentation intended to the user.

0 Kudos
holysword
Novice
1,986 Views
Hi Jhon, thank you for answering.
Yes, I know all the four points you mentioned, and that's why I asked for a suggestion to workaround.
Well, your idea is a workaround indeed, but the trick is just "don't tell the user abouttoggle_read_only", trusting the user will not mess up with what is not documented, if I understood it correctly. If so, I could let the variable PUBLIC and don't document it.
Another thing that concerns me is that your suggestion would generate an error at runtime, not compile time, which would be the choice of my heart for this situation. I wonder if anything could be done in this sense.
0 Kudos
Steven_L_Intel1
Employee
1,986 Views
The model Fortran has for accessibility is that everything is visible in the defining module - accessibility controls what USErs of the module can see. Perhaps you could work something with the base type and initializer in one module and then extensions go in a second module.
0 Kudos
holysword
Novice
1,986 Views
I think that you comment has gave me a good idea to workaround...
[fortran]MODULE m_generic


TYPE, ABSTRACT :: T_Father    
  INTEGER :: Attrib1
  REAL :: Attrib2
  
  CONTAINS  
   PROCEDURE(IsInitialized_Abstract), DEFERRED :: IsInitialized
   PROCEDURE(Initialize_Abstract),    DEFERRED :: Initialize
END TYPE T_Father


ABSTRACT INTERFACE

   FUNCTION IsInitialized_Abstract(self) RESULT(val)
      IMPORT :: T_Father
      CLASS(T_Father), INTENT(IN)  :: self
      LOGICAL                      :: val
   END FUNCTION IsInitialized_Abstract
   
   SUBROUTINE Initialize_Abstract(self)
      IMPORT :: T_Father
      CLASS(T_Father), INTENT(INOUT)  :: self
   END SUBROUTINE Initialize_Abstract
   
END INTERFACE



END MODULE m_generic[/fortran]
[fortran]MODULE m_specific

   USE m_generic


TYPE, EXTENDS(T_Father) :: T_Child
  LOGICAL, PRIVATE :: Initialized = .FALSE.
  
  CONTAINS  
   PROCEDURE, PASS(self) :: IsInitialized
   PROCEDURE, PASS(self) :: Initialize
END TYPE T_Child


 CONTAINS

FUNCTION IsInitialized(self) RESULT(val)
   CLASS(T_Child), INTENT(IN)  :: self
   LOGICAL                     :: val
   
   val = self%Initialized
END FUNCTION IsInitialized


SUBROUTINE Initialize(self)
   CLASS(T_Child), INTENT(INOUT)  :: self
   
   PRINT *,'Im doing initialization'
   
   self%Initialized = .TRUE.
END SUBROUTINE Initialize



END MODULE m_specific [/fortran]
[fortran]PROGRAM Main

   USE m_generic
   USE m_specific

CLASS(T_Father), ALLOCATABLE :: father1
TYPE(T_Child)  :: child1

 
 child1%Attrib1 = 5
 child1%Attrib2 = 3.14
 
 ALLOCATE(father1, SOURCE=child1)
 
 PRINT *,'Before Init: ', father1%IsInitialized()
 CALL father1%Initialize()
 PRINT *,'After Init: ', father1%IsInitialized()
 
END PROGRAM[/fortran]
It will print False first, and then True. The attribute Initialized cannot be accessed via T_Father just because it is not defined there. A drawback is the need to redefine Initialized in every child and as well the get method IsInitialized(). In my case at least, the set method is supposed to be rewriten for every single object, so its not a drawback. An alternative would be to create and intermediate layer with both get and set generic functions and then extend the intermediate layer instead of t_father. I don't like the idea of having these intermediate layers though.
0 Kudos
Reply