<p><b>dwj07@fsu.edu</b> 2012-08-27 12:28:21 -0600 (Mon, 27 Aug 2012)</p><p><br>
        -- BRANCH COMMIT --<br>
<br>
        5th cut at openmp on element loops<br>
</p><hr noshade><pre><font color="gray">Modified: branches/omp_blocks/openmp_test/src/core_sw_elements/mpas_sw_mpas_core.F
===================================================================
--- branches/omp_blocks/openmp_test/src/core_sw_elements/mpas_sw_mpas_core.F        2012-08-27 17:33:04 UTC (rev 2127)
+++ branches/omp_blocks/openmp_test/src/core_sw_elements/mpas_sw_mpas_core.F        2012-08-27 18:28:21 UTC (rev 2128)
@@ -164,6 +164,8 @@
       integer :: ierr
    
       ! Eventually, dt should be domain specific
+      !$omp parallel
+      !$omp single
       dt = config_dt
 
       currTime = mpas_get_clock_time(clock, MPAS_NOW, ierr)
@@ -171,12 +173,14 @@
       write(0,*) 'Initial timestep ', trim(timeStamp)
 
       call write_output_frame(output_obj, output_frame, domain)
+      !$omp end single
 
       ! During integration, time level 1 stores the model state at the beginning of the
       !   time step, and time level 2 stores the state advanced dt in time by timestep(...)
       itimestep = 0
       do while (.not. mpas_is_clock_stop_time(clock))
 
+         !$omp single
          itimestep = itimestep + 1
          call mpas_advance_clock(clock)
 
@@ -185,16 +189,21 @@
          write(0,*) 'Doing timestep ', trim(timeStamp)
 
          call mpas_timer_start(&quot;time integration&quot;)
+         !$omp end single
          call mpas_timestep(domain, itimestep, dt, timeStamp)
+         !$omp single
          call mpas_timer_stop(&quot;time integration&quot;)
 
          ! Move time level 2 fields back into time level 1 for next time step
          block_ptr =&gt; domain % blocklist
          do while(associated(block_ptr))
             block = block_ptr 
+            !$omp task firstprivate(block)
             call mpas_shift_time_levels_state(block % state)
+            !$omp end task
             block_ptr =&gt; block_ptr % next
          end do
+         !$omp taskwait
 
          !TODO: mpas_get_clock_ringing_alarms is probably faster than multiple mpas_is_alarm_ringing...
 
@@ -216,8 +225,10 @@
             call mpas_output_state_for_domain(restart_obj, domain, 1)
             call mpas_output_state_finalize(restart_obj, domain % dminfo)
          end if
+         !$omp end single
 
       end do
+      !$omp end parallel
 
    end subroutine mpas_core_run
    

Modified: branches/omp_blocks/openmp_test/src/core_sw_elements/mpas_sw_time_integration.F
===================================================================
--- branches/omp_blocks/openmp_test/src/core_sw_elements/mpas_sw_time_integration.F        2012-08-27 17:33:04 UTC (rev 2127)
+++ branches/omp_blocks/openmp_test/src/core_sw_elements/mpas_sw_time_integration.F        2012-08-27 18:28:21 UTC (rev 2128)
@@ -26,22 +26,24 @@
       character(len=*), intent(in) :: timeStamp
 
       type (block_type), pointer :: block
-      type (block_type) :: block_d
 
       if (trim(config_time_integration) == 'RK4') then
          call sw_rk4(domain, dt)
       else
+         !$omp single
          write(0,*) 'Unknown time integration option '//trim(config_time_integration)
          write(0,*) 'Currently, only ''RK4'' is supported.'
+         !$omp end single
          stop
       end if
 
       block =&gt; domain % blocklist
+      !$omp single
       do while (associated(block))
-         block_d = block
-         block_d % state % time_levs(2) % state % xtime % scalar = timeStamp 
+         block % state % time_levs(2) % state % xtime % scalar = timeStamp 
          block =&gt; block % next
       end do
+      !$omp end single
 
    end subroutine sw_timestep
 
@@ -71,7 +73,6 @@
 
       real (kind=RKIND), dimension(4) :: rk_weights, rk_substep_weights
 
-      !$omp parallel
       !$omp single
       call mpas_timer_start('computations')
       call mpas_setup_provis_states(domain % blocklist)
