Using Type-Bound Procedures in Fortran: A Simple Fortran Timer Class

In the next few posts I'll describe some of the experiments that I have been making to develop a general purpose object oriented Fortran library. Nothing here is Mac Fortran specific, so everyone is free to read along.

Fortran 2003 now has the features we need to do fully object oriented programming. In this post, I describe a simple timer class that illustrates the use of type bound procedures. The addition of this feature to the language makes calling such procedures (AKA "class methods") closer to what is done in other languages. You can download the source code for the Class here. You are free to use it as you like. Send any comments or suggestions to me through our contact page.

Fortran 95 provides the basic subroutine, cpu_time(t) to time sections of code. In its standard non-OO usage one calls it twice with two real arguments. The difference gives the elapsed time. 

The Object Oriented Timer Class

[Update 8/5/15. The class has been modified for parallel computations. See here.]

In our object-orient approach, we create a class in a module named FTTimerClass with a derived type FTTimer  that serves as the class. In the module we define the precision, TP = "Timer Precision" to which the time will be stored and reported, along with some constants we'll use to request the units the time will be reported in.  The FTTimer derived type saves the start and stop times as private instance variables (derived type components). 

      MODULE FTTimerClass 
      IMPLICIT NONE
      PRIVATE
!
!     -----------------
!     Private constants
!     -----------------
!

     
INTEGER, PARAMETER, PRIVATE :: d = 15
!
!     ----------------
!     Public constants
!     ----------------
!

     
INTEGER, PARAMETER, PUBLIC  :: TP = SELECTED_REAL_KIND(d)
     
INTEGER, PARAMETER, PUBLIC  :: TC_SECONDS = 0, &
                                     TC_MINUTES = 1, TC_HOURS = 2
!
!     ---------------------
!     Class type definition
!     ---------------------
!

     
TYPE, PUBLIC :: FTTimer
         
LOGICAL      , PRIVATE :: started    = .FALSE.
         
LOGICAL      , PRIVATE :: stopped    = .FALSE.
         
REAL(KIND=TP), PRIVATE :: startTime  = 0.0_TP
         
REAL(KIND=TP), PRIVATE :: finishTime = 0.0_TP
!
!        ========
         CONTAINS
!        ========
!

         
PROCEDURE, PASS :: start => startTimer
         
PROCEDURE, PASS :: stop  => stopTimer
         
PROCEDURE, PASS :: elapsedTime         

      END TYPE FTTimer
!
!     ========
      CONTAINS
!     ========
!
 


Type bound procedures follow the CONTAINS statement inside the type definition. They are the subroutines that start and stop the timer, plus a function that returns the elapsed time. We rename the first two procedures (the "binding name") for usage outside the module using the => syntax in case there are similarly named procedures elsewhere in the program. The elapsed time function is not renamed. The PASS option is the default, and indicates that the object is passed as the first argument of the procedure. 

The actual procedures are defined after the second CONTAINS statment, as in a F90/95 module. The startTimer procedure simply calls the F95 CPU_TIME subroutine with the start time type component, and sets the started value to .TRUE. so that we know that it has been started. We will use this to tell if we accidently call the elapsedTime function without first starting the timer. Notice that self, which is the FTTimer being PASSed into the procedure is declared by CLASS rather than TYPE to be used in a type-bound procedure.

      SUBROUTINE startTimer(self)  
         IMPLICIT NONE
         CLASS(FTTimer) :: self
         self % started = .TRUE.
         
CALL CPU_TIME(self % startTime)         
     
END SUBROUTINE startTimer

Similarly, the stopTimer procedure calls the CPU_TIME function again, this time with the stop time component. To know that we have indeed stopped the timer, we set the stopped variable to .TRUE. 

      SUBROUTINE stopTimer(self)  
         
IMPLICIT NONE
         
CLASS(FTTimer) :: self
         
CALL CPU_TIME(self % finishTime)
         self % stopped = .TRUE.
     
END SUBROUTINE stopTimer

Finally, we read the timer using the elapsedTime function. If the timer has not been started, then the function returns an elapsed time of zero. If the timer has not been stopped, it is stopped before computing the time. Finally, we have an optional parameter, units, that allows us to select the time units (seconds, minutes and hours - the default is seconds) at run time.

       FUNCTION elapsedTime(self,units)  
       
 IMPLICIT NONE
!
!        ---------
!        Arguments
!        ---------
!

         
CLASS(FTTimer)    :: self
         
INTEGER, OPTIONAL :: units
         
REAL(KIND=TP)     :: elapsedTime
!
!        ------------------------------------------
!        Return zero if the timer was never started
!        ------------------------------------------
!

         
IF ( .NOT.self % started )     THEN
            elapsedTime = 0.0_TP
           
RETURN
         END IF 
!
!        ----------------------------------------------
!        If the timer was not stopped, then return the 
!        current time elapsed
!        ----------------------------------------------
!

         IF ( .NOT.self % stopped )     THEN
           
CALL self % stop() 
         
END IF 

         elapsedTime =  self % finishTime - self % startTime

!
!        -------------------------------------
!        Convert to requested units if present
!        -------------------------------------
!

         
IF ( PRESENT(units) )     THEN

            SELECT CASE ( units )
               
CASE( TC_MINUTES ) 

                  elapsedTime = elapsedTime/60.0_TP

               CASE( TC_HOURS )

                  elapsedTime = elapsedTime/3600.0_TP

               CASE DEFAULT

            END SELECT 
         
END IF 

      END FUNCTION elapsedTime


Using the Timer with Type-Bound Procedures

The advantage of the object oriented timer is that it is easy to set up multiple timers to simultaneously time different parts of a code. The following example defines two timers, the outerTimer and the innerTimer, whose execution will overlap. At the end of the program, the timers are read and the results are printed. Note that the parentheses () are optional in the subroutine calls but required in the function calls. I just like using them. 

PROGRAM timeIt 
  USE FTTimerClass
  IMPLICIT NONE  
  TYPE(FTTimer) :: innerTimer, outerTimer
 
CALL outerTimer % start()
  ! Do some work
  CALL innerTimer % start()
  ! Do some more work
  CALL innerTimer % stop()
  ! Do even more work
  CALL outerTimer % stop()
 
PRINT *,"Outer work=",outerTimer%elapsedTime(TC_MINUTES)," min"
 
PRINT *, "Inner work = ", innerTimer % elapsedTime()," sec"
END PROGRAM timeIt



© Nocturnal Aviation Software 2011-2015. Mac and Mac OS are trademarks of Apple Inc., registered in the U.S. and other countries. iMac drawing by dinodigital. All other trademarks are the property of their respective owners. Privacy Policy. Press Releases.