Skip to content

Commit

Permalink
replace a single $OMP PARALLEL DO construct with $OMP PARALLEL + $OMP…
Browse files Browse the repository at this point in the history
… DO constructs
  • Loading branch information
nmizukami committed Jun 20, 2019
1 parent 2e11481 commit 9b00d3a
Show file tree
Hide file tree
Showing 2 changed files with 12 additions and 18 deletions.
15 changes: 6 additions & 9 deletions route/build/src/irf_route.f90
Original file line number Diff line number Diff line change
Expand Up @@ -94,7 +94,7 @@ subroutine irf_route(iEns, & ! input: index of runoff ensemble to be p
nTrib=size(river_basin(ix)%branch)

! 1. Route tributary reaches (parallel)
!$OMP PARALLEL default(none) &
!$OMP PARALLEL DO schedule(dynamic,1) &
!$OMP private(jSeg, iSeg) & ! private for a given thread
!$OMP private(ierr, cmessage) & ! private for a given thread
!$OMP shared(river_basin) & ! data structure shared
Expand All @@ -103,18 +103,15 @@ subroutine irf_route(iEns, & ! input: index of runoff ensemble to be p
!$OMP shared(RCHFLX_out) & ! data structure shared
!$OMP shared(ix, iEns, ixDesire) & ! indices shared
!$OMP firstprivate(nTrib)

!$OMP DO schedule(dynamic,1)
do iTrib = 1,nTrib
do iSeg=1,river_basin(ix)%branch(iTrib)%nRch
trib:do iTrib = 1,nTrib
seg:do iSeg=1,river_basin(ix)%branch(iTrib)%nRch
jSeg = river_basin(ix)%branch(iTrib)%segIndex(iSeg)
if (.not. doRoute(jSeg)) cycle
call segment_irf(iEns, jSeg, ixDesire, NETOPO_IN, RCHFLX_out, ierr, cmessage)
! if(ierr/=0)then; ixmessage(iTrib)=trim(message)//trim(cmessage); exit; endif
end do
end do
!$OMP END DO
!$OMP END PARALLEL
end do seg
end do trib
!$OMP END PARALLEL DO

end do

Expand Down
15 changes: 6 additions & 9 deletions route/build/src/kwt_route.f90
Original file line number Diff line number Diff line change
Expand Up @@ -100,7 +100,7 @@ SUBROUTINE kwt_route(iens, & ! input: ensemble index
nTrib=size(river_basin(ix)%branch)

! 1. Route tributary reaches (parallel)
!$OMP parallel default(none) &
!$OMP PARALLEL DO schedule(dynamic,1) & ! chunk size of 1
!$OMP private(jSeg, iSeg) & ! private for a given thread
!$OMP private(ierr, cmessage) & ! private for a given thread
!$OMP shared(T0,T1) & ! private for a given thread
Expand All @@ -113,10 +113,8 @@ SUBROUTINE kwt_route(iens, & ! input: ensemble index
!$OMP shared(RCHFLX_out) & ! data structure shared
!$OMP shared(ix, iEns, ixDesire) & ! indices shared
!$OMP firstprivate(nTrib)

!$OMP DO schedule(dynamic, 1) ! chunk size of 1
do iTrib = 1,nTrib
do iSeg=1,river_basin(ix)%branch(iTrib)%nRch
trib:do iTrib = 1,nTrib
seg:do iSeg=1,river_basin(ix)%branch(iTrib)%nRch
jSeg = river_basin(ix)%branch(iTrib)%segIndex(iSeg)
if (.not. doRoute(jSeg)) cycle
! route kinematic waves through the river network
Expand All @@ -130,10 +128,9 @@ SUBROUTINE kwt_route(iens, & ! input: ensemble index
RCHFLX_out, & ! inout: reach flux data structure
ierr,cmessage) ! output: error control
!if (ierr/=0)then; message=trim(message)//trim(cmessage); return; endif
end do ! (looping through stream segments)
end do ! (looping through stream segments)
!$OMP END DO
!$OMP END PARALLEL
end do seg
end do trib
!$OMP END PARALLEL DO

end do

Expand Down

0 comments on commit 9b00d3a

Please sign in to comment.