<p><b>dwj07@fsu.edu</b> 2011-10-17 14:15:27 -0600 (Mon, 17 Oct 2011)</p><p><br>
        -- BRANCH COMMIT --<br>
<br>
        Renaming functions and subroutines that were either skipped on accident by the script or just missed completely.<br>
</p><hr noshade><pre><font color="gray">Modified: branches/source_renaming/src/core_sw/mpas_sw_advection.F
===================================================================
--- branches/source_renaming/src/core_sw/mpas_sw_advection.F        2011-10-17 20:09:04 UTC (rev 1100)
+++ branches/source_renaming/src/core_sw/mpas_sw_advection.F        2011-10-17 20:15:27 UTC (rev 1101)
@@ -522,7 +522,7 @@
    
    
    !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
-   ! SUBROUTine sw_arc_bisect
+   ! subroutine sw_arc_bisect
    !
    ! Returns the point C=(cx, cy, cz) that bisects the great circle arc from
    !   A=(ax, ay, az) to B=(bx, by, bz). It is assumed that A and B lie on the
@@ -630,9 +630,9 @@
 !                                                                       !
 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
 !
-SUBROUTine sw_migs (A,N,X,INDX)
+subroutine sw_migs (A,N,X,INDX)
 !
-! Subroutine to invert matrix A(N,N) with the inverse stored
+! subroutine to invert matrix A(N,N) with the inverse stored
 ! in X(N,N) in the output.  Copyright (c) Tao Pang 2001.
 !
   IMPLICIT NONE
@@ -672,12 +672,12 @@
       X(J,I) =  X(J,I)/A(INDX(J),J)
     END DO
   END DO
-END SUBROUTine sw_migs
+end subroutine sw_migs
 
 
-SUBROUTine sw_elgs (A,N,INDX)
+subroutine sw_elgs (A,N,INDX)
 !
-! Subroutine to perform the partial-pivoting Gaussian elimination.
+! subroutine to perform the partial-pivoting Gaussian elimination.
 ! A(N,N) is the original matrix in the input and transformed matrix
 ! plus the pivoting element ratios below the diagonal in the output.
 ! INDX(N) records the pivoting order.  Copyright (c) Tao Pang 2001.
@@ -738,7 +738,7 @@
     END DO
   END DO
 !
-END SUBROUTine sw_elgs
+end subroutine sw_elgs
 
 !-------------------------------------------------------------
 

Modified: branches/source_renaming/src/core_sw/mpas_sw_global_diagnostics.F
===================================================================
--- branches/source_renaming/src/core_sw/mpas_sw_global_diagnostics.F        2011-10-17 20:09:04 UTC (rev 1100)
+++ branches/source_renaming/src/core_sw/mpas_sw_global_diagnostics.F        2011-10-17 20:15:27 UTC (rev 1101)
@@ -267,7 +267,7 @@
       ! Step 6
       ! 6. Write out your global stat to the file
       if (dminfo % my_proc_id == IO_NODE) then
-         fileID = getFreeUnit()
+         fileID = sw_get_free_unit()
 
          if (timeIndex/config_stats_interval == 1) then
              open(fileID, file='GlobalIntegrals.txt',STATUS='unknown')
@@ -283,23 +283,23 @@
       deallocate(areaEdge)
    end subroutine sw_compute_global_diagnostics
 
-   integer function getFreeUnit()
+   integer function sw_get_free_unit()
       implicit none
 
       integer :: index
       logical :: isOpened
 
-      getFreeUnit = 0
+      sw_get_free_unit = 0
       do index = 1,99
          if((index /= 5) .and. (index /= 6)) then
             inquire(unit = index, opened = isOpened)
             if( .not. isOpened) then
-               getFreeUnit = index
+               sw_get_free_unit = index
                return
             end if
          end if
       end do
-   end function getFreeUnit
+   end function sw_get_free_unit
 
    subroutine sw_compute_global_sum(dminfo, nVertLevels, nElements, field, globalSum)
 
@@ -349,7 +349,7 @@
 
    end subroutine sw_compute_global_max
 
