'self' and 'this' in OO-Fortran

self-this.txt (2.0 KB)

LS,
As physicist born in the Stone Age (1936) and using Fortran (2018)
almost daily, I wish to report to you my chat with ChatGPT of today,
2023-10-09. Please, see attachment. Can you offer any help with
this ‘self/this’-issue?
Thank you in advance,
Dirk van Ormondt (Delft, NL).

dvo (me):
I wish to express that in English ‘self’ and ‘this’ occur already
frequently outside the field of programming. In OO-tutorials, one
often does not know whether this/self belong to the English
explanation or to the OO-code.

ChatGPT:
I completely understand your point. The dual usage of “self” and
“this” in both programming context and natural language can indeed
introduce confusion, especially in tutorials or explanations where the
distinction is not made clear. It’s an added layer of complexity when
these words have common usage outside of programming. This ambiguity
can make it challenging for learners to differentiate between the
programming constructs and their general language meaning, potentially
causing confusion and hindering the learning process. It underscores
the importance of clarity in documentation and teaching materials to
avoid any misunderstanding for those who are new to object-oriented
programming.

dvo:
Herewith I inform you that I have not yet encountered an English
OO-programming text that seemed to be aware of the potential
confusion. Alas.

ChatGPT
Got it. It’s unfortunate that you haven’t come across object-oriented
programming (OO) texts that explicitly address the potential confusion
between the programming constructs like “self” or “this” and their
general English usage. It can indeed be a challenge for learners when
the distinction is not clearly made.

Authors and educators in the programming community could benefit from
being more mindful of this issue and adopting practices that enhance
clarity, such as using consistent formatting or providing explicit
explanations.

As the programming community evolves, there’s an ongoing effort to
improve educational materials, so it’s possible that future tutorials
may become more aware of and responsive to the challenges learners
face in distinguishing between programming jargon and everyday
language. If you have the opportunity, providing feedback to authors
or educational platforms about this issue could contribute to positive
changes in their materials.

The ChatGPT output is gibberish as usual. What exactly are you trying to ask here? Have you encountered self and/or this in some code and what to know what it means in a OO context?

It seems ChatGPT likes chatting… :smile: Much ado about nothing…
It is just conventional, and could be named differently.

And welcome to the Discourse @ormo Dirk,
and kudos, you may be the elder here. It’s great to have you in the community. When did you begin using FORTRAN?

2 Likes

Welcome to the comunity, @ormo!

@ormo ,

Welcome to Fortran Discourse. You can “chat” even more here, and perhaps at the Intel Fortran forum also where you can find a kindred spirit.

@vmagnin , I am no fan of attempts at generative AI, but OP appeared to only want to “chat” with what OP fed to that system, and it appears the output from it is as any such chat feed will produce.

I remember chatting with ELIZA nearly 40 years ago and it was using what I typed to “answer”, but it was far less chatty. Progress is impressive. But, well, it’s interesting to see that ChatGPT can be so boring… :yawning_face:

1 Like

Hello Jacob Williams. Thank you for responding: “What exactly are you trying to ask here?”
I have troubles using/understanding ‘self/this’, and wish to read all that my English-language electronic textbooks say about it. But when one searches with a pdf-viewer for ‘self/this’ in an English book, one gets way too many results. One could just as well read the whole book like in the past when there were only paper-versions. Do you know a tutorial that is aware of the struggle that (some) people have with ‘self/this’ and go at length to explain it. (My 4 English modern-Fortran-textbooks do not (try to) explain the issue.)
I shall answer the other responses later.
BTW, for me ChatGTP proved useful most of the time: It could debug more than half of my OO-Fortran files.

Welcome @ormo, with all due respect to a Fortran programmer who experienced the horrors of using stacks of punchcards (I never had to use them since we had dumb terminals when I started, but I got several of those, and still use them as bookmarks.) :slightly_smiling_face:

ChatGPT is good at chatting, but not so good at programming. In almost all cases, it fails several times in a row, and in the end it may or may not give a correct answer. Typically it gives code with functions having a wrong number of arguments, or arguments that don’t exist at all. A few times it fell in an endless loop, giving the same code as before, despite the fact I told it this won’t work: “you are right, here is a modified version that should work” - and the “modified” version was exactly the same code as before.

P.S.: Personally, I use self in OO all the time, but this seems to be more popular.

There is a Wikipedia page:

In many object-oriented programming languages, this (also called self or Me) is a variable that is used in instance methods to refer to the object on which they are working

