Extendable object factories with OOP Fortran

Dear Fortran community, in our Fortran OOP code, we take advantage of the factory-object to initialize the right object based on a string, coming from user input. We use a simple if-else construct in subroutine, like this

  subroutine factory(concrete_type, typename)
    class(base_t), intent(inout), allocatable :: concrete_type
    character(len=*) :: typename

    if (trim(typename) .eq. 'type1') then
       allocate(type1_t::concrete_type)
    else if (trim(typename) .eq. 'type2') then
       allocate(type2_t::concrete_type)
    end if
  end subroutine

Dead simple and works as intended. But the obvious issue here is that whenever a new subtype of base_t is added to the code, it should be manually added to the factory. Not a big deal, perhaps, but we envision that in the future people will write their own subcomponents to our code, which will add new subtypes. We will probably not want to integrate all of those centrally, so people would have to maintain their own fork, where they added the subtype to the factory.

An ideal alterantive would be something similar to the following Julia code, which was recently shared in a blog post.

module RegisterFruitFactory

    abstract type Fruit end

    const FRUIT_MAP = Dict{String, DataType}()

    function register!(fruit::Type{<:Fruit}, name::String)
        FRUIT_MAP[name] = fruit
    end

    function fruit(str::String)
        fruit_type = get(FRUIT_MAP, str, nothing)
        if isnothing(fruit_type)
            error("Unknown fruit $str")
        else
            return fruit_type()
        end
    end
end

# Add type to the factory in a separate module
module RegisterFruitExtension
    import ..RegisterFruitFactory
    struct Banana <: RegisterFruitFactory.Fruit end
    RegisterFruitFactory.register!(Banana, "banana")
end

So there is basically a map from string to type, which can be extended in submodules. I’ve been trying to wrap my head around whether this is possible to achieve in Frotran, and could not arrive to a solution.

Does anyone have an idea? Or maybe knows another way of creating an extendable factory.

1 Like

One approach may be to register some “make” routine with a module variable and then use the latter with a specified typename…? (but I am afraid I may not have understood the question very well…)

module basket_m
    implicit none

    type, abstract :: Fruit_t
    end type

    type Maker_t
        procedure(make_i), pointer, nopass :: make
        character(50) :: name = ""
    end type

    integer       :: ntype = 0
    type(Maker_t) :: makers(100)

    abstract interface
        subroutine make_i(fruit)
            import; implicit none
            class(Fruit_t), allocatable :: fruit
        end
    end interface

contains
    subroutine register(make, name)
        procedure(make_i) :: make
        character(*) :: name

        ntype = ntype + 1
        makers(ntype)% make => make
        makers(ntype)% name = trim(name)
    end

    subroutine make(fruit, name)
        class(Fruit_t), allocatable :: fruit
        character(*) :: name
        integer i

        do i = 1, ntype
            if (makers(i)% name == name) &
                call makers(i)% make(fruit)
        end do
    end
end module

module apple_m
    use basket_m, only: Fruit_t
    implicit none

    type, extends(Fruit_t) :: Apple_t
    end type

contains
    subroutine make_apple(fruit)
        class(Fruit_t), allocatable :: fruit

        print *, "making an apple..."
        allocate( Apple_t :: fruit )
    end
end module

program main
    use basket_m, only: Fruit_t, register, make
    use apple_m,  only: make_apple
    implicit none

    class(Fruit_t), allocatable :: fruit

    call register( make_apple, "apple" )
    call make( fruit, "apple" )
end

Compile and run:

$ gfortran-10 test.f90 && ./a.out
 making an apple...

@timofeymukha ,

Welcome to the Discourse.

The answer to your inquiry is technically a no. You can consider a user derived type that gets you a rudimentary “dictionary” class but note Fortran doesn’t quite support the kind of type introspection and reflection type of facilities needed to get you anything like the Julia code. You will instead need to consider a much poorer person’s design using other data types (strings, integers/enums) combined with programming logic and it will still somewhat clunky.