@@ -102,9 +103,9 @@
 
         !$omp single
         call mpas_copy_state(block % provis, block % state % time_levs(1) % state)
+        !$omp end single
 
         block =&gt; block % next
-        !$omp end single
      end do
 
      rk_weights(1) = dt/6.
@@ -117,8 +118,8 @@
      rk_substep_weights(3) = dt
      rk_substep_weights(4) = 0.
      !$omp single
-      call mpas_timer_stop('computations')
-      !$omp end single
+     call mpas_timer_stop('computations')
+     !$omp end single
 
      !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 
      ! BEGIN RK loop 
@@ -128,16 +129,16 @@
 ! --- update halos for diagnostic variables
        !$omp barrier
        !$omp single
-        call mpas_timer_start('communications')
-        call mpas_dmpar_exch_halo_field(domain % blocklist % provis % pv_edge)
+       call mpas_timer_start('communications')
+       call mpas_dmpar_exch_halo_field(domain % blocklist % provis % pv_edge)
 
-        if (config_h_mom_eddy_visc4 &gt; 0.0) then
+       if (config_h_mom_eddy_visc4 &gt; 0.0) then
             call mpas_dmpar_exch_halo_field(domain % blocklist % provis % divergence)
             call mpas_dmpar_exch_halo_field(domain % blocklist % provis % vorticity)
        end if
-        call mpas_timer_stop('communications')
-        call mpas_timer_start('computations')
-        !$omp end single
+       call mpas_timer_stop('communications')
+       call mpas_timer_start('computations')
+       !$omp end single
 
 ! --- compute tendencies
 
@@ -159,23 +160,23 @@
           call sw_enforce_boundary_edge(block % tend, block % mesh)
           !$omp single
           call mpas_timer_stop('sw_enforce_boundary')
+          !$omp end single
           block =&gt; block % next
-          !$omp end single
        end do
 
 ! --- update halos for prognostic variables
 
-        !$omp barrier
+       !$omp barrier
 
-        !$omp single
-        call mpas_timer_stop('computations')
-        call mpas_timer_start('communications')
+       !$omp single
+       call mpas_timer_stop('computations')
+       call mpas_timer_start('communications')
        call mpas_dmpar_exch_halo_field(domain % blocklist % tend % u)
        call mpas_dmpar_exch_halo_field(domain % blocklist % tend % h)
        call mpas_dmpar_exch_halo_field(domain % blocklist % tend % tracers)
-        call mpas_timer_stop('communications')
-        call mpas_timer_start('computations')
-        !$omp end single
+       call mpas_timer_stop('communications')
+       call mpas_timer_start('computations')
+       !$omp end single
 
 ! --- compute next substep state
 
@@ -210,8 +211,8 @@
              call sw_compute_solve_diagnostics(dt, block % provis, block % mesh)
              !$omp single
              call mpas_timer_stop('sw_compute_solve_diagnostics')
+             !$omp end single
              block =&gt; block % next
-             !$omp end single
           end do
        end if
 !--- accumulate update (for RK4)
@@ -237,9 +238,7 @@
           end do
           !$omp end do
 
-          !$omp single
           block =&gt; block % next
-          !$omp end single
        end do
 
         !$omp single
@@ -273,11 +272,12 @@
          if (config_test_case == 1) then    ! For case 1, wind field should be fixed
             !$omp workshare
             block % state % time_levs(2) % state % u % array(:,:) = block % state % time_levs(1) % state % u % array(:,:)
-            !$omp end  workshare
+            !$omp end workshare
          end if
 
          call sw_compute_solve_diagnostics(dt, block % state % time_levs(2) % state, block % mesh)
 
+         !$omp barrier
          !$omp single
          call mpas_reconstruct(block % mesh, block % state % time_levs(2) % state % u % array,          &amp;
                           block % state % time_levs(2) % state % uReconstructX % array,            &amp;
@@ -286,18 +286,17 @@
                           block % state % time_levs(2) % state % uReconstructZonal % array,        &amp;
                           block % state % time_levs(2) % state % uReconstructMeridional % array    &amp;
                          )
+         !$omp end single
 
          block =&gt; block % next
-         !$omp end single
       end do
 
+      !$omp barrier
       !$omp single
       call mpas_deallocate_provis_states(domain % blocklist)
       call mpas_timer_stop('computations')
       !$omp end single
 
-      !$omp end parallel
-
    end subroutine sw_rk4
 
 

</font>
</pre>