Hi there! First post here - 20+ years of experience with Fortran, currently working on a large HPC physics-based numerical simulation code, trying to leverage the best of modern Fortran (polymorphism, coarrays, etc.).
I would like to know if there is an elegant solution to the following problem:
Take a look at the code below.
M is a module of a library - meant to be used by other developers.
I would like a user of that module to define a variable VAR of type T_B, and then to be able to call VAR%A%HELLO - while being prevented from modifying VAR%A (for encapsulation / safety reasons). Additionally, both T_A and T_B need to be public entities of M.
In other words, I would like A to be a private component of T_B, but A%HELLO to be accessible/public.
The scoping rules of Fortran and their interplay with type extension and private/public attributes make this impossible of course. That’s too bad because it means that you need to introduce a level of redirection (the type-bound procedure B_HELLO) to go around this.
When you have deeply nested types which need to expose procedures at the top-level (user-facing) derived type, this redirection mechanism becomes extremely unwieldy / tedious.
Ideally, the Fortran could introduce some kind of ‘protected’ attribute for components of a derived type (just like it does for module variables), but I am afraid though that Fortran has cornered itself with its arcane rules on the interplay of scope/extension/inheritance/privacy rules and that it may be too late to change the trajectory.
Does anybody has an elegant solution for this problem?
MODULE M
IMPLICIT NONE
TYPE T_A
CONTAINS
PROCEDURE, NOPASS, PUBLIC :: HELLO => A_HELLO
END TYPE T_A
TYPE T_B
TYPE(T_A), PRIVATE :: A
CONTAINS
PROCEDURE, PUBLIC :: HELLO => B_HELLO
END TYPE T_B
CONTAINS
SUBROUTINE A_HELLO
IMPLICIT NONE
WRITE(*,*) 'Hello!'
END SUBROUTINE A_HELLO
SUBROUTINE B_HELLO(SELF)
IMPLICIT NONE
CLASS(T_B), INTENT(IN) :: SELF
CALL SELF%A%HELLO
END SUBROUTINE B_HELLO
END MODULE M
PROGRAM P
USE M
IMPLICIT NONE
TYPE(T_B) :: VAR
CALL VAR%HELLO
END PROGRAM P
If I have correctly understood your question, I think that the following should work
module m
implicit none
type, public :: t_a
private
! content of t_a here that is private
contains
procedure, nopass, public :: hello => a_hello
end type t_a
type, public :: t_b
type(t_a) a
! contains
! procedure, public :: hello => b_hello
end type t_b
contains
subroutine a_hello
write(*,*) 'hello!'
end subroutine a_hello
! subroutine b_hello(self)
! class(t_b), intent(in) :: self
! call self%a%hello()
! end subroutine b_hello
end module m
program p
use m
implicit none
type(t_b) :: var
call var%a%hello()
end program p
In this way the “content” of t_a instances cannot be accessed (they are somehow “protected”), but you can access all their public type bound procedures. Is it what you are looking for? (I have left parts now unnecessary commented in my example).
BTW, I have removed the redundant implicit none in the type bound procedures that is inherited in the module by host association (I hope I’ve got my terminology right ).
PS: sorry for having converted to lower case your code and indented it, but I find it more readable in this form.
Thanks @epagone … but in your code nothing prevents the user to modify the A component of a variable of type T_B. Consider this:
...
USE M
TYPE(T_B) :: VAR
TYPE(T_A) :: SWITCHEROO
...
! The user calls an initialization procedure bound to TYPE_B (not shown in example)
! That procedure calls, in turn, an initialization procedure (bound to TYPE_A) for VAR%A.
! The process is repeated recursively for all nested-derived types.
! At that point, the content of VAR (and, recursively, of all its components) is initialized.
CALL VAR%INITIALIZE
...
! Now, if the user does this all initializations are lost.
! Since A is a public component of T_B, this is possible.
VAR%A = SWITCHEROO
...
Welcome to the forum, and all the very best with your modernization effort.
See this paper as part of Fortran 202X development - https://j3-fortran.org/doc/year/21/21-168.txt - toward a PROTECTED attribute of derived type components. There are limitations with everything, of course, in that with too “clever” a programming and enough malintent, someone can work around such an attribute too.
However at first glance at your original post, this feature proposal, if it makes into the official publication, will allow you what you seek.
In the meantime, with current Fortran 2018 standard nothing much “elegant” you can do for sure to avoid such indirection.
Interesting: even overloading the assignment operator with a private method does not seem to work in this case
module m
implicit none
type, public :: t_a
private
integer :: foo
contains
procedure, nopass, public :: hello => a_hello
procedure, private, pass(lhs) :: set_a
generic, private :: assignment(=) => set_a
end type t_a
type, public :: t_b
type(t_a) a
end type t_b
contains
subroutine a_hello
write(*,*) 'hello!'
end subroutine a_hello
subroutine set_a(lhs,rhs)
class(t_a), intent(out) :: lhs
type(t_a), intent(in) :: rhs
lhs%foo = rhs%foo
end subroutine set_a
end module m
program p
use m
implicit none
type(t_b) :: var
type(t_a) :: switcheroo
call var%a%hello()
var%a = switcheroo
end program p
All the compilers I have access to (i.e. gfortran, ifort and ifx) agree in allowing the assignment. There must be something that I’m missing…
@FortranFan thanks for the link to the paper! I hope this will be adopted. Also, the code I have been working on (for years now!) is a brand new code, not a modernization effort.
I think that the idea of decoupling the attributes of ‘privacy’ and ‘protection’ should also be extended to the attributes of ‘privacy’ and ‘inheritability’.
In other words, a derived-type component could be both PRIVATE (no direct access) and INHERITABLE (access granted to extensions of the type, even if those extensions are NOT declared in the same module as the parent type).
Lastly, it would be beneficial to prevent a type to be extensible. In the same way we have the NONOVERRIDABLE attribute for type-bound procedures, a type itself could have the NONEXTENSIBLE attribute.
With these modifications (and some facilities associated with templates/generic programming) I would be a very happy camper! The rest of Fortran 2018 is really on solid ground (coarrays, interoperability, etc.) and these features are enjoyable to use. The points mentioned above are… hindrances or limitations that hurt productivity (and code design).