<p><b>ringler@lanl.gov</b> 2009-08-10 20:50:49 -0600 (Mon, 10 Aug 2009)</p><p><br>
added basic timer code.<br>
<br>
module_timer.F has directions for use at the top of the file.<br>
<br>
briefly, &quot;call timer_start(&quot;string&quot;) to start time associated with &quot;string&quot; and<br>
call timer_stop(&quot;string&quot;) to stop the time. Recursive start/stop with the<br>
same string accumulates time associated with &quot;string&quot;. Call write_timer() to<br>
have each proc dump results to stdout.<br>
</p><hr noshade><pre><font color="gray">Modified: trunk/swmodel/Makefile
===================================================================
--- trunk/swmodel/Makefile        2009-08-11 00:00:58 UTC (rev 21)
+++ trunk/swmodel/Makefile        2009-08-11 02:50:49 UTC (rev 22)
@@ -8,7 +8,7 @@
 #FFLAGS = -qrealsize=8 -g -C 
 #CFLAGS = -g
 #LDFLAGS = -g -C
-

 FC = mpif90
 CC = mpicc
 FFLAGS = -r8 -O3
@@ -31,6 +31,7 @@
 CPP = cpp -C -P -traditional
 
 OBJS = swmodel.o \
+       module_timer.o \
        module_configure.o \
        module_constants.o \
        module_test_cases.o \
@@ -47,7 +48,7 @@
 
 all: swmodel
 
-swmodel.o: module_configure.o module_dmpar.o module_grid_types.o module_test_cases.o module_io_input.o module_sw_solver.o
+swmodel.o: module_configure.o module_dmpar.o module_grid_types.o module_test_cases.o module_io_input.o module_sw_solver.o module_timer.o
 
 module_grid_types.o: module_dmpar.o
 
@@ -59,7 +60,7 @@
 
 module_io_output.o: module_grid_types.o module_dmpar.o module_sort.o
 
-module_sw_solver.o: module_configure.o module_grid_types.o module_io_output.o module_time_integration.o module_dmpar.o
+module_sw_solver.o: module_configure.o module_grid_types.o module_io_output.o module_time_integration.o module_dmpar.o module_timer.o
 
 module_time_integration.o: module_grid_types.o module_configure.o module_dmpar.o
 

Modified: trunk/swmodel/module_sw_solver.F
===================================================================
--- trunk/swmodel/module_sw_solver.F        2009-08-11 00:00:58 UTC (rev 21)
+++ trunk/swmodel/module_sw_solver.F        2009-08-11 02:50:49 UTC (rev 22)
@@ -5,6 +5,7 @@
    use time_integration
    use configure
    use dmpar
+   use timer
 
    integer :: iframe
 
@@ -53,7 +54,9 @@
       !   time step, and time level 2 stores the state advanced dt in time by timestep(...)
       do itimestep = 1,ntimesteps     
          write(0,*) 'Doing timestep ', itimestep
+         call timer_start(&quot;time integration&quot;)
          call timestep(domain, dt) 
+         call timer_stop(&quot;time integration&quot;)
 
          ! Move time level 2 fields back into time level 1 for next time step
          call shift_time_levels(domain)