-   subroutine computeGlobalVertSumHorizMin(dminfo, nVertLevels, nElements, field, globalMin)
+   subroutine compute_global_vert_sum_horiz_min(dminfo, nVertLevels, nElements, field, globalMin)
 
       implicit none
 
@@ -363,7 +363,7 @@
       localMin = minval(sum(field,1))
       call dmpar_min_real(dminfo, localMin, globalMin)
 
-   end subroutine computeGlobalVertSumHorizMin
+   end subroutine compute_global_vert_sum_horiz_min
 
    subroutine sw_compute_global_vert_sum_horiz_max(dminfo, nVertLevels, nElements, field, globalMax)
 

Modified: branches/source_renaming/src/core_sw/mpas_sw_test_cases.F
===================================================================
--- branches/source_renaming/src/core_sw/mpas_sw_test_cases.F        2011-10-17 20:09:04 UTC (rev 1100)
+++ branches/source_renaming/src/core_sw/mpas_sw_test_cases.F        2011-10-17 20:15:27 UTC (rev 1101)
@@ -442,9 +442,9 @@
       ! Initialize height field (actually, fluid thickness field)
       !
       do iCell=1,grid % nCells
-         state % h % array(1,iCell) = (gravity * h0 + a*a*AA(grid%latCell%array(iCell)) + &amp;
-                                                      a*a*BB(grid%latCell%array(iCell)) * cos(R*grid%lonCell%array(iCell)) + &amp;
-                                                      a*a*CC(grid%latCell%array(iCell)) * cos(2.0*R*grid%lonCell%array(iCell)) &amp;
+         state % h % array(1,iCell) = (gravity * h0 + a*a*aa(grid%latCell%array(iCell)) + &amp;
+                                                      a*a*bb(grid%latCell%array(iCell)) * cos(R*grid%lonCell%array(iCell)) + &amp;
+                                                      a*a*cc(grid%latCell%array(iCell)) * cos(2.0*R*grid%lonCell%array(iCell)) &amp;
                                       ) / gravity
       end do
 
@@ -470,7 +470,7 @@
    end function sphere_distance
 
 
-   real function AA(theta)
+   real function aa(theta)
    !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    ! A, used in height field computation for Rossby-Haurwitz wave
    !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
@@ -483,13 +483,13 @@
 
       real (kind=RKIND), intent(in) :: theta
 
-      AA = 0.5 * w * (2.0 * omega + w) * cos(theta)**2.0 + &amp;
+      aa = 0.5 * w * (2.0 * omega + w) * cos(theta)**2.0 + &amp;
           0.25 * K**2.0 * cos(theta)**(2.0*R) * ((R+1.0)*cos(theta)**2.0 + 2.0*R**2.0 - R - 2.0 - 2.0*R**2.0 * cos(theta)**(-2.0))
 
-   end function AA
+   end function aa
 
    
-   real function BB(theta)
+   real function bb(theta)
    !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    ! B, used in height field computation for Rossby-Haurwitz wave
    !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
@@ -502,12 +502,12 @@
 
       real (kind=RKIND), intent(in) :: theta
 
-      BB = (2.0*(omega + w)*K / ((R+1.0)*(R+2.0))) * cos(theta)**R * ((R**2.0 + 2.0*R + 2.0) - ((R+1.0)*cos(theta))**2.0)
+      bb = (2.0*(omega + w)*K / ((R+1.0)*(R+2.0))) * cos(theta)**R * ((R**2.0 + 2.0*R + 2.0) - ((R+1.0)*cos(theta))**2.0)
 
-   end function BB
+   end function bb
 
 
-   real function CC(theta)
+   real function cc(theta)
    !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    ! C, used in height field computation for Rossby-Haurwitz wave
    !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
@@ -520,8 +520,8 @@
 
       real (kind=RKIND), intent(in) :: theta
 
-      CC = 0.25 * K**2.0 * cos(theta)**(2.0*R) * ((R+1.0)*cos(theta)**2.0 - R - 2.0)
+      cc = 0.25 * K**2.0 * cos(theta)**(2.0*R) * ((R+1.0)*cos(theta)**2.0 - R - 2.0)
 
-   end function CC
+   end function cc
 
 end module test_cases

</font>
</pre>