kim-api  2.3.0+v2.3.0.GNU.GNU.
An Application Programming Interface (API) for the Knowledgebase of Interatomic Models (KIM).
kim_model_refresh_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-2.3.0 package.
28 !
29 
36  use, intrinsic :: iso_c_binding
37  implicit none
38  private
39 
40  public &
41  ! Derived types
42  kim_model_refresh_handle_type, &
43  ! Constants
45  ! Routines
46  operator(.eq.), &
47  operator(.ne.), &
48  kim_set_influence_distance_pointer, &
49  kim_set_neighbor_list_pointers, &
50  kim_get_model_buffer_pointer, &
51  kim_log_entry, &
52  kim_to_string
53 
59  type, bind(c) :: kim_model_refresh_handle_type
60  type(c_ptr) :: p = c_null_ptr
61  end type kim_model_refresh_handle_type
62 
66  type(kim_model_refresh_handle_type), protected, save &
68 
72  interface operator(.eq.)
73  module procedure kim_model_refresh_handle_equal
74  end interface operator(.eq.)
75 
79  interface operator(.ne.)
80  module procedure kim_model_refresh_handle_not_equal
81  end interface operator(.ne.)
82 
89  interface kim_set_influence_distance_pointer
90  module procedure kim_model_refresh_set_influence_distance_pointer
91  end interface kim_set_influence_distance_pointer
92 
99  interface kim_set_neighbor_list_pointers
101  end interface kim_set_neighbor_list_pointers
102 
109  interface kim_get_model_buffer_pointer
111  end interface kim_get_model_buffer_pointer
112 
118  interface kim_log_entry
119  module procedure kim_model_refresh_log_entry
120  end interface kim_log_entry
121 
127  interface kim_to_string
128  module procedure kim_model_refresh_to_string
129  end interface kim_to_string
130 
131 contains
135  logical recursive function kim_model_refresh_handle_equal(lhs, rhs)
136  implicit none
137  type(kim_model_refresh_handle_type), intent(in) :: lhs
138  type(kim_model_refresh_handle_type), intent(in) :: rhs
139 
140  if ((.not. c_associated(lhs%p) .and. c_associated(rhs%p))) then
141  kim_model_refresh_handle_equal = .true.
142  else
143  kim_model_refresh_handle_equal = c_associated(lhs%p, rhs%p)
144  end if
145  end function kim_model_refresh_handle_equal
146 
150  logical recursive function kim_model_refresh_handle_not_equal(lhs, rhs)
151  implicit none
152  type(kim_model_refresh_handle_type), intent(in) :: lhs
153  type(kim_model_refresh_handle_type), intent(in) :: rhs
154 
155  kim_model_refresh_handle_not_equal = .not. (lhs == rhs)
156  end function kim_model_refresh_handle_not_equal
157 
164  recursive subroutine kim_model_refresh_set_influence_distance_pointer( &
165  model_refresh_handle, influence_distance)
166  use kim_interoperable_types_module, only: kim_model_refresh_type
167  implicit none
168  interface
169  recursive subroutine set_influence_distance_pointer(model_refresh, &
170  influence_distance) &
171  bind(c, name="KIM_ModelRefresh_SetInfluenceDistancePointer")
172  use, intrinsic :: iso_c_binding
173  use kim_interoperable_types_module, only: kim_model_refresh_type
174  implicit none
175  type(kim_model_refresh_type), intent(in) :: &
176  model_refresh
177  type(c_ptr), intent(in), value :: influence_distance
178  end subroutine set_influence_distance_pointer
179  end interface
180  type(kim_model_refresh_handle_type), intent(in) :: model_refresh_handle
181  real(c_double), intent(in), target :: influence_distance
182  type(kim_model_refresh_type), pointer :: model_refresh
183 
184  call c_f_pointer(model_refresh_handle%p, model_refresh)
185  call set_influence_distance_pointer(model_refresh, &
186  c_loc(influence_distance))
187  end subroutine kim_model_refresh_set_influence_distance_pointer
188 
195  recursive subroutine kim_model_refresh_set_neighbor_list_pointers( &
196  model_refresh_handle, number_of_neighbor_lists, cutoffs, &
197  modelWillNotRequestNeighborsOfNoncontributingParticles)
198  use kim_interoperable_types_module, only: kim_model_refresh_type
199  implicit none
200  interface
201  recursive subroutine set_neighbor_list_pointers( &
202  model_refresh, number_of_neighbor_lists, cutoffs_ptr, &
203  modelWillNotRequestNeighborsOfNoncontributingParticles) &
204  bind(c, name="KIM_ModelRefresh_SetNeighborListPointers")
205  use, intrinsic :: iso_c_binding
206  use kim_interoperable_types_module, only: kim_model_refresh_type
207  implicit none
208  type(kim_model_refresh_type), intent(in) :: &
209  model_refresh
210  integer(c_int), intent(in), value :: number_of_neighbor_lists
211  type(c_ptr), intent(in), value :: cutoffs_ptr
212  type(c_ptr), intent(in), value :: &
213  modelWillNotRequestNeighborsOfNoncontributingParticles
214  end subroutine set_neighbor_list_pointers
215  end interface
216  type(kim_model_refresh_handle_type), intent(in) :: model_refresh_handle
217  integer(c_int), intent(in) :: number_of_neighbor_lists
218  real(c_double), intent(in), target :: cutoffs(number_of_neighbor_lists)
219  integer(c_int), intent(in), target :: &
220  modelWillNotRequestNeighborsOfNoncontributingParticles( &
221  number_of_neighbor_lists)
222  type(kim_model_refresh_type), pointer :: model_refresh
223 
224  call c_f_pointer(model_refresh_handle%p, model_refresh)
225  call set_neighbor_list_pointers( &
226  model_refresh, number_of_neighbor_lists, c_loc(cutoffs), &
227  c_loc(modelwillnotrequestneighborsofnoncontributingparticles))
229 
236  recursive subroutine kim_model_refresh_get_model_buffer_pointer( &
237  model_refresh_handle, ptr)
238  use kim_interoperable_types_module, only: kim_model_refresh_type
239  implicit none
240  interface
241  recursive subroutine get_model_buffer_pointer(model_refresh, ptr) &
242  bind(c, name="KIM_ModelRefresh_GetModelBufferPointer")
243  use, intrinsic :: iso_c_binding
244  use kim_interoperable_types_module, only: kim_model_refresh_type
245  implicit none
246  type(kim_model_refresh_type), intent(in) :: &
247  model_refresh
248  type(c_ptr), intent(out) :: ptr
249  end subroutine get_model_buffer_pointer
250  end interface
251  type(kim_model_refresh_handle_type), intent(in) :: model_refresh_handle
252  type(c_ptr), intent(out) :: ptr
253  type(kim_model_refresh_type), pointer :: model_refresh
254 
255  call c_f_pointer(model_refresh_handle%p, model_refresh)
256  call get_model_buffer_pointer(model_refresh, ptr)
258 
264  recursive subroutine kim_model_refresh_log_entry(model_refresh_handle, &
265  log_verbosity, message)
266  use kim_log_verbosity_module, only: kim_log_verbosity_type
267  use kim_interoperable_types_module, only: kim_model_refresh_type
268  implicit none
269  interface
270  recursive subroutine log_entry( &
271  model_refresh, log_verbosity, message, line_number, file_name) &
272  bind(c, name="KIM_ModelRefresh_LogEntry")
273  use, intrinsic :: iso_c_binding
274  use kim_log_verbosity_module, only: kim_log_verbosity_type
275  use kim_interoperable_types_module, only: kim_model_refresh_type
276  implicit none
277  type(kim_model_refresh_type), intent(in) :: &
278  model_refresh
279  type(kim_log_verbosity_type), intent(in), value :: log_verbosity
280  character(c_char), intent(in) :: message(*)
281  integer(c_int), intent(in), value :: line_number
282  character(c_char), intent(in) :: file_name(*)
283  end subroutine log_entry
284  end interface
285  type(kim_model_refresh_handle_type), intent(in) :: model_refresh_handle
286  type(kim_log_verbosity_type), intent(in) :: log_verbosity
287  character(len=*, kind=c_char), intent(in) :: message
288  type(kim_model_refresh_type), pointer :: model_refresh
289 
290  call c_f_pointer(model_refresh_handle%p, model_refresh)
291  call log_entry(model_refresh, log_verbosity, trim(message)//c_null_char, &
292  0, ""//c_null_char)
293  end subroutine kim_model_refresh_log_entry
294 
300  recursive subroutine kim_model_refresh_to_string(model_refresh_handle, string)
301  use kim_convert_string_module, only: kim_convert_c_char_ptr_to_string
302  use kim_interoperable_types_module, only: kim_model_refresh_type
303  implicit none
304  interface
305  type(c_ptr) recursive function model_refresh_string(model_refresh) &
306  bind(c, name="KIM_ModelRefresh_ToString")
307  use, intrinsic :: iso_c_binding
308  use kim_interoperable_types_module, only: kim_model_refresh_type
309  implicit none
310  type(kim_model_refresh_type), intent(in) :: &
311  model_refresh
312  end function model_refresh_string
313  end interface
314  type(kim_model_refresh_handle_type), intent(in) :: model_refresh_handle
315  character(len=*, kind=c_char), intent(out) :: string
316  type(kim_model_refresh_type), pointer :: model_refresh
317 
318  type(c_ptr) :: p
319 
320  call c_f_pointer(model_refresh_handle%p, model_refresh)
321  p = model_refresh_string(model_refresh)
322  call kim_convert_c_char_ptr_to_string(p, string)
323  end subroutine kim_model_refresh_to_string
324 end module kim_model_refresh_module
recursive subroutine kim_model_refresh_log_entry(model_refresh_handle, log_verbosity, message)
Write a log entry into the log file.
recursive subroutine kim_model_refresh_set_neighbor_list_pointers(model_refresh_handle, number_of_neighbor_lists, cutoffs, modelWillNotRequestNeighborsOfNoncontributingParticles)
Set the Model's neighbor list data pointers.
Provides the interface to a KIM API Model object for use by models within their MODEL_ROUTINE_NAME::R...
recursive subroutine kim_model_refresh_to_string(model_refresh_handle, string)
Get a string representing the internal state of the Model object.
recursive subroutine kim_model_refresh_get_model_buffer_pointer(model_refresh_handle, ptr)
Get the Model's buffer pointer within the Model object.
type(kim_model_refresh_handle_type), save, public, protected kim_model_refresh_null_handle
NULL handle for use in comparisons.
An Extensible Enumeration for the LogVerbosity's supported by the KIM API.