- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
I originally posted this question on Stackoverflow (http://stackoverflow.com/questions/30823756/invoking-constructor-of-abstract-base-class-in-fortrant), but perhaps the Intel community har more knowledge on this topic?
Consider one of the classic OOP examples (see source code at the end of the post):
- Abstract base class Shape
- Class Rectangle extending Shape
I have two questions:
- In the source code below I've tried to define a constructor for the abstract class Shape using class(Shape), pointer :: this as result without ever allocating the pointer. Is this the correct way of defining a constructor for an abstract class in Fortran?
- How can I invoke the constructor of the base class (Shape) in the constructor of the extending class (Rectangle)? Using this%Shape = Shape(xCenter, yCenter) works for non-abstract base classes, but both the Intel compiler and gfortran gives me errors when the result type is class(Shape), pointer (required for an abstract class).
module Shape_mod
implicit none
private
public Shape
type, abstract :: Shape
private
double precision :: centerPoint(2)
contains
procedure :: getCenterPoint
procedure(getArea), deferred :: getArea
end type Shape
interface Shape
module procedure constructor
end interface Shape
abstract interface
function getArea(this) result(area)
import
class(Shape), intent(in) :: this
double precision :: area
end function getArea
end interface
contains
!Correct way of defining a constructor for an abstract class?
function constructor(xCenter, yCenter) result(this)
class(Shape), pointer :: this
double precision, intent(in) :: xCenter
double precision, intent(in) :: yCenter
print *, "constructing base shape"
this%centerPoint = [xCenter, yCenter]
end function constructor
function getCenterPoint(this) result(point)
class(Shape), intent(in) :: this
double precision point(2)
point = this%centerPoint
end function getCenterPoint
end module Shape_mod
module Rectangle_mod
use Shape_mod
implicit none
private
public Rectangle
type, extends(Shape) :: Rectangle
private
double precision :: length
double precision :: width
contains
procedure :: getArea
end type Rectangle
interface Rectangle
module procedure constructor
end interface Rectangle
contains
function constructor(length, width, xCenter, yCenter) result(this)
type(Rectangle), pointer :: this
double precision :: length
double precision :: width
double precision :: xCenter
double precision :: yCenter
print *, "Constructing rectangle"
allocate(this)
this%length = length
this%width = width
!How to invoke the base class constructor here?
!The line below works for non-abstract base classes where the
!constructor result can be type(Shape)
this%Shape = Shape(xCenter, yCenter)
end function constructor
function getArea(this) result(area)
class(Rectangle), intent(in) :: this
double precision :: area
area = this%length * this%width
end function getArea
end module Rectangle_mod
program main
use Rectangle_mod
implicit none
type(Rectangle) :: r
r = Rectangle(4.0d0, 3.0d0, 0.0d0, 2.0d0)
print *, "Rectangle with center point", r%getCenterPoint(), " has area ", r%getArea()
end program main
Link Copied
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
You may want to post this on comp.lang.fortran to get an even broader perspective on OO design patterns with Fortran. In addition, you may want to consult the books mentioned by Dr Fortran on his blog, especially the one by Rouson et al. on Scientific Software Design mentioned in the footnote.
Given Fortran's lack of "new" keyword similar to that in OO-centric languages and intricacies with type construction, my own preference is to use to simple methods that operate on classes (type-bound procedures in Fortran parlance, as you know very well) rather than constructors and in general, I try to avoid Fortran pointers (aliases) if I can, given all the complexities involving efficiency and optimization and proper clean up and in handling them in assignment contexts. So my approach would fall along the lines below where the "generic" is made use of and expanded upon to "create" the class:
module kinds_mod use, intrinsic :: iso_fortran_env, only : r8 => real64 private public :: r8 end module kinds_mod
module Shape_mod
use kinds_mod, only : r8
implicit none
private
type, abstract, public :: Shape
private
real(r8) :: centerPoint(2)
contains
private
procedure, pass(this) :: ConstructShape
procedure, pass(this), public :: getCenterPoint
procedure(IgetArea), pass(this), deferred, public :: getArea
generic, public :: Construct => ConstructShape
end type Shape
abstract interface
function IgetArea(this) result(area)
import :: Shape, r8
class(Shape), intent(in) :: this
real(r8) :: area
end function IgetArea
end interface
contains
!Correct way of defining a constructor for an abstract class?
subroutine ConstructShape(this, xCenter, yCenter)
class(Shape), intent(inout) :: this
real(r8), intent(in) :: xCenter
real(r8), intent(in) :: yCenter
print *, "constructing base shape"
this%centerPoint = [ xCenter, yCenter ]
return
end subroutine ConstructShape
function getCenterPoint(this) result(point)
class(Shape), intent(in) :: this
real(r8) point(2)
point = this%centerPoint
return
end function getCenterPoint
end module Shape_mod
module Rectangle_mod
use kinds_mod, only : r8
use Shape_mod, only : Shape
implicit none
private
type, extends(Shape), public :: Rectangle
private
real(r8) :: length
real(r8) :: width
contains
private
procedure, pass(this) :: ConstructRectangle
procedure, pass(this), public :: getArea
generic, public :: Construct => ConstructRectangle
end type Rectangle
contains
subroutine ConstructRectangle(this, length, width, xCenter, yCenter)
class(Rectangle), intent(inout) :: this
real(r8), intent(in) :: length
real(r8), intent(in) :: width
real(r8), intent(in) :: xCenter
real(r8), intent(in) :: yCenter
call this%Construct(xCenter=xCenter, yCenter=yCenter) !.. Create the base class
print *, "Constructing rectangle"
this%length = length
this%width = width
!How to invoke the base class constructor here?
!The line below works for non-abstract base classes where the
!constructor result can be type(Shape)
return
end subroutine ConstructRectangle
function getArea(this) result(area)
class(Rectangle), intent(in) :: this
real(r8) :: area
area = this%length * this%width
return
end function getArea
end module Rectangle_mod
program main use kinds_mod, only : r8 use Rectangle_mod, only : Rectangle implicit none type(Rectangle) :: r call r%Construct( length=4.0_r8, width=3.0_r8, xCenter=0.0_r8, yCenter=2.0_r8 ) print *, "Rectangle with center point", r%getCenterPoint(), " has area ", r%getArea() stop end program main
Upon execution,
constructing base shape Constructing rectangle Rectangle with center point 0.00000000000000 2.00000000000000 has area 12.0000000000000 Press any key to continue . . .
You might notice a few other stylistic preferences; the above mentioned books offer multiple views on this matter. But perhaps the important thing to note is "double precision" is deprecated in Fortran; you might find it helps to have a defined kind for floating-point types in portable code.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
The basic answer to the OP's question is "use a subroutine to carry out the steps required to "construct" the parent object", along the lines of what FortranFan shows for the abstract parent class.
For the concrete extension class, it may be worth considering using a function. With F2008 support this can simplify the code invoking the constructor (you can directly assign to a polymorphic allocatable object of declared type Shape, which might save having a temporary of declared type Rectangle), though it may come with the downside of some additional overhead associated with the "value copy" associated with assignment of the function result. In Fortran 2003 you can simulate aspects of the Fortran 2008 behaviour (and work around some ifort 15 bugs...) using ALLOCATE(...SOURCE=constructor_function(xxx)).
For the subroutine case, there may be benefits to making the argument of the object to be constructed INTENT(OUT), though this does mean that you have invoke the procedure for the parent constructor before you define any components in the extension. INTENT(OUT) gives guarantees about the state of default initialized and allocatable components, which can make subsequent construction logic simpler.
I'm in two minds about whether it is useful having these construction procedures as type bound procedures. I don't think it makes sense to override them (perhaps I'm wrong??), so its just a bit of a namespace nicety (which is still nice) with the downside of the restrictions on passed arguments.
(Deprecation of double precision is a issue of style, it is not formally obsolescent in the current or draft next standard).
- Subscribe to RSS Feed
- Mark Topic as New
- Mark Topic as Read
- Float this Topic for Current User
- Bookmark
- Subscribe
- Printer Friendly Page