Welcome @ormo
So, the thing is that while in some languages such as python there is a strict nomenclature for OOP. In Fortran it is up to you to stick with whichever nomenclature you preferer. I personally chose self but it is just as good as any.

module test
implicit none

type :: mytype
    real :: x
contains
    procedure :: add
    procedure :: print_me
end type

contains

subroutine add(self,val)
    class(mytype), intent(inout) :: self
    real, intent(in) :: val
    self % x = self % x + val
end subroutine

subroutine print_me( something )
    class(mytype), intent(inout) :: something
    print *, something%x
end subroutine

end module

program main
use test

type(mytype) :: A
call A%add( 3.0 )
call A%print_me
end program

So, this is totally valid code, what you should keep in mind is that by default, a bound type procedure assumes that the first argument is the type itself such that you can call your procedure in this way:

call type%procedure_name( other, arguments , etc)

instead of

call procedure_name( type , other, arguments , etc )

(same applies to functions)

You can override this behavior… but that is less common

There is a very extensive page of resources to learn more Tutorials in Fortran Wiki
And if I should recommend one (the one that got me started with OOP in Fortran) : https://wiki.uiowa.edu/download/attachments/109785161/fortran-novella-Holcomb.pdf Jump to page 81 :wink:

1 Like

The most important is to understand that in Fortran you can name it as you want: self, this, this_one, this_object, the_present_object, ego...
We could make a poll! Personally, I am using self like @pap, I feel this would be strange (no reason, just my feeling). It would be interesting to consider if being a native speaker or not has an effect on what is preferred…

1 Like

I have used procedure( this , that ) in some cases where I needed to work with a second variable of the same type and just felt that procedure( self , that ) was not so clear. This was more of an exception.

Sure it is a great and impressive tool!

But its boring chatty answer inspires me: we could imagine that the greatest threat of IA would not concern labour, but boredom. And humanity would slowly die due to boredom, because we would interact most of the time with chat agents. Probably that scenario was already used many times. Maybe Asimov in his robots short stories? I don’t remember.

No conflict, but no friendship, no passion… Talking about Fortran and programming without passion would be so terrible… Our Discourse would die.

I used self because it sounds more “natural” to me, but from now on I will use it_is_not_me instead. Real programmers should make the code as frustrating as possible (and of course they should never ever add useful comments.) It was hard to write it, it should be hard to understand it. :laughing:
Joke aside, it really doesn’t matter.

That would ruin any reason for a totally pointless (but so much “fun”) flame war concerning a detail of details that nobody would normally care about. :laughing:

But seriously, AI is a potential threat, if you ask me. For now, however, it doesn’t seem to be much more than a glorified search engine with an advanced parser. At least every time I use it, it gives me that impression. And it’s good at that, but cannot be called “intelligence” no matter how you stretch the term.

Some people have various interests to glorify it. And they say “IA will replace this or that”, and they use a lot of time the world “will”, will, will, will… As if they knew the future. But the future is often different of what we predicted, the impact is different from what was expected.

In the mid-2010’s, MOOCs were the great buzz, and it would completely change teaching in universities, and blah blah blah… Well, it’s an interesting tool in some situations. But we experienced teaching/learning remotely during the COVID, and now so few want to continue that experience… So few want to teach/learn alone in their room.

I also remember the buzz about the optical computer in the 90’s. Well, you can have now chips with some built-in photonic waveguides to improve the communication between their circuits, but the optical computer is gone…

So wait and see the future. Maybe they are right, maybe half right, or just a little. When the buzz will fade, things will appear more clearly.

And I am still waiting the metaverse… (just a joke, I am not interested…)

1 Like

In the context of object-oriented programming in C++, this is the name of the expression whose value is the address of an implicit object parameter.

The following is a minimalistic example:

class T
{
    int x;

    void foo()
    {
        x = 6;       // same as this->x = 6;
        this->x = 5; // explicit use of this->
    }

    void foo(int x) // parameter x shadows the member with the same name
    {
        this->x = x; // unqualified x refers to the parameter
                     // 'this->' required for disambiguation
    }
};

As showed by this example, this is needed in some circumstances to disambiguate from other parameters. Now where does this implicit object come actually come from? It comes from an actual instance:

    T my_instance(42);
    my_instance.foo(); // call the member function

In other words the compiler sees this more like,

    T::foo(&my_instance); // pass address of my_instance to foo method of T

and the &my_instance is what is referred to as this internally.

