kim-api  2.3.1-git+v2.3.0-git-2-g378406f9.GNU.GNU.
An Application Programming Interface (API) for the Knowledgebase of Interatomic Models (KIM).
kim_model_compute_arguments_module.f90
Go to the documentation of this file.
1 !
2 ! KIM-API: An API for interatomic models
3 ! Copyright (c) 2013--2022, Regents of the University of Minnesota.
4 ! All rights reserved.
5 !
6 ! Contributors:
7 ! Ryan S. Elliott
8 !
9 ! SPDX-License-Identifier: LGPL-2.1-or-later
10 !
11 ! This library is free software; you can redistribute it and/or
12 ! modify it under the terms of the GNU Lesser General Public
13 ! License as published by the Free Software Foundation; either
14 ! version 2.1 of the License, or (at your option) any later version.
15 !
16 ! This library is distributed in the hope that it will be useful,
17 ! but WITHOUT ANY WARRANTY; without even the implied warranty of
18 ! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
19 ! Lesser General Public License for more details.
20 !
21 ! You should have received a copy of the GNU Lesser General Public License
22 ! along with this library; if not, write to the Free Software Foundation,
23 ! Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA
24 !
25 
26 !
27 ! Release: This file is part of the kim-api.git repository.
28 !
29 
36  use, intrinsic :: iso_c_binding
37  implicit none
38  private
39 
40  public &
41  ! Derived types
42  kim_model_compute_arguments_handle_type, &
43  ! Constants
45  ! Routines
46  operator(.eq.), &
47  operator(.ne.), &
48  kim_get_neighbor_list, &
49  kim_process_dedr_term, &
50  kim_process_d2edr2_term, &
51  kim_get_argument_pointer, &
52  kim_is_callback_present, &
53  kim_set_model_buffer_pointer, &
54  kim_get_model_buffer_pointer, &
55  kim_log_entry, &
56  kim_to_string
57 
63  type, bind(c) :: kim_model_compute_arguments_handle_type
64  type(c_ptr) :: p = c_null_ptr
65  end type kim_model_compute_arguments_handle_type
66 
70  type(kim_model_compute_arguments_handle_type), protected, save &
72 
77  interface operator(.eq.)
78  module procedure kim_model_compute_arguments_handle_equal
79  end interface operator(.eq.)
80 
85  interface operator(.ne.)
86  module procedure kim_model_compute_arguments_handle_not_equal
87  end interface operator(.ne.)
88 
95  interface kim_get_neighbor_list
96  module procedure kim_model_compute_arguments_get_neighbor_list
97  end interface kim_get_neighbor_list
98 
105  interface kim_process_dedr_term
107  end interface kim_process_dedr_term
108 
115  interface kim_process_d2edr2_term
117  end interface kim_process_d2edr2_term
118 
126  interface kim_get_argument_pointer
133  end interface kim_get_argument_pointer
134 
141  interface kim_is_callback_present
143  end interface kim_is_callback_present
144 
151  interface kim_set_model_buffer_pointer
153  end interface kim_set_model_buffer_pointer
154 
161  interface kim_get_model_buffer_pointer
163  end interface kim_get_model_buffer_pointer
164 
171  interface kim_log_entry
173  end interface kim_log_entry
174 
181  interface kim_to_string
183  end interface kim_to_string
184 
185 contains
190  logical recursive function kim_model_compute_arguments_handle_equal(lhs, rhs)
191  implicit none
192  type(kim_model_compute_arguments_handle_type), intent(in) :: lhs
193  type(kim_model_compute_arguments_handle_type), intent(in) :: rhs
194 
195  if ((.not. c_associated(lhs%p)) .and. (.not. c_associated(rhs%p))) then
196  kim_model_compute_arguments_handle_equal = .true.
197  else
198  kim_model_compute_arguments_handle_equal = c_associated(lhs%p, rhs%p)
199  end if
200  end function kim_model_compute_arguments_handle_equal
201 
206  logical recursive function kim_model_compute_arguments_handle_not_equal(lhs, &
207  rhs)
208  implicit none
209  type(kim_model_compute_arguments_handle_type), intent(in) :: lhs
210  type(kim_model_compute_arguments_handle_type), intent(in) :: rhs
211 
212  kim_model_compute_arguments_handle_not_equal = .not. (lhs == rhs)
213  end function kim_model_compute_arguments_handle_not_equal
214 
249  recursive subroutine kim_model_compute_arguments_get_neighbor_list( &
250  model_compute_arguments_handle, neighbor_list_index, particle_number, &
251  number_of_neighbors, neighbors_of_particle, ierr)
252  use kim_interoperable_types_module, only: kim_model_compute_arguments_type
253  implicit none
254  interface
255  integer(c_int) recursive function get_neighbor_list( &
256  model_compute_arguments, neighbor_list_index, particle_number, &
257  number_of_neighbors, neighbors_of_particle) &
258  bind(c, name="KIM_ModelComputeArguments_GetNeighborList")
259  use, intrinsic :: iso_c_binding
260  use kim_interoperable_types_module, only: &
261  kim_model_compute_arguments_type
262  implicit none
263  type(kim_model_compute_arguments_type), intent(in) :: &
264  model_compute_arguments
265  integer(c_int), intent(in), value :: neighbor_list_index
266  integer(c_int), intent(in), value :: particle_number
267  integer(c_int), intent(out) :: number_of_neighbors
268  type(c_ptr), intent(out) :: neighbors_of_particle
269  end function get_neighbor_list
270  end interface
271  type(kim_model_compute_arguments_handle_type), intent(in) :: &
272  model_compute_arguments_handle
273  integer(c_int), intent(in) :: neighbor_list_index
274  integer(c_int), intent(in) :: particle_number
275  integer(c_int), intent(out) :: number_of_neighbors
276  integer(c_int), intent(out), pointer :: neighbors_of_particle(:)
277  integer(c_int), intent(out) :: ierr
278  type(kim_model_compute_arguments_type), pointer :: model_compute_arguments
279 
280  type(c_ptr) p
281 
282  call c_f_pointer(model_compute_arguments_handle%p, model_compute_arguments)
283  ierr = get_neighbor_list(model_compute_arguments, neighbor_list_index - 1, &
284  particle_number, number_of_neighbors, p)
285  if (c_associated(p)) then
286  call c_f_pointer(p, neighbors_of_particle, [number_of_neighbors])
287  else
288  nullify (neighbors_of_particle)
289  end if
290  end subroutine kim_model_compute_arguments_get_neighbor_list
291 
319  recursive subroutine kim_model_compute_arguments_process_dedr_term( &
320  model_compute_arguments_handle, de, r, dx, i, j, ierr)
321  use kim_interoperable_types_module, only: kim_model_compute_arguments_type
322  implicit none
323  interface
324  integer(c_int) recursive function process_dedr_term( &
325  model_compute_arguments, de, r, dx, i, j) &
326  bind(c, name="KIM_ModelComputeArguments_ProcessDEDrTerm")
327  use, intrinsic :: iso_c_binding
328  use kim_interoperable_types_module, only: &
329  kim_model_compute_arguments_type
330  implicit none
331  type(kim_model_compute_arguments_type), intent(in) :: &
332  model_compute_arguments
333  real(c_double), intent(in), value :: de
334  real(c_double), intent(in), value :: r
335  real(c_double), intent(in) :: dx
336  integer(c_int), intent(in), value :: i
337  integer(c_int), intent(in), value :: j
338  end function process_dedr_term
339  end interface
340  type(kim_model_compute_arguments_handle_type), intent(in) :: &
341  model_compute_arguments_handle
342  real(c_double), intent(in) :: de
343  real(c_double), intent(in) :: r
344  real(c_double), intent(in) :: dx(:)
345  integer(c_int), intent(in) :: i
346  integer(c_int), intent(in) :: j
347  integer(c_int), intent(out) :: ierr
348  type(kim_model_compute_arguments_type), pointer :: model_compute_arguments
349 
350  call c_f_pointer(model_compute_arguments_handle%p, model_compute_arguments)
351  ierr = process_dedr_term(model_compute_arguments, de, r, dx(1), i, j)
353 
382  model_compute_arguments_handle, de, r, dx, i, j, ierr)
383  use kim_interoperable_types_module, only: kim_model_compute_arguments_type
384  implicit none
385  interface
386  integer(c_int) recursive function process_d2edr2_term( &
387  model_compute_arguments, de, r, dx, i, j) &
388  bind(c, name="KIM_ModelComputeArguments_ProcessD2EDr2Term")
389  use, intrinsic :: iso_c_binding
390  use kim_interoperable_types_module, only: &
391  kim_model_compute_arguments_type
392  implicit none
393  type(kim_model_compute_arguments_type), intent(in) :: &
394  model_compute_arguments
395  real(c_double), intent(in), value :: de
396  real(c_double), intent(in) :: r
397  real(c_double), intent(in) :: dx
398  integer(c_int), intent(in) :: i
399  integer(c_int), intent(in) :: j
400  end function process_d2edr2_term
401  end interface
402  type(kim_model_compute_arguments_handle_type), intent(in) :: &
403  model_compute_arguments_handle
404  real(c_double), intent(in) :: de
405  real(c_double), intent(in) :: r(:)
406  real(c_double), intent(in) :: dx(:, :)
407  integer(c_int), intent(in) :: i(:)
408  integer(c_int), intent(in) :: j(:)
409  integer(c_int), intent(out) :: ierr
410  type(kim_model_compute_arguments_type), pointer :: model_compute_arguments
411 
412  call c_f_pointer(model_compute_arguments_handle%p, model_compute_arguments)
413  ierr = process_d2edr2_term(model_compute_arguments, &
414  de, r(1), dx(1, 1), i(1), j(1))
416 
424  model_compute_arguments_handle, compute_argument_name, int0, ierr)
425  use kim_compute_argument_name_module, only: kim_compute_argument_name_type
426  use kim_interoperable_types_module, only: kim_model_compute_arguments_type
427  implicit none
428  interface
429  integer(c_int) recursive function get_argument_pointer_integer( &
430  model_compute_arguments, compute_argument_name, ptr) &
431  bind(c, name="KIM_ModelComputeArguments_GetArgumentPointerInteger")
432  use, intrinsic :: iso_c_binding
434  kim_compute_argument_name_type
435  use kim_interoperable_types_module, only: &
436  kim_model_compute_arguments_type
437  implicit none
438  type(kim_model_compute_arguments_type), intent(in) :: &
439  model_compute_arguments
440  type(kim_compute_argument_name_type), intent(in), value :: &
441  compute_argument_name
442  type(c_ptr), intent(out) :: ptr
443  end function get_argument_pointer_integer
444  end interface
445  type(kim_model_compute_arguments_handle_type), intent(in) :: &
446  model_compute_arguments_handle
447  type(kim_compute_argument_name_type), intent(in) :: &
448  compute_argument_name
449  integer(c_int), intent(out), pointer :: int0
450  integer(c_int), intent(out) :: ierr
451  type(kim_model_compute_arguments_type), pointer :: model_compute_arguments
452 
453  type(c_ptr) p
454 
455  call c_f_pointer(model_compute_arguments_handle%p, model_compute_arguments)
456  ierr = get_argument_pointer_integer(model_compute_arguments, &
457  compute_argument_name, p)
458  if (c_associated(p)) then
459  call c_f_pointer(p, int0)
460  else
461  nullify (int0)
462  end if
464 
472  model_compute_arguments_handle, compute_argument_name, extent1, int1, ierr)
473  use kim_compute_argument_name_module, only: kim_compute_argument_name_type
474  use kim_interoperable_types_module, only: kim_model_compute_arguments_type
475  implicit none
476  interface
477  integer(c_int) recursive function get_argument_pointer_integer( &
478  model_compute_arguments, compute_argument_name, ptr) &
479  bind(c, name="KIM_ModelComputeArguments_GetArgumentPointerInteger")
480  use, intrinsic :: iso_c_binding
482  kim_compute_argument_name_type
483  use kim_interoperable_types_module, only: &
484  kim_model_compute_arguments_type
485  implicit none
486  type(kim_model_compute_arguments_type), intent(in) :: &
487  model_compute_arguments
488  type(kim_compute_argument_name_type), intent(in), value :: &
489  compute_argument_name
490  type(c_ptr), intent(out) :: ptr
491  end function get_argument_pointer_integer
492  end interface
493  type(kim_model_compute_arguments_handle_type), intent(in) :: &
494  model_compute_arguments_handle
495  type(kim_compute_argument_name_type), intent(in) :: &
496  compute_argument_name
497  integer(c_int), intent(in) :: extent1
498  integer(c_int), intent(out), pointer :: int1(:)
499  integer(c_int), intent(out) :: ierr
500  type(kim_model_compute_arguments_type), pointer :: model_compute_arguments
501 
502  type(c_ptr) p
503 
504  call c_f_pointer(model_compute_arguments_handle%p, model_compute_arguments)
505  ierr = get_argument_pointer_integer(model_compute_arguments, &
506  compute_argument_name, p)
507  if (c_associated(p)) then
508  call c_f_pointer(p, int1, [extent1])
509  else
510  nullify (int1)
511  end if
512 
514 
522  model_compute_arguments_handle, compute_argument_name, extent1, extent2, &
523  int2, ierr)
524  use kim_compute_argument_name_module, only: kim_compute_argument_name_type
525  use kim_interoperable_types_module, only: kim_model_compute_arguments_type
526  implicit none
527  interface
528  integer(c_int) recursive function get_argument_pointer_integer( &
529  model_compute_arguments, compute_argument_name, ptr) &
530  bind(c, name="KIM_ModelComputeArguments_GetArgumentPointerInteger")
531  use, intrinsic :: iso_c_binding
533  kim_compute_argument_name_type
534  use kim_interoperable_types_module, only: &
535  kim_model_compute_arguments_type
536  implicit none
537  type(kim_model_compute_arguments_type), intent(in) :: &
538  model_compute_arguments
539  type(kim_compute_argument_name_type), intent(in), value :: &
540  compute_argument_name
541  type(c_ptr), intent(out) :: ptr
542  end function get_argument_pointer_integer
543  end interface
544  type(kim_model_compute_arguments_handle_type), intent(in) :: &
545  model_compute_arguments_handle
546  type(kim_compute_argument_name_type), intent(in) :: &
547  compute_argument_name
548  integer(c_int), intent(in) :: extent1
549  integer(c_int), intent(in) :: extent2
550  integer(c_int), intent(out), pointer :: int2(:, :)
551  integer(c_int), intent(out) :: ierr
552  type(kim_model_compute_arguments_type), pointer :: model_compute_arguments
553 
554  type(c_ptr) p
555 
556  call c_f_pointer(model_compute_arguments_handle%p, model_compute_arguments)
557  ierr = get_argument_pointer_integer(model_compute_arguments, &
558  compute_argument_name, p)
559  if (c_associated(p)) then
560  call c_f_pointer(p, int2, [extent1, extent2])
561  else
562  nullify (int2)
563  end if
565 
572  recursive subroutine &
574  model_compute_arguments_handle, compute_argument_name, double0, ierr)
575  use kim_compute_argument_name_module, only: kim_compute_argument_name_type
576  use kim_interoperable_types_module, only: kim_model_compute_arguments_type
577  implicit none
578  interface
579  integer(c_int) recursive function get_argument_pointer_double( &
580  model_compute_arguments, compute_argument_name, ptr) &
581  bind(c, name="KIM_ModelComputeArguments_GetArgumentPointerDouble")
582  use, intrinsic :: iso_c_binding
584  kim_compute_argument_name_type
585  use kim_interoperable_types_module, only: &
586  kim_model_compute_arguments_type
587  implicit none
588  type(kim_model_compute_arguments_type), intent(in) :: &
589  model_compute_arguments
590  type(kim_compute_argument_name_type), intent(in), value :: &
591  compute_argument_name
592  type(c_ptr), intent(out) :: ptr
593  end function get_argument_pointer_double
594  end interface
595  type(kim_model_compute_arguments_handle_type), intent(in) :: &
596  model_compute_arguments_handle
597  type(kim_compute_argument_name_type), intent(in) :: &
598  compute_argument_name
599  real(c_double), intent(out), pointer :: double0
600  integer(c_int), intent(out) :: ierr
601  type(kim_model_compute_arguments_type), pointer :: model_compute_arguments
602 
603  type(c_ptr) p
604 
605  call c_f_pointer(model_compute_arguments_handle%p, model_compute_arguments)
606  ierr = get_argument_pointer_double(model_compute_arguments, &
607  compute_argument_name, p)
608  if (c_associated(p)) then
609  call c_f_pointer(p, double0)
610  else
611  nullify (double0)
612  end if
614 
621  recursive subroutine &
623  model_compute_arguments_handle, compute_argument_name, extent1, double1, &
624  ierr)
625  use kim_compute_argument_name_module, only: kim_compute_argument_name_type
626  use kim_interoperable_types_module, only: kim_model_compute_arguments_type
627  implicit none
628  interface
629  integer(c_int) recursive function get_argument_pointer_double( &
630  model_compute_arguments, compute_argument_name, ptr) &
631  bind(c, name="KIM_ModelComputeArguments_GetArgumentPointerDouble")
632  use, intrinsic :: iso_c_binding
634  kim_compute_argument_name_type
635  use kim_interoperable_types_module, only: &
636  kim_model_compute_arguments_type
637  implicit none
638  type(kim_model_compute_arguments_type), intent(in) :: &
639  model_compute_arguments
640  type(kim_compute_argument_name_type), intent(in), value :: &
641  compute_argument_name
642  type(c_ptr), intent(out) :: ptr
643  end function get_argument_pointer_double
644  end interface
645  type(kim_model_compute_arguments_handle_type), intent(in) :: &
646  model_compute_arguments_handle
647  type(kim_compute_argument_name_type), intent(in) :: &
648  compute_argument_name
649  integer(c_int), intent(in) :: extent1
650  real(c_double), intent(out), pointer :: double1(:)
651  integer(c_int), intent(out) :: ierr
652  type(kim_model_compute_arguments_type), pointer :: model_compute_arguments
653 
654  type(c_ptr) p
655 
656  call c_f_pointer(model_compute_arguments_handle%p, model_compute_arguments)
657  ierr = get_argument_pointer_double(model_compute_arguments, &
658  compute_argument_name, p)
659  if (c_associated(p)) then
660  call c_f_pointer(p, double1, [extent1])
661  else
662  nullify (double1)
663  end if
665 
672  recursive subroutine &
674  model_compute_arguments_handle, compute_argument_name, extent1, extent2, &
675  double2, ierr)
676  use kim_compute_argument_name_module, only: kim_compute_argument_name_type
677  use kim_interoperable_types_module, only: kim_model_compute_arguments_type
678  implicit none
679  interface
680  integer(c_int) recursive function get_argument_pointer_double( &
681  model_compute_arguments, compute_argument_name, ptr) &
682  bind(c, name="KIM_ModelComputeArguments_GetArgumentPointerDouble")
683  use, intrinsic :: iso_c_binding
685  kim_compute_argument_name_type
686  use kim_interoperable_types_module, only: &
687  kim_model_compute_arguments_type
688  implicit none
689  type(kim_model_compute_arguments_type), intent(in) :: &
690  model_compute_arguments
691  type(kim_compute_argument_name_type), intent(in), value :: &
692  compute_argument_name
693  type(c_ptr), intent(out) :: ptr
694  end function get_argument_pointer_double
695  end interface
696  type(kim_model_compute_arguments_handle_type), intent(in) :: &
697  model_compute_arguments_handle
698  type(kim_compute_argument_name_type), intent(in) :: &
699  compute_argument_name
700  integer(c_int), intent(in) :: extent1
701  integer(c_int), intent(in) :: extent2
702  real(c_double), intent(out), pointer :: double2(:, :)
703  integer(c_int), intent(out) :: ierr
704  type(kim_model_compute_arguments_type), pointer :: model_compute_arguments
705 
706  type(c_ptr) p
707 
708  call c_f_pointer(model_compute_arguments_handle%p, model_compute_arguments)
709  ierr = get_argument_pointer_double(model_compute_arguments, &
710  compute_argument_name, p)
711  if (c_associated(p)) then
712  call c_f_pointer(p, double2, [extent1, extent2])
713  else
714  nullify (double2)
715  end if
717 
725  model_compute_arguments_handle, compute_callback_name, present, ierr)
726  use kim_compute_callback_name_module, only: kim_compute_callback_name_type
727  use kim_interoperable_types_module, only: kim_model_compute_arguments_type
728  implicit none
729  interface
730  integer(c_int) recursive function is_callback_present( &
731  model_compute_arguments, compute_callback_name, present) &
732  bind(c, name="KIM_ModelComputeArguments_IsCallbackPresent")
733  use, intrinsic :: iso_c_binding
735  kim_compute_callback_name_type
736  use kim_interoperable_types_module, only: &
737  kim_model_compute_arguments_type
738  implicit none
739  type(kim_model_compute_arguments_type), intent(in) :: &
740  model_compute_arguments
741  type(kim_compute_callback_name_type), intent(in), value :: &
742  compute_callback_name
743  integer(c_int), intent(out) :: present
744  end function is_callback_present
745  end interface
746  type(kim_model_compute_arguments_handle_type), intent(in) :: &
747  model_compute_arguments_handle
748  type(kim_compute_callback_name_type), intent(in) :: &
749  compute_callback_name
750  integer(c_int), intent(out) :: present
751  integer(c_int), intent(out) :: ierr
752  type(kim_model_compute_arguments_type), pointer :: model_compute_arguments
753 
754  call c_f_pointer(model_compute_arguments_handle%p, model_compute_arguments)
755  ierr = is_callback_present(model_compute_arguments, compute_callback_name, &
756  present)
758 
766  model_compute_arguments_handle, ptr)
767  use kim_interoperable_types_module, only: kim_model_compute_arguments_type
768  implicit none
769  interface
770  recursive subroutine set_model_buffer_pointer( &
771  model_compute_arguments, ptr) &
772  bind(c, name="KIM_ModelComputeArguments_SetModelBufferPointer")
773  use, intrinsic :: iso_c_binding
774  use kim_interoperable_types_module, only: &
775  kim_model_compute_arguments_type
776  implicit none
777  type(kim_model_compute_arguments_type), intent(in) :: &
778  model_compute_arguments
779  type(c_ptr), intent(in), value :: ptr
780  end subroutine set_model_buffer_pointer
781  end interface
782  type(kim_model_compute_arguments_handle_type), intent(in) :: &
783  model_compute_arguments_handle
784  type(c_ptr), intent(in) :: ptr
785  type(kim_model_compute_arguments_type), pointer :: model_compute_arguments
786 
787  call c_f_pointer(model_compute_arguments_handle%p, model_compute_arguments)
788  call set_model_buffer_pointer(model_compute_arguments, ptr)
790 
798  model_compute_arguments_handle, ptr)
799  use kim_interoperable_types_module, only: kim_model_compute_arguments_type
800  implicit none
801  interface
802  recursive subroutine get_model_buffer_pointer( &
803  model_compute_arguments, ptr) &
804  bind(c, name="KIM_ModelComputeArguments_GetModelBufferPointer")
805  use, intrinsic :: iso_c_binding
806  use kim_interoperable_types_module, only: &
807  kim_model_compute_arguments_type
808  implicit none
809  type(kim_model_compute_arguments_type), intent(in) :: &
810  model_compute_arguments
811  type(c_ptr), intent(out) :: ptr
812  end subroutine get_model_buffer_pointer
813  end interface
814  type(kim_model_compute_arguments_handle_type), intent(in) :: &
815  model_compute_arguments_handle
816  type(c_ptr), intent(out) :: ptr
817  type(kim_model_compute_arguments_type), pointer :: model_compute_arguments
818 
819  call c_f_pointer(model_compute_arguments_handle%p, model_compute_arguments)
820  call get_model_buffer_pointer(model_compute_arguments, ptr)
822 
829  recursive subroutine kim_model_compute_arguments_log_entry( &
830  model_compute_arguments_handle, log_verbosity, message)
831  use kim_log_verbosity_module, only: kim_log_verbosity_type
832  use kim_interoperable_types_module, only: kim_model_compute_arguments_type
833  implicit none
834  interface
835  recursive subroutine log_entry(model_compute_arguments, log_verbosity, &
836  message, line_number, file_name) &
837  bind(c, name="KIM_ModelComputeArguments_LogEntry")
838  use, intrinsic :: iso_c_binding
839  use kim_log_verbosity_module, only: kim_log_verbosity_type
840  use kim_interoperable_types_module, only: &
841  kim_model_compute_arguments_type
842  implicit none
843  type(kim_model_compute_arguments_type), intent(in) :: &
844  model_compute_arguments
845  type(kim_log_verbosity_type), intent(in), value :: log_verbosity
846  character(c_char), intent(in) :: message(*)
847  integer(c_int), intent(in), value :: line_number
848  character(c_char), intent(in) :: file_name(*)
849  end subroutine log_entry
850  end interface
851  type(kim_model_compute_arguments_handle_type), intent(in) :: &
852  model_compute_arguments_handle
853  type(kim_log_verbosity_type), intent(in) :: log_verbosity
854  character(len=*, kind=c_char), intent(in) :: message
855  type(kim_model_compute_arguments_type), pointer :: model_compute_arguments
856 
857  call c_f_pointer(model_compute_arguments_handle%p, model_compute_arguments)
858  call log_entry(model_compute_arguments, log_verbosity, &
859  trim(message)//c_null_char, 0, ""//c_null_char)
861 
868  recursive subroutine kim_model_compute_arguments_to_string( &
869  model_compute_arguments_handle, string)
870  use kim_convert_string_module, only: kim_convert_c_char_ptr_to_string
871  use kim_interoperable_types_module, only: kim_model_compute_arguments_type
872  implicit none
873  interface
874  type(c_ptr) recursive function model_compute_string( &
875  model_compute_arguments) &
876  bind(c, name="KIM_ModelComputeArguments_ToString")
877  use, intrinsic :: iso_c_binding
878  use kim_interoperable_types_module, only: &
879  kim_model_compute_arguments_type
880  implicit none
881  type(kim_model_compute_arguments_type), intent(in) :: &
882  model_compute_arguments
883  end function model_compute_string
884  end interface
885  type(kim_model_compute_arguments_handle_type), intent(in) :: &
886  model_compute_arguments_handle
887  character(len=*, kind=c_char), intent(out) :: string
888  type(kim_model_compute_arguments_type), pointer :: model_compute_arguments
889 
890  type(c_ptr) :: p
891 
892  call c_f_pointer(model_compute_arguments_handle%p, model_compute_arguments)
893  p = model_compute_string(model_compute_arguments)
894  call kim_convert_c_char_ptr_to_string(p, string)
type(kim_model_compute_arguments_handle_type), save, public, protected kim_model_compute_arguments_null_handle
NULL handle for use in comparisons.
recursive subroutine kim_model_compute_arguments_get_argument_pointer_int1(model_compute_arguments_handle, compute_argument_name, extent1, int1, ierr)
Get the data pointer for a ComputeArgumentName.
recursive subroutine kim_model_compute_arguments_log_entry(model_compute_arguments_handle, log_verbosity, message)
Write a log entry into the log file.
recursive subroutine kim_model_compute_arguments_get_argument_pointer_double0(model_compute_arguments_handle, compute_argument_name, double0, ierr)
Get the data pointer for a ComputeArgumentName.
recursive subroutine kim_model_compute_arguments_process_d2edr2_term(model_compute_arguments_handle, de, r, dx, i, j, ierr)
Call the Simulator's COMPUTE_CALLBACK_NAME::ProcessD2EDr2Term routine.
recursive subroutine kim_model_compute_arguments_set_model_buffer_pointer(model_compute_arguments_handle, ptr)
Set the Model's buffer pointer within the ComputeArguments object.
recursive subroutine kim_model_compute_arguments_process_dedr_term(model_compute_arguments_handle, de, r, dx, i, j, ierr)
Call the Simulator's COMPUTE_CALLBACK_NAME::ProcessDEDrTerm routine.
recursive subroutine kim_model_compute_arguments_get_argument_pointer_int0(model_compute_arguments_handle, compute_argument_name, int0, ierr)
Get the data pointer for a ComputeArgumentName.
recursive subroutine kim_model_compute_arguments_is_callback_present(model_compute_arguments_handle, compute_callback_name, present, ierr)
Determine if the Simulator has provided a non-NULL function pointer for a ComputeCallbackName of inte...
recursive subroutine kim_model_compute_arguments_get_argument_pointer_int2(model_compute_arguments_handle, compute_argument_name, extent1, extent2, int2, ierr)
Get the data pointer for a ComputeArgumentName.
recursive subroutine kim_model_compute_arguments_get_model_buffer_pointer(model_compute_arguments_handle, ptr)
Get the Model's buffer pointer within the ComputeArguments object.
recursive subroutine kim_model_compute_arguments_to_string(model_compute_arguments_handle, string)
Get a string representing the internal state of the ComputeArguments object.
recursive subroutine kim_model_compute_arguments_get_argument_pointer_double2(model_compute_arguments_handle, compute_argument_name, extent1, extent2, double2, ierr)
Get the data pointer for a ComputeArgumentName.
Provides the interface to a KIM API ComputeArguments object for use by models within their MODEL_ROUT...
recursive subroutine kim_model_compute_arguments_get_argument_pointer_double1(model_compute_arguments_handle, compute_argument_name, extent1, double1, ierr)
Get the data pointer for a ComputeArgumentName.
An Extensible Enumeration for the ComputeCallbackName's supported by the KIM API. ...
An Extensible Enumeration for the ComputeArgumentName's supported by the KIM API. ...
An Extensible Enumeration for the LogVerbosity's supported by the KIM API.