kim-api  2.2.1+v2.2.1.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 ! 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) 2016--2020, Regents of the University of Minnesota.
23 ! All rights reserved.
24 !
25 ! Contributors:
26 ! Ryan S. Elliott
27 !
28 
29 !
30 ! Release: This file is part of the kim-api-2.2.1 package.
31 !
32 
39  use, intrinsic :: iso_c_binding
40  implicit none
41  private
42 
43  public &
44  ! Derived types
45  kim_model_refresh_handle_type, &
46  ! Constants
48  ! Routines
49  operator(.eq.), &
50  operator(.ne.), &
51  kim_set_influence_distance_pointer, &
52  kim_set_neighbor_list_pointers, &
53  kim_get_model_buffer_pointer, &
54  kim_log_entry, &
55  kim_to_string
56 
62  type, bind(c) :: kim_model_refresh_handle_type
63  type(c_ptr) :: p = c_null_ptr
64  end type kim_model_refresh_handle_type
65 
69  type(kim_model_refresh_handle_type), protected, save &
71 
75  interface operator(.eq.)
76  module procedure kim_model_refresh_handle_equal
77  end interface operator(.eq.)
78 
82  interface operator(.ne.)
83  module procedure kim_model_refresh_handle_not_equal
84  end interface operator(.ne.)
85 
92  interface kim_set_influence_distance_pointer
93  module procedure kim_model_refresh_set_influence_distance_pointer
94  end interface kim_set_influence_distance_pointer
95 
102  interface kim_set_neighbor_list_pointers
104  end interface kim_set_neighbor_list_pointers
105 
112  interface kim_get_model_buffer_pointer
114  end interface kim_get_model_buffer_pointer
115 
121  interface kim_log_entry
122  module procedure kim_model_refresh_log_entry
123  end interface kim_log_entry
124 
130  interface kim_to_string
131  module procedure kim_model_refresh_to_string
132  end interface kim_to_string
133 
134 contains
138  logical recursive function kim_model_refresh_handle_equal(lhs, rhs)
139  implicit none
140  type(kim_model_refresh_handle_type), intent(in) :: lhs
141  type(kim_model_refresh_handle_type), intent(in) :: rhs
142 
143  if ((.not. c_associated(lhs%p) .and. c_associated(rhs%p))) then
144  kim_model_refresh_handle_equal = .true.
145  else
146  kim_model_refresh_handle_equal = c_associated(lhs%p, rhs%p)
147  end if
148  end function kim_model_refresh_handle_equal
149 
153  logical recursive function kim_model_refresh_handle_not_equal(lhs, rhs)
154  implicit none
155  type(kim_model_refresh_handle_type), intent(in) :: lhs
156  type(kim_model_refresh_handle_type), intent(in) :: rhs
157 
158  kim_model_refresh_handle_not_equal = .not. (lhs == rhs)
159  end function kim_model_refresh_handle_not_equal
160 
167  recursive subroutine kim_model_refresh_set_influence_distance_pointer( &
168  model_refresh_handle, influence_distance)
169  use kim_interoperable_types_module, only: kim_model_refresh_type
170  implicit none
171  interface
172  recursive subroutine set_influence_distance_pointer(model_refresh, &
173  influence_distance) &
174  bind(c, name="KIM_ModelRefresh_SetInfluenceDistancePointer")
175  use, intrinsic :: iso_c_binding
176  use kim_interoperable_types_module, only: kim_model_refresh_type
177  implicit none
178  type(kim_model_refresh_type), intent(in) :: &
179  model_refresh
180  type(c_ptr), intent(in), value :: influence_distance
181  end subroutine set_influence_distance_pointer
182  end interface
183  type(kim_model_refresh_handle_type), intent(in) :: model_refresh_handle
184  real(c_double), intent(in), target :: influence_distance
185  type(kim_model_refresh_type), pointer :: model_refresh
186 
187  call c_f_pointer(model_refresh_handle%p, model_refresh)
188  call set_influence_distance_pointer(model_refresh, &
189  c_loc(influence_distance))
190  end subroutine kim_model_refresh_set_influence_distance_pointer
191 
198  recursive subroutine kim_model_refresh_set_neighbor_list_pointers( &
199  model_refresh_handle, number_of_neighbor_lists, cutoffs, &
200  modelWillNotRequestNeighborsOfNoncontributingParticles)
201  use kim_interoperable_types_module, only: kim_model_refresh_type
202  implicit none
203  interface
204  recursive subroutine set_neighbor_list_pointers( &
205  model_refresh, number_of_neighbor_lists, cutoffs_ptr, &
206  modelWillNotRequestNeighborsOfNoncontributingParticles) &
207  bind(c, name="KIM_ModelRefresh_SetNeighborListPointers")
208  use, intrinsic :: iso_c_binding
209  use kim_interoperable_types_module, only: kim_model_refresh_type
210  implicit none
211  type(kim_model_refresh_type), intent(in) :: &
212  model_refresh
213  integer(c_int), intent(in), value :: number_of_neighbor_lists
214  type(c_ptr), intent(in), value :: cutoffs_ptr
215  type(c_ptr), intent(in), value :: &
216  modelWillNotRequestNeighborsOfNoncontributingParticles
217  end subroutine set_neighbor_list_pointers
218  end interface
219  type(kim_model_refresh_handle_type), intent(in) :: model_refresh_handle
220  integer(c_int), intent(in) :: number_of_neighbor_lists
221  real(c_double), intent(in), target :: cutoffs(number_of_neighbor_lists)
222  integer(c_int), intent(in), target :: &
223  modelWillNotRequestNeighborsOfNoncontributingParticles( &
224  number_of_neighbor_lists)
225  type(kim_model_refresh_type), pointer :: model_refresh
226 
227  call c_f_pointer(model_refresh_handle%p, model_refresh)
228  call set_neighbor_list_pointers( &
229  model_refresh, number_of_neighbor_lists, c_loc(cutoffs), &
230  c_loc(modelwillnotrequestneighborsofnoncontributingparticles))
232 
239  recursive subroutine kim_model_refresh_get_model_buffer_pointer( &
240  model_refresh_handle, ptr)
241  use kim_interoperable_types_module, only: kim_model_refresh_type
242  implicit none
243  interface
244  recursive subroutine get_model_buffer_pointer(model_refresh, ptr) &
245  bind(c, name="KIM_ModelRefresh_GetModelBufferPointer")
246  use, intrinsic :: iso_c_binding
247  use kim_interoperable_types_module, only: kim_model_refresh_type
248  implicit none
249  type(kim_model_refresh_type), intent(in) :: &
250  model_refresh
251  type(c_ptr), intent(out) :: ptr
252  end subroutine get_model_buffer_pointer
253  end interface
254  type(kim_model_refresh_handle_type), intent(in) :: model_refresh_handle
255  type(c_ptr), intent(out) :: ptr
256  type(kim_model_refresh_type), pointer :: model_refresh
257 
258  call c_f_pointer(model_refresh_handle%p, model_refresh)
259  call get_model_buffer_pointer(model_refresh, ptr)
261 
267  recursive subroutine kim_model_refresh_log_entry(model_refresh_handle, &
268  log_verbosity, message)
269  use kim_log_verbosity_module, only: kim_log_verbosity_type
270  use kim_interoperable_types_module, only: kim_model_refresh_type
271  implicit none
272  interface
273  recursive subroutine log_entry( &
274  model_refresh, log_verbosity, message, line_number, file_name) &
275  bind(c, name="KIM_ModelRefresh_LogEntry")
276  use, intrinsic :: iso_c_binding
277  use kim_log_verbosity_module, only: kim_log_verbosity_type
278  use kim_interoperable_types_module, only: kim_model_refresh_type
279  implicit none
280  type(kim_model_refresh_type), intent(in) :: &
281  model_refresh
282  type(kim_log_verbosity_type), intent(in), value :: log_verbosity
283  character(c_char), intent(in) :: message(*)
284  integer(c_int), intent(in), value :: line_number
285  character(c_char), intent(in) :: file_name(*)
286  end subroutine log_entry
287  end interface
288  type(kim_model_refresh_handle_type), intent(in) :: model_refresh_handle
289  type(kim_log_verbosity_type), intent(in) :: log_verbosity
290  character(len=*, kind=c_char), intent(in) :: message
291  type(kim_model_refresh_type), pointer :: model_refresh
292 
293  call c_f_pointer(model_refresh_handle%p, model_refresh)
294  call log_entry(model_refresh, log_verbosity, trim(message)//c_null_char, &
295  0, ""//c_null_char)
296  end subroutine kim_model_refresh_log_entry
297 
303  recursive subroutine kim_model_refresh_to_string(model_refresh_handle, string)
304  use kim_convert_string_module, only: kim_convert_c_char_ptr_to_string
305  use kim_interoperable_types_module, only: kim_model_refresh_type
306  implicit none
307  interface
308  type(c_ptr) recursive function model_refresh_string(model_refresh) &
309  bind(c, name="KIM_ModelRefresh_ToString")
310  use, intrinsic :: iso_c_binding
311  use kim_interoperable_types_module, only: kim_model_refresh_type
312  implicit none
313  type(kim_model_refresh_type), intent(in) :: &
314  model_refresh
315  end function model_refresh_string
316  end interface
317  type(kim_model_refresh_handle_type), intent(in) :: model_refresh_handle
318  character(len=*, kind=c_char), intent(out) :: string
319  type(kim_model_refresh_type), pointer :: model_refresh
320 
321  type(c_ptr) :: p
322 
323  call c_f_pointer(model_refresh_handle%p, model_refresh)
324  p = model_refresh_string(model_refresh)
325  call kim_convert_c_char_ptr_to_string(p, string)
326  end subroutine kim_model_refresh_to_string
327 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.