ViewVC Help
View File | Revision Log | Show Annotations | View Changeset | Root Listing
root/group/trunk/mdtools/md_code/mpiSimulation.F90
(Generate patch)

Comparing trunk/mdtools/md_code/mpiSimulation.F90 (file contents):
Revision 207 by chuckv, Fri Dec 13 16:51:23 2002 UTC vs.
Revision 211 by chuckv, Fri Dec 13 19:15:57 2002 UTC

# Line 5 | Line 5
5   !!
6   !! @author Charles F. Vardeman II
7   !! @author Matthew Meineke
8 < !! @version $Id: mpiSimulation.F90,v 1.1 2002-12-13 16:51:23 chuckv Exp $, $Date: 2002-12-13 16:51:23 $, $Name: not supported by cvs2svn $, $Revision: 1.1 $
8 > !! @version $Id: mpiSimulation.F90,v 1.3 2002-12-13 19:15:57 chuckv Exp $, $Date: 2002-12-13 19:15:57 $, $Name: not supported by cvs2svn $, $Revision: 1.3 $
9  
10  
11  
# Line 22 | Line 22 | module mpiSimulation  
22   !! to gather and scatter routines
23    public :: gather, scatter
24    public :: setupSimParallel
25 +  public :: replanSimParallel
26   !! PUBLIC  Subroutines contained in MPI module
27    public :: mpi_bcast
28    public :: mpi_allreduce
# Line 57 | Line 58 | module mpiSimulation  
58   !! gs_plan contains plans for gather and scatter routines
59    type, public :: gs_plan
60       private
61 <     type (mpiComponentPlan), pointer :: gsComponentPlan
62 < !     integer ::  me, nprocs, n_datum,full_size  !n = # of datums on local proc
63 <     integer, dimension(:), pointer :: displs
64 <     integer, dimension(:), pointer :: counts
65 <     integer :: planComm !! Communicator for this plan
61 >     type (mpiComponentPlan), pointer :: gsComponentPlan => NULL()
62 >     integer :: gsPlanSize !! size of this plan (nDim*nComponents)
63 >     integer :: globalPlanSize !! size of all components in plan
64 >     integer, dimension(:), pointer :: displs !! Displacements array for mpi indexed from 0.
65 >     integer, dimension(:), pointer :: counts !! Counts array for mpi indexed from 0.
66 >     integer :: myPlanComm  !! My communicator for this plan
67 >     integer :: myPlanRank  !! My rank in this plan
68 >     integer :: planNprocs  !! Number of processors in this plan
69    end type gs_plan
70  
71   ! plans for different decompositions
# Line 96 | Line 100 | contains
100   contains
101  
102   !! Sets up mpiComponentPlan with structure passed from C++.
103 <  subroutine setupSimParallel(nDim,thisComponentPlan)
103 >  subroutine setupSimParallel(nDim,thisComponentPlan,status)
104   !  Passed Arguments
105      integer, intent(inout) :: nDim !! Number of dimensions
106      !! mpiComponentPlan struct from C
107      type (mpiComponentPlan), intent(inout) :: thisComponentPlan  
108 <    integer :: status
109 <    
110 <    if (componentPlanSet) return
111 <    
108 >    integer, intent(out) :: status
109 >    integer, intnet(out) :: localStatus
110 >
111 >    status = 0
112 >    if (componentPlanSet) then
113 >       return
114 >    endif
115 >
116      componentPlanSet = .true.
117  
118 <    call make_Force_Grid(thisComponentPlan,status)
119 <    call updateGriComponents(thisComponentPlan,status)
120 <    
118 >    call make_Force_Grid(thisComponentPlan,localStatus)
119 >    if (localStatus /= 0) then
120 >       status = -1
121 >       return
122 >    endif
123  
124 <    call plan_gather_scatter(1,thisComponentPlan,row_comm,plan_row)
125 <    call plan_gather_scatter(nDim,thisComponentPlan,row_comm,plan_row3d)
126 <    call plan_gather_scatter(1,thisComponentPlan,col_comm,plan_col)
127 <    call plan_gather_scatte(nDim,thisComponentPlan,col_comm,plan_col3d)
124 >    call updateGridComponents(thisComponentPlan,localStatus)
125 >    if (localStatus /= 0) then
126 >       status = -1
127 >       return
128 >    endif
129 >    
130 >    !! initialize gather and scatter plans used in this simulation
131 >    call plan_gather_scatter(1,thisComponentPlan%nComponentsRow,&
132 >         thisComponentPlan,row_comm,plan_row)
133 >    call plan_gather_scatter(nDim,thisComponentPlan%nComponentsRow,&
134 >         thisComponentPlan,row_comm,plan_row3d)
135 >    call plan_gather_scatter(1,thisComponentPlan%nComponentsColumn,&
136 >         thisComponentPlan,col_comm,plan_col)
137 >    call plan_gather_scatter(nDim,thisComponentPlan%nComponentsColumn,&
138 >         thisComponentPlan,col_comm,plan_col3d)
139  
140  
141  
142    end subroutine setupSimParallel
143  
144 +  subroutine replanSimParallel(thisComponentPlan,status)
145 + !  Passed Arguments
146 +    !! mpiComponentPlan struct from C
147 +    type (mpiComponentPlan), intent(inout) :: thisComponentPlan  
148 +    integer, intent(out) :: status
149 +    integer, intnet(out) :: localStatus
150 +
151 +    status = 0
152 +
153 +    call updateGridComponents(thisComponentPlan,localStatus)
154 +    if (localStatus /= 0) then
155 +       status = -1
156 +       return
157 +    endif
158 +    
159 +    !! Unplan Gather Scatter plans
160 +    call unplan_gather_scatter(plan_row)
161 +    call unplan_gather_scatter(plan_row3d)
162 +    call unplan_gather_scatter(plan_col)
163 +    call unplan_gather_scatter(plan_col3d)
164 +
165 +
166 +    !! initialize gather and scatter plans used in this simulation
167 +    call plan_gather_scatter(1,thisComponentPlan%nComponentsRow,&
168 +         thisComponentPlan,row_comm,plan_row)
169 +    call plan_gather_scatter(nDim,thisComponentPlan%nComponentsRow,&
170 +         thisComponentPlan,row_comm,plan_row3d)
171 +    call plan_gather_scatter(1,thisComponentPlan%nComponentsColumn,&
172 +         thisComponentPlan,col_comm,plan_col)
173 +    call plan_gather_scatter(nDim,thisComponentPlan%nComponentsColumn,&
174 +         thisComponentPlan,col_comm,plan_col3d)
175 +
176 +
177 +
178 +  end subroutine replanSimParallel
179 +
180   !! Updates number of row and column components for long range forces.
181    subroutine updateGridComponents(thisComponentPlan,status)
182      type (mpiComponentPlan) :: thisComponentPlan !! mpiComponentPlan
# Line 242 | Line 299 | contains
299  
300  
301    !! initalizes a gather scatter plan
302 <  subroutine plan_gather_scatter( nDim,thisComponentPlan, &
303 <       thisComm, this_plan)  
302 >  subroutine plan_gather_scatter( nDim,nComponents,thisComponentPlan, &
303 >       thisComm, this_plan,status)  
304      integer, intent(in) :: nDim !! Number of dimensions for gather scatter plan
305 <    type (mpiComponentPlan), intent(in) :: thisComponentPlan
305 >    integer, intent(in) :: nComponents
306 >    type (mpiComponentPlan), intent(in), target :: thisComponentPlan
307      type (gs_plan), intent(out) :: this_plan !! MPI Component Plan
308 <    integer, intent(in) :: thisComm !!
309 <    integer :: sizeof_int
308 >    integer, intent(in) :: thisComm !! MPI communicator for this plan
309 >
310 >    integer :: arraySize !! size to allocate plan for
311 >    integer, intent(out), optional :: status
312      integer :: ierror
253    integer :: comm
254    integer :: me
255    integer :: comm_procs
313      integer :: i,junk
314 <    integer :: number_of_particles
314 >
315 >    if (present(status)) status = 0
316 >  
317  
318 + !! Set gsComponetPlan pointer
319 + !! to the componet plan we want to use for this gather scatter plan.
320 + !! WARNING this could be dangerous since thisComponentPlan was origionally
321 + !! allocated in C++ and there is a significant difference between c and
322 + !! f95 pointers....  
323 +    gsComponentPlan => thisComponetPlan
324  
325 + ! Set this plan size for displs array.
326 +    this_plan%gsPlanSize = nDim * nComponents
327  
328 <    number_of_particles = 0
329 <    call mpi_comm_dup(orig_comm,comm,mpi_err)
330 <    call mpi_comm_rank(comm,me,mpi_err)
331 <    call mpi_comm_size(comm,comm_procs,mpi_err)
328 > ! Duplicate communicator for this plan
329 >    call mpi_comm_dup(thisComm,this_plan%myPlanComm,mpi_err)
330 >    if (mpi_err /= 0) then
331 >       if (present(status)) status = -1
332 >       return
333 >    end if
334 >    call mpi_comm_rank(this_plan%myPlanComm,this_plan%myPlanRank,mpi_err)
335 >    if (mpi_err /= 0) then
336 >       if (present(status)) status = -1
337 >       return
338 >    end if
339  
340 <    sizeof_int = selected_int_kind(4)
340 >    call mpi_comm_size(this_plan%myPlanComm,this_plan%planNprocs,mpi_err)
341  
342 <    allocate (this_plan%counts(0:comm_procs-1),STAT=ierror)
343 <    if (ierror /= 0) then
344 <
342 >    if (mpi_err /= 0) then
343 >       if (present(status)) status = -1
344 >       return
345      end if
346  
347 <    allocate (this_plan%displs(0:comm_procs-1),STAT=ierror)
347 >    !! counts and displacements arrays are indexed from 0 to be compatable
348 >    !! with MPI arrays.
349 >    allocate (this_plan%counts(0:this_plan%planNprocs-1),STAT=ierror)
350      if (ierror /= 0) then
351 +       if (present(status)) status = -1
352 +       return
353 +    end if
354  
355 +    allocate (this_plan%displs(0:this_plan%planNprocs-1),STAT=ierror)
356 +    if (ierror /= 0) then
357 +       if (present(status)) status = -1
358 +       return
359      end if
360  
361 <
362 <    call mpi_allgather(local_number,1,mpi_integer,this_plan%counts, &
361 >   !! gather all the local sizes into a size # processors array.
362 >    call mpi_allgather(gs_plan%gsPlanSize,1,mpi_integer,this_plan%counts, &
363           1,mpi_integer,comm,mpi_err)
364 +
365 +    if (mpi_err /= 0) then
366 +       if (present(status)) status = -1
367 +       return
368 +    end if
369    
370  
371      !! figure out the total number of particles in this plan
372 <    number_of_particles = sum(this_plan%counts)
372 >    this_plan%globalPlanSize = sum(this_plan%counts)
373    
374  
375 <    !initialize plan
375 >    !! initialize plan displacements.
376      this_plan%displs(0) = 0
377 <    do i = 1, comm_procs - 1,1
377 >    do i = 1, this_plan%planNprocs - 1,1
378         this_plan%displs(i) = this_plan%displs(i-1) + this_plan%counts(i-1)
379      end do
380  
293
294    this_plan%me = me
295    this_plan%nprocs = comm_procs
296    this_plan%full_size = number_of_particles
297    this_plan%comm = comm
298    this_plan%n_datum = local_number
299
381    end subroutine plan_gather_scatter
382  
383  
384    subroutine unplan_gather_scatter(this_plan)
304
385      type (gs_plan), intent(inout) :: this_plan
386 <
386 >    
387 >    
388 >    this_plan%gsComponentPlan => null()
389      call mpi_comm_free(this_plan%comm,mpi_err)
390  
391      deallocate(this_plan%counts)
# Line 320 | Line 402 | contains
402      integer, intent(out), optional :: status
403  
404      if (present(status)) status = 0
405 <    noffset = this_plan%displs(this_plan%me)
405 >    noffset = this_plan%displs(this_plan%myPlanRank)
406  
407 <    call mpi_allgatherv(sbuffer,this_plan%n_datum, mpi_integer, &
407 >    call mpi_allgatherv(sbuffer,this_plan%gsPlanSize, mpi_integer, &
408           rbuffer,this_plan%counts,this_plan%displs,mpi_integer, &
409 <         this_plan%comm, mpi_err)
409 >         this_plan%myPlanComm, mpi_err)
410  
411      if (mpi_err /= 0) then
412        if (present(status)) status  = -1
# Line 343 | Line 425 | contains
425      if (present(status)) status = 0
426      noffset = this_plan%displs(this_plan%me)
427  
428 <    call mpi_allgatherv(sbuffer,this_plan%n_datum, mpi_double_precision, &
428 >    call mpi_allgatherv(sbuffer,this_plan%gsPlanSize, mpi_double_precision, &
429           rbuffer,this_plan%counts,this_plan%displs,mpi_double_precision, &
430 <         this_plan%comm, mpi_err)
430 >         this_plan%myPlanComm, mpi_err)
431  
432      if (mpi_err /= 0) then
433        if (present(status)) status  = -1
# Line 367 | Line 449 | contains
449  
450   !    noffset = this_plan%displs(this_plan%me)
451      
452 <    call mpi_allgatherv(sbuffer,this_plan%n_datum, mpi_double_precision, &
452 >    call mpi_allgatherv(sbuffer,this_plan%gsPlanSize, mpi_double_precision, &
453          rbuffer,this_plan%counts,this_plan%displs,mpi_double_precision, &
454 <        this_plan%comm, mpi_err)
454 >        this_plan%myPlanComm, mpi_err)
455  
456      if (mpi_err /= 0) then
457        if (present(status)) status = -1
# Line 388 | Line 470 | contains
470     if (present(status)) status = 0
471  
472      call mpi_reduce_scatter(sbuffer,rbuffer, this_plan%counts, &
473 <         mpi_double_precision, MPI_SUM, this_plan%comm, mpi_err)
473 >         mpi_double_precision, MPI_SUM, this_plan%myPlanComm, mpi_err)
474  
475      if (mpi_err /= 0) then
476       if (present(status))  status = -1
# Line 406 | Line 488 | contains
488  
489     if (present(status)) status = 0
490      call mpi_reduce_scatter(sbuffer,rbuffer, this_plan%counts, &
491 <         mpi_double_precision, MPI_SUM, this_plan%comm, mpi_err)
491 >         mpi_double_precision, MPI_SUM, this_plan%myPlanComm, mpi_err)
492  
493      if (mpi_err /= 0) then
494        if (present(status)) status = -1

Diff Legend

Removed lines
+ Added lines
< Changed lines
> Changed lines