kim-api  2.2.1+v2.2.1.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 ! 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_compute_arguments_destroy_handle_type, &
46  ! Constants
48  ! Routines
49  operator(.eq.), &
50  operator(.ne.), &
51  kim_get_model_buffer_pointer, &
52  kim_log_entry, &
53  kim_to_string
54 
60  type, bind(c) :: kim_model_compute_arguments_destroy_handle_type
61  type(c_ptr) :: p = c_null_ptr
62  end type kim_model_compute_arguments_destroy_handle_type
63 
67  type(kim_model_compute_arguments_destroy_handle_type), protected, save &
69 
74  interface operator(.eq.)
75  module procedure kim_model_compute_arguments_destroy_handle_equal
76  end interface operator(.eq.)
77 
82  interface operator(.ne.)
83  module procedure kim_model_compute_arguments_destroy_handle_not_equal
84  end interface operator(.ne.)
85 
93  interface kim_get_model_buffer_pointer
94  module procedure &
95  kim_model_compute_arguments_destroy_get_model_buffer_pointer
96  end interface kim_get_model_buffer_pointer
97 
104  interface kim_log_entry
106  end interface kim_log_entry
107 
114  interface kim_to_string
116  end interface kim_to_string
117 
118 contains
123  logical recursive function kim_model_compute_arguments_destroy_handle_equal( &
124  lhs, rhs)
125  implicit none
126  type(kim_model_compute_arguments_destroy_handle_type), intent(in) :: lhs
127  type(kim_model_compute_arguments_destroy_handle_type), intent(in) :: rhs
128 
129  if ((.not. c_associated(lhs%p)) .and. (.not. c_associated(rhs%p))) then
130  kim_model_compute_arguments_destroy_handle_equal = .true.
131  else
132  kim_model_compute_arguments_destroy_handle_equal = c_associated(lhs%p, &
133  rhs%p)
134  end if
135  end function kim_model_compute_arguments_destroy_handle_equal
136 
141  logical recursive function &
142  kim_model_compute_arguments_destroy_handle_not_equal(lhs, rhs)
143  implicit none
144  type(kim_model_compute_arguments_destroy_handle_type), intent(in) :: lhs
145  type(kim_model_compute_arguments_destroy_handle_type), intent(in) :: rhs
146 
147  kim_model_compute_arguments_destroy_handle_not_equal = &
148  .not. (lhs == rhs)
149  end function kim_model_compute_arguments_destroy_handle_not_equal
150 
158  recursive subroutine &
159  kim_model_compute_arguments_destroy_get_model_buffer_pointer( &
160  model_compute_arguments_destroy_handle, ptr)
161  use kim_interoperable_types_module, only: &
162  kim_model_compute_arguments_destroy_type
163  implicit none
164  interface
165  recursive subroutine get_model_buffer_pointer( &
166  model_compute_arguments_destroy, ptr) &
167  bind(c, name="KIM_ModelComputeArgumentsDestroy_GetModelBufferPointer")
168  use, intrinsic :: iso_c_binding
169  use kim_interoperable_types_module, only: &
170  kim_model_compute_arguments_destroy_type
171  implicit none
172  type(kim_model_compute_arguments_destroy_type), intent(in) :: &
173  model_compute_arguments_destroy
174  type(c_ptr), intent(out) :: ptr
175  end subroutine get_model_buffer_pointer
176  end interface
177  type(kim_model_compute_arguments_destroy_handle_type), intent(in) :: &
178  model_compute_arguments_destroy_handle
179  type(c_ptr), intent(out) :: ptr
180  type(kim_model_compute_arguments_destroy_type), pointer :: &
181  model_compute_arguments_destroy
182 
183  call c_f_pointer(model_compute_arguments_destroy_handle%p, &
184  model_compute_arguments_destroy)
185  call get_model_buffer_pointer(model_compute_arguments_destroy, ptr)
186  end subroutine kim_model_compute_arguments_destroy_get_model_buffer_pointer
187 
194  recursive subroutine kim_model_compute_arguments_destroy_log_entry( &
195  model_compute_arguments_destroy_handle, log_verbosity, message)
196  use kim_log_verbosity_module, only: kim_log_verbosity_type
197  use kim_interoperable_types_module, only: &
198  kim_model_compute_arguments_destroy_type
199  implicit none
200  interface
201  recursive subroutine log_entry( &
202  model_compute_arguments_destroy, log_verbosity, message, line_number, &
203  file_name) bind(c, name="KIM_ModelComputeArgumentsDestroy_LogEntry")
204  use, intrinsic :: iso_c_binding
205  use kim_log_verbosity_module, only: kim_log_verbosity_type
206  use kim_interoperable_types_module, only: &
207  kim_model_compute_arguments_destroy_type
208  implicit none
209  type(kim_model_compute_arguments_destroy_type), intent(in) :: &
210  model_compute_arguments_destroy
211  type(kim_log_verbosity_type), intent(in), value :: log_verbosity
212  character(c_char), intent(in) :: message(*)
213  integer(c_int), intent(in), value :: line_number
214  character(c_char), intent(in) :: file_name(*)
215  end subroutine log_entry
216  end interface
217  type(kim_model_compute_arguments_destroy_handle_type), intent(in) :: &
218  model_compute_arguments_destroy_handle
219  type(kim_log_verbosity_type), intent(in) :: log_verbosity
220  character(len=*, kind=c_char), intent(in) :: message
221  type(kim_model_compute_arguments_destroy_type), pointer :: &
222  model_compute_arguments_destroy
223 
224  call c_f_pointer(model_compute_arguments_destroy_handle%p, &
225  model_compute_arguments_destroy)
226  call log_entry(model_compute_arguments_destroy, log_verbosity, &
227  trim(message)//c_null_char, 0, ""//c_null_char)
229 
236  recursive subroutine kim_model_compute_arguments_destroy_to_string( &
237  model_compute_arguments_destroy_handle, string)
238  use kim_convert_string_module, only: kim_convert_c_char_ptr_to_string
239  use kim_interoperable_types_module, only: &
240  kim_model_compute_arguments_destroy_type
241  implicit none
242  interface
243  type(c_ptr) recursive function model_compute_arguments_destroy_string( &
244  model_compute_arguments_destroy) &
245  bind(c, name="KIM_ModelComputeArgumentsDestroy_ToString")
246  use, intrinsic :: iso_c_binding
247  use kim_interoperable_types_module, only: &
248  kim_model_compute_arguments_destroy_type
249  implicit none
250  type(kim_model_compute_arguments_destroy_type), intent(in) :: &
251  model_compute_arguments_destroy
252  end function model_compute_arguments_destroy_string
253  end interface
254  type(kim_model_compute_arguments_destroy_handle_type), intent(in) :: &
255  model_compute_arguments_destroy_handle
256  character(len=*, kind=c_char), intent(out) :: string
257  type(kim_model_compute_arguments_destroy_type), pointer :: &
258  model_compute_arguments_destroy
259 
260  type(c_ptr) :: p
261 
262  call c_f_pointer(model_compute_arguments_destroy_handle%p, &
263  model_compute_arguments_destroy)
264  p = model_compute_arguments_destroy_string(model_compute_arguments_destroy)
265  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.