Doubts about polymorphism in Fortran

  TYPE,ABSTRACT :: propiedad_casa
   END TYPE propiedad_casa

  TYPE,EXTENDS(propiedad_casa) :: propiedad_interna
    type(svg_color):: piso
    type(svg_color):: pared
    REAL(8) :: costo_disen = -0.1d0
    REAL(8) :: costo_piso = -0.1d0
    REAL(8) :: costo_pared = -0.1d0
    CHARACTER(LEN=10) ::  material_piso  = "" 
    CHARACTER(LEN=10) :: material_pared = ""
  END TYPE propiedad_interna

  TYPE,EXTENDS(propiedad_casa) :: propiedad_externa
    type(svg_color):: piso
    type(svg_color):: frontera
    REAL(8) :: costo_prod = -0.1d0
    REAL(8) :: costo_piso = -0.1d0
    REAL(8) :: costo_frontera = -0.1d0
    CHARACTER(LEN=10) ::  material_piso  = "" 
    CHARACTER(LEN=10) :: material_frontera = ""
END TYPE propiedad_externa

 SUBROUTINE prototipos_casa(name, props)
    CHARACTER(LEN=*), INTENT(IN) :: name
    CLASS(propiedad_casa), INTENT(IN) :: props
    INTEGER :: idx
    ! Verificar si ya existe
    idx = get_props_index(name)
    IF (idx > 0) THEN
      ! Actualizar propiedades existentes
      props_map(idx) = props
    ELSE
      ! Agregar nuevas propiedades
      num_props = num_props + 1
      IF (.NOT. ALLOCATED(props_map)) THEN
        ALLOCATE(props_map(1), props_names(1))
      ELSE
        CALL resize_props_map(num_props)
      END IF
      props_map(num_props) = props
      props_names(num_props) = name
    END IF
  END SUBROUTINE prototipos_casa

This code worked when there was only
TYPE,EXTENDS(propiedad_casa) :: propiedad_interna

  • But when adding more types, I am forced to use polymorphism to avoid creating a subroutine for each type, which is why I have the following question

When to use MOLD or SOURCE in ALLOCATE ?

     ALLOCATE(props_map(num_props), MOLD=props)    
     ALLOCATE(props_map(num_props), SOURCE=props)

Welcome to the forum @zzz!

Please remember:

  • mold: props_map takes the same type as prop, but not the contents: it will be an empty array
  • source: props_map takes both the type and contents of prop, i.e, all elements 1:num_props of the array will contain one copy of prop.
1 Like

This is unrelated to your question, but you might want to think of inheritance as a last resort (i.e., when components might substantially differ).
In the code you showed, both types can be dealt with with simple indices:

  INTEGER, PARAMETER :: INTERNA = 1, EXTERNA = 2

  TYPE,EXTENDS(propiedad_casa) :: propiedad_intex
    INTEGER :: tipo
    TYPE(svg_color):: color(2)
    REAL(8) :: costo(0:2) = -HUGE(1.d0)
    CHARACTER(LEN=10) ::  material(2)  = ""
  END TYPE propiedad_intex

  ! ĂŤndices para propiedades internas
  INTEGER, PARAMETER :: DISENNO = 0, PISO = 1, PARED = 2

  ! ĂŤndices para propiedades externas
  INTEGER, PARAMETER :: PROD = 0, FRONTERA = 2   ! PISO is the same

So, for example, an internal property can be handled as:

TYPE(propiedad_intex) :: a
a%tipo = INTERNA

! ... Set costs here ...

print*,'Costo de piso=',a%costo(PISO)
print*,'Costo de pared=',a%costo(PARED)

a%costo(DISENNO) = SUM(a%costo([PISO, PARED]))
print*,'Costo de diseño=',a%costo(DISENNO)

Notice that I changed the default cost to -HUGE(1.d0), to make it easier to know that something goes wrong if a proper value is not set.

The Fortran array model assumes that all members of an array have the same type. So if you need to maintain a list of properties, the following won’t work:

class(propiedad_casa), allocatable :: props_map(:)

! All elements of the array have the same dynamic type
allocate( propriedad_externa :: props_map(100) )

To have different polymorphic entities in an array, you will need to introduce another type (we really ought to find a better name for such “wrapper” types):

type :: any_prop
   class(propiedad_casa), allocatable :: p
end type

type(any_prop), allocatable :: props_map(:)

allocate(props_map(10))

props_map(1)%p = propriedad_interna(piso=...,pared=...)
props_map(2)%p = propriedad_externa(piso=...,frontera=...)
...

Otherwise I agree with @jwmwalrus that a non-polymorphic solution may be a better fit. If it is only two types, I can certainly imagine just keeping two lists:

type :: properties
  type(propiedad_interna), allocatable :: pi(:)
  type(propiedad_externe), allocatable :: pe(:)
end type