kim-api  2.3.0+v2.3.0.GNU.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 ! 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_compute_arguments_destroy_handle_type, &
43  ! Constants
45  ! Routines
46  operator(.eq.), &
47  operator(.ne.), &
48  kim_get_model_buffer_pointer, &
49  kim_log_entry, &
50  kim_to_string
51 
57  type, bind(c) :: kim_model_compute_arguments_destroy_handle_type
58  type(c_ptr) :: p = c_null_ptr
59  end type kim_model_compute_arguments_destroy_handle_type
60 
64  type(kim_model_compute_arguments_destroy_handle_type), protected, save &
66 
71  interface operator(.eq.)
72  module procedure kim_model_compute_arguments_destroy_handle_equal
73  end interface operator(.eq.)
74 
79  interface operator(.ne.)
80  module procedure kim_model_compute_arguments_destroy_handle_not_equal
81  end interface operator(.ne.)
82 
90  interface kim_get_model_buffer_pointer
91  module procedure &
92  kim_model_compute_arguments_destroy_get_model_buffer_pointer
93  end interface kim_get_model_buffer_pointer
94 
101  interface kim_log_entry
103  end interface kim_log_entry
104 
111  interface kim_to_string
113  end interface kim_to_string
114 
115 contains
120  logical recursive function kim_model_compute_arguments_destroy_handle_equal( &
121  lhs, rhs)
122  implicit none
123  type(kim_model_compute_arguments_destroy_handle_type), intent(in) :: lhs
124  type(kim_model_compute_arguments_destroy_handle_type), intent(in) :: rhs
125 
126  if ((.not. c_associated(lhs%p)) .and. (.not. c_associated(rhs%p))) then
127  kim_model_compute_arguments_destroy_handle_equal = .true.
128  else
129  kim_model_compute_arguments_destroy_handle_equal = c_associated(lhs%p, &
130  rhs%p)
131  end if
132  end function kim_model_compute_arguments_destroy_handle_equal
133 
138  logical recursive function &
139  kim_model_compute_arguments_destroy_handle_not_equal(lhs, rhs)
140  implicit none
141  type(kim_model_compute_arguments_destroy_handle_type), intent(in) :: lhs
142  type(kim_model_compute_arguments_destroy_handle_type), intent(in) :: rhs
143 
144  kim_model_compute_arguments_destroy_handle_not_equal = &
145  .not. (lhs == rhs)
146  end function kim_model_compute_arguments_destroy_handle_not_equal
147 
155  recursive subroutine &
156  kim_model_compute_arguments_destroy_get_model_buffer_pointer( &
157  model_compute_arguments_destroy_handle, ptr)
158  use kim_interoperable_types_module, only: &
159  kim_model_compute_arguments_destroy_type
160  implicit none
161  interface
162  recursive subroutine get_model_buffer_pointer( &
163  model_compute_arguments_destroy, ptr) &
164  bind(c, name="KIM_ModelComputeArgumentsDestroy_GetModelBufferPointer")
165  use, intrinsic :: iso_c_binding
166  use kim_interoperable_types_module, only: &
167  kim_model_compute_arguments_destroy_type
168  implicit none
169  type(kim_model_compute_arguments_destroy_type), intent(in) :: &
170  model_compute_arguments_destroy
171  type(c_ptr), intent(out) :: ptr
172  end subroutine get_model_buffer_pointer
173  end interface
174  type(kim_model_compute_arguments_destroy_handle_type), intent(in) :: &
175  model_compute_arguments_destroy_handle
176  type(c_ptr), intent(out) :: ptr
177  type(kim_model_compute_arguments_destroy_type), pointer :: &
178  model_compute_arguments_destroy
179 
180  call c_f_pointer(model_compute_arguments_destroy_handle%p, &
181  model_compute_arguments_destroy)
182  call get_model_buffer_pointer(model_compute_arguments_destroy, ptr)
183  end subroutine kim_model_compute_arguments_destroy_get_model_buffer_pointer
184 
191  recursive subroutine kim_model_compute_arguments_destroy_log_entry( &
192  model_compute_arguments_destroy_handle, log_verbosity, message)
193  use kim_log_verbosity_module, only: kim_log_verbosity_type
194  use kim_interoperable_types_module, only: &
195  kim_model_compute_arguments_destroy_type
196  implicit none
197  interface
198  recursive subroutine log_entry( &
199  model_compute_arguments_destroy, log_verbosity, message, line_number, &
200  file_name) bind(c, name="KIM_ModelComputeArgumentsDestroy_LogEntry")
201  use, intrinsic :: iso_c_binding
202  use kim_log_verbosity_module, only: kim_log_verbosity_type
203  use kim_interoperable_types_module, only: &
204  kim_model_compute_arguments_destroy_type
205  implicit none
206  type(kim_model_compute_arguments_destroy_type), intent(in) :: &
207  model_compute_arguments_destroy
208  type(kim_log_verbosity_type), intent(in), value :: log_verbosity
209  character(c_char), intent(in) :: message(*)
210  integer(c_int), intent(in), value :: line_number
211  character(c_char), intent(in) :: file_name(*)
212  end subroutine log_entry
213  end interface
214  type(kim_model_compute_arguments_destroy_handle_type), intent(in) :: &
215  model_compute_arguments_destroy_handle
216  type(kim_log_verbosity_type), intent(in) :: log_verbosity
217  character(len=*, kind=c_char), intent(in) :: message
218  type(kim_model_compute_arguments_destroy_type), pointer :: &
219  model_compute_arguments_destroy
220 
221  call c_f_pointer(model_compute_arguments_destroy_handle%p, &
222  model_compute_arguments_destroy)
223  call log_entry(model_compute_arguments_destroy, log_verbosity, &
224  trim(message)//c_null_char, 0, ""//c_null_char)
226 
233  recursive subroutine kim_model_compute_arguments_destroy_to_string( &
234  model_compute_arguments_destroy_handle, string)
235  use kim_convert_string_module, only: kim_convert_c_char_ptr_to_string
236  use kim_interoperable_types_module, only: &
237  kim_model_compute_arguments_destroy_type
238  implicit none
239  interface
240  type(c_ptr) recursive function model_compute_arguments_destroy_string( &
241  model_compute_arguments_destroy) &
242  bind(c, name="KIM_ModelComputeArgumentsDestroy_ToString")
243  use, intrinsic :: iso_c_binding
244  use kim_interoperable_types_module, only: &
245  kim_model_compute_arguments_destroy_type
246  implicit none
247  type(kim_model_compute_arguments_destroy_type), intent(in) :: &
248  model_compute_arguments_destroy
249  end function model_compute_arguments_destroy_string
250  end interface
251  type(kim_model_compute_arguments_destroy_handle_type), intent(in) :: &
252  model_compute_arguments_destroy_handle
253  character(len=*, kind=c_char), intent(out) :: string
254  type(kim_model_compute_arguments_destroy_type), pointer :: &
255  model_compute_arguments_destroy
256 
257  type(c_ptr) :: p
258 
259  call c_f_pointer(model_compute_arguments_destroy_handle%p, &
260  model_compute_arguments_destroy)
261  p = model_compute_arguments_destroy_string(model_compute_arguments_destroy)
262  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.