kim-api-v2  2.0.0+912e79a.GNU
An Application Programming Interface (API) for the Knowledgebase of Interatomic Models (KIM).
utility_forces_numer_deriv.f90
Go to the documentation of this file.
1 !
2 ! CDDL HEADER START
3 !
4 ! The contents of this file are subject to the terms of the Common Development
5 ! and Distribution License Version 1.0 (the "License").
6 !
7 ! You can obtain a copy of the license at
8 ! http://www.opensource.org/licenses/CDDL-1.0. See the License for the
9 ! specific language governing permissions and limitations under the License.
10 !
11 ! When distributing Covered Code, include this CDDL HEADER in each file and
12 ! include the License file in a prominent location with the name LICENSE.CDDL.
13 ! If applicable, add the following below this CDDL HEADER, with the fields
14 ! enclosed by brackets "[]" replaced with your own identifying information:
15 !
16 ! Portions Copyright (c) [yyyy] [name of copyright owner]. All rights reserved.
17 !
18 ! CDDL HEADER END
19 !
20 
21 !
22 ! Copyright (c) 2013--2019, Regents of the University of Minnesota.
23 ! All rights reserved.
24 !
25 ! Contributors:
26 ! Ellad B. Tadmor
27 ! Ryan S. Elliott
28 ! Stephen M. Whalen
29 !
30 
31 
32 module error
33  use, intrinsic :: iso_c_binding
34  implicit none
35  public
36 
37 contains
38  recursive subroutine my_error(message)
39  implicit none
40  character(len=*, kind=c_char), intent(in) :: message
41 
42  print *,"* Error : ", trim(message)
43  stop
44  end subroutine my_error
45 
46  recursive subroutine my_warning(message)
47  implicit none
48  character(len=*, kind=c_char), intent(in) :: message
49 
50  print *,"* Warning : ", trim(message)
51  end subroutine my_warning
52 end module error
53 
54 
55 !-------------------------------------------------------------------------------
56 !
57 ! module mod_neighborlist :
58 !
59 ! Module contains type and routines related to neighbor list calculation
60 !
61 !-------------------------------------------------------------------------------
62 
63 module mod_neighborlist
64 
65  use, intrinsic :: iso_c_binding
66 
67  public get_neigh
68 
69  type, bind(c) :: neighobject_type
70  real(c_double) :: cutoff
71  integer(c_int) :: number_of_particles
72  type(c_ptr) :: neighbor_list_pointer
73  end type neighobject_type
74 contains
75 
76 !-------------------------------------------------------------------------------
77 !
78 ! get_neigh neighbor list access function
79 !
80 ! This function implements Locator and Iterator mode
81 !
82 !-------------------------------------------------------------------------------
83 !-------------------------------------------------------------------------------
84 !
85 ! get_neigh neighbor list access function
86 !
87 ! This function implements Locator and Iterator mode
88 !
89 !-------------------------------------------------------------------------------
90 recursive subroutine get_neigh(data_object, number_of_neighbor_lists, cutoffs, &
91  neighbor_list_index, request, numnei, pnei1part, ierr) bind(c)
92  use error
93  implicit none
94 
95  !-- Transferred variables
96  type(c_ptr), value, intent(in) :: data_object
97  integer(c_int), value, intent(in) :: number_of_neighbor_lists
98  real(c_double), intent(in) :: cutoffs(number_of_neighbor_lists)
99  integer(c_int), value, intent(in) :: neighbor_list_index
100  integer(c_int), value, intent(in) :: request
101  integer(c_int), intent(out) :: numnei
102  type(c_ptr), intent(out) :: pnei1part
103  integer(c_int), intent(out) :: ierr
104 
105  !-- Local variables
106  integer(c_int) numberofparticles
107  type(neighobject_type), pointer :: neighobject
108  integer(c_int), pointer :: neighborlist(:,:)
109 
110  call c_f_pointer(data_object, neighobject)
111  numberofparticles = neighobject%number_of_particles
112  call c_f_pointer(neighobject%neighbor_list_pointer, neighborlist, &
113  [numberofparticles+1, numberofparticles])
114 
115  if (cutoffs(neighbor_list_index) > neighobject%cutoff) then
116  call my_warning("neighbor list cutoff too small for model cutoff")
117  ierr = 1
118  return
119  endif
120 
121  if ( (request.gt.numberofparticles) .or. (request.lt.1)) then
122  print *, request
123  call my_warning("Invalid part ID in get_neigh")
124  ierr = 1
125  return
126  endif
127 
128  ! set the returned number of neighbors for the returned part
129  numnei = neighborlist(1,request)
130 
131  ! set the location for the returned neighbor list
132  pnei1part = c_loc(neighborlist(2,request))
133 
134  ierr = 0
135  return
136 end subroutine get_neigh
137 
138 end module mod_neighborlist
139 
142  implicit none
143  public
144 
145 contains
146 
147 !-------------------------------------------------------------------------------
148 !
149 ! Check if we are compatible with the model
150 !
151 !-------------------------------------------------------------------------------
152 recursive subroutine check_model_compatibility(compute_arguments_handle, &
153  forces_optional, model_is_compatible, ierr)
154  use, intrinsic :: iso_c_binding
155  use error
156  implicit none
157 
158  !-- Transferred variables
159  type(kim_compute_arguments_handle_type), intent(in) :: compute_arguments_handle
160  logical, intent(out) :: forces_optional
161  logical, intent(out) :: model_is_compatible
162  integer(c_int), intent(out) :: ierr
163 
164  !-- Local variables
165  integer(c_int) i
166  integer(c_int) number_of_argument_names
167  integer(c_int) number_of_callback_names
168  type(kim_compute_argument_name_type) argument_name
169  type(kim_support_status_type) support_status
170  type(kim_compute_callback_name_type) callback_name
171 
172 
173  ! assume fail
174  model_is_compatible = .false.
175  ierr = 0
176 
177  ! check arguments
178  call kim_get_number_of_compute_argument_names(&
179  number_of_argument_names)
180  do i=1,number_of_argument_names
181  call kim_get_compute_argument_name(i, argument_name, &
182  ierr)
183  if (ierr /= 0) then
184  call my_warning("can't get argument name")
185  return
186  end if
187  call kim_get_argument_support_status( &
188  compute_arguments_handle, argument_name, support_status, ierr)
189  if (ierr /= 0) then
190  call my_warning("can't get argument support_status")
191  return
192  end if
193 
194  ! can only handle energy and forces as required args
195  if (support_status == kim_support_status_required) then
196  if (.not. ( &
197  (argument_name == kim_compute_argument_name_partial_energy) .or. &
198  (argument_name == kim_compute_argument_name_partial_forces))) then
199  call my_warning("unsupported required argument")
200  ierr = 0
201  return
202  end if
203  end if
204 
205  ! need both energy and forces not "notSupported"
206  if ((argument_name == kim_compute_argument_name_partial_energy) .and. &
207  (support_status == kim_support_status_not_supported)) then
208  call my_warning("model does not support energy")
209  ierr = 0
210  return
211  end if
212  if (argument_name == kim_compute_argument_name_partial_forces) then
213  if (support_status == kim_support_status_not_supported) then
214  call my_warning("model does not support forces")
215  ierr = 0
216  return
217  else if (support_status == kim_support_status_required) then
218  forces_optional = .false.
219  else if (support_status == kim_support_status_optional) then
220  forces_optional = .true.
221  else
222  call my_warning("unknown support_status for forces")
223  ierr = 0
224  return
225  end if
226  end if
227  end do
228 
229  ! check call backs
230  call kim_get_number_of_compute_callback_names( &
231  number_of_callback_names)
232  do i=1,number_of_callback_names
233  call kim_get_compute_callback_name(i, callback_name, &
234  ierr)
235  if (ierr /= 0) then
236  call my_warning("can't get call back name")
237  return
238  end if
239  call kim_get_callback_support_status( &
240  compute_arguments_handle, callback_name, support_status, ierr)
241  if (ierr /= 0) then
242  call my_warning("can't get call back support_status")
243  return
244  end if
245 
246  ! cannot handle any "required" call backs
247  if (support_status == kim_support_status_required) then
248  call my_warning("unsupported required call back")
249  ierr = 0
250  return
251  end if
252  end do
253 
254  ! got to here, then everything must be OK
255  model_is_compatible = .true.
256  ierr = 0
257  return
258 end subroutine check_model_compatibility
259 
260 !-------------------------------------------------------------------------------
261 !
262 ! Get number and identities of particle species supported by
263 ! KIM Model `modelname'
264 !
265 !-------------------------------------------------------------------------------
266 recursive subroutine get_model_supported_species(model_handle, max_species, &
267  model_species, num_species, ier)
268 use, intrinsic :: iso_c_binding
269 implicit none
270 
271 !-- Transferred variables
272 type(kim_model_handle_type), intent(in) :: model_handle
273 integer(c_int), intent(in) :: max_species
274 type(kim_species_name_type), intent(out) :: model_species(max_species)
275 integer(c_int), intent(out) :: num_species
276 integer(c_int), intent(out) :: ier
277 
278 !-- Local variables
279 integer(c_int) i
280 integer(c_int) total_num_species
281 type(kim_species_name_type) :: species_name
282 integer(c_int) species_is_supported
283 integer(c_int) code
284 
285 ! Initialize error flag
286 ier = 1
287 
288 call kim_get_number_of_species_names(total_num_species)
289 
290 if (total_num_species .gt. max_species) return
291 
292 num_species = 0
293 do i=1,total_num_species
294  call kim_get_species_name(i, species_name, ier)
295  call kim_get_species_support_and_code(model_handle, species_name, &
296  species_is_supported, code, ier)
297  if ((ier == 0) .and. (species_is_supported .ne. 0)) then
298  num_species = num_species + 1
299  model_species(num_species) = species_name
300  end if
301 end do
302 
303 ier = 0
304 return
305 
306 end subroutine get_model_supported_species
307 
308 recursive subroutine update_neighborlist(DIM,N,coords,cutoff,cutpad, &
309  do_update_list,coordsave, &
310  neighObject,ierr)
311 use, intrinsic :: iso_c_binding
313 implicit none
314 integer(c_int), parameter :: cd = c_double ! used for literal constants
315 
316 !-- Transferred variables
317 integer(c_int), intent(in) :: DIM
318 integer(c_int), intent(in) :: N
319 real(c_double), intent(in) :: coords(dim,n)
320 real(c_double), intent(in) :: cutoff
321 real(c_double), intent(in) :: cutpad
322 logical, intent(inout) :: do_update_list
323 real(c_double), intent(inout) :: coordsave(dim,n)
324 type(neighobject_type), intent(inout) :: neighObject
325 integer(c_int), intent(out) :: ierr
326 
327 !-- Local variables
328 real(c_double) disp, disp1, disp2, cutrange, dispvec(dim)
329 integer(c_int) i
330 
331 ! Initialize error code
332 !
333 ierr = 0
334 
335 ! Update neighbor lists if necessary
336 !
337 if (.not.do_update_list) then ! if update not requested
338 
339  ! check whether a neighbor list update is necessary even if it hasn't been
340  ! requested using the "two max sum" criterion
341  disp1 = 0.0_cd
342  disp2 = 0.0_cd
343  do i=1,n
344  dispvec(1:dim) = coords(1:dim,i) - coordsave(1:dim,i)
345  disp = sqrt( dot_product(dispvec,dispvec) )
346  if (disp >= disp1) then ! 1st position taken
347  disp2 = disp1 ! push current 1st into 2nd place
348  disp1 = disp ! and put this one into current 1st
349  else if (disp >= disp2) then ! 2nd position taken
350  disp2 = disp
351  endif
352  enddo
353  do_update_list = ( disp1 + disp2 > cutpad )
354 
355 endif
356 
357 if (do_update_list) then
358 
359  ! save current coordinates
360  coordsave(1:dim,1:n) = coords(1:dim,1:n)
361 
362  ! compute neighbor lists
363  cutrange = cutoff + cutpad
364  call neigh_pure_cluster_neighborlist(.false., n, coords, cutrange, &
365  neighobject)
366 
367  ! neighbor list uptodate, no need to compute again for now
368  do_update_list = .false.
369 endif
370 
371 return
372 
373 end subroutine update_neighborlist
374 
375 
376 
377 !-------------------------------------------------------------------------------
378 !
379 ! NEIGH_PURE_cluster_neighborlist
380 !
381 !-------------------------------------------------------------------------------
382 recursive subroutine neigh_pure_cluster_neighborlist(half, numberOfParticles, &
383  coords, cutoff, neighObject)
384  use, intrinsic :: iso_c_binding
385  use mod_neighborlist
386  implicit none
387 
388  !-- Transferred variables
389  logical, intent(in) :: half
390  integer(c_int), intent(in) :: numberOfParticles
391  real(c_double), dimension(3,numberOfParticles), &
392  intent(in) :: coords
393  real(c_double), intent(in) :: cutoff
394  type(neighobject_type), intent(inout) :: neighObject
395 
396  !-- Local variables
397  integer(c_int), pointer :: neighborList(:,:)
398  integer(c_int) i, j, a
399  real(c_double) dx(3)
400  real(c_double) r2
401  real(c_double) cutoff2
402 
403  call c_f_pointer(neighobject%neighbor_list_pointer, neighborlist, &
404  [numberofparticles+1, numberofparticles])
405 
406  neighobject%cutoff = cutoff
407 
408  cutoff2 = cutoff**2
409 
410  do i=1,numberofparticles
411  a = 1
412  do j=1,numberofparticles
413  dx(:) = coords(:, j) - coords(:, i)
414  r2 = dot_product(dx, dx)
415  if (r2.le.cutoff2) then
416  ! part j is a neighbor of part i
417  if ( (j .gt. i) .OR. ((.not. half) .AND. (i.ne.j)) ) then
418  a = a+1
419  neighborlist(a,i) = j
420  endif
421  endif
422  enddo
423  ! part i has a-1 neighbors
424  neighborlist(1,i) = a-1
425  enddo
426 
427  return
428 
429 end subroutine neigh_pure_cluster_neighborlist
430 
431 !-------------------------------------------------------------------------------
432 !
433 ! create_FCC_configuration subroutine
434 !
435 ! creates a cubic configuration of FCC particles with lattice spacing
436 ! `FCCspacing' and `nCellsPerSide' cells along each direction.
437 !
438 ! With periodic==.true. this will result in a total number of particles equal
439 ! to 4*(nCellsPerSide)**3 + 6*(nCellsPerSide)**2 + 3*(nCellsPerSide) + 1
440 !
441 ! With periodic==.false. this will result in a total number of particles equal
442 ! to 4*(nCellsPerSide)**3
443 !
444 ! Returns the Id of the particle situated in the middle of the configuration
445 ! (this particle will have the most neighbors.)
446 !
447 !-------------------------------------------------------------------------------
448 recursive subroutine create_fcc_configuration(FCCspacing, nCellsPerSide, &
449  periodic, coords, MiddlePartId)
450  use, intrinsic :: iso_c_binding
451  implicit none
452  integer(c_int), parameter :: cd = c_double ! used for literal constants
453 
454  !-- Transferred variables
455  real(c_double), intent(in) :: FCCspacing
456  integer(c_int), intent(in) :: nCellsPerSide
457  logical, intent(in) :: periodic
458  real(c_double), intent(out) :: coords(3,*)
459  integer(c_int), intent(out) :: MiddlePartId
460  !
461  ! cluster setup variables
462  !
463  real(c_double) FCCshifts(3,4)
464  real(c_double) latVec(3)
465  integer(c_int) a, i, j, k, m
466 
467  ! Create a cubic FCC cluster
468  !
469  fccshifts(1,1) = 0.0_cd
470  fccshifts(2,1) = 0.0_cd
471  fccshifts(3,1) = 0.0_cd
472  fccshifts(1,2) = 0.5_cd*fccspacing
473  fccshifts(2,2) = 0.5_cd*fccspacing
474  fccshifts(3,2) = 0.0_cd
475  fccshifts(1,3) = 0.5_cd*fccspacing
476  fccshifts(2,3) = 0.0_cd
477  fccshifts(3,3) = 0.5_cd*fccspacing
478  fccshifts(1,4) = 0.0_cd
479  fccshifts(2,4) = 0.5_cd*fccspacing
480  fccshifts(3,4) = 0.5_cd*fccspacing
481 
482  middlepartid = 1 ! Always put middle particle as #1
483  a = 1 ! leave space for middle particle as particle #1
484  do i=1,ncellsperside
485  latvec(1) = (i-1)*fccspacing
486  do j=1,ncellsperside
487  latvec(2) = (j-1)*fccspacing
488  do k=1,ncellsperside
489  latvec(3) = (k-1)*fccspacing
490  do m=1,4
491  a = a+1
492  coords(:,a) = latvec + fccshifts(:,m)
493  if ((i.eq.ncellsperside/2+1).and.(j.eq.ncellsperside/2+1) .and. &
494  (k.eq.ncellsperside/2+1) .and. (m.eq.1)) then
495  coords(:,1) = latvec + fccshifts(:,m) ! put middle particle as #1
496  a = a - 1
497  endif
498  enddo
499  enddo
500  if (.not. periodic) then
501  ! Add in the remaining three faces
502  ! pos-x face
503  latvec(1) = ncellsperside*fccspacing
504  latvec(2) = (i-1)*fccspacing
505  latvec(3) = (j-1)*fccspacing
506  a = a+1; coords(:,a) = latvec
507  a = a+1; coords(:,a) = latvec + fccshifts(:,4)
508  ! pos-y face
509  latvec(1) = (i-1)*fccspacing
510  latvec(2) = ncellsperside*fccspacing
511  latvec(3) = (j-1)*fccspacing
512  a = a+1; coords(:,a) = latvec
513  a = a+1; coords(:,a) = latvec + fccshifts(:,3)
514  ! pos-z face
515  latvec(1) = (i-1)*fccspacing
516  latvec(2) = (j-1)*fccspacing
517  latvec(3) = ncellsperside*fccspacing
518  a = a+1; coords(:,a) = latvec
519  a = a+1; coords(:,a) = latvec + fccshifts(:,2)
520  endif
521  enddo
522  if (.not. periodic) then
523  ! Add in the remaining three edges
524  latvec(1) = (i-1)*fccspacing
525  latvec(2) = ncellsperside*fccspacing
526  latvec(3) = ncellsperside*fccspacing
527  a = a+1; coords(:,a) = latvec
528  latvec(1) = ncellsperside*fccspacing
529  latvec(2) = (i-1)*fccspacing
530  latvec(3) = ncellsperside*fccspacing
531  a = a+1; coords(:,a) = latvec
532  latvec(1) = ncellsperside*fccspacing
533  latvec(2) = ncellsperside*fccspacing
534  latvec(3) = (i-1)*fccspacing
535  a = a+1; coords(:,a) = latvec
536  endif
537  enddo
538  if (.not. periodic) then
539  ! Add in the remaining corner
540  a = a+1; coords(:,a) = ncellsperside*fccspacing
541  endif
542 
543  return
544 
545 end subroutine create_fcc_configuration
546 
547 recursive subroutine compute_numer_deriv(partnum,dir,model_handle, &
548  compute_arguments_handle,DIM,N,coords,cutoff,cutpad,energy,do_update_list, &
549  coordsave,neighObject,deriv,deriv_err,ierr)
550 use, intrinsic :: iso_c_binding
551 use error
553 implicit none
554 integer(c_int), parameter :: cd = c_double ! used for literal constants
555 
556 !--Transferred variables
557 integer(c_int), intent(in) :: partnum
558 integer(c_int), intent(in) :: dir
559 type(kim_model_handle_type), intent(in) :: model_handle
560 type(kim_compute_arguments_handle_type), intent(in) :: compute_arguments_handle
561 integer(c_int), intent(in) :: DIM
562 integer(c_int), intent(in) :: N
563 real(c_double), intent(inout) :: coords(dim,n)
564 real(c_double), intent(in) :: cutoff
565 real(c_double), intent(in) :: cutpad
566 real(c_double), intent(inout) :: energy
567 logical, intent(inout) :: do_update_list
568 real(c_double), intent(inout) :: coordsave(dim,n)
569 type(neighobject_type), intent(inout) :: neighObject
570 real(c_double), intent(out) :: deriv
571 real(c_double), intent(out) :: deriv_err
572 integer(c_int), intent(out) :: ierr
573 
574 !-- Local variables
575 real(c_double), parameter :: eps_init = 1.e-6_cd
576 integer(c_int), parameter :: number_eps_levels = 15
577 real(c_double) eps, deriv_last, deriv_err_last
578 integer(c_int) i
579 
580 ! Initialize error flag
581 ierr = 0
582 
583 deriv_last = 0.0_cd ! initialize
584 
585 ! Outer loop of Ridders' method for computing numerical derivative
586 !
587 eps = eps_init
588 deriv_err_last = huge(1.0_cd)
589 do i=1,number_eps_levels
590  deriv = dfridr(eps,deriv_err)
591  if (ierr /= 0) then
592  call my_error("compute_numer_deriv")
593  endif
594  if (deriv_err>deriv_err_last) then
595  deriv = deriv_last
596  deriv_err = deriv_err_last
597  exit
598  endif
599  eps = eps*10.0_cd
600  deriv_last = deriv
601  deriv_err_last = deriv_err
602 enddo
603 
604 return
605 
606 contains
607 
608  !----------------------------------------------------------------------------
609  !
610  ! Compute numerical derivative using Ridders' method
611  !
612  ! Based on code from Numerical Recipes, Press et al., Second Ed., Cambridge,
613  ! 1992
614  !
615  ! Ref: Ridders, C. J. F., "Two algorithms for the calculation of F'(x)=D",
616  ! Advances in Engineering Software, Vol. 4, no. 2, pp. 75-76, 1982.
617  !
618  !
619  ! Returns the gradient grad() of a KIM-compliant interatomic model at the
620  ! current configuration by Ridders' method of polynomial extrapolation.
621  ! An estimate for the error in each component of the gradient is returned in
622  ! grad_err().
623  !
624  !----------------------------------------------------------------------------
625  real(c_double) recursive function dfridr(h,err)
626  implicit none
627 
628  !-- Transferred variables
629  real(c_double), intent(inout) :: h
630  real(c_double), intent(out) :: err
631 
632  !-- Local variables
633  integer(c_int), parameter :: NTAB=10 ! Maximum size of tableau
634  real(c_double), parameter :: CON=1.4_cd ! Stepsize incr. by CON at each iter
635  real(c_double), parameter :: CON2=con*con
636  real(c_double), parameter :: BIG=huge(1.0_cd)
637  real(c_double), parameter :: SAFE=2.0_cd ! Returns when error is SAFE worse
638  ! than the best so far
639  integer(c_int) i,j
640  real(c_double) errt,fac,hh,a(ntab,ntab),fp,fm,coordorig
641 
642  dfridr = 0.0_cd ! initialize
643 
644  if (abs(h).le.tiny(0.0_cd)) then ! avoid division by zero
645  ierr = 1
646  return
647  endif
648 
649  hh = h
650  coordorig = coords(dir,partnum)
651  coords(dir,partnum) = coordorig + hh
652  call update_neighborlist(dim,n,coords,cutoff,cutpad, &
653  do_update_list,coordsave, &
654  neighobject,ierr)
655  call kim_compute(model_handle, compute_arguments_handle, ierr)
656  if (ierr /= 0) then
657  call my_error("kim_api_model_compute")
658  endif
659  fp = energy
660  coords(dir,partnum) = coordorig - hh
661  call update_neighborlist(dim,n,coords,cutoff,cutpad,&
662  do_update_list,coordsave, &
663  neighobject,ierr)
664  call kim_compute(model_handle, compute_arguments_handle, ierr)
665  if (ierr /= 0) then
666  call my_error("kim_api_model_compute")
667  endif
668  fm = energy
669  coords(dir,partnum) = coordorig
670  call update_neighborlist(dim,n,coords,cutoff,cutpad,&
671  do_update_list,coordsave, &
672  neighobject,ierr)
673  a(1,1)=(fp-fm)/(2.0_cd*hh)
674  err=big
675  ! successive columns in the Neville tableau will go to smaller step sizes
676  ! and higher orders of extrapolation
677  do i=2,ntab
678  ! try new, smaller step size
679  hh=hh/con
680  coords(dir,partnum) = coordorig + hh
681  call update_neighborlist(dim,n,coords,cutoff,cutpad, &
682  do_update_list,coordsave, &
683  neighobject,ierr)
684  call kim_compute(model_handle, compute_arguments_handle, ierr)
685  if (ierr /= 0) then
686  call my_error("kim_api_model_compute")
687  endif
688  fp = energy
689  coords(dir,partnum) = coordorig - hh
690  call update_neighborlist(dim,n,coords,cutoff,cutpad, &
691  do_update_list,coordsave, &
692  neighobject,ierr)
693  call kim_compute(model_handle, compute_arguments_handle, ierr)
694  if (ierr /= 0) then
695  call my_error("kim_api_model_compute")
696  endif
697  fm = energy
698  coords(dir,partnum) = coordorig
699  call update_neighborlist(dim,n,coords,cutoff,cutpad, &
700  do_update_list,coordsave, &
701  neighobject,ierr)
702  a(1,i)=(fp-fm)/(2.0_cd*hh)
703  fac=con2
704  ! compute extrapolations of various orders, requiring no new function
705  ! evaluations
706  do j=2,i
707  a(j,i)=(a(j-1,i)*fac-a(j-1,i-1))/(fac-1.0_cd)
708  fac=con2*fac
709  ! The error strategy is to compute each new extrapolation to one order
710  ! lower, both at the present step size and the previous one.
711  errt = max(abs(a(j,i)-a(j-1,i)),abs(a(j,i)-a(j-1,i-1)))
712  if (errt.le.err) then ! if error is decreased, save the improved answer
713  err = errt
714  dfridr=a(j,i)
715  endif
716  enddo
717  if (abs(a(i,i)-a(i-1,i-1)).ge.safe*err) return ! if higher order is worse
718  ! by significant factor
719  ! `SAFE', then quit early.
720  enddo
721  return
722  end function dfridr
723 
724  end subroutine compute_numer_deriv
725 
726 end module mod_utilities
727 
728 !*******************************************************************************
729 !**
730 !** PROGRAM vc_forces_numer_deriv
731 !**
732 !** KIM compliant program to perform numerical derivative check on a model
733 !**
734 !*******************************************************************************
735 
736 !-------------------------------------------------------------------------------
737 !
738 ! Main program
739 !
740 !-------------------------------------------------------------------------------
742  use, intrinsic :: iso_c_binding
743  use error
744  use mod_neighborlist
745  use mod_utilities
746  implicit none
747  integer(c_int), parameter :: cd = c_double ! used for literal constants
748 
749  integer(c_int), parameter :: nCellsPerSide = 2
750  integer(c_int), parameter :: DIM = 3
751  real(c_double), parameter :: cutpad = 0.75_cd
752  integer(c_int), parameter :: max_species = 200 ! most species supported
753  real(c_double), parameter :: eps_prec = epsilon(1.0_cd)
754  real(c_double) FCCspacing
755 
756  integer(c_int), parameter :: &
757  N = 4*(ncellsperside)**3 + 6*(ncellsperside)**2 + 3*(ncellsperside) + 1
758  real(c_double), allocatable :: forces_num(:,:)
759  real(c_double), allocatable :: forces_num_err(:,:)
760  type(kim_species_name_type) :: model_species(max_species)
761  integer(c_int), target :: num_species
762  character(len=5, kind=c_char) :: passfail
763  real(c_double) :: forcediff
764  real(c_double) :: forcediff_sumsq
765  real(c_double) :: weight
766  real(c_double) :: weight_sum
767  real(c_double) :: alpha
768  real(c_double) :: term
769  real(c_double) :: term_max
770  real(c_double), allocatable :: cluster_coords(:,:)
771  real(c_double), allocatable :: cluster_disps(:,:)
772  type(kim_species_name_type), allocatable :: cluster_species(:)
773  integer(c_int) I,J,Imax,Jmax,species_code
774  integer(c_int) seed_size
775  integer(c_int), allocatable :: seed(:)
776 
777  !
778  ! neighbor list
779  !
780  type(neighobject_type), target :: neighObject
781  integer(c_int), allocatable, target :: neighborList(:,:)
782  real(c_double), allocatable :: coordsave(:,:)
783  logical do_update_list
784 
785  !
786  ! KIM variables
787  !
788  character(len=256, kind=c_char) :: testname = "vc_forces_numer_deriv"
789  character(len=256, kind=c_char) :: modelname
790 
791  type(kim_model_handle_type) :: model_handle
792  type(kim_compute_arguments_handle_type) :: compute_arguments_handle
793  integer(c_int) ierr, ierr2
794  integer(c_int) species_is_supported
795  integer(c_int), target :: numberOfParticles
796  integer(c_int), target :: particleSpeciesCodes(n)
797  integer(c_int), target :: particleContributing(n)
798  real(c_double) :: influence_distance
799  integer(c_int) :: number_of_neighbor_lists
800  real(c_double), allocatable :: cutoffs(:)
801  integer(c_int), allocatable :: &
802  model_will_not_request_neighbors_of_noncontributing_particles(:)
803  real(c_double) :: cutoff
804  real(c_double), target :: energy
805  real(c_double), target :: coords(3,n)
806  real(c_double), target :: forces_kim(3,n)
807  real(c_double) :: forces(3,n)
808  integer(c_int) middleDum
809  logical forces_optional
810  logical model_is_compatible
811  integer(c_int) number_of_model_routine_names
812  type(kim_model_routine_name_type) model_routine_name
813  integer(c_int) present
814  integer(c_int) required
815  integer(c_int) requested_units_accepted
816  real(c_double) rnd, deriv, deriv_err
817  real(c_double), pointer :: null_pointer
818 
819  nullify(null_pointer)
820 
821  numberofparticles = n
822 
823  term_max = 0.0_cd ! initialize
824 
825  ! Initialize error flag
826  ierr = 0
827 
828  ! Initialize seed for random number generator
829  !
830  ! NOTE: Here, we set the seed to a fixed value for reproducibility
831  call random_seed(size=seed_size) ! Get seed size for this CPU
832  allocate(seed(seed_size))
833  seed(:) = 13
834  call random_seed(put=seed)
835  deallocate(seed)
836 
837  ! Get KIM Model name to use
838  print '("Please enter a valid KIM model name: ")'
839  read(*,*) modelname
840 
841  ! Print output header
842  !
843  print *
844  print *,'VERIFICATION CHECK: NUMERICAL DERIVATIVE VERIFICATION OF FORCES'
845  print *
846  print '(120(''-''))'
847  print '("This is Test : ",A)', trim(testname)
848  print '("Results for KIM Model : ",A)', trim(modelname)
849 
850  ! Create empty KIM object
851  !
852  call kim_model_create(kim_numbering_one_based, &
853  kim_length_unit_a, &
854  kim_energy_unit_ev, &
855  kim_charge_unit_e, &
856  kim_temperature_unit_k, &
857  kim_time_unit_ps, &
858  trim(modelname), &
859  requested_units_accepted, &
860  model_handle, ierr)
861  if (ierr /= 0) then
862  call my_error("kim_api_create")
863  endif
864 
865  ! check that we are compatible
866  if (requested_units_accepted == 0) then
867  call my_error("Must adapt to model units")
868  end if
869 
870  ! check that we know about all required routines
871  call kim_get_number_of_model_routine_names(number_of_model_routine_names)
872  do i=1,number_of_model_routine_names
873  call kim_get_model_routine_name(i, model_routine_name, ierr)
874  if (ierr /= 0) then
875  call my_error("kim_get_model_routine_name")
876  endif
877  call kim_is_routine_present(model_handle, model_routine_name, present, &
878  required, ierr)
879  if (ierr /= 0) then
880  call my_error("kim_is_routine_present")
881  endif
882 
883  if ((present == 1) .and. (required == 1)) then
884  if (.not. ((model_routine_name == kim_model_routine_name_create) &
885  .or. (model_routine_name == &
886  kim_model_routine_name_compute_arguments_create) &
887  .or. (model_routine_name == kim_model_routine_name_compute) &
888  .or. (model_routine_name == kim_model_routine_name_refresh) &
889  .or. (model_routine_name == &
890  kim_model_routine_name_compute_arguments_destroy) &
891  .or. (model_routine_name == kim_model_routine_name_destroy))) then
892 
893  call my_error("Unknown required ModelRoutineName found.")
894  endif
895  endif
896  enddo
897 
898  ! create compute_arguments object
899  call kim_compute_arguments_create(model_handle, &
900  compute_arguments_handle, ierr)
901  if (ierr /= 0) then
902  call my_error("kim_model_compute_arguments_create")
903  endif
904 
905  call check_model_compatibility(compute_arguments_handle, forces_optional, &
906  model_is_compatible, ierr)
907  if (ierr /= 0) then
908  call my_error("error checking compatibility")
909  end if
910  if (.not. model_is_compatible) then
911  call my_error("incompatibility reported by check_model_compatibility")
912  end if
913 
914  ! Get list of particle species supported by the model
915  !
916  call get_model_supported_species(model_handle, max_species, model_species, &
917  num_species, ierr)
918  if (ierr /= 0) then
919  call my_error("Get_Model_Supported_Species")
920  endif
921  ! Setup random cluster
922  !
923  allocate(cluster_coords(3,n),cluster_disps(3,n),cluster_species(n))
924  do i=1,n
925  call random_number(rnd) ! return random number between 0 and 1
926  species_code = 1 + int(rnd*num_species)
927  cluster_species(i) = model_species(species_code)
928  enddo
929  fccspacing = 1.0_cd ! initially generate an FCC cluster with lattice
930  ! spacing equal to one. This is scaled below based
931  ! on the cutoff radius of the model.
932  call create_fcc_configuration(fccspacing, ncellsperside, .false., &
933  cluster_coords, middledum)
934  ! Generate random displacements for all particles
935  !
936  do i=1,n
937  do j=1,dim
938  call random_number(rnd) ! return random number between 0 and 1
939  cluster_disps(j,i) = 0.1_cd*(rnd-0.5_cd)
940  enddo
941  enddo
942 
943  ! register memory with the KIM system
944  ierr = 0
945  call kim_set_argument_pointer(compute_arguments_handle, &
946  kim_compute_argument_name_number_of_particles, numberofparticles, ierr2)
947  ierr = ierr + ierr2
948  call kim_set_argument_pointer(compute_arguments_handle, &
949  kim_compute_argument_name_particle_species_codes, particlespeciescodes, &
950  ierr2)
951  ierr = ierr + ierr2
952  call kim_set_argument_pointer(compute_arguments_handle, &
953  kim_compute_argument_name_particle_contributing, particlecontributing, &
954  ierr2)
955  ierr = ierr + ierr2
956  call kim_set_argument_pointer(compute_arguments_handle, &
957  kim_compute_argument_name_coordinates, coords, ierr2)
958  ierr = ierr + ierr2
959  call kim_set_argument_pointer(compute_arguments_handle, &
960  kim_compute_argument_name_partial_energy, energy, ierr2)
961  ierr = ierr + ierr2
962  call kim_set_argument_pointer(compute_arguments_handle, &
963  kim_compute_argument_name_partial_forces, forces_kim, ierr2)
964  ierr = ierr + ierr2
965  if (ierr /= 0) then
966  call my_error("set_argument_pointer")
967  endif
968 
969  ! Allocate storage for neighbor lists and
970  ! store pointers to neighbor list object and access function
971  !
972  allocate(neighborlist(n+1,n))
973  neighobject%neighbor_list_pointer = c_loc(neighborlist)
974  neighobject%number_of_particles = n
975 
976  ! Set pointer in KIM object to neighbor list routine and object
977  !
978  call kim_set_callback_pointer(compute_arguments_handle, &
979  kim_compute_callback_name_get_neighbor_list, kim_language_name_fortran, &
980  c_funloc(get_neigh), c_loc(neighobject), ierr)
981  if (ierr /= 0) then
982  call my_error("set_callback_pointer")
983  end if
984 
985  call kim_get_influence_distance(model_handle, influence_distance)
986  call kim_get_number_of_neighbor_lists(model_handle, &
987  number_of_neighbor_lists)
988  allocate(cutoffs(number_of_neighbor_lists), &
989  model_will_not_request_neighbors_of_noncontributing_particles( &
990  number_of_neighbor_lists))
991  call kim_get_neighbor_list_values(model_handle, cutoffs, &
992  model_will_not_request_neighbors_of_noncontributing_particles, ierr)
993  if (ierr /= 0) then
994  call my_error("get_neighbor_list_values")
995  end if
996  cutoff = maxval(cutoffs)
997 
998  ! Scale reference FCC configuration based on cutoff radius.
999  fccspacing = 0.75_cd*cutoff ! set the FCC spacing to a fraction
1000  ! of the cutoff radius
1001  do i=1,n
1002  cluster_coords(:,i) = fccspacing*cluster_coords(:,i)
1003  enddo
1004  print '("Using FCC lattice parameter: ",f12.5)', fccspacing
1005 
1006  do i=1,n
1007  call kim_get_species_support_and_code(model_handle, &
1008  cluster_species(i), species_is_supported, particlespeciescodes(i), ierr)
1009  enddo
1010  if (ierr /= 0) then
1011  call my_error("kim_api_get_species_code")
1012  endif
1013  do i=1,n
1014  particlecontributing(i) = 1 ! every particle contributes
1015  enddo
1016  do i=1,n
1017  coords(:,i) = cluster_coords(:,i) + cluster_disps(:,i)
1018  enddo
1019 
1020  ! Compute neighbor lists
1021  !
1022  do_update_list = .true.
1023  allocate(coordsave(dim,n))
1024  call update_neighborlist(dim,n,coords,cutoff,cutpad, &
1025  do_update_list,coordsave, &
1026  neighobject,ierr)
1027  if (ierr /= 0) then
1028  call my_error("update_neighborlist")
1029  endif
1030 
1031  ! Call model compute to get forces (gradient)
1032  !
1033  call kim_compute(model_handle, compute_arguments_handle, ierr)
1034  if (ierr /= 0) then
1035  call my_error("kim_api_model_compute")
1036  endif
1037 
1038  ! Copy forces in case model will overwrite forces_kim below
1039  !
1040  forces = forces_kim
1041 
1042  ! Print results to screen
1043  !
1044  print '(41(''=''))'
1045  print '("Energy = ",ES25.15)', energy
1046  print '(41(''=''))'
1047  print *
1048 
1049  ! Turn off force computation, if possible
1050  !
1051  if (forces_optional) then
1052  call kim_set_argument_pointer(compute_arguments_handle, &
1053  kim_compute_argument_name_partial_forces, null_pointer, ierr)
1054  if (ierr /= 0) then
1055  call my_error("set_argument_pointer")
1056  endif
1057  endif
1058 
1059  ! Compute gradient using numerical differentiation
1060  !
1061  allocate(forces_num(dim,n),forces_num_err(dim,n))
1062  do i=1,n
1063  do j=1,dim
1064  call compute_numer_deriv(i,j,model_handle,compute_arguments_handle,&
1065  dim,n,coords,cutoff, &
1066  cutpad, energy, do_update_list, &
1067  coordsave,neighobject,deriv,deriv_err,ierr)
1068  if (ierr /= 0) then
1069  call my_error("compute_numer_deriv")
1070  endif
1071  forces_num(j,i) = -deriv
1072  forces_num_err(j,i) = deriv_err
1073  enddo
1074  enddo
1075 
1076  ! Continue printing results to screen
1077  !
1078  print '(A6,2X,A4,2X,A3,2X,2A25,3A15,2X,A4)',"Part","Spec","Dir", &
1079  "Force_model", "Force_numer", "Force diff", "pred error", "weight", &
1080  "stat"
1081  forcediff_sumsq = 0.0_cd
1082  weight_sum = 0.0_cd
1083  do i=1,n
1084  do j=1,dim
1085  forcediff = abs(forces(j,i)-forces_num(j,i))
1086  if (forcediff<forces_num_err(j,i)) then
1087  passfail = "ideal"
1088  else
1089  passfail = " "
1090  endif
1091  weight = max(abs(forces_num(j,i)),eps_prec)/ &
1092  max(abs(forces_num_err(j,i)),eps_prec)
1093  term = weight*forcediff**2
1094  if (term.gt.term_max) then
1095  term_max = term
1096  imax = i
1097  jmax = j
1098  endif
1099  forcediff_sumsq = forcediff_sumsq + term
1100  weight_sum = weight_sum + weight
1101  if (j.eq.1) then
1102  print '(I6,2X,I4,2X,I3,2X,2ES25.15,3ES15.5,2X,A5)', &
1103  i,particlespeciescodes(i),j,forces(j,i),forces_num(j,i), &
1104  forcediff,forces_num_err(j,i),weight,passfail
1105  else
1106  print '(14X,I3,2X,2ES25.15,3ES15.5,2X,A5)', &
1107  j,forces(j,i),forces_num(j,i), &
1108  forcediff,forces_num_err(j,i),weight,passfail
1109  endif
1110  enddo
1111  print *
1112  enddo
1113  alpha = sqrt(forcediff_sumsq/weight_sum)/dble(dim*n)
1114  print *
1115  print '("alpha = |Force_model - Force_numer|_w/(DIM*N) = ",ES15.5," (units of force)")', &
1116  alpha
1117  print *
1118  print '(''Maximum term obtained for Part = '',I6,'', Dir = '',I1,' // &
1119  ''', forcediff = '',ES15.5, '', forcediff/force_model = '',ES15.5)', &
1120  imax,jmax,abs(forces(jmax,imax)-forces_num(jmax,imax)), &
1121  abs(forces(jmax,imax)-forces_num(jmax,imax))/abs(forces(jmax,imax))
1122 
1123  ! Free temporary storage
1124  !
1125  deallocate(forces_num)
1126  deallocate(forces_num_err)
1127  deallocate(neighborlist)
1128  deallocate(coordsave)
1129  deallocate(cutoffs, model_will_not_request_neighbors_of_noncontributing_particles)
1130 
1131  call kim_compute_arguments_destroy(model_handle, &
1132  compute_arguments_handle, ierr)
1133  if (ierr /= 0) then
1134  call my_error("kim_model_compute_arguments_destroy")
1135  endif
1136  call kim_model_destroy(model_handle)
1137 
1138  ! Print output footer
1139  !
1140  print *
1141  print '(120(''-''))'
1142 
1143  ! Free cluster storage
1144  !
1145  deallocate(cluster_coords,cluster_disps,cluster_species)
1146 
1147  stop
1148 
1149 end program vc_forces_numer_deriv
recursive subroutine check_model_compatibility(compute_arguments_handle, forces_optional, model_is_compatible, ierr)
recursive subroutine, public get_neigh(data_object, number_of_neighbor_lists, cutoffs, neighbor_list_index, request, numnei, pnei1part, ierr)
real(c_double) recursive function dfridr(h, err)
recursive subroutine my_warning(message)
recursive subroutine update_neighborlist(DIM, N, coords, cutoff, cutpad, do_update_list, coordsave, neighObject, ierr)
recursive subroutine get_model_supported_species(model_handle, max_species, model_species, num_species, ier)
recursive subroutine my_error(message)
program vc_forces_numer_deriv
recursive subroutine compute_numer_deriv(partnum, dir, model_handle, compute_arguments_handle, DIM, N, coords, cutoff, cutpad, energy, do_update_list, coordsave, neighObject, deriv, deriv_err, ierr)
recursive subroutine neigh_pure_cluster_neighborlist(half, numberOfParticles, coords, cutoff, neighObject)
recursive subroutine create_fcc_configuration(FCCspacing, nCellsPerSide, periodic, coords, MiddlePartId)