Re: “in our Fortran OOP code, we … factory-object to initialize the right object based on a string,” note with the OO approach involving Fortran, one often needs to do Fortran-specific object-oriented analysis (OOA) followed by Fortran-specific object-oriented design (OOD) before jumping into the programming. If you try to apply OO patterns for fully object-oriented languages (e.g., OCaml) and try to apply them to Fortran without suitable adaptation, it can prove unwieldy. The factory pattern can be one such casualty given the poor support for object construction in Fortran and the need for setters to construct an object.

The closest way to achieve what you want IMHO is an array of containers for all your extensible derived types:

  1. require each type to procure their registered name:
type, abstract :: base_t
   ...
  procedure(registered_name), deferred :: name
end type base_t
  1. Have a data struct of polymorphic containers (showing an array here, could well be a list), where a new instance is added each time an extended type is registered
type :: registered
   class(base_t), allocatable :: x ! needs to be allocated with the registered type
end type registered

type(registered), allocatable :: registered_classes(:)
  1. Generate by searching for them:
subroutine class_by_name(name,object)
   character(*), intent(in) :: name
   class(base_t), allocatable, intent(out) :: object

   do i=1,size(registered_classes)
      if (registered_classes(i)%x%name()==name) then 
          allocate(object,mold=registered_classes(i)%x)
          return
      endif
   end do
end subroutine
1 Like

Thank you for the comments and the suggestions! What seems to be the gist of the issue to me is that even with the solutions of @FedericoPerini and @septc, there needs to be some code, where we add the types to the factory object. For example, the statement call register( make_apple, "apple" ). What will happen in practice is that a subroutine to collect these statements will be created, and so one is essentially back to the same approach as with a simple if-else: those extending the code will have to modify this central subroutine. What one would theoretically need is some magic way of having call register( make_apple, "apple" ) in the apple_m module itself and have it execute automagically :slight_smile:

1 Like

Thanks for your additional input, and I guess I’ve understood the gist of the problem more… Probably, the need is to completely separate the main or host codes from any user add-on codes (about new types), such that it is not necessary to update any main/host codes for object creation?

(FWIW, in my codes I added the factory routines manually every time a new child type was added, because the total number of different types was pretty limited.)

Now I tried to think about possible “automagical” way to do this, but still not in success… (so I’m also interested to learn if it is available).

Though a workaround, if it is no problem to rely on other tools/languages for pre-processing, another approach might be to create the body of factory() routine programmatically with Python or something, e.g., first asking the author of a new type to attach some tag above the type definition, and use some Python script to search all sources to find such tags and create a body of factory() on the fly before compilation… :farmer:

[[createfactory]]    <-- some tag
type Apple_t
...
end type

Another workaround might be to add an auxiliary C++ code for bootstrapping a “module initializer” routine, something like

!! mylib_mod.f90
module mylib_m
    use iso_c_binding
    implicit none
contains

function mylib_init() result(err) bind(c)
    integer(c_int) :: err
    print *, "entering mylib_init()"
    err = 0
end

end module

// mylib_aux.cpp
extern "C" int mylib_init();
int mylib_err = mylib_init();

!! main.f90
program main
    print *, "fort main"
end

$ gfortran mylib_mod.f90 mylib_aux.cpp main.f90 && ./a.out
 entering mylib_init()
 fort main

mylib_aux.cpp might be written manually by the author of a new type, or possibly created automatically by some Python script (but I guess the timing of such auto-initialization may need careful check because two different languages are involved).

I think it would be great if Fortran has a “module initializer” feature (like in some other languages) because it makes the above kind of coding much simpler… (and also the timing of auto-initialization etc are specified explicitly by each language).

1 Like

You could try putting the relevant code in a final routine (see here) but I don’t believe the attempt would be successful, because to trigger it’s call, you need either an allocatable or an automatic instance of your class being finalized exiting a routine

@septc The idea of using C bindings is very nice. It seems to work, at least in a demo. I’ve created a github repo with a proof of concept

1 Like