Hopefully you have a better feel of self/this in the context of Fortran.
If you do pursue object-oriented design and programming (OOD and OOP), hopefully that will be preceded by thorough object-oriented analysis (OOA), and then with the aspect of your self/this, you may want to consider employing the PASS attribute in Fortran as self-evident indicator! And be consistent with your usage.
module messenger_m
type :: messenger_t
private
character(len=:), allocatable :: message
contains
procedure, pass(this) :: get => get_message !<-- PASSed object called as `this`
procedure, pass(self) :: set => set_message !<-- PASSed object called as `self`
end type
contains
function get_message( this ) result(message)
class(messenger_t), intent(in) :: this
character(len=:), allocatable :: message
message = this%message
end function
subroutine set_message( self )
class(messenger_t), intent(inout) :: self
self%message = "Hello World!"
end subroutine
end module
use messenger_m, only : messenger_t
type(messenger_t) :: msg
call msg%set()
print *, msg%get()
end
Thank you for the pep-talk, Pap. Nonetheless, when existing code one needs to work with/on is OO, thorough understanding of âself/thisâ appears indispensable.
As for vmagninâs query: I taught myself Fortran from Daniel D. McCrackenâs book âA guide to FORTRAN IV programmingâ, Wiley 1965, in 1968. BTW, this book uses flowcharts.
I am using the same OOP syntax with Coarray Fortran for distributed (fragmented) objects programming (Fragmented object - Wikipedia).
Syntactically the only difference is the implementation of the type bound procedures where I have to combine multiple (usually 2) subroutines into a single module procedure to make kernel programming more easily feasible. All fragments that form a single fragmented object are implemented as abstract classes.
â(Note: In the code examples I am using âfo %â instead of the usual âthis %â object identifier to make a clear distinction between OOP codes and distributed objects codes. My actual codes are already embedded into a distributed (fragmented) objects model (fo), and I am using the traditional OOP syntax merely to define and implement such distributed objects.) â
âTransforming OOP towards Distributed Objects Programming (âŚ):
All of my kernel programming is already embedded into distributed objects programming, and I am already using the same OOP syntax (including inheritance) to define and implement distributed objects in Fortran. While the syntax for distributed objects is the same as in OOP, the meaning of the syntax does become something completely different with distributed objects. A crucial advantage of using OOP syntax for Distributed Objects Programming is the already improved compile time analysis for parallel programming in Fortran, since compile time analysis does not distinguish between OOP and Distributed Objects Programming.â
Using fo% as (fragmented) object identifier does indicate that only one (local) fragment of the (distributed) object is addressed at a time.
From what I can see yet, using such kind of (truly) distributed object model in Fortran could become a very efficient way to develop/map out sophisticates parallel codes for spatial devices (e.g. FPGAs) in the near future. It does already work on CPUs.
McCrackenâs book âA guide to FORTRAN IV programmingâ, Wiley 1965 is a good book for FORTRAN IV, an excellent place to learn the dominant dialect at the time
Re: âexisting code one needs to work with/on is OO,â note if you are serious about this, I strongly urge you to thoroughly review the following books in order:
Thanks to your useful advices, I could obtain and test the code below (dvo = ormo) Preformatted text:
module MyModule ! Supplied by ChatGPT, adapted by dvo.
implicit none ! dvo added.
type :: MyType ! ChatGPT.
integer :: ivalue ! ChatGPT, plus 'i'.
real*4 :: rvalue ! dvo added.
real*8 :: dvalue ! dvo added.
contains
procedure :: PrintValue ! Type-bound procedure.
end type MyType ! ChatGPT.
CONTAINS
subroutine PrintValue(self) ! ChatGPT.
! type (MyType), intent(in) :: self ! Error by ChatGPT.
class(MyType), intent(in) :: self ! dvo adapted.
print *, " Real*4: ", self%rvalue ! dvo added.
print *, " Real*8: ", self%dvalue ! dvo added.
print *, "Integer: ", self%ivalue ! ChatGPT, plus 'i'.
end subroutine PrintValue ! ChatGPT.
end module MyModule
!
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
!
program Main ! Supplied by ChatGPT, adapted by dvo.
use MyModule
implicit none ! dvo added.
type(MyType) :: obj ! ChatGPT.
obj%dvalue = 42.d0 ! dvo added.
obj%rvalue = 42. ! dvo added.
obj%ivalue = 42 ! ChatGPT, plus 'i'.
call obj%PrintValue ! Original ChatGPT-call suffices.
end program Main
,
which resulted in:
! [ormo@rolls5 more-stuff1]$ gfortran stuff1.f90 -o stuff1.x
! [ormo@rolls5 more-stuff1]$ ./stuff1.x
! Real*4: 42.0000000
! Real*8: 42.000000000000000
! Integer: 42
! [ormo@rolls5 more-stuff1]$
There are 3 âinstancesâ and just 1 print-call.
On purpose, I did not keep the order of the 3 instances constant, within the code.
Only one of the tried orders is shown here.
The matter is much clearer to me now.
Thank you again.
Dirk van Ormondt.
Glad youâre starting to get the hang of it. A couple of points.
This is a very strange formatting style. I had to re-read it twice to notice the type definition. Not to start style-guide flame wars, but a formatting style should at least aid in seeing the structure of the code, and certainly avoid obscuring it.
As a matter of terminology, there are not â3 âinstancesââ. There is one object with 3 components.
Hello hkvzjal,
Thank you for your help. I understand better now. Admittedly, I have not yet fully digested the omnipresent phrase âthe first argument is the type itselfâ. In non-OO code an argument is a just single thing, i.e., a real or integer number, while in OO a âtypeâ is an entire block of code. How to interpret this ?
So, try to think of an object (type(something)) not as a block of code, but as an array on steroids⌠meaning, just as you can pass as argument something like integer, intent(in) :: a(3) which is a collection of 3 values. An object or structure enables you to pass with a single name, a collection of things with different intrinsic types.
@ormo, you may want to learn to use the @ symbol followed by the nom de plume (e.g., @hkvzjal ) to refer to other readers who provide you with guidance.