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

Comparing trunk/mdtools/md_code/lj_FF.F90 (file contents):
Revision 216 by chuckv, Sun Dec 29 16:43:11 2002 UTC vs.
Revision 231 by chuckv, Thu Jan 9 21:31:16 2003 UTC

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

Diff Legend

Removed lines
+ Added lines
< Changed lines
> Changed lines