The bridge pattern is one of the famous patterns introduced by the Gang of Four, meant to “decouple an abstraction from its implementation so that the two can vary independently”. The main purposes of the pattern are,
- to allow the abstraction and its implementation to be extended independently from each other
- allow the implementation to be selected at runtime.
There are situations in software development where concealing implementation details becomes necessary. This might be to safeguard intelectual property, or to facilitate bug fixes while retaining binary code compatibility, typically in combination with shared libraries. The bridge is also useful in this situation.
A common way of implementing this pattern is by using an opaque pointer. In C++ this is also called the “pointer to implementation idiom” or just “Pimpl”:
// Visible.h
class Visible {
public:
Visible(); // Constructor
void do_something()
// ... Other operations ...
private:
struct Impl_; // forward declaration
std::unique_ptr<Impl_> impl; // the pimpl
};
// Visible.cpp
struct Visible::Impl_ {
// ... secret implementation details ...
}
// Constructor
Visible::Visible() : impl(std::make_uniqze<Impl_>()) {}
void Visible::do_something() {
}
// ... Operations ...
To keep the actual implementation hidden from the end-user of the library, you would distribute the header and a shared library with the executable contents of the compiled .cpp
file. In a real business scenario you may accompany this with a end-user license agreement that prohibits disassembly and reverse engineering.
Fortran doesn’t support forward declarations in the way C++ does. What we can do instead is to use a c_ptr
:
type :: visible
private
type(c_ptr) :: impl_
end type
Another (older) approach is to simply use an integer scalar or array as a pseudo-handle. (This approach is used by the Pardiso library.)
I’ve been imagining what the modern Fortran approach would look like, using a sub-module and a private base class. For instance:
! flux_capacitor.f90
!
! Public Flux Capacitor API
!
module flux_capacitor
implicit none
private
public :: flux_capacitor_t
type :: flux_capacitor_t
private
class(fc_impl), allocatable :: impl
contains
procedure, public :: charge
procedure, public :: run
procedure, public :: shutdown
end type
type :: fc_impl
end type
interface
module subroutine charge(cap,power)
class(flux_capacitor_t), intent(out) :: cap
real, intent(in) :: power
end subroutine
module subroutine run(cap)
class(flux_capacitor_t), intent(inout) :: cap
end subroutine
module subroutine shutdown(cap)
class(flux_capacitor_t), intent(inout) :: cap
end subroutine
end interface
end module
! flux_capacitor_impl.f90
!
! Private implementation (only distribute this in binary object format!)
!
submodule (flux_capacitor) flux_capacitor_impl
use, intrinsic :: iso_fortran_env, only: error_unit
implicit none
type, extends(fc_impl) :: impl
logical :: connected
real :: power ! jigawatts
end type
contains
module subroutine charge(cap,power)
class(flux_capacitor_t), intent(out) :: cap
real, intent(in) :: power
type(impl), allocatable :: this
this = impl(.true.,power=power)
call move_alloc(from=this,to=cap%impl)
end subroutine
module subroutine run(cap)
class(flux_capacitor_t), intent(inout) :: cap
if (.not. allocated(cap%impl)) then
write(error_unit,'(A)') &
"error: flux_capacitor%run: the flux capacitor is not charged."
error stop 1
end if
select type(this => cap%impl)
type is (impl)
print *, "Flux capacitor running at ", this%power, "jigawatts."
end select
end subroutine
module subroutine shutdown(cap)
class(flux_capacitor_t), intent(inout) :: cap
! ... reserved for future variations ...
end subroutine
end submodule
On Linux, the flux capacitor library can be compiled as follows (note the explicit usage of the instruction set and the symbol visibilty),
FC=gfortran-13
FFLAGS=-O2 -march=x86-64-v2 -fPIC -fvisibility=hidden
main: main.f90 libflux_capacitor.so
$(FC) -O2 -L./ -o $@ $< -lflux_capacitor
libflux_capacitor.so flux_capacitor.mod: flux_capacitor.f90 flux_capacitor_impl.f90
$(FC) -shared $(FFLAGS) -o $@ $^
.PHONY: flux_capacitor.tar.gz
flux_capacitor.tar.gz: libflux_capacitor.so flux_capacitor.mod
tar -czvf $@ $^
One caveat of Fortran is the compiled module format is compiler-specific.
Are there any other aspects which are relevant?