kim-api  2.1.2+v2.1.2.GNU
An Application Programming Interface (API) for the Knowledgebase of Interatomic Models (KIM).
kim_model_compute_arguments_destroy_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--2019, 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.1.2 package.
31 !
32 
33 
40  use, intrinsic :: iso_c_binding
41  implicit none
42  private
43 
44  public &
45  ! Derived types
46  kim_model_compute_arguments_destroy_handle_type, &
47 
48  ! Constants
50 
51  ! Routines
52  operator (.eq.), &
53  operator (.ne.), &
54  kim_get_model_buffer_pointer, &
55  kim_log_entry, &
56  kim_to_string
57 
58 
64  type, bind(c) :: kim_model_compute_arguments_destroy_handle_type
65  type(c_ptr) :: p = c_null_ptr
66  end type kim_model_compute_arguments_destroy_handle_type
67 
71  type(kim_model_compute_arguments_destroy_handle_type), protected, save &
73 
78  interface operator (.eq.)
79  module procedure kim_model_compute_arguments_destroy_handle_equal
80  end interface operator (.eq.)
81 
86  interface operator (.ne.)
87  module procedure kim_model_compute_arguments_destroy_handle_not_equal
88  end interface operator (.ne.)
89 
97  interface kim_get_model_buffer_pointer
98  module procedure &
99  kim_model_compute_arguments_destroy_get_model_buffer_pointer
100  end interface kim_get_model_buffer_pointer
101 
108  interface kim_log_entry
110  end interface kim_log_entry
111 
118  interface kim_to_string
120  end interface kim_to_string
121 
122 contains
127  logical recursive function kim_model_compute_arguments_destroy_handle_equal( &
128  lhs, rhs)
129  implicit none
130  type(kim_model_compute_arguments_destroy_handle_type), intent(in) :: lhs
131  type(kim_model_compute_arguments_destroy_handle_type), intent(in) :: rhs
132 
133  if ((.not. c_associated(lhs%p)) .and. (.not. c_associated(rhs%p))) then
134  kim_model_compute_arguments_destroy_handle_equal = .true.
135  else
136  kim_model_compute_arguments_destroy_handle_equal = c_associated(lhs%p, &
137  rhs%p)
138  end if
139  end function kim_model_compute_arguments_destroy_handle_equal
140 
145  logical recursive function &
146  kim_model_compute_arguments_destroy_handle_not_equal(lhs, rhs)
147  implicit none
148  type(kim_model_compute_arguments_destroy_handle_type), intent(in) :: lhs
149  type(kim_model_compute_arguments_destroy_handle_type), intent(in) :: rhs
150 
151  kim_model_compute_arguments_destroy_handle_not_equal = &
152  .not. (lhs .eq. rhs)
153  end function kim_model_compute_arguments_destroy_handle_not_equal
154 
162  recursive subroutine &
163  kim_model_compute_arguments_destroy_get_model_buffer_pointer( &
164  model_compute_arguments_destroy_handle, ptr)
165  use kim_interoperable_types_module, only : &
166  kim_model_compute_arguments_destroy_type
167  implicit none
168  interface
169  recursive subroutine get_model_buffer_pointer( &
170  model_compute_arguments_destroy, ptr) bind(c, &
171  name="KIM_ModelComputeArgumentsDestroy_GetModelBufferPointer")
172  use, intrinsic :: iso_c_binding
173  use kim_interoperable_types_module, only : &
174  kim_model_compute_arguments_destroy_type
175  implicit none
176  type(kim_model_compute_arguments_destroy_type), intent(in) :: &
177  model_compute_arguments_destroy
178  type(c_ptr), intent(out) :: ptr
179  end subroutine get_model_buffer_pointer
180  end interface
181  type(kim_model_compute_arguments_destroy_handle_type), intent(in) :: &
182  model_compute_arguments_destroy_handle
183  type(c_ptr), intent(out) :: ptr
184  type(kim_model_compute_arguments_destroy_type), pointer :: &
185  model_compute_arguments_destroy
186 
187  call c_f_pointer(model_compute_arguments_destroy_handle%p, &
188  model_compute_arguments_destroy)
189  call get_model_buffer_pointer(model_compute_arguments_destroy, ptr)
190  end subroutine kim_model_compute_arguments_destroy_get_model_buffer_pointer
191 
198  recursive subroutine kim_model_compute_arguments_destroy_log_entry( &
199  model_compute_arguments_destroy_handle, log_verbosity, message)
200  use kim_log_verbosity_module, only : kim_log_verbosity_type
201  use kim_interoperable_types_module, only : &
202  kim_model_compute_arguments_destroy_type
203  implicit none
204  interface
205  recursive subroutine log_entry(model_compute_arguments_destroy, &
206  log_verbosity, message, line_number, file_name) &
207  bind(c, name="KIM_ModelComputeArgumentsDestroy_LogEntry")
208  use, intrinsic :: iso_c_binding
209  use kim_log_verbosity_module, only : kim_log_verbosity_type
210  use kim_interoperable_types_module, only : &
211  kim_model_compute_arguments_destroy_type
212  implicit none
213  type(kim_model_compute_arguments_destroy_type), intent(in) :: &
214  model_compute_arguments_destroy
215  type(kim_log_verbosity_type), intent(in), value :: log_verbosity
216  character(c_char), intent(in) :: message(*)
217  integer(c_int), intent(in), value :: line_number
218  character(c_char), intent(in) :: file_name(*)
219  end subroutine log_entry
220  end interface
221  type(kim_model_compute_arguments_destroy_handle_type), intent(in) :: &
222  model_compute_arguments_destroy_handle
223  type(kim_log_verbosity_type), intent(in) :: log_verbosity
224  character(len=*, kind=c_char), intent(in) :: message
225  type(kim_model_compute_arguments_destroy_type), pointer :: &
226  model_compute_arguments_destroy
227 
228  call c_f_pointer(model_compute_arguments_destroy_handle%p, &
229  model_compute_arguments_destroy)
230  call log_entry(model_compute_arguments_destroy, log_verbosity, &
231  trim(message)//c_null_char, 0, ""//c_null_char)
233 
240  recursive subroutine kim_model_compute_arguments_destroy_to_string( &
241  model_compute_arguments_destroy_handle, string)
242  use kim_convert_string_module, only : kim_convert_c_char_ptr_to_string
243  use kim_interoperable_types_module, only : &
244  kim_model_compute_arguments_destroy_type
245  implicit none
246  interface
247  type(c_ptr) recursive function model_compute_arguments_destroy_string( &
248  model_compute_arguments_destroy) &
249  bind(c, name="KIM_ModelComputeArgumentsDestroy_ToString")
250  use, intrinsic :: iso_c_binding
251  use kim_interoperable_types_module, only : &
252  kim_model_compute_arguments_destroy_type
253  implicit none
254  type(kim_model_compute_arguments_destroy_type), intent(in) :: &
255  model_compute_arguments_destroy
256  end function model_compute_arguments_destroy_string
257  end interface
258  type(kim_model_compute_arguments_destroy_handle_type), intent(in) :: &
259  model_compute_arguments_destroy_handle
260  character(len=*, kind=c_char), intent(out) :: string
261  type(kim_model_compute_arguments_destroy_type), pointer :: &
262  model_compute_arguments_destroy
263 
264  type(c_ptr) :: p
265 
266  call c_f_pointer(model_compute_arguments_destroy_handle%p, &
267  model_compute_arguments_destroy)
268  p = model_compute_arguments_destroy_string(model_compute_arguments_destroy)
269  call kim_convert_c_char_ptr_to_string(p, string)
type(kim_model_compute_arguments_destroy_handle_type), save, public, protected kim_model_compute_arguments_destroy_null_handle
NULL handle for use in comparisons.
recursive subroutine kim_model_compute_arguments_destroy_log_entry(model_compute_arguments_destroy_handle, log_verbosity, message)
Write a log entry into the log file.
Provides the interface to a KIM API ComputeArguments object for use by models within their MODEL_ROUT...
recursive subroutine kim_model_compute_arguments_destroy_to_string(model_compute_arguments_destroy_handle, string)
Get a string representing the internal state of the ComputeArguments object.
An Extensible Enumeration for the LogVerbosity's supported by the KIM API.