I have updated my hat_polykite project with the latest mathematical result (they have found the Grail, see at the end of this message) but need help to improve the OOP architecture. I am learning Fortran OOP and I feel confused on the following problem:
type :: Hat_polykite
complex(dp), private :: vertex(13)
contains
procedure :: set
procedure :: draw
procedure :: print
end type Hat_polykite
and
type :: Tile1_1
complex(dp), private :: vertex(14)
contains
procedure :: set
procedure :: draw
procedure :: print
end type Tile1_1
The draw and print procedures are identical. But the set procedures are different, as the first polygon has 13 vertices and the second one 14 vertices, with totally different coordinates. Maybe I could use an allocatable vertex array and put an if in the set procedure. But it seems that in OOP I should rather have a polygon object and define my two polygons by inheritance? Should I create an abstract class? The problem is probably trivial but I feel confused here on how to manage the two different sizes arraysā¦
Mathematical context
On May 28, 2023, they deposited a second preprint on arXiv describing aperiodic tiling of the plane using a single chiral (tiling the plane without its reflected version) fourteen-sided shape, named Tile(1,1). They have finally found the Grail! In fact, if you use both Tile(1,1) and its reflected shape, the tiling will be periodic. If the reflected shape is prohibited, the tiling is aperiodic. And by replacing the edges of Tile(1,1) by curves, you can obtain the Spectre which admits aperiodic tiling of the plane, but no tiling if you use it with its reflected shape.
If you want to keep things simple and straightforward, I think the best would be that you keep your objects as they are, declare everything private in your modules except for the object. As for your class procedures you could declare as follows:
type :: Hat_polykite
complex(dp), private :: vertex(13)
contains
procedure :: set => set_hat_polykite
procedure :: draw => draw_hat_polykite
procedure :: print => print_hat_polykite
end type Hat_polykite
...
Subroutine set_hat_polykite()
...
End subroutine
If you would like to mix both types and use polymorphism then you could create a single function that takes as first argument an abstract class and then use select type to switch between implementations.
You could, if you already have an idea of your base class and you would like to exploit polymorphism then it might be worth it. For that it is best to do a top-down design having in mind how you would like the end user to interact with the objects. Here a very simple idea:
Factorizing into a single module with polymorphism
module geom
use iso_fortran_env, only: dp=>real64
type, abstract :: geom_t
complex(dp), allocatable :: vertex(:)
contains
procedure :: set
procedure :: print
end type
type, extends(geom_t) :: hat_polykite
end type
type, extends(geom_t) :: tile1_1
end type
contains
subroutine set(self)
class(geom_t) :: self
select type(self)
type is(hat_polykite)
allocate(self%vertex(13))
type is(tile1_1)
allocate(self%vertex(14))
end select
end subroutine
subroutine print(self)
class(geom_t) :: self
select type(self)
type is(hat_polykite)
print *, 'hat_polykite:', self%vertex(:)
type is(tile1_1)
print *, 'tile1_1:', self%vertex(:)
end select
end subroutine
end module
program main
use geom
type(hat_polykite) :: A
type(tile1_1) :: B
call A%set()
call A%print()
call B%set()
call B%print()
end program
You can use it to override a procedure, or in this case, as a kind of procedure mask⦠So, if you declare everything private except for the type then you actually donāt need to do that, using different names would be necessary if you have everything public in you modules:
Separate classes with private procedures
module polykite
use iso_fortran_env, only: dp=>real64
private
type :: hat_polykite
complex(dp), allocatable :: vertex(:)
contains
procedure :: set
procedure :: print
end type
public :: hat_polykite
contains
subroutine set(self)
class(hat_polykite) :: self
allocate(self%vertex(13))
end subroutine
subroutine print(self)
class(hat_polykite) :: self
print *, 'hat_polykite:', self%vertex(:)
end subroutine
end module
module tile
use iso_fortran_env, only: dp=>real64
private
type :: tile1_1
complex(dp), allocatable :: vertex(:)
contains
procedure :: set
procedure :: print
end type
public :: tile1_1
contains
subroutine set(self)
class(tile1_1) :: self
allocate(self%vertex(13))
end subroutine
subroutine print(self)
class(tile1_1) :: self
print *, 'tile1_1:', self%vertex(:)
end subroutine
end module
program main
use polykite
use tile
type(hat_polykite) :: A
type(tile1_1) :: B
call A%set()
call A%print()
call B%set()
call B%print()
end program
Personally, I try to move as much as possible all common code to parent abstract classes and then extend to particular cases. In your case, I could imagine something like so:
module kytes
implicit none
private
public :: Hat_polykite, Tile1_1
type, abstract :: polygon
complex(dp), allocatable :: vertex(:)
contains
procedure, pass(self) :: draw => polygon_draw
procedure, pass(self) :: print => polygon_print
end type
type, extends(polygon) :: Hat_polykite
contains
procedure, pass(self) :: set => Hat_polykite_set
end type
type, extends(polygon) :: Tile1_1
contains
procedure, pass(self) :: set => Tile1_1_set
end type
contains
subroutine Hat_polykite_set(self, ...)
class(Hat_polykite), intent(inout) :: self
! Allocate and set code
end
subroutine Tile1_1_set(self, ...)
class(Tile1_1), intent(inout) :: self
! Allocate and set code
end
end module
@HugoMVale , I am trying your solution but I encounter a problem with the allocate statements in my set procedures at runtime:
$ fpm run
Project is up to date
At line 66 of file ././src/tile_class.f90
Fortran runtime error: Attempting to allocate already allocated variable 'self'
Error termination. Backtrace:
Line 66 is:
allocate(self%vertex(13))
in the subroutine Hat_polykite_set(self, start, hx_side)
Tested with GFortran and Intel ifx.
I can make it run by making the allocation in the main program instead:
type(Hat_polykite) :: hat
...
allocate(hat%vertex(13))
but I feel that it is not totally satisfying to define that size outside the class moduleā¦
Is there a better way?
do j = 1, 3
y = 20._dp ! mm top margin
do i = 1, 7
call hat%set(start=cmplx(x+10._dp, y, dp), hx_side=HX_SIDE)
If you call set within this loop with the allocation inside this is bound to happen as you are creating (mem allocation) the object and setting its values in the same procedure.
The easy fix would be to: in tile_class.f90, line 66: if(.not.allocated(self%vertex)) allocate(self%vertex(13)) that way you can keep your implementation as is.
Otherwise you should separate the memory allocation and the values setting as two distintic member procedures such that you force yourself to create the memory space just once and then play around with the actual values as you please.
A non-related note, make sure to implement also a final procedure
type, abstract :: Polygon
complex(dp), allocatable :: vertex(:)
contains
procedure, pass(self) :: draw => polygon_draw
procedure, pass(self) :: print => polygon_print
final :: polygon_clear
end type Polygon
...
subroutine polygon_clear(self)
class(polygon) :: self
if(allocated(self%vertex)) deallocate(self%vertex)
end subroutine
That way, as your objects become more complicated youāll be sure that theyāll be properlly destroyed when their local scope ends.
Thanks Jose. If I understand, in that loop it is always the same instance of the object that is used. In my mind I was thinking that each hat was a different instance created by my set procedureā¦
Could another solution be to use a BLOCK? something like:
do i = 1, 7
block
type(Hat_polykite) :: hat
call hat%set(start=cmplx(x+10._dp, y, dp), hx_side=HX_SIDE)
call hat%draw(cr)
end block
y = y + sqrt(3._dp) * HX_SIDE
end do
Some (or lot of?) things are not yet clear in my mind in Fortran OOP. Especially concerning constructors. Could I have the set procedure be called automatically when I declare my instance? (but it needs the two arguments start and hx_side)
And concerning the destructor ( polygon_clear), is it really necessary in my BLOCK construct? Wouldnāt the array be deallocated automatically at the end of the block?
Since you declared hat in line 39 of your main, you only have one object, so every time you do call hat%some_procedure(...) you are taking an action on that single object (just as if you had declared an allocatable array that you create and then do stuff with the values).
This could be one solution if you only need your object to exist during that limited scope. If you want to keep all your hats available after the loop, you could declare a list of hats:
type(hat_polykite), allocatable :: hat_list(:)
allocate( hat_list(3*7) )
do j = 1, 3
y = 20._dp ! mm top margin
do i = 1, 7
call hat_list(7*(j-1)+i)%set(start=cmplx(x+10._dp, y, dp), hx_side=HX_SIDE)
call hat_list(7*(j-1)+i)%draw(cr)
y = y + sqrt(3._dp) * HX_SIDE
end do
x = x + 3 * HX_SIDE
end do
Not sure about this one, Iāll be tempted to say no, have to take a look ā¦
When you declare a āfinalā procedure, you do not need to call it explicitly. The whole point is that it will be called automatically as you exit a scope (a block, a procedure, a main). So it is more a matter of āgood practiceā, you can live without it for this simple object, but for more complicated objects it might be a good idea. So better get use to writing it down from the beginning. It is helpful to have the explicit implementation declared when debugging for memory corruption issues
Thanks a lot @hkvzjal and @HugoMVale for taking time to help me. I feel I have learned a lot with you. Things are becoming clearer.
A last question concerning the attribute: , pass(self) ::
I read it was not necessary if self is the first argument of a procedure. But if you however write it, I imagine there is a reason in the general case?
Yes, if you make sure that the object is your first argument the default behavior is as if you wrote pass(self), so you can avoid it! writting it down would be more a matter of explicitness.
There is a fair argument to be made in this case an object-oriented design with type extension is neither a compact way to go nor one that is likely to be efficient.
An argument you should consider a generic programming design is stronger than that for OO.
And in the current standard a somewhat verbose way to achieve a generic design here is via the parameterized derived type, see an extremely simple illustration below that tries to make it a more type-safe and mnemonic with the use of enumerators:
module tile_m
enum, bind(C)
enumerator :: nsides_Hat_polykite = 13
enumerator :: nsides_Tile1_1 = 14
end enum
type :: tile_t( nsides )
integer, kind :: nsides = int( nsides_Hat_polykite )
complex :: vertex( nsides )
contains
procedure :: print_Hat_polykite
procedure :: print_Tile1_1
generic :: print => print_Hat_polykite, print_Tile1_1
end type
contains
subroutine print_Hat_polykite( this )
class(tile_t(nsides=int(nsides_Hat_polykite))), intent(in) :: this
print *, "print_Hat_polykite: nsides = ", this%nsides
end subroutine
subroutine print_Tile1_1( this )
class(tile_t(nsides=int(nsides_Tile1_1))), intent(in) :: this
print *, "print_Tile1_1: nsides = ", this%nsides
end subroutine
end module
use tile_m, only : tile_t, nsides_Hat_polykite, nsides_Tile1_1
type(tile_t(nsides=int(nsides_Hat_polykite))) :: hpk
type(tile_t(nsides=int(nsides_Tile1_1))) :: t1
call hpk%print()
call t1%print()
end
C:\temp>ifort /free /standard-semantics p.f
Intel(R) Fortran Intel(R) 64 Compiler Classic for applications running on Intel(R) 64, Version 2021.9.0 Build 20230302_000000
Copyright (C) 1985-2023 Intel Corporation. All rights reserved.
Microsoft (R) Incremental Linker Version 14.34.31937.0
Copyright (C) Microsoft Corporation. All rights reserved.
-out:p.exe
-subsystem:console
p.obj
C:\temp>p.exe
print_Hat_polykite: nsides = 13
print_Tile1_1: nsides = 14
Note: a named constant toward a derived type with integer components can be a replacement for the enum. But enumās are generally better suited in a big picture sense, though the type in the current standard as well as the upcoming 2023 revsion leaves a lot to be desired.
By the way, in your current code with the ALLOCATABLE attribute of the type component, you do not need an explicit finalizer.
Would you mind recommending some books on OO design (C++ ones work too)? I feel that the ones I have seen so far are not applicable to someone like me who does scientific computing.