ViewVC Help
View File | Revision Log | Show Annotations | View Changeset | Root Listing
root/group/trunk/OOPSE_old/src/mdtools/libmdCode/simulation_module.F90
(Generate patch)

Comparing trunk/OOPSE_old/src/mdtools/libmdCode/simulation_module.F90 (file contents):
Revision 329 by gezelter, Wed Mar 12 22:27:59 2003 UTC vs.
Revision 332 by gezelter, Thu Mar 13 15:28:43 2003 UTC

# Line 19 | Line 19 | module simulation
19    logical, save :: simulation_setup_complete = .false.
20  
21    integer :: natoms
22 +  integer, public, save :: nExcludes_Global = 0
23 +  integer, public, save :: nExcludes_Local = 0
24 +
25    real(kind=dp), save :: rcut2 = 0.0_DP
26    real(kind=dp), save :: rcut6 = 0.0_DP
27    real(kind=dp), save :: rlist2 = 0.0_DP
28 +  real(kind=dp), public, dimension(3), save :: box
29  
30   #ifdef IS_MPI
31    real( kind = dp ), allocatable, dimension(:,:), public :: q_Row
# Line 42 | Line 46 | module simulation
46    real( kind = dp ), allocatable, dimension(:,:), public :: t_Temp
47    real( kind = dp ), allocatable, dimension(:,:), public :: rf_Row
48    real( kind = dp ), allocatable, dimension(:,:), public :: rf_Col
49 +  real( kind = dp ), allocatable, dimension(:,:), public :: rf_Temp
50  
51    integer, allocatable, dimension(:), public :: atid_Row
52    integer, allocatable, dimension(:), public :: atid_Col
53   #else
49  real( kind = dp ), allocatable, dimension(:,:), public :: rf
54    integer, allocatable, dimension(:), public :: atid
55   #endif
56 <
56 >  real( kind = dp ), allocatable, dimension(:,:), public :: rf
57 >  integer, allocatable, dimension(:,:), public :: excludesLocal
58 >  integer, allocatable, dimension(:), public :: excludesGlobal
59    real(kind = dp), dimension(9), public :: tau_Temp = 0.0_dp
60    real(kind = dp), public :: virial_Temp = 0.0_dp
61    
# Line 70 | Line 76 | module simulation
76    public :: SimUsesEAM
77    public :: SimRequiresPrepairCalc
78    public :: SimRequiresPostpairCalc
79 +  public :: SimUsesDirectionalAtoms
80  
81    interface getBox
82       module procedure getBox_3d
# Line 79 | Line 86 | contains
86   contains
87    
88    subroutine SimulationSetup(setThisSim, nComponents, c_idents, &
89 <       nExcludes_local, excludesLocal, nExcludes_global, excludesGlobal, &
90 <       status)
84 <    
89 >       CnLocalExcludes, CexcludesLocal, CnGlobalExcludes, CexcludesGlobal, &
90 >       status)    
91      type (simtype) :: setThisSim
92      integer, intent(inout) :: nComponents
93      integer, dimension(nComponents),intent(inout) :: c_idents
94 <    integer :: nExcludes_local
95 <    integer, dimension(nExcludes_local),intent(inout) :: excludesLocal
96 <    integer :: nExcludes_global
97 <    integer, dimension(nExcludes_global),intent(inout) :: excludesGlobal
94 >
95 >    integer :: CnLocalExcludes
96 >    integer, dimension(2,CnLocalExcludes), intent(in) :: CexcludesLocal
97 >    integer :: CnGlobalExcludes
98 >    integer, dimension(CnGlobalExcludes), intent(in) :: CexcludesGlobal
99      !!  Result status, success = 0, status = -1
100      integer, intent(out) :: status
101      integer :: i, me, thisStat, alloc_stat, myNode
95
102   #ifdef IS_MPI
103      integer, allocatable, dimension(:) :: c_idents_Row
104      integer, allocatable, dimension(:) :: c_idents_Col
105      integer :: nrow
106      integer :: ncol
107 < #endif
107 > #endif  
108  
109      simulation_setup_complete = .false.
110      status = 0
# Line 109 | Line 115 | contains
115      rcut2 = thisSim%rcut * thisSim%rcut
116      rcut6 = rcut2 * rcut2 * rcut2
117      rlist2 = thisSim%rlist * thisSim%rlist
118 +    box = thisSim%box
119 +    nExcludes_Global = CnGlobalExcludes
120 +    nExcludes_Local = CnLocalExcludes
121  
122 +    call setupGlobals(thisStat)
123 +    if (thisStat /= 0) then
124 +       status = -1
125 +       return
126 +    endif
127 +
128   #ifdef IS_MPI
129      ! We can only set up forces if mpiSimulation has been setup.
130      if (.not. isMPISimSet()) then
# Line 136 | Line 151 | contains
151      call gather(c_idents, c_idents_Row, plan_row)
152      call gather(c_idents, c_idents_Col, plan_col)
153  
139    allocate(atid_Row(nrow),stat=alloc_stat)
140    if (alloc_stat /= 0 ) then
141       status = -1
142       return
143    endif
144
145    allocate(atid_Col(ncol),stat=alloc_stat)
146    if (alloc_stat /= 0 ) then
147       status = -1
148       return
149    endif
150
154      do i = 1, nrow
155         me = getFirstMatchingElement(atypes, "c_ident", c_idents_Row(i))
156         atid_Row(i) = me
# Line 175 | Line 178 | contains
178      enddo
179   #endif
180  
178    call setupGlobals(thisStat)
179    if (thisStat /= 0) then
180       status = -1
181       return
182    endif
183
181      !! Create neighbor lists
182      call expandNeighborList(nComponents, thisStat)
183      if (thisStat /= 0) then
184         status = -1
185         return
186      endif
187 +
188 +    do i = 1, nExcludes_Local
189 +       excludesLocal(1,i) = CexcludesLocal(1,i)
190 +       excludesLocal(2,i) = CexcludesLocal(2,i)
191 +    enddo
192      
193 +    do i = 1, nExcludes_Global
194 +       excludesGlobal(i) = CexcludesGlobal(i)
195 +    enddo
196 +    
197      if (status == 0) simulation_setup_complete = .true.
198 <      
198 >    
199    end subroutine SimulationSetup
200    
201    subroutine change_box_size(new_box_size)
202      real(kind=dp), dimension(3) :: new_box_size
203      thisSim%box = new_box_size
204 +    box = thisSim%box
205    end subroutine change_box_size
206  
207    function getBox_3d() result(thisBox)
# Line 303 | Line 310 | contains
310      logical :: doesit
311      doesit = thisSim%SIM_uses_dipoles .or. thisSim%SIM_uses_sticky .or. &
312           thisSim%SIM_uses_GB .or. thisSim%SIM_uses_RF
313 <  end function SimRequiresPrepairCalc
313 >  end function SimUsesDirectionalAtoms
314  
315    function SimRequiresPrepairCalc() result(doesit)
316      logical :: doesit
# Line 337 | Line 344 | contains
344  
345      allocate(q_Row(ndim,nrow),stat=alloc_stat)
346      if (alloc_stat /= 0 ) then
347 <       thisStat = 0
347 >       thisStat = -1
348         return
349      endif
350          
351      allocate(q_Col(ndim,ncol),stat=alloc_stat)
352      if (alloc_stat /= 0 ) then
353 <       thisStat = 0
353 >       thisStat = -1
354         return
355      endif
356        
357      allocate(u_l_Row(ndim,nrow),stat=alloc_stat)
358      if (alloc_stat /= 0 ) then
359 <       thisStat = 0
359 >       thisStat = -1
360         return
361      endif
362      
363      allocate(u_l_Col(ndim,ncol),stat=alloc_stat)
364      if (alloc_stat /= 0 ) then
365 <       thisStat = 0
365 >       thisStat = -1
366         return
367      endif
368      
369      allocate(A_row(9,nrow),stat=alloc_stat)
370      if (alloc_stat /= 0 ) then
371 <       thisStat = 0
371 >       thisStat = -1
372         return
373      endif
374          
375      allocate(A_Col(9,ncol),stat=alloc_stat)
376      if (alloc_stat /= 0 ) then
377 <       thisStat = 0
377 >       thisStat = -1
378         return
379      endif
380      
381      allocate(pot_row(nrow),stat=alloc_stat)
382      if (alloc_stat /= 0 ) then
383 <       thisStat = 0
383 >       thisStat = -1
384         return
385      endif
386      
387      allocate(pot_Col(ncol),stat=alloc_stat)
388      if (alloc_stat /= 0 ) then
389 <       thisStat = 0
389 >       thisStat = -1
390         return
391      endif
392  
393      allocate(pot_Temp(nlocal),stat=alloc_stat)
394      if (alloc_stat /= 0 ) then
395 <       thisStat = 0
395 >       thisStat = -1
396         return
397      endif
398      
399      allocate(f_Row(ndim,nrow),stat=alloc_stat)
400      if (alloc_stat /= 0 ) then
401 <       thisStat = 0
401 >       thisStat = -1
402         return
403      endif
404      
405      allocate(f_Col(ndim,ncol),stat=alloc_stat)
406      if (alloc_stat /= 0 ) then
407 <       thisStat = 0
407 >       thisStat = -1
408         return
409      endif
410      
411      allocate(f_Temp(ndim,nlocal),stat=alloc_stat)
412      if (alloc_stat /= 0 ) then
413 <       thisStat = 0
413 >       thisStat = -1
414         return
415      endif
416      
417      allocate(t_Row(ndim,nrow),stat=alloc_stat)
418      if (alloc_stat /= 0 ) then
419 <       thisStat = 0
419 >       thisStat = -1
420         return
421      endif
422      
423      allocate(t_Col(ndim,ncol),stat=alloc_stat)
424      if (alloc_stat /= 0 ) then
425 <       thisStat = 0
425 >       thisStat = -1
426         return
427      endif
428  
429      allocate(t_temp(ndim,nlocal),stat=alloc_stat)
430      if (alloc_stat /= 0 ) then
431 <       thisStat = 0
431 >       thisStat = -1
432         return
433      endif
434  
435      allocate(atid_Row(nrow),stat=alloc_stat)
436      if (alloc_stat /= 0 ) then
437 <       thisStat = 0
437 >       thisStat = -1
438         return
439      endif
440  
441      allocate(atid_Col(ncol),stat=alloc_stat)
442      if (alloc_stat /= 0 ) then
443 <       thisStat = 0
443 >       thisStat = -1
444         return
445      endif
446  
447      allocate(rf_Row(ndim,nrow),stat=alloc_stat)
448      if (alloc_stat /= 0 ) then
449 <       thisStat = 0
449 >       thisStat = -1
450         return
451      endif
452  
453      allocate(rf_Col(ndim,ncol),stat=alloc_stat)
454      if (alloc_stat /= 0 ) then
455 <       thisStat = 0
455 >       thisStat = -1
456         return
457      endif
458  
459 +    allocate(rf_Temp(ndim,nlocal),stat=alloc_stat)
460 +    if (alloc_stat /= 0 ) then
461 +       thisStat = -1
462 +       return
463 +    endif
464  
465 +
466   #else
467  
468      allocate(atid(nlocal),stat=alloc_stat)
469      if (alloc_stat /= 0 ) then
470 <       thisStat = 0
470 >       thisStat = -1
471         return
472      end if
473  
474 + #endif
475 +    
476      allocate(rf(ndim,nlocal),stat=alloc_stat)
477      if (alloc_stat /= 0 ) then
478 <       thisStat = 0
478 >       thisStat = -1
479         return
480      endif
481  
467 #endif
482  
483 +    allocate(excludesLocal(2,nExcludes_Local), stat=alloc_stat)
484 +    if (alloc_stat /= 0 ) then
485 +       thisStat = -1
486 +       return
487 +    endif
488 +
489 +    allocate(excludesGlobal(nExcludes_Global), stat=alloc_stat)
490 +    if (alloc_stat /= 0 ) then
491 +       thisStat = -1
492 +       return
493 +    endif
494 +
495    end subroutine setupGlobals
496    
497    subroutine freeGlobals()
498      
499      !We free in the opposite order in which we allocate in.
500 +    
501 +    if (allocated(excludesGlobal)) deallocate(excludesGlobal)
502 +    if (allocated(excludesLocal)) deallocate(excludesLocal)
503 +    if (allocated(rf))         deallocate(rf)
504   #ifdef IS_MPI
505 <
505 >    if (allocated(rf_Temp))    deallocate(rf_Temp)
506      if (allocated(rf_Col))     deallocate(rf_Col)
507      if (allocated(rf_Row))     deallocate(rf_Row)    
508      if (allocated(atid_Col))   deallocate(atid_Col)
# Line 491 | Line 521 | contains
521      if (allocated(u_l_Col))    deallocate(u_l_Col)
522      if (allocated(u_l_Row))    deallocate(u_l_Row)
523      if (allocated(q_Col))      deallocate(q_Col)
524 <    if (allocated(q_Row))      deallocate(q_Row)
525 <    
526 < #else
497 <    
498 <    if (allocated(rf))         deallocate(rf)
499 <    if (allocated(atid))       deallocate(atid)
500 <    
524 >    if (allocated(q_Row))      deallocate(q_Row)    
525 > #else    
526 >    if (allocated(atid))       deallocate(atid)    
527   #endif
528          
529    end subroutine freeGlobals

Diff Legend

Removed lines
+ Added lines
< Changed lines
> Changed lines