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.