ViewVC Help
View File | Revision Log | Show Annotations | View Changeset | Root Listing
root/group/trunk/mdtools/md_code/lj_FF.F90
Revision: 230
Committed: Thu Jan 9 19:40:38 2003 UTC (21 years, 6 months ago) by chuckv
File size: 18100 byte(s)
Log Message:
More changes to lj_FF.

File Contents

# User Rev Content
1 chuckv 215 module lj_ff
2     use simulation
3     use definitions, ONLY : dp, ndim
4 chuckv 230 #ifdef IS_MPI
5     use mpiSimulation
6     #endif
7 chuckv 215 implicit none
8 chuckv 230 PRIVATE
9 chuckv 215
10 chuckv 230 !! Number of lj_atypes in lj_atype_list
11 chuckv 215 integer, save :: n_lj_atypes = 0
12    
13 chuckv 230 !! Starting Size for ljMixed Array
14     integer, parameter :: ljMixed_blocksize = 10
15    
16 chuckv 215 type, public :: lj_atype
17     private
18     sequence
19 chuckv 230 !! Unique number for place in linked list
20     integer :: atype_number = 0
21     !! Name of atype
22     character(len = 15) :: name = "NULL"
23     !! Unique indentifier number (ie atomic no, etc)
24 chuckv 215 integer :: atype_ident = 0
25 chuckv 230 !! Mass of Particle
26 chuckv 215 real ( kind = dp ) :: mass = 0.0_dp
27 chuckv 230 !! Lennard-Jones epslon
28 chuckv 215 real ( kind = dp ) :: epslon = 0.0_dp
29 chuckv 230 !! Lennard-Jones Sigma
30 chuckv 215 real ( kind = dp ) :: sigma = 0.0_dp
31 chuckv 230 !! Lennard-Jones Sigma Squared
32     real ( kind = dp ) :: sigma2 = 0.0_dp
33     !! Lennard-Jones Sigma to sixth
34     real ( kind = dp ) :: sigma6 = 0.0_dp
35     !! Pointer for linked list creation
36 chuckv 215 type (lj_atype), pointer :: next => null()
37     end type lj_atype
38    
39 chuckv 230 !! Pointer type for atype ident array
40     type :: lj_atypePtr
41     type (lj_atype), pointer :: this => null()
42     end type lj_atypePtr
43    
44     !! Global list of lj atypes in simulation
45 chuckv 215 type (lj_atype), pointer :: lj_atype_list => null()
46 chuckv 230 !! LJ mixing array
47     type (lj_atype), dimension(:,:), allocatable, pointer :: ljMixed =>null()
48     !! identity pointer list for force loop.
49     type (lj_atypePtr), dimension(:), allocatable :: identPtrList
50 chuckv 215
51 chuckv 230
52     !! Neighbor list and commom arrays
53     integer, allocatable, dimension(:) :: point
54     integer, allocatable, dimension(:) :: list
55    
56     #ifdef IS_MPI
57     ! Universal routines: All types of force calculations will need these arrays
58     ! Arrays specific to a type of force calculation should be declared in that module.
59     real( kind = dp ), allocatable, dimension(:,:) :: qRow
60     real( kind = dp ), allocatable, dimension(:,:) :: qColumn
61    
62     real( kind = dp ), allocatable, dimension(:,:) :: fRow
63     real( kind = dp ), allocatable, dimension(:,:) :: fColumn
64     #endif
65    
66    
67    
68    
69    
70    
71     !! Public methods and data
72 chuckv 215 public :: new_lj_atype
73 chuckv 230 public :: do_lj_ff
74     public :: getLjPot
75    
76 chuckv 215
77 chuckv 230
78    
79    
80 chuckv 215 contains
81    
82 chuckv 230 subroutine new_lj_atype(name,ident,mass,epslon,sigma,status)
83 chuckv 215 character( len = 15 ) :: name
84     real( kind = dp ), intent(in) :: mass
85     real( kind = dp ), intent(in) :: epslon
86 chuckv 230 real( kind = dp ), intent(in) :: sigma
87     integer, intent(in) :: ident
88 chuckv 215 integer, intent(out) :: status
89    
90 chuckv 216 type (lj_atype), pointer :: this_lj_atype
91     type (lj_atype), pointer :: lj_atype_ptr
92    
93 chuckv 230 type (lj_atype), allocatable, dimension(:,:), pointer :: thisMix
94     type (lj_atype), allocatable, dimension(:,:), pointer :: oldMix
95 chuckv 216 integer :: alloc_error
96     integer :: atype_counter = 0
97 chuckv 230 integer :: alloc_size
98 chuckv 216
99 chuckv 215 status = 0
100    
101 chuckv 230
102    
103     ! allocate a new atype
104 chuckv 216 allocate(this_lj_atype,stat=alloc_error)
105     if (alloc_error /= 0 ) then
106     status = -1
107     return
108     end if
109    
110     ! assign our new lj_atype information
111     this_lj_atype%name = name
112     this_lj_atype%mass = mass
113     this_lj_atype%epslon = epslon
114     this_lj_atype%sigma = sigma
115 chuckv 230 this_lj_atype%sigma2 = sigma * sigma
116     this_lj_atype%sigma6 = this_lj_atype%sigma2 * this_lj_atype%sigma2 &
117     * this_lj_atype%sigma2
118     ! assume that this atype will be successfully added
119     this_lj_atype%atype_ident = ident
120     this_lj_atype%number = n_lj_atypes + 1
121 chuckv 216
122    
123 chuckv 230 ! First time through allocate a array of size ljMixed_blocksize
124     if(.not. associated(ljMixed)) then
125     allocate(thisMix(ljMixed_blocksize,ljMixed_blocksize))
126     if (alloc_error /= 0 ) then
127     status = -1
128     return
129     end if
130     ljMixed => thisMix
131     ! If we have outgrown ljMixed_blocksize, allocate a new matrix twice the size and
132     ! point ljMix at the new matrix.
133     else if( (n_lj_atypes + 1) > size(ljMixed)) then
134     alloc_size = 2*size(ljMix)
135     allocate(thisMix(alloc_size,alloc_size))
136     if (alloc_error /= 0 ) then
137     status = -1
138     return
139     end if
140     ! point oldMix at old ljMixed array
141     oldMix => ljMixed
142     ! Copy oldMix into new Mixed array
143     thisMix = oldMix
144     ! Point ljMixed at new array
145     ljMixed => thisMix
146     ! Free old array so we don't have a memory leak
147     deallocate(oldMix)
148     endif
149    
150    
151    
152    
153    
154     ! Find bottom of atype master list
155 chuckv 216 ! if lj_atype_list is null then we are at the top of the list.
156     if (.not. associated(lj_atype_list)) then
157     lj_atype_ptr => this_lj_atype
158     atype_counter = 1
159 chuckv 230
160     else ! we need to find the bottom of the list to insert new atype
161 chuckv 216 lj_atype_ptr => lj_atype_list%next
162 chuckv 230 atype_counter = 1
163 chuckv 216 find_end: do
164     if (.not. associated(lj_atype_ptr%next)) then
165     exit find_end
166     end if
167 chuckv 230 ! Set up mixing for new atype and current atype in list
168     ljMix(this_lj_atype%atype_number,lj_atype_ptr%atype_number)%sigma = &
169     calcLJMix("sigma",this_lj_atype%sigma, &
170     lj_atype_prt%sigma)
171    
172     ljMix(this_lj_atype%atype_number,lj_atype_ptr%atype_number)%sigma2 = &
173     ljMix(this_lj_atype%atype_number,lj_atype_ptr%atype_number)%sigma &
174     * ljMix(this_lj_atype%atype_number,lj_atype_ptr%atype_number)%sigma
175    
176     ljMix(this_lj_atype%atype_number,lj_atype_ptr%atype_number)%sigma6 = &
177     ljMix(this_lj_atype%atype_number,lj_atype_ptr%atype_number)%sigma2 &
178     * ljMix(this_lj_atype%atype_number,lj_atype_ptr%atype_number)%sigma2 &
179     * ljMix(this_lj_atype%atype_number,lj_atype_ptr%atype_number)%sigma2
180    
181     ljMix(this_lj_atype%atype_number,lj_atype_ptr%atype_number)%epslon = &
182     calcLJMix("epslon",this_lj_atype%epslon, &
183     lj_atype_prt%epslon)
184    
185     ! Advance to next pointer
186     lj_atype_ptr => lj_atype_ptr%next
187     atype_counter = atype_counter + 1
188    
189 chuckv 216 end do find_end
190     end if
191 chuckv 230
192    
193    
194 chuckv 216
195 chuckv 230 ! Insert new atype at end of list
196 chuckv 216 lj_atype_ptr => this_lj_atype
197 chuckv 230 ! Increment number of atypes
198    
199     n_lj_atypes = n_lj_atypes + 1
200    
201     ! Set up self mixing
202    
203     ljMix(n_lj_atypes,n_lj_atypes)%sigma = this_lj_atype%sigma
204    
205     ljMix(n_lj_atypes,n_lj_atypes)%sigma2 = ljMix(n_lj_atypes,n_lj_atypes)%sigma &
206     * ljMix(n_lj_atypes,n_lj_atypes)%sigma
207    
208     ljMix(n_lj_atypes,n_lj_atypes)%sigma6 = ljMix(n_lj_atypes,n_lj_atypes)%sigma2 &
209     * ljMix(n_lj_atypes,n_lj_atypes)%sigma2 &
210     * ljMix(n_lj_atypes,n_lj_atypes)%sigma2
211    
212     ljMix(n_lj_atypes,n_lj_atypes)%epslon = this_lj_atype%epslon
213    
214    
215 chuckv 215 end subroutine new_lj_atype
216    
217    
218 chuckv 230 subroutine init_ljFF()
219 chuckv 215
220    
221 chuckv 230 #ifdef IS_MPI
222 chuckv 215
223 chuckv 230
224 chuckv 215
225 chuckv 230 #endif
226    
227     end subroutine init_ljFF
228    
229     !! Takes an ident array and creates an atype pointer list
230     !! based on those identities
231     subroutine new_ljatypePtrList(mysize,ident,PtrList,status)
232     integer, intent(in) :: mysize
233     integer, intent(in) :: ident
234     integer, optional :: status
235     type(lj_atypePtr), dimension(:) :: PtrList
236    
237     integer :: thisIdent
238     integer :: i
239     integer :: alloc_error
240     type (lj_atype), pointer :: tmpPtr
241    
242     if (present(status)) status = 0
243    
244     ! First time through, allocate list
245     if (.not.(allocated)) then
246     allocate(PtrList(mysize))
247     else
248     ! We want to creat a new ident list so free old list
249     deallocate(PrtList)
250     allocate(PtrList(mysize))
251     endif
252    
253     ! Match pointer list
254     do i = 1, mysize
255     thisIdent = ident(i)
256     call getLJatype(thisIdent,tmpPtr)
257    
258     if (.not. associated(tmpPtr)) then
259     status = -1
260     return
261     endif
262    
263     PtrList(i)%this => tmpPtr
264     end do
265    
266     end subroutine new_ljatypePtrList
267    
268     !! Finds a lj_atype based upon numerical ident
269     !! returns a null pointer if error
270     subroutine getLJatype(ident,ljAtypePtr)
271     integer, intent(in) :: ident
272     type (lj_atype), intent(out),pointer :: ljAtypePtr => null()
273    
274     type (lj_atype), pointer :: tmplj_atype_ptr => null()
275    
276     if(.not. associated(lj_atype_list)) return
277    
278     ! Point at head of list.
279     tmplj_atype_ptr => lj_atype_list
280     find_ident: do
281     if (.not.associated(tmplj_atype_ptr)) then
282     exit find_ident
283     else if( lj_atype_ptr%atype_ident == ident)
284     ljAtypePtr => tmplj_atype_ptr
285     exit find_ident
286     endif
287     tmplj_atype_ptr => tmplj_atype_ptr%next
288     end do find_ident
289    
290     end subroutine getLJatype
291    
292    
293     ! FORCE routine
294     !------------------------------------------------------------->
295     subroutine do_lj_ff(q,f,potE,do_pot)
296 chuckv 222 real ( kind = dp ), dimension(ndim,) :: q
297     real ( kind = dp ), dimension(ndim,nLRparticles) :: f
298     real ( kind = dp ) :: potE
299 chuckv 216
300 chuckv 230 #ifdef MPI
301     real( kind = DP ), dimension(3,ncol) :: efr
302     real( kind = DP ) :: pot_local
303     #else
304     ! real( kind = DP ), dimension(3,natoms) :: efr
305     #endif
306    
307     real( kind = DP ) :: pe
308     logical, :: update_nlist
309     logical :: do_pot
310 chuckv 216
311 chuckv 230 integer :: i, j, jbeg, jend, jnab, idim, jdim, idim2, jdim2, dim, dim2
312     integer :: nlist
313     integer :: j_start
314     integer :: tag_i,tag_j
315     real( kind = DP ) :: r, pot, ftmp, dudr, d2, drdx1, kt1, kt2, kt3, ktmp
316     real( kind = DP ) :: rxi, ryi, rzi, rxij, ryij, rzij, rijsq
317 chuckv 222
318 chuckv 230 integer :: nrow
319     integer :: ncol
320 chuckv 222
321    
322    
323 chuckv 230 #ifndef IS_MPI
324     nrow = natoms - 1
325     ncol = natoms
326     #else
327     j_start = 1
328     #endif
329 chuckv 222
330 chuckv 230 call check(update_nlist)
331    
332     do_pot = .false.
333     if (present(pe)) do_pot = .true.
334    
335     #ifndef IS_MPI
336     nloops = nloops + 1
337     pot = 0.0E0_DP
338     f = 0.0E0_DP
339     e = 0.0E0_DP
340     #else
341     f_row = 0.0E0_DP
342     f_col = 0.0E0_DP
343    
344     pot_local = 0.0E0_DP
345    
346     e_row = 0.0E0_DP
347     e_col = 0.0E0_DP
348     e_tmp = 0.0E0_DP
349     #endif
350     efr = 0.0E0_DP
351    
352     ! communicate MPI positions
353     #ifdef MPI
354     call gather(q,q_row,plan_row3)
355     call gather(q,q_col,plan_col3)
356     #endif
357    
358     #ifndef MPI
359    
360     #endif
361    
362     if (update_nlist) then
363    
364     ! save current configuration, contruct neighbor list,
365     ! and calculate forces
366     call save_nlist()
367    
368     nlist = 0
369    
370    
371    
372     do i = 1, nrow
373     point(i) = nlist + 1
374     #ifdef MPI
375     tag_i = tag_row(i)
376     rxi = q_row(1,i)
377     ryi = q_row(2,i)
378     rzi = q_row(3,i)
379     #else
380     j_start = i + 1
381     rxi = q(1,i)
382     ryi = q(2,i)
383     rzi = q(3,i)
384     #endif
385    
386     inner: do j = j_start, ncol
387     #ifdef MPI
388     tag_j = tag_col(j)
389     if (newtons_thrd) then
390     if (tag_i <= tag_j) then
391     if (mod(tag_i + tag_j,2) == 0) cycle inner
392     else
393     if (mod(tag_i + tag_j,2) == 1) cycle inner
394     endif
395     endif
396    
397     rxij = wrap(rxi - q_col(1,j), 1)
398     ryij = wrap(ryi - q_col(2,j), 2)
399     rzij = wrap(rzi - q_col(3,j), 3)
400     #else
401    
402     rxij = wrap(rxi - q(1,j), 1)
403     ryij = wrap(ryi - q(2,j), 2)
404     rzij = wrap(rzi - q(3,j), 3)
405    
406     #endif
407     rijsq = rxij*rxij + ryij*ryij + rzij*rzij
408    
409     #ifdef MPI
410     if (rijsq <= rlstsq .AND. &
411     tag_j /= tag_i) then
412     #else
413     if (rijsq < rlstsq) then
414     #endif
415    
416     nlist = nlist + 1
417     if (nlist > size(list)) then
418     call info("FORCE_LJ","error size list smaller then nlist")
419     write(msg,*) "nlist size(list)", nlist, size(list)
420     call info("FORCE_LJ",msg)
421     #ifdef MPI
422     call mpi_abort(MPI_COMM_WORLD,mpi_err)
423     #endif
424     stop
425     endif
426     list(nlist) = j
427    
428    
429     if (rijsq < rcutsq) then
430    
431     r = dsqrt(rijsq)
432    
433     call LJ_mix(r,pot,dudr,d2,i,j)
434    
435     #ifdef MPI
436     e_row(i) = e_row(i) + pot*0.5
437     e_col(i) = e_col(i) + pot*0.5
438     #else
439     pe = pe + pot
440     #endif
441    
442     efr(1,j) = -rxij
443     efr(2,j) = -ryij
444     efr(3,j) = -rzij
445    
446     do dim = 1, 3
447    
448    
449     drdx1 = efr(dim,j) / r
450     ftmp = dudr * drdx1
451    
452    
453     #ifdef MPI
454     f_col(dim,j) = f_col(dim,j) - ftmp
455     f_row(dim,i) = f_row(dim,i) + ftmp
456     #else
457    
458     f(dim,j) = f(dim,j) - ftmp
459     f(dim,i) = f(dim,i) + ftmp
460    
461     #endif
462     enddo
463     endif
464     endif
465     enddo inner
466     enddo
467    
468     #ifdef MPI
469     point(nrow + 1) = nlist + 1
470     #else
471     point(natoms) = nlist + 1
472     #endif
473    
474     else
475    
476     ! use the list to find the neighbors
477     do i = 1, nrow
478     JBEG = POINT(i)
479     JEND = POINT(i+1) - 1
480     ! check thiat molecule i has neighbors
481     if (jbeg .le. jend) then
482     #ifdef MPI
483     rxi = q_row(1,i)
484     ryi = q_row(2,i)
485     rzi = q_row(3,i)
486     #else
487     rxi = q(1,i)
488     ryi = q(2,i)
489     rzi = q(3,i)
490     #endif
491     do jnab = jbeg, jend
492     j = list(jnab)
493     #ifdef MPI
494     rxij = wrap(rxi - q_col(1,j), 1)
495     ryij = wrap(ryi - q_col(2,j), 2)
496     rzij = wrap(rzi - q_col(3,j), 3)
497     #else
498     rxij = wrap(rxi - q(1,j), 1)
499     ryij = wrap(ryi - q(2,j), 2)
500     rzij = wrap(rzi - q(3,j), 3)
501     #endif
502     rijsq = rxij*rxij + ryij*ryij + rzij*rzij
503    
504     if (rijsq < rcutsq) then
505    
506     r = dsqrt(rijsq)
507    
508     call LJ_mix(r,pot,dudr,d2,i,j)
509     #ifdef MPI
510     e_row(i) = e_row(i) + pot*0.5
511     e_col(i) = e_col(i) + pot*0.5
512     #else
513     if (do_pot) pe = pe + pot
514     #endif
515    
516    
517     efr(1,j) = -rxij
518     efr(2,j) = -ryij
519     efr(3,j) = -rzij
520    
521     do dim = 1, 3
522    
523     drdx1 = efr(dim,j) / r
524     ftmp = dudr * drdx1
525     #ifdef MPI
526     f_col(dim,j) = f_col(dim,j) - ftmp
527     f_row(dim,i) = f_row(dim,i) + ftmp
528     #else
529     f(dim,j) = f(dim,j) - ftmp
530     f(dim,i) = f(dim,i) + ftmp
531     #endif
532     enddo
533     endif
534     enddo
535     endif
536     enddo
537     endif
538    
539    
540    
541     #ifdef MPI
542     !!distribute forces
543     call scatter(f_row,f,plan_row3)
544    
545     call scatter(f_col,f_tmp,plan_col3)
546     do i = 1,nlocal
547     do dim = 1,3
548     f(dim,i) = f(dim,i) + f_tmp(dim,i)
549     end do
550     end do
551    
552    
553    
554     if (do_pot) then
555     ! scatter/gather pot_row into the members of my column
556     call scatter(e_row,e_tmp,plan_row)
557    
558     ! scatter/gather pot_local into all other procs
559     ! add resultant to get total pot
560     do i = 1, nlocal
561     pot_local = pot_local + e_tmp(i)
562     enddo
563     if (newtons_thrd) then
564     e_tmp = 0.0E0_DP
565     call scatter(e_col,e_tmp,plan_col)
566     do i = 1, nlocal
567     pot_local = pot_local + e_tmp(i)
568     enddo
569     endif
570     endif
571     #endif
572    
573    
574    
575    
576 chuckv 222 end subroutine do_lj_ff
577    
578 chuckv 230 !! Calculates the potential between two lj particles, optionally returns second
579     !! derivatives.
580     subroutine getLjPot(r,pot,dudr,atype1,atype2,d2,status)
581     ! arguments
582     !! Length of vector between particles
583     real( kind = dp ), intent(in) :: r
584     !! Potential Energy
585     real( kind = dp ), intent(out) :: pot
586     !! Derivatve wrt postion
587     real( kind = dp ), intent(out) :: dudr
588     !! Second Derivative, optional, used mainly for normal mode calculations.
589     real( kind = dp ), intent(out), optional :: d2
590    
591     type (lj_atype), intent(in) :: atype1
592     type (lj_atype), intent(in) :: atype2
593 chuckv 222
594 chuckv 230 integer, intent(out), optional :: status
595 chuckv 222
596 chuckv 230 ! local Variables
597     real( kind = dp ) :: sigma
598     real( kind = dp ) :: sigma2
599     real( kind = dp ) :: sigma6
600     real( kind = dp ) :: epslon
601    
602     real( kind = dp ) :: rcut
603     real( kind = dp ) :: rcut2
604     real( kind = dp ) :: rcut6
605     real( kind = dp ) :: r2
606     real( kind = dp ) :: r6
607    
608     real( kind = dp ) :: t6
609     real( kind = dp ) :: t12
610     real( kind = dp ) :: tp6
611     real( kind = dp ) :: tp12
612     real( kind = dp ) :: delta
613    
614     logical :: doSec = .false.
615    
616     integer :: errorStat
617    
618     !! Optional Argument Checking
619     ! Check to see if we need to do second derivatives
620    
621     if (present(d2)) doSec = .true.
622     if (present(status)) status = 0
623    
624     ! Look up the correct parameters in the mixing matrix
625     sigma = ljMixed(atype1%atype_ident,atype2_atype_ident)%sigma
626     sigma2 = ljMixed(atype1%atype_ident,atype2_atype_ident)%sigma2
627     sigma6 = ljMixed(atype1%atype_ident,atype2_atype_ident)%sigma6
628     epslon = ljMixed(atype1%atype_ident,atype2_atype_ident)%epslon
629    
630    
631    
632     call getRcut(rcut,rcut2=rcut2,rcut6=rcut6,status=errorStat)
633    
634     r2 = r * r
635     r6 = r2 * r2 * r2
636    
637     t6 = sigma6/ r6
638     t12 = t6 * t6
639    
640    
641    
642     tp6 = sigma6 / rcut6
643     tp12 = tp6*tp6
644    
645     delta = -4.0E0_DP*epsilon * (tp12 - tp6)
646    
647     if (r.le.rcut) then
648     u = 4.0E0_DP * epsilon * (t12 - t6) + delta
649     dudr = 24.0E0_DP * epsilon * (t6 - 2.0E0_DP*t12) / r
650     if(doSec) d2 = 24.0E0_DP * epsilon * (26.0E0_DP*t12 - 7.0E0_DP*t6)/r/r
651     else
652     u = 0.0E0_DP
653     dudr = 0.0E0_DP
654     if(doSec) d2 = 0.0E0_DP
655     endif
656    
657     return
658    
659    
660    
661     end subroutine getLjPot
662    
663    
664     !! Calculates the mixing for sigma or epslon based on character string
665     function calcLJMix(thisParam,param1,param2,status) result(myMixParam)
666     character(len=*) :: thisParam
667     real(kind = dp) :: param1
668     real(kind = dp) :: param2
669     real(kind = dp ) :: myMixParam
670     integer, optional :: status
671    
672    
673     myMixParam = 0.0_dp
674    
675     if (present(status)) status = 0
676    
677     select case (thisParam)
678    
679     case ("sigma")
680     myMixParam = 0.5_dp * (param1 + param2)
681     case ("epslon")
682     myMixParam = sqrt(param1 * param2)
683     case default
684     status = -1
685     end select
686    
687     end function calcLJMix
688    
689    
690    
691 chuckv 215 end module lj_ff