this isn't your parents' fortran: managing c++ objects with modern fortran

9
46 THIS ARTICLE HAS BEEN PEER-REVIEWED. COMPUTING IN SCIENCE & ENGINEERING S OFTWARE E NGINEERING FOR CSE Modern Fortran automates dynamic memory deallocations, except in two cases: memory allocated via pointers and via a second language at the request of a Fortran driver. This article focuses on the second exception and presents a reference-counting architecture that requires minimal user intervention to safely free memory if and only if no references remain. This Isn’t Your Parents’ Fortran: Managing C++ Objects with Modern Fortran T he Fortran 77/90/95 and C/C++ language families dominate com- putational science and engineering (CSE). Over the past two decades, CSE programmers who sought the code reusabil- ity and maintainability benefits of object-oriented programming (OOP) largely flocked to C++. We’re modern Fortran enthusiasts, and we believe recent compiler support for Fortran 2003 offers an exciting opportunity to interface OOP in Fortran and C++ to leverage the sizeable code bases in each language. (Cray and IBM compil- ers fully support Fortran 2003. Also, upcoming Numerical Algorithms Group and Intel compiler releases will support all of the features discussed in this article. The Gnu and Portland Group com- pilers already support most of the features that we describe. 1 ) Among the issues that immediately arise, however, is the two languages’ differing memory-management models: Fortran places the compiler in charge of determining the lifetime of almost all data structures, but it can’t do this for memory that C++ allocates at the request of Fortran code. Because Fortran is essentially a domain-specific language, this dilemma is unique to the field of software engineering for CSE, which is this special issue’s theme. Here, we dem- onstrate how to automate dynamic memory man- agement in mixed Fortran/C++ OOP. Employing an RCA A common motivation for manipulating C++ data structures from Fortran relates to refactor- ing an existing Fortran application to exploit algorithms in a C++ library. This is, in fact, what motivates us: two of the authors (Damian Rouson and Karla Morris) develop the ForTrilinos Fortran interfaces to the Trilinos library of open source parallel C++ solvers and services (see http://trilinos.sandia.gov/packages/fortrilinos). Our end users are interested in incorporating ForTrilinos into electromagnetics, heat conduc- tion, and magnetohydrodynamics applications. We also count ourselves among those users. As fluid dynamicists by training, we’re incorporat- ing Trilinos linear algebra packages into our turbulence research codes. Although we could write C++ wrappers to manipulate Trilinos data structures for each user, providing a native For- tran object model greatly increases users’ power to vary their use cases as their application needs evolve. Damian Rouson and Karla Morris Sandia National Laboratories Jim Xia IBM 1521-9615/12/$31.00 © 2012 IEEE COPUBLISHED BY THE IEEE CS AND THE AIP

Upload: j

Post on 22-Sep-2016

228 views

Category:

Documents


0 download

TRANSCRIPT

Page 1: This Isn't Your Parents' Fortran: Managing C++ Objects with Modern Fortran

46 This arTicle has been peer-reviewed. Computing in SCienCe & engineering

S o f t w a r e E n g i n e e r i n g f o r C S E

Modern Fortran automates dynamic memory deallocations, except in two cases: memory allocated via pointers and via a second language at the request of a Fortran driver. This article focuses on the second exception and presents a reference-counting architecture that requires minimal user intervention to safely free memory if and only if no references remain.

This Isn’t Your Parents’ Fortran: Managing C++ Objects with Modern Fortran

T he Fortran 77/90/95 and C/C++ language families dominate com-putational science and engineering (CSE). Over the past two decades,

CSE programmers who sought the code reusabil-ity and maintainability benefits of object-oriented programming (OOP) largely flocked to C++.

We’re modern Fortran enthusiasts, and we believe recent compiler support for Fortran 2003 offers an exciting opportunity to interface OOP in Fortran and C++ to leverage the sizeable code bases in each language. (Cray and IBM compil-ers fully support Fortran 2003. Also, upcoming Numerical Algorithms Group and Intel compiler releases will support all of the features discussed in this article. The Gnu and Portland Group com-pilers already support most of the features that we describe.1) Among the issues that immediately arise, however, is the two languages’ differing memory-management models: Fortran places the compiler in charge of determining the lifetime of almost all data structures, but it can’t do this

for memory that C++ allocates at the request of Fortran code. Because Fortran is essentially a domain-specific language, this dilemma is unique to the field of software engineering for CSE, which is this special issue’s theme. Here, we dem-onstrate how to automate dynamic memory man-agement in mixed Fortran/C++ OOP.

employing an rCaA common motivation for manipulating C++ data structures from Fortran relates to refactor-ing an existing Fortran application to exploit algorithms in a C++ library. This is, in fact, what motivates us: two of the authors (Damian Rouson and Karla Morris) develop the ForTrilinos Fortran interfaces to the Trilinos library of open source parallel C++ solvers and services (see http://trilinos.sandia.gov/packages/fortrilinos). Our end users are interested in incorporating ForTrilinos into electromagnetics, heat conduc-tion, and magnetohydrodynamics applications. We also count ourselves among those users. As fluid dynamicists by training, we’re incorporat-ing Trilinos linear algebra packages into our turbulence research codes. Although we could write C++ wrappers to manipulate Trilinos data structures for each user, providing a native For-tran object model greatly increases users’ power to vary their use cases as their application needs evolve.

Damian Rouson and Karla MorrisSandia National LaboratoriesJim XiaIBM

1521-9615/12/$31.00 © 2012 ieee

CopubliShed by the ieee CS and the aip

CISE-14-2-Morris.indd 46 1/20/12 11:09 AM

Page 2: This Isn't Your Parents' Fortran: Managing C++ Objects with Modern Fortran

marCh/april 2012 47

Mark Gray and his colleagues developed an object-shadowing strategy to interface C++ with Fortran 95 using Fortran 95 derived types to emu-late OOP.2 In their approach, a server-language object exports a flat interface through which a driver- language shadow object accesses desired func-tionality. Server-language objects hold the data. Driver-language shadow objects contain metadata about server-language objects. The driver language initiates all of the construction and finalization. The server language executes all of the consequent dynamic memory allocations and deallocations upon receipt of driver-language requests.

Fortran’s OOP constructs inspire an elegant approach to automating the driver-language re-quests with minimal impact on user code. The solution employs three derived types to automati-cally tally references to objects, deleting an object only when the count drops to zero. A shadow-object developer need only embed the reference-counting architecture (RCA) into the shadow object, register the shadow object for reference counting when the object comes into existence, and invoke the C++ destructor when the shadow object ceases to exist. This approach has no im-pact on end-user code.

Although reference counting dates almost as far back as Fortran,3 it had greater impact on languages for which programmers have a greater need for pointer-allocated memory. Although ref-erence counting has reached a high level of art in C++,4 only a handful of authors have published reference-counting schemes for Fortran, and these prior Fortran solutions required users to manually update the reference count5 or use tools outside Fortran.6

We recently published the object-oriented de-sign (OOD) of our RCA7 and released its imple-mentation in ForTrilinos. This OOD is comprised of language-independent diagrams of program organization and behavior. Here, we describe its implementation in a common CSE context: nu-merical quadrature of ordinary differential equa-tions (ODEs). We do this using the most common CSE language mix: Fortran and C++.

Discrete Calculus for ordinary Differential equationsConsider tracking a particle through a flowing fluid or plasma. The equations of motion for a particle of mass m moving at velocity v(t) at spatial location x at time t are

ddt

tx v= ( ),

(1)

ddt

tm

v F x v g= +( , , ) ,

(2)

where F is the sum of all forces the surrounding medium exerts on the particle and g is the gravita-tional acceleration. For simplicity, we consider the case of a still fluid that influences the particle only by Stokesian drag, so F/m = −v/τP, where τP is an aerodynamic response time that depends on the fluid viscosity and the particle mass and diameter.8

Discrete time advancement occurs by inte-grating Equations 1 and 2 over one time step Δt ≡ tn+1 − tn:

x x v( ) ( ) ,t t dtn nt

t

n

n

+ = + ′+

∫1

1

(3)

v v g v( ) ( ) ,t t dtn n

pt

t

n

n

+ = + −

+

∫1

1

τ (4)

where t′ is the integration variable. Any advance-ment algorithm corresponds to a particular approximation to the integrals in Equations 3 and 4.9

A software-based discrete calculus results from encapsulating the solution vector {x, v}T in a data structure packaged with functions implement-ing the mathematical operators in Equations 3 and 4.10 Lines 9–11 in Figure 1 exemplify the use of a vector data type supporting the desired functionality. Figure 2 shows the vector imple-mentation, including the requisite operators.

Figure 2’s procedures delegate all data alloca-tions and manipulations to a faux C++ package (not shown) implemented in Fortran using For-tran’s C-interoperability features to emulate a C++ package enclosed in a C++ extern "C" {} construct. We pass only C types, and we pass by value.

Lines 13–14 in Figure 1 present the two central dilemmas resolved by our RCA. First, the user-defined operators +, .integral., *, -, and / must each request that the server language allo-cates memory for the results they produce. Each result gets passed as an operand to the operator of next-highest precedence; yet when the receiv-ing operator later terminates, the program re-tains no handle by which it could explicitly free the allocated memory. A naive implementation might delete all operands, but some arguments, such as the v operand of the * operator in line 13, must be retained for later use. A need arises to de-termine when it’s safe to deallocate an operand’s memory. Upon such determination, the natural place for the deallocation is in the object’s final

CISE-14-2-Morris.indd 47 1/20/12 11:09 AM

Page 3: This Isn't Your Parents' Fortran: Managing C++ Objects with Modern Fortran

48 Computing in SCienCe & engineering

Figure 1. Time advancement of a Stokesian particle motion in a still fluid. The particle’s properties are encapsulated in derived types that implement all the necessary operators required to time-advance the particle’s position and velocity.

1 program main

2 use iso_c_binding, only : c_double

3 use vector_implementation, only: vector

4 implicit none

5 type(vector)::x,v,g ! Position,velocity,gravity

6 real(c_double)::t=0.,t_final=1.0,dt=0.05 ! Time, end time, time step

7 real(c_double), parameter:: tau_p=0.1 ! Aerodynamic response time

8 real(c_double), parameter:: zero=0._c_double,one=1._c_double

9 x = vector([zero,zero,zero]) ! Object construction

10 v = vector([one,one,one]) ! Object construction

11 g = vector([zero,zero,-9.81_c_double]) ! Object construction

12 do while (t<t_final)

13 x = x + .integral. ( v*dt ) ! Advance position

14 v = v + .integral. ( (g - v/tau_p)*dt ) ! Advance velocity

15 t=t+dt ! Advance time

16 end do

17 ! Final clean-up:

18 call x%force_finalize();call v%force_finalize();call g%force_finalize()

19 end program

1 module vector_implementation

2 use iso_c_binding, only : c_int,c_double

3 use universal_interface, only: universal

4 use faux_cpp_server

5

6 implicit none ! Prevent implicit typing

7

8 private ! Hide everything by default

9 public :: vector ! Expose type, constructors, type-bound procedures

10

11 ! Shadow object

12 type, extends(universal) :: vector

13 private

14 integer(c_int) :: id ! C++ object identification tag

15 contains

16 procedure :: sum

17 procedure :: difference

18 procedure :: product

19 procedure :: ratio

20 procedure :: integral

21 generic :: operator(+) => sum

22 generic :: operator(-) => difference

23 generic :: operator(*) => product

24 generic :: operator(/) => ratio

25 generic :: operator(.integral.) => integral

26 procedure :: cpp_delete => call_cpp_delete_vector

27 end type

Figure 2. Vector implementation, including the requisite operators. Note the shadow vector data structure (lines 12–27) with overloaded operators (lines 21–25) and an implementation for the deferred object-destruction procedure (line 26). Continued on the next page.

CISE-14-2-Morris.indd 48 1/20/12 11:09 AM

Page 4: This Isn't Your Parents' Fortran: Managing C++ Objects with Modern Fortran

marCh/april 2012 49

28

29 ! Constructors

30 interface vector

31 module procedure new_vector,default_vector,duplicate

32 end interface

33

34 contains

35

36 type(vector) function default_vector(id)

37 integer(c_int),intent(in) :: id

38 default_vector%id = id

39 call default_vector%register_self

40 end function

41

42 type(vector) function new_vector(vec)

43 real(c_double), dimension(3) :: vec

44 new_vector = vector(cpp_new_vector(vec(1),vec(2),vec(3)))

45 end function

46

47 type(vector) function duplicate(original)

48 type(vector), intent(in) :: original

49 duplicate = vector(cpp_new_vector(original%id))

50 end function

51

52 type(vector) function sum(lhs,rhs)

53 class(vector), intent(in) :: lhs,rhs

54 sum = vector(cpp_add_vectors(lhs%id,rhs%id))

55 end function

56

57 type(vector) function difference(lhs,rhs)

58 class(vector), intent(in) :: lhs,rhs

59 difference = vector(cpp_subtract_vectors(lhs%id,rhs%id))

60 end function

61

62 type(vector) function product(lhs,rhs)

63 class(vector), intent(in) :: lhs

64 real(c_double), intent(in) :: rhs

65 product = vector(cpp_rescale_vector(lhs%id,rhs))

66 end function

67

68 type(vector) function ratio(lhs,rhs)

69 class(vector), intent(in) :: lhs

70 real(c_double), intent(in) :: rhs

71 ratio = vector(cpp_rescale_vector(lhs%id,1._c_double/rhs))

72 end function

73

74 type(vector) function integral(rhs) ! Explicit Euler quadrature

75 class(vector) ,intent(in) :: rhs

76 integral = vector(rhs)

77 end function

78

79 subroutine call_cpp_delete_vector(this)

80 class(vector),intent(inout) :: this

81 call cpp_delete_vector(this%id)

82 end subroutine

83 end module

Figure 2. Continued from the previous page.

CISE-14-2-Morris.indd 49 1/20/12 11:09 AM

Page 5: This Isn't Your Parents' Fortran: Managing C++ Objects with Modern Fortran

50 Computing in SCienCe & engineering

subroutine, which a Fortran 2003 compiler calls when no handles remain. Our approach embeds the final subroutine in the RCA so that neither the end user (the writer of main) nor the vector discrete calculus developer needs to define a final subroutine. The vector developer provides only a cpp_delete procedure that serves as a hook for the RCA to invoke the C++ destructor. All such details are invisible to the end user.

Second, when the right-hand-side (RHS) op-erator of lowest precedence (+ in lines 13–14) ter-minates, the Fortran 2003 standard obligates the compiler to finalize its result after copying it into the assignment’s left-hand side (LHS). When the object stores metadata about a server-language object, however, freeing the memory associated with the RHS result after copying the metadata invalidates the metadata. For example, the meta-data might include an identification tag that now refers to an object that was just destroyed! This dilemma even arises in the simple object-con-struction processes at lines 9–11.

rCa implementationModern Fortran lets users declare any extensible derived type as a “class,” which is a polymorphic entity that can take any runtime dynamic type supporting the declared class’s interface. Figures 3 and 4 depict three classes comprising the RCA’s Fortran implementation: an abstract hermetic class, an abstract universal class, and a concrete ref_counter class. Although users can’t directly construct an abstract class, the two abstract classes in Figure 3 provide interfaces through which all objects that have a universal parent can be ma-nipulated by invoking the procedures published by universal and hermetic.

Our RCA follows the object design pattern.11 Modeled after a Java class, the object pattern defines a class that serves as a universal base for extension by all other classes in a package. This approach embeds basic functionality in all child classes and provides a universal way to manipu-late child objects through the interface published by their universal parent. Any class that ex-tends the universal class inherits the reference-counting capacity.

The RCA also employs a surrogate design pat-tern11 to emulate C++ forward references, wherein C++ programs can refer to a type before defining it. Forward references facilitate circular depen-dencies. Because Fortran 2003 prohibits circular module dependencies, the hermetic class serves as a surrogate for the universal class whenever the ref_counter module needs to access the

underlying object. The ref_counter module can’t gain access directly because of the aggrega-tion of a ref_counter instance as a component of the universal abstract class. Furthermore, the reason universal aggregates ref_counter is that extending ref_counter (basically another mechanism for inserting it as a component) would force all child classes to implement a defined assignment.

The hermetic class imposes one critical re-quirement on all of its concrete child classes: they must implement the deferred binding cpp_delete named in line 6 of Figure 3a. Each implementation must conform to the abstract in-terface in lines 8–13. As the binding’s name and its interface imply, the role of any implementation is to instruct C++ to free the memory associated with the object on which the binding is invoked. The abstract universal class in Figure 3b ex-tends hermetic and thereby passes down the aforementioned requirements to all of its concrete child classes.

The universal class publishes two type-bound procedures in lines 10–11. The first, force_finalize, removes one reference to the child ob-ject. We intend for this method to be invoked only on entities declared in the main program, and only as the last action before program termination (as in Figure 1, line 18). These final clean-up actions re-lease any remaining dynamically allocated memory before returning control to the operating system. Child classes invoke the second universal method, register_self, inside object constructors to construct the ref_counter for each new child instance. Figure 3b implements both universal methods at lines 14–21 and prevents child classes from overriding these methods at lines 10–11.

Figure 4 shows the ref_counter implementa-tion. Each ref_counter has two pointer compo-nents (lines 6–7): an integer pointer count that tallies references and a hermetic pointer obj that holds a deep copy of the shadow object. The shadow’s obj copy is lightweight, storing only the metadata in the shadow, not the actual data in the server-side object.

The ref_counter class publishes a like-named, user-defined constructor (lines 16–21) and a defined assignment (lines 36–39). The only explicit use of these occurs in the universal class register_self procedure, wherein the constructor returns a new ref_counter and the defined assignment copies its components into the LHS before invoking grab.

The ref_counter class publishes two type-bound procedures: grab increments the reference

CISE-14-2-Morris.indd 50 1/20/12 11:09 AM

Page 6: This Isn't Your Parents' Fortran: Managing C++ Objects with Modern Fortran

marCh/april 2012 51

count and release decrements the count. If count reaches zero, release invokes cpp_delete and deallocates the count as well as the shadow’s obj deep copy. If the count isn’t zero, release just nullifies the count and obj pointer components.

The ref_counter implementation includes a finalize_ref_counter final subroutine. This ref_counter final subroutine calls release on any objects that have an associated count. Two critical subtleties are that implicit invocations

of the ref_counter defined assignment and final subroutine occur without the need to de-fine an assignment or a final subroutine in any classes into which the RCA is embedded by type extension. Even an intrinsic assignment of a universal child triggers the defined assign-ment of the embedded ref_counter compo-nent. Likewise, the universal child object going out of scope triggers an invocation of the finalize_ref_counter final subroutine, which in turn invokes release. The subsequent

Figure 3. The reference-counting architecture (RCA) has two abstract classes: (a) hermetic and (b) universal. These classes provide interfaces through which all objects that have a universal parent can be manipulated by invoking the procedures published by universal and hermetic.

1 module hermetic_interface

2 private

3 public :: hermetic

4 type, abstract :: hermetic

5 contains

6 procedure(free_memory), deferred :: cpp_delete

7 end type

8 abstract interface

9 subroutine free_memory (this)

10 import :: hermetic

11 class(hermetic), intent(inout) :: this

12 end subroutine

13 end interface

14 end module

(a)

1 module universal_interface

2 use hermetic_interface, only: hermetic

3 use ref_counter_implementation, only: ref_counter

4 implicit none

5 private

6 public :: universal

7 type, abstract, extends(hermetic) :: universal

8 type(ref_counter) :: counter

9 contains

10 procedure, non_overridable :: force_finalize

11 procedure, non_overridable :: register_self

12 end type

13 contains

14 subroutine force_finalize (this)

15 class(universal), intent(inout) :: this

16 call this%counter%release

17 end subroutine

18 subroutine register_self (this)

19 class(universal), intent(inout) :: this

20 this%counter = ref_counter(this)

21 end subroutine

22 end module

(b)

CISE-14-2-Morris.indd 51 1/20/12 11:09 AM

Page 7: This Isn't Your Parents' Fortran: Managing C++ Objects with Modern Fortran

52 Computing in SCienCe & engineering

deallocation of obj inside release causes another firing of the final subroutine. The count component’s concurrent disassociation ulti-mately prevents an additional call to release and thereby halts this recursive chain of events. The process necessitates applying the recursive attribute to the final subroutine at line 40 in Figure 4.

rCa in actionThe object construction for lines 9–11 in Figure 1 registers x, v, and g for reference counting. In previous work,7 we described RCA’s behavior in the context of an analogous object-construc-tion process. Here, we run the RCA through the more challenging obstacle course set up by the expression and assignment in line 13 of main

Figure 4. The RCA concrete ref_counter class implementation. This class provides the functionality required to construct and destroy a reference-counted object, and update the object’s count.

1 module ref_counter_implementation

2 use hermetic_interface, only : hermetic

3 private; public :: ref_counter

4 type ref_counter

5 private

6 integer, pointer :: count => null()

7 class(hermetic), pointer :: obj => null()

8 contains

9 procedure, non_overridable :: grab

10 procedure, non_overridable :: release

11 procedure :: assign; generic :: assignment(=) => assign

12 final :: finalize_ref_counter

13 end type

14 interface ref_counter; module procedure new_ref_counter; end interface

15 contains

16 function new_ref_counter(object)

17 class(hermetic), intent(in) :: object

18 type(ref_counter), allocatable :: new_ref_counter

19 allocate (new_ref_counter); allocate (new_ref_counter%count, source=0)

20 allocate (new_ref_counter%obj, source=object)

21 call new_ref_counter%grab; end function

22 subroutine grab(this)

23 class(ref_counter), intent(inout) :: this

24 if (associated(this%count)) then; this%count = this%count + 1

25 else; stop ’Error in grab: count not associated’

26 end if; end subroutine

27 subroutine release(this)

28 class (ref_counter), intent(inout) :: this

29 if (associated(this%count)) then; this%count = this%count - 1

30 if (this%count == 0) then

31 call this%obj%cpp_delete; deallocate (this%count, this%obj)

32 else; this%count => null(); this%obj => null()

33 end if

34 else; stop ‘Error in release: count not associated’

35 end if; end subroutine

36 subroutine assign (lhs, rhs)

37 class (ref_counter), intent(inout) :: lhs

38 class (ref_counter), intent(in) :: rhs

39 lhs%count =>rhs%count; lhs%obj =>rhs%obj; call lhs%grab;end subroutine

40 recursive subroutine finalize_ref_counter (this)

41 type(ref_counter), intent(inout) :: this

42 if (associated(this%count)) call this%release; end subroutine

43 end module

CISE-14-2-Morris.indd 52 1/20/12 11:09 AM

Page 8: This Isn't Your Parents' Fortran: Managing C++ Objects with Modern Fortran

marCh/april 2012 53

(see Figure 1). The generalization to line 14’s case—as well as more complicated expressions—is straightforward.

Line 13 in the main program generates a deeply nested cascade of explicit and implicit proce-dure calls. The explicit calls appear in the line’s syntax. From first to last execution, they’re the user-defined operators *, .integral., +, and the intrinsic assignment (=). Each operator delegates the actual data allocations and manipulations to the faux C++ code. The Fortran implementation of each operator thus has only one executable line: a user-defined structure-constructor call and as-signment wherein the constructor argument is the object identifier returned by the C++ procedure. Each constructor call invokes register_self to start the reference counting for the newly con-structed object.

Additionally, after each vector goes out of scope, the compiler calls the final subroutine associated with the ref_counter inside the universal parent that that vector extends. We delineate the operator executions in the follow-ing enumerated lists and the associated implicit compiler calls in sublists. Because we describe object construction elsewhere,7 our presentation omits the details of many of the calls that the com-piler handles implicitly during the construction processes embedded in each operator.

1. product operator. The binary * operator receives arguments v and dt. The operator constructs a vector shadow object to store the (identifier for) the product v*dt. Upon the operator’s termina-tion, the tally of references to the object holding v*dt is 1, corresponding to the handle (rhs at line 75 in Figure 2) that the .integral. operator at-taches to it.

2. integral operator. The unary .integral. opera-tor receives v*dt as its sole argument. For explicit Euler time advancement, this operator can simply return a copy of its argument. It delegates the copy-ing to the C++ server and passes the returned iden-tifier to a duplicate constructor that constructs a new shadow of the underlying C++ object copy. Upon termination, separate vector objects shadow separate copies of the underlying data and the object holding .integral.(v*dt) has a reference count of 1, corresponding to the handle (rhs at line 53 in Figure 2) that the + operator attaches to it upon receipt. The compiler’s behavior is as follows:

a. Because the program has no handle for v*dt, the compiler is obligated to finalize its

ref_counter component. (In our experi-ence, most compilers finalize intermediate results after evaluating the entire RHS ex-pression and assigning the final result to the LHS.)

b. The ref_counter final subroutine finalize_ref_counter calls release, dropping the v*dt reference count to zero.

c. The resultant cpp_delete call at line 31 in Figure 4 frees the memory allocated by C++.

d. The subsequent deallocate—also at line 31 in Figure 4—explicitly frees the count pointer and the shadow’s obj deep copy and implicitly causes another execution of the ref_counter final subroutine.

e. The newly unassociated status of the count halts the recursive chain of calls.

3. sum operator. The binary + operator receives vector LHS argument x and RHS .integral.(v*dt). Both arguments have reference counts of 1. Upon termination, the main program still holds a handle on x, preventing its destruction, whereas for the RHS, steps 2a through 2e repeat, leading to its destruction. The operator result has a refer-ence count of 1, corresponding to the handle that the assignment holds on it.

4. assignment. The intrinsic assignment (=) takes in the LHS argument x and RHS result of the + operator. The compiler produces the following cascade of calls:

a. The language semantics require that the compiler first finalize the LHS, invoking steps 2a through 2e on x.

b. Next, the compiler executes the ref_counter component’s defined assignment, includ-ing a pointer assignment of the LHS ref_counter components (count, obj) to their RHS counterparts.

c. The defined assignment calls grab, increas-ing the object’s reference count as both x and the result of the + operator hold a reference to the same server object.

d. Upon termination, no handle remains for the RHS, so the compiler finalizes the shadow object.

e. The f inal subroutine, finalize_ref_counter, is invoked in the RHS.

f. A call to release decreases the count of ref-erences to the server object from 2 to 1.

The same systematic behavior results for any operator combination: timely destruction of the

CISE-14-2-Morris.indd 53 1/20/12 11:09 AM

Page 9: This Isn't Your Parents' Fortran: Managing C++ Objects with Modern Fortran

54 Computing in SCienCe & engineering

shadow and server objects occurs for any object constructed by a user-defined constructor. The force_finalize calls in line 18 of Figure 1—good programming practice, although not imperative—free all remaining memory before the program terminates.

Last, consider the cyclic references that break most reference-counting schemes when an object A refers to an object B, which refers back to A. In our RCA, A=B establishes A as a reference to B. If users want to copy B into A, retaining two distinct objects, they must pass B as an argument to a copy constructor: A=vector(B).

type(vector) :: A,B

A=vector([zero,zero,zero]);

B=vector([zero,zero,zero])

A=B; B=A

Given the semantics just explained, a cycle seems the likely result. In actuality, after con-structing A and B, A=B deletes A (and the C++ ob-ject it shadows) and assigns B to A. There are then two references to B. Next, B=A deletes one refer-ence to B (but not the C++ data) and assigns A to B, yielding two references. The force_finalize in main then destroys one reference. The second call ultimately destroys the last reference and the C++ object.

T his RCA implementation manages shadow objects’ lifetimes and their server-language counterparts, pre-venting memory leaks and premature

memory release. One implementation of the RCA appears in the recently released ForTrilinos par-allel solver interfaces. Current ForTrilinos pack-ages use the message passing interface (MPI) distributed-memory parallel library. Future work will include developing a thread-safe RCA suit-able for use with shared-memory parallel- programming models.

Here, we demonstrated RCA in Fortran in the challenging context of a discrete calculus for ODEs. However, we’ve also had success using it in solving partial differential equations, which we’ll present in a future publication.

references1. I.D. Chivers and J. Sleightholme, “Compiler Support

for the Fortran 2003 and 2008 Standards,” ACM

Fortran Forum, vol. 31, no. 2, 2009, pp. 15–20.

2. M.G. Gray, R.M. Roberts, and T.M. Evans, “Shadow-

Object Interface between Fortran 95 and C++,”

Computing in Science & Eng., vol. 1, no. 2, 1999,

pp. 63–70.

3. G.E. Collins, “A Method for Overlapping and Erasure of

Lists,” Comm. ACM, vol. 3, no. 12, 1960, pp. 655–657.

4. R.A. Bartlett, Teuchos C++ Memory Management

Classes, Idioms, and Related Topics, tech. report

SAND2010-2234, Sandia Nat’l Laboratory, 2011.

5. G.W. Stewart, “Memory Leaks in Derived Types

Revisited,” ACM Fortran Forum, vol. 22, no. 3, 2003,

pp. 25–27.

6. D. Car, “A Reference Counting Implementation in

Fortran 95/2003,” ACM Fortran Forum, vol. 29, no. 1,

2010, pp. 21–28.

7. K. Morris, D.W.I. Rouson, and J. Xia, “On the Object-

Oriented Design of Reference-Counted Shadow Ob-

jects,” Proc. Int’l Workshop Software Eng. for Computa-

tional Science and Eng., ACM, 2011, pp. 19–27.

8. C.T. Crowe, M. Sommerfeld, and Y. Tsuji, Multiphase

Flows with Droplets and Particles, CRC Press, 1998.

9. G.H. Golub and J.M. Ortega, Scientific Computing and

Differential Equations: An Introduction to Numerical

Methods, Academic Press, 1992.

10. D.W.I. Rouson, “Towards Analysis-Driven Scientific

Software Architecture: The Case for Abstract Data

Type Calculus,” Scientific Programming, vol. 16, no. 4,

2008, pp. 329–339.

11. D.W.I. Rouson, J. Xia, and X. Xu, Scientific Software

Design: The Object-Oriented Way, Cambridge Univ.

Press, 2011.

damian rouson is the manager of the Reacting Flows Research Department at Sandia National Laborato-ries and the architect of the ForTrilinos and Morfeus open source software projects. His research interests include scientific software design, multiphysics mod-eling, and classical-, quantum-, and magneto-fluid turbulence. Rouson has a PhD in mechanical en-gineering from Stanford University. Contact him at [email protected].

Karla Morris is a senior member of technical staff in the Reacting Flows Research Department at Sandia National Laboratories, where she is the lead developer of ForTrilinos (the object-oriented Fortran 2003 inter-faces to Trilinos). Her research interests include com-putational fluid dynamics to multiphysics flows and scientific software architecture. Morris has a PhD in mechanical engineering from The City University of New York. Contact her at [email protected].

Jim Xia is a consultant with IBM. His research interests include programming languages, software design, software architecture, and system configurations. Xia has a PhD in physics from the University of Western Ontario, Canada. Contact him at [email protected].

CISE-14-2-Morris.indd 54 1/20/12 11:09 AM