Added: trunk/swmodel/module_timer.F
===================================================================
--- trunk/swmodel/module_timer.F                                (rev 0)
+++ trunk/swmodel/module_timer.F        2009-08-11 02:50:49 UTC (rev 22)
@@ -0,0 +1,398 @@
+      MODULE timer
+!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+! This module contains utilities for timing individual blocks of code.
+!
+! The module is comprised of three subroutines.  These are discussed below:
+!
+! 1) timer_start.  This subroutine starts a timer.
+!
+!    input:   event_name   CHARACTER (LEN=72)  name of event
+!             clear_timer  LOGICAL,OPTIONAL    clear accumulated times
+!
+!      The block of code being timed is associated with an event.  
+!      The subroutine argument is a character string called event_name.  
+!      The character string provides a name for the event (or block of code)
+!      to be timed.   A timer event has a logical attribute called &quot;running&quot; 
+!      to indicate if the timer is &quot;on&quot; or &quot;off&quot;.  This is analogous to 
+!      a stopwatch being &quot;on&quot; or &quot;off&quot;.
+!
+!      If the event does not already exist, its start time is initialized 
+!      to the current time, and the timer is turned on.  On the other hand, 
+!      if the event already exists and the timer is off, then the start 
+!      time is re-initialized to the current time, and the timer is turned 
+!      on.  If it already exists and is on, nothing happens.
+!
+!      The optional argument, clear_timer, allows the accumulated times 
+!      associated with the event to be cleared.
+!
+! 2) timer_stop.   this subroutine stops a timer.
+!
+!    input:   event_name   CHARACTER (LEN=72) name of event
+!
+!      This subroutine records the current time and turns the timer off.
+!      It subtracts the start time of the input event from the current time 
+!      and records accumulated time for the event.
+!
+! 3) timer_write.  this subroutine writes a list of the timings.
+!
+!    input:   event_name   CHARACTER (LEN=72) name of event
+!
+!      This subroutine writes a list of times for each event.
+!     
+!      If an event called &quot;total time&quot; has been initiated, then
+!      the subroutine writes the fractional time of the total time 
+!      for each event.
+!
+! For example...
+!
+!     CALL timer_start (&quot;total time&quot;)
+!     DO i = 1,100
+!     
+!        CALL timer_start (&quot;event 1&quot;)
+!            &lt; code block 1 &gt;
+!        CALL timer_stop  (&quot;event 1&quot;)
+!
+!        CALL timer_start (&quot;event 2&quot;)
+!            &lt; code block 2 &gt;
+!        CALL timer_stop  (&quot;event 2&quot;)
+!     ENDDO
+!
+!     CALL timer_stop (&quot;total_time&quot;)
+!     CALL timer_write ()
+!
+!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+      IMPLICIT NONE
+      SAVE
+      PRIVATE
+
+      include 'mpif.h'
+
+      TYPE timer_node
+         CHARACTER (LEN=72) :: event_name
+         LOGICAL  :: running
+         REAL  ::  cpu_start, cpu_stop, cpu_total
+         REAL  :: wall_start,wall_stop,wall_total
+         TYPE (timer_node), POINTER :: next
+      END TYPE timer_node
+
+      TYPE (timer_node), POINTER :: timer_events
+
+! public member functions
+      PUBLIC ::                                                      &amp;
+         timer_start,                                                &amp;
+         timer_stop,                                                 &amp;
+         timer_write
+      CONTAINS
+!cccccccc1ccccccccc2ccccccccc3ccccccccc4ccccccccc5cccgtgccc6ccccccccc7cc
+      SUBROUTINE timer_start (event_name,clear_timer)
+! 19 SEPTEMBER 2002   
+      CHARACTER (LEN=*),INTENT (IN) :: event_name
+      LOGICAL ,OPTIONAL,INTENT (IN) :: clear_timer
+      LOGICAL  :: event_added,event_found,string_equal
+      INTEGER  :: clock,hz
+      TYPE (timer_node), POINTER :: current,temp
+
+      event_added = .FALSE.
+      event_found = .FALSE.
+!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+! THE FIRST TIME timer_start IS CALLED, INITIALIZE LIST
+!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+      IF (.NOT.ASSOCIATED (timer_events)) THEN
+         event_added = .TRUE.
+         ALLOCATE (timer_events); ALLOCATE (timer_events%next)
+         timer_events%event_name = ' '
+         current =&gt; timer_events%next
+         NULLIFY (current%next)
+      ELSE
+!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+! LOOK THROUGH THE LIST OF EVENTS TO FIND EVENTS WHICH ALREADY EXIST
+!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+         current =&gt; timer_events
+         DO WHILE ((.NOT.event_found).AND.(ASSOCIATED (current)))
+!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+! IF AN EVENTS NAME IS ALREADY ON THE LIST, THEN IT ALREADY EXISTS.
+!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+            string_equal = (TRIM (current%event_name)==TRIM (event_name))
+            IF (string_equal) THEN
+               event_found = .TRUE.
+            ENDIF
+!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+! IF NOT FOUND, THEN KEEP LOOKING
+!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+            IF (.NOT.event_found) THEN
+               current =&gt; current%next
+            ENDIF
+         ENDDO
+!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+! IF NOT FOUND, THEN LOOK THROUGH LIST TO FIND POSITION TO ADD NEW EVENT
+!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+         IF (.NOT.event_found) THEN
+            current =&gt; timer_events
+            DO WHILE ((.NOT.event_added).AND.(ASSOCIATED (current%next)))
+!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+! ADD A NEW NODE IN THE MIDDLE OF THE LIST
+!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+               IF (LLT (TRIM (current%event_name),TRIM (event_name)).AND.    &amp;
+                   LLT (TRIM (event_name),TRIM (current%next%event_name))) THEN
+                  event_added = .TRUE.
+                  temp =&gt; current%next
+                  NULLIFY (current%next); ALLOCATE (current%next)
+                  current =&gt; current%next
+                  current%next =&gt; temp
+               ENDIF
+!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+! IF NOT ADDED, THEN KEEP LOOKING
+!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+               IF (.NOT.event_added) THEN
+                  current =&gt; current%next
+               ENDIF
+            ENDDO
+         ENDIF
+!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+! IF THE END OF THE LIST IS REACHED AND NOT ADDED 
+! AND NOT DOES NOT ALREADY EXIST THEN ADD TO END OF LIST
+!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+         IF ((.NOT.event_added).AND.(.NOT.event_found)) THEN
+            event_added = .TRUE.
+            ALLOCATE (current%next)
+            current =&gt; current%next
+            NULLIFY (current%next)
+         ENDIF
+      ENDIF
+!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+! IF NEW EVENT ADDED, THEN INITIALIZE STUFF
+!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+      IF (event_added) THEN
+         current%event_name = event_name
+         current%running    = .FALSE.
+         current% cpu_total = 0.0
+         current%wall_total = 0.0
+      ENDIF
+!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+! If (NEW EVENT ADDED) OR (THE EVENT WAS FOUND ON THE LIST BUT IS NOT
+! CURRENTLY running) THEN TURN TIMER ON AND GET THE BEGINNING TIME
+!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+      IF ((event_added).OR.((event_found).AND.(.NOT.current%running))) THEN
+         current%running   = .TRUE.
+
+         current% cpu_start = 0.0 ! figure this out later
+
+         CALL system_clock (count=clock)
+         CALL system_clock (count_rate=hz)
+         current%wall_start = REAL (clock)/REAL (hz)
+
+      ENDIF
+
+      IF (PRESENT (clear_timer)) THEN
+         IF (clear_timer) THEN
+            current% cpu_start = 0.0
+            current% cpu_stop  = 0.0
+            current% cpu_total = 0.0
+            current%wall_start = 0.0
+            current%wall_stop  = 0.0
+            current%wall_total = 0.0
+         ENDIF
+      ENDIF
+
+      END SUBROUTINE timer_start
+!cccccccc1ccccccccc2ccccccccc3ccccccccc4ccccccccc5cccgtgccc6ccccccccc7cc
+      SUBROUTINE timer_stop (event_name)
+! 19 SEPTEMBER 2002    
+      LOGICAL  :: event_found,string_equal
+      INTEGER :: clock,hz
+      CHARACTER (LEN=*), intent(in) :: event_name
+      TYPE (timer_node), POINTER :: current
+
+      event_found = .FALSE.
+
+      IF (.NOT.ASSOCIATED (timer_events)) THEN
+         PRINT *,' timer_stop :: timer_stop called with no events initiated '
+         STOP
+      ELSE
+         current =&gt; timer_events
+         DO WHILE ((.NOT.event_found).AND.(ASSOCIATED (current)))
+!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+! THE EVENT IS FOUND
+!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+            string_equal = (TRIM (current%event_name)==TRIM (event_name))
+            IF (string_equal) THEN
+               event_found = .TRUE.
+            ENDIF
+!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+! IF NOT FOUND THEN KEEP LOOKING
+!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+            IF (.NOT.event_found) THEN
+               current =&gt; current%next
+            ENDIF
+         ENDDO
+!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+! IF THE END OF THE LIST IS REACHED AND EVENT NOT FOUND THEN ERROR
+!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+         IF (.NOT.event_found) THEN
+            PRINT *,' timer_stop :: timer_stop called with event_name = &quot;',  &amp;
+                                                           event_name,'&quot;'
+            PRINT *,'               this event has not been initiated  '
+            STOP
+         ENDIF
+      ENDIF
+!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+! IF THE TIMER IS CURRENTLY running, THEN TURN THE TIMER OFF, 
+! GET THE STOPPING TIME AND TOTAL ACCUMULATED TIME
+!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+      IF (current%running) THEN
+        current%running   = .FALSE.
+
+        current% cpu_stop = 0.0 ! figure this out later
+
+        CALL system_clock (count=clock)
+        CALL system_clock (count_rate=hz)
+        current%wall_stop = REAL (clock)/REAL (hz)
+
+      current% cpu_total = current% cpu_total +                              &amp;
+                                  (current% cpu_stop-current% cpu_start)
+      current%wall_total = current%wall_total +                              &amp;
+                                  (current%wall_stop-current%wall_start)
+      ENDIF
+
+      END SUBROUTINE timer_stop
+!cccccccc1ccccccccc2ccccccccc3ccccccccc4ccccccccc5cccgtgccc6ccccccccc7cc
+      SUBROUTINE timer_write ( component_name )
+! 19 SEPTEMBER 2002   
+      CHARACTER(len=*), intent(in), optional :: component_name
+
+      LOGICAL  :: total_found,string_equal
+      INTEGER  :: task, my_task, npe
+      INTEGER  :: ierr
+      INTEGER  :: clock,hz
+      REAL  ::  cpu_now, cpu_save, cpu_temp
+      REAL  :: wall_now,wall_save,wall_temp
+      REAL  :: frac
+
+      TYPE (timer_node), POINTER :: current
+!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+! GET THE CURRENT TIME
+!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+      cpu_now = 0.0 ! figure this out later
+
+      CALL system_clock (count=clock)
+      CALL system_clock (count_rate=hz)
+      wall_now = REAL (clock)/REAL (hz)
+
+      CALL MPI_BARRIER (MPI_COMM_WORLD,ierr)
+
+      IF (.NOT.ASSOCIATED (timer_events)) THEN
+         PRINT *,' timer_write :: timer_write called with no events initiated '
+         STOP
+      ELSE
+!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+! LOOK FOR AN EVENT CALLED 'total time'
+!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+         total_found = .FALSE.
+         current =&gt; timer_events%next
+         DO WHILE ((.NOT.total_found).AND.(ASSOCIATED (current)))
+            string_equal = (TRIM (current%event_name)=='total time')
+            IF (string_equal) THEN
+               total_found = .TRUE.
+               IF (current%running) THEN
+                   cpu_save = current% cpu_total +                           &amp;
+                                           ( cpu_now-current% cpu_start)
+                  wall_save = current%wall_total +                           &amp;
+                                           (wall_now-current%wall_start)
+               ELSE
+                   cpu_save = current% cpu_total
+                  wall_save = current%wall_total
+               ENDIF
+            ENDIF
+            IF (.NOT.total_found) THEN
+               current =&gt; current%next
+            ENDIF
+         ENDDO
+
+! tdr -- need to link to POP MPI
+!        my_task = get_my_task(component_name)
+!        npe = get_my_npe(component_name)
+         my_task = 0
+         npe = 1
+
+         DO task = 0,npe-1
+            IF (task==my_task) THEN
+               PRINT  *,' '
+               IF (total_found) THEN
+                  IF (my_task==0) THEN
+                     PRINT  *,' TIMINGS (process:event,running,',            &amp;
+                                       'cpu,wall,100*(wall/total wall))'
+                  ENDIF
+                  PRINT 20,task,current%event_name,current%running,          &amp;
+                                                      cpu_save,wall_save
+                  PRINT  *,' '
+               ELSE
+                  IF (my_task==0) THEN
+                     PRINT  *,' TIMINGS (process:event,running,',            &amp;
+                                                             'cpu,wall)'
+                  ENDIF
+               ENDIF
+
+               current =&gt; timer_events%next
+               DO WHILE (ASSOCIATED (current))
+!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+! IF THE TIMER IS RUNNING, COMPUTE THE ACCUMULATED TIME USING THE CURRENT TIME
+!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+                  IF (current%running) THEN
+                      cpu_temp = current% cpu_total +                        &amp;
+                                           ( cpu_now-current% cpu_start)
+                     wall_temp = current%wall_total +                        &amp;
+                                           (wall_now-current%wall_start)
+                  ELSE
+                      cpu_temp = current% cpu_total
+                     wall_temp = current%wall_total
+                  ENDIF
+!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+! IF 'total time' EVENT EXISTS, THEN COMPUTE WALL TIME FRACTION
+! USING TOTAL TIME
+!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+                  IF (total_found) THEN 
+                     string_equal = (TRIM (current%event_name)=='total time')
+                     IF (.NOT.string_equal) THEN
+                        frac = 100.*wall_temp/(wall_save+1.E-5)
+                        PRINT 10, task,current%event_name,current%running,   &amp;
+                                                 cpu_temp,wall_temp,frac
+                     ENDIF
+                  ELSE
+                     PRINT 20, task,current%event_name,current%running,      &amp;
+                                                 cpu_temp,wall_temp
+                  ENDIF
+                  current =&gt; current%next
+               ENDDO
+            ENDIF
+
+            CALL MPI_BARRIER (MPI_COMM_WORLD,ierr)
+
+         ENDDO
+      ENDIF
+
+      CALL MPI_BARRIER (MPI_COMM_WORLD,ierr)
+
+   10 FORMAT (1x,i5,' : ',a20,l1,2f15.5,f8.2)
+   20 FORMAT (1x,i5,' : ',a20,l1,2f15.5     )
+
+      END SUBROUTINE timer_write
+!cccccccc1ccccccccc2ccccccccc3ccccccccc4ccccccccc5cccgtgccc6ccccccccc7cc
+      CHARACTER*03 FUNCTION integer_to_string (i) RESULT (string)
+      INTEGER :: i,n
+      REAL*8 :: xi
+      CHARACTER*01 :: char_i(3)
+      CHARACTER*01 :: integers(12)
+
+      integers = (/'0','1','2','3','4','5','6','7','8','9','0','1'/)
+
+      xi = FLOAT (i)/1000.0
+      DO n = 1,3
+         char_i(n) = integers(INT (10.*xi+0.00001)+1)
+         xi = 10.*xi - FLOAT (INT (10.*xi)) + 0.00001
+      ENDDO
+      string = char_i(1)//char_i(2)//char_i(3)
+
+      END FUNCTION integer_to_string
+!cccccccc1ccccccccc2ccccccccc3ccccccccc4ccccccccc5cccgtgccc6ccccccccc7cc 
+      END MODULE timer
+!cccccccc1ccccccccc2ccccccccc3ccccccccc4ccccccccc5cccgtgccc6ccccccccc7cc

Modified: trunk/swmodel/swmodel.F
===================================================================
--- trunk/swmodel/swmodel.F        2009-08-11 00:00:58 UTC (rev 21)
+++ trunk/swmodel/swmodel.F        2009-08-11 02:50:49 UTC (rev 22)
@@ -6,6 +6,7 @@
    use test_cases
    use io_input
    use dmpar
+   use timer
 
    implicit none
 
@@ -18,16 +19,23 @@
    allocate(dminfo)
    call dmpar_init(dminfo)
 
+   call timer_start(&quot;total time&quot;)
+
+   call timer_start(&quot;initialize&quot;)
    call allocate_domain(domain, dminfo)
 
    call input_state_for_domain(domain)
 
    call setup_sw_test_case(domain)
+   call timer_stop(&quot;initialize&quot;)
 
    call sw_solve(domain) 
 
    call deallocate_domain(domain)
 
+   call timer_stop(&quot;total time&quot;)
+   call timer_write()
+
    call dmpar_finalize(dminfo)
 
    stop

</font>
</pre>