When doing object-oriented programming in Fortran, use of the dummy parameter names this or self (from Python) is nothing more than a programmer convention, and arguably - a misleading one. The reason being that in Fortran type-bound methods can be bound as named arguments.

By default a type-bound procedure (TBP) will have a passed-object dummy argument (PODA) that is the first argument. A passed-object dummy argument can be changed by declaring the type-bound procedure with the PASS(arg-name) attribute. In this case, the variable is passed as the named argument.

This makes Fortran quite different from C++ or Python, because it allows us to bind a procedure to multiple types. I believe this is also known as multiple dispatch in other programming languages. In this scenario names like self or this don’t sound suitable to me.

The following Discourse thread looks for motivations behind pass and nopass:

Here’s an example case I have been contemplating before. Saw we write a module for nonlinear optimization, using two types:

    !> A handle to a user-defined problem
    type :: problem_type
       procedure(objective_callback), pointer, nopass :: objective => null()
       procedure(gradient_callback), pointer, nopass :: gradient => null()
    contains
        procedure, non_overridable :: eval => eval_objective
        procedure, non_overridable :: eval_grad => eval_gradient
        procedure(solve_method), pass(problem) :: solve => solve_problem
    end type

    !> A type encapsulating solution algorithms
    type, abstract :: solver_type
    contains
       procedure(solve_method), pass(solver) :: solve => solve_problem
    end type

We proceed to implement several extended types encapsulating different solution algorithms.

subroutine solve_problem(problem,result,x,solver,params,istat)
        class(problem_type), intent(in), target :: problem
        real(wp), intent(out) :: result
        real(wp), intent(inout), contiguous :: x(:)
        class(*), intent(in), optional, target :: params
        class(solver_type), intent(in), optional :: solver
        integer, intent(out), optional :: istat
        
        select type (solver)
        type is (lbgfs)
            ! ... 
        type is (nelder_mead)
            ! ... 
        type is (conjugate_gradient)
            ! ... 
        type is (particle_swarm)
            ! ... 
        class default
            call solver%solve(problem,result,x,params,istat)
        end select

end subroutine

The idea being that we can adopt either a “problem-centric” view, or a “solver-centric” view:

class(solver_type) :: solver
type(problem_type) :: problem
real(wp) :: x(4)

! We use a factory method to initialize the solver
! (we could pick this dynamically based on a configuration file or namelist)
solver = create_solver('LBFGS',atol=1.e-6,max_iter=2000)

! Define the callback functions of our problem
problem = problem_type(my_objective,my_gradient) 

! Set initial guess
x = 0 

! We can pass the solver to the problem
call problem%solve(x,solver)

! or we pass the problem to the solver
call solver%solve(problem,x)

contains

   subroutine my_objective(...)
     ! ...
   end subroutine

   subroutine my_gradient(...)
     ! ...
   end subroutine
end

Admittedly, the example is incomplete and I haven’t yet figured out the details of how this would work in practice.

1 Like

Thank you very much hkvzjal, vmagnin, and others who spent their precious time on my question!
New homework to do now before tackling my ultimate goal which is optimising hyperparameters
in neural fortran, GitHub - modern-fortran/neural-fortran: A parallel framework for deep learning.
So far, this task is beyond me due to OO. If I succeed, I shall let you know.

3 Likes

Caveat emptor: any confusion or haziness with the “view” you adopt on such matters, especially in numerical modeling, such as with solvers and simulations, can leave you with a gorilla holding a banana and the entire jungle, when all you wanted was the banana!!

1 Like

This is why I always say OOP is not the solution to every problem, and new programmers should not overestimate it. OOP can be very effective, making the code much easier to write and maintain. But that 's not true for every problem. People new to OOP tend to think it is a must no matter what. It is not.

It all depends on the problem at hand. And even when it is effective, bad OOP design (especially concerning inheritance) can cause a mess. You can easily end up in the middle of a jungle you never asked for, with a gorilla you don’t really need, and with said gorilla already eating the banana - which was all you wanted.
It’s not uncommon to go for an object-oriented solution which may work but without any real benefit for the problem you wanted to solve, or even with unnecessary complexity added. And you just end up wondering why you went that way in the first place. Never go for an OOP solution before you make sure it will make things easier, and without good planning for your objects first.

The beauty of Fortran is you can pick what’s best for the situation: module-oriented programming, object-oriented programming, or a mix of the two, as appropriate. All that without the header hell, which is inevitable in several other languages.

3 Likes