kim-api  2.3.0+v2.3.0.GNU.GNU.
An Application Programming Interface (API) for the Knowledgebase of Interatomic Models (KIM).
kim_compute_argument_name_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_compute_argument_name_type, &
43  ! Constants
53  ! Routines
54  kim_known, &
55  operator(.eq.), &
56  operator(.ne.), &
57  kim_from_string, &
58  kim_to_string, &
62 
68  type, bind(c) :: kim_compute_argument_name_type
75  integer(c_int) compute_argument_name_id
76  end type kim_compute_argument_name_type
77 
84  type(kim_compute_argument_name_type), protected, save, &
85  bind(c, name="KIM_COMPUTE_ARGUMENT_NAME_numberOfParticles") &
87 
94  type(kim_compute_argument_name_type), protected, save, &
95  bind(c, name="KIM_COMPUTE_ARGUMENT_NAME_particleSpeciesCodes") &
97 
104  type(kim_compute_argument_name_type), protected, save, &
105  bind(c, name="KIM_COMPUTE_ARGUMENT_NAME_particleContributing") &
107 
114  type(kim_compute_argument_name_type), protected, save, &
115  bind(c, name="KIM_COMPUTE_ARGUMENT_NAME_coordinates") &
117 
124  type(kim_compute_argument_name_type), protected, save, &
125  bind(c, name="KIM_COMPUTE_ARGUMENT_NAME_partialEnergy") &
127 
134  type(kim_compute_argument_name_type), protected, save, &
135  bind(c, name="KIM_COMPUTE_ARGUMENT_NAME_partialForces") &
137 
144  type(kim_compute_argument_name_type), protected, save, &
145  bind(c, name="KIM_COMPUTE_ARGUMENT_NAME_partialParticleEnergy") &
147 
154  type(kim_compute_argument_name_type), protected, save, &
155  bind(c, name="KIM_COMPUTE_ARGUMENT_NAME_partialVirial") &
157 
164  type(kim_compute_argument_name_type), protected, save, &
165  bind(c, name="KIM_COMPUTE_ARGUMENT_NAME_partialParticleVirial") &
167 
173  interface kim_known
174  module procedure kim_compute_argument_name_known
175  end interface kim_known
176 
182  interface operator(.eq.)
183  module procedure kim_compute_argument_name_equal
184  end interface operator(.eq.)
185 
192  interface operator(.ne.)
193  module procedure kim_compute_argument_name_not_equal
194  end interface operator(.ne.)
195 
203  interface kim_from_string
204  module procedure kim_compute_argument_name_from_string
205  end interface kim_from_string
206 
212  interface kim_to_string
213  module procedure kim_compute_argument_name_to_string
214  end interface kim_to_string
215 
216 contains
222  logical recursive function kim_compute_argument_name_known( &
223  compute_argument_name)
224  implicit none
225  interface
226  integer(c_int) recursive function known(compute_argument_name) &
227  bind(c, name="KIM_ComputeArgumentName_Known")
228  use, intrinsic :: iso_c_binding
229  import kim_compute_argument_name_type
230  implicit none
231  type(kim_compute_argument_name_type), intent(in), value :: &
232  compute_argument_name
233  end function known
234  end interface
235  type(kim_compute_argument_name_type), intent(in) :: compute_argument_name
236 
237  kim_compute_argument_name_known = (known(compute_argument_name) /= 0)
238  end function kim_compute_argument_name_known
239 
245  logical recursive function kim_compute_argument_name_equal(lhs, rhs)
246  implicit none
247  type(kim_compute_argument_name_type), intent(in) :: lhs
248  type(kim_compute_argument_name_type), intent(in) :: rhs
249 
250  kim_compute_argument_name_equal &
251  = (lhs%compute_argument_name_id == rhs%compute_argument_name_id)
252  end function kim_compute_argument_name_equal
253 
260  logical recursive function kim_compute_argument_name_not_equal(lhs, rhs)
261  implicit none
262  type(kim_compute_argument_name_type), intent(in) :: lhs
263  type(kim_compute_argument_name_type), intent(in) :: rhs
264 
265  kim_compute_argument_name_not_equal = .not. (lhs == rhs)
266  end function kim_compute_argument_name_not_equal
267 
275  recursive subroutine kim_compute_argument_name_from_string( &
276  string, compute_argument_name)
277  implicit none
278  interface
279  type(kim_compute_argument_name_type) recursive function from_string( &
280  string) bind(c, name="KIM_ComputeArgumentName_FromString")
281  use, intrinsic :: iso_c_binding
282  import kim_compute_argument_name_type
283  implicit none
284  character(c_char), intent(in) :: string(*)
285  end function from_string
286  end interface
287  character(len=*, kind=c_char), intent(in) :: string
288  type(kim_compute_argument_name_type), intent(out) :: compute_argument_name
289 
290  compute_argument_name = from_string(trim(string)//c_null_char)
291  end subroutine kim_compute_argument_name_from_string
292 
298  recursive subroutine kim_compute_argument_name_to_string( &
299  compute_argument_name, string)
300  use kim_convert_string_module, only: kim_convert_c_char_ptr_to_string
301  implicit none
302  interface
303  type(c_ptr) recursive function get_string(compute_argument_name) &
304  bind(c, name="KIM_ComputeArgumentName_ToString")
305  use, intrinsic :: iso_c_binding
306  import kim_compute_argument_name_type
307  implicit none
308  type(kim_compute_argument_name_type), intent(in), value :: &
309  compute_argument_name
310  end function get_string
311  end interface
312  type(kim_compute_argument_name_type), intent(in) :: &
313  compute_argument_name
314  character(len=*, kind=c_char), intent(out) :: string
315 
316  type(c_ptr) :: p
317 
318  p = get_string(compute_argument_name)
319  call kim_convert_c_char_ptr_to_string(p, string)
320  end subroutine kim_compute_argument_name_to_string
321 
329  recursive subroutine kim_get_number_of_compute_argument_names( &
330  number_of_compute_argument_names)
331  implicit none
332  interface
333  recursive subroutine get_number_of_compute_argument_names( &
334  number_of_compute_argument_names) &
335  bind(c, &
336  name="KIM_COMPUTE_ARGUMENT_NAME_GetNumberOfComputeArgumentNames")
337  use, intrinsic :: iso_c_binding
338  integer(c_int), intent(out) :: number_of_compute_argument_names
339  end subroutine get_number_of_compute_argument_names
340  end interface
341  integer(c_int), intent(out) :: number_of_compute_argument_names
342 
343  call get_number_of_compute_argument_names(number_of_compute_argument_names)
345 
353  recursive subroutine kim_get_compute_argument_name( &
354  index, compute_argument_name, ierr)
355  implicit none
356  interface
357  integer(c_int) recursive function get_compute_argument_name( &
358  index, compute_argument_name) &
359  bind(c, name="KIM_COMPUTE_ARGUMENT_NAME_GetComputeArgumentName")
360  use, intrinsic :: iso_c_binding
361  import kim_compute_argument_name_type
362  implicit none
363  integer(c_int), intent(in), value :: index
364  type(kim_compute_argument_name_type), intent(out) :: &
365  compute_argument_name
366  end function get_compute_argument_name
367  end interface
368  integer(c_int), intent(in) :: index
369  type(kim_compute_argument_name_type), intent(out) :: compute_argument_name
370  integer(c_int), intent(out) :: ierr
371 
372  ierr = get_compute_argument_name(index - 1, compute_argument_name)
373  end subroutine kim_get_compute_argument_name
374 
382  recursive subroutine kim_get_compute_argument_data_type( &
383  compute_argument_name, &
384  data_type, ierr)
385  use kim_data_type_module, only: kim_data_type_type
386  implicit none
387  interface
388  integer(c_int) recursive function get_compute_argument_data_type( &
389  compute_argument_name, data_type) &
390  bind(c, name="KIM_COMPUTE_ARGUMENT_NAME_GetComputeArgumentDataType")
391  use, intrinsic :: iso_c_binding
392  use kim_data_type_module, only: kim_data_type_type
393  import kim_compute_argument_name_type
394  implicit none
395  type(kim_compute_argument_name_type), intent(in), value :: &
396  compute_argument_name
397  type(kim_data_type_type), intent(out) :: data_type
398  end function get_compute_argument_data_type
399  end interface
400  type(kim_compute_argument_name_type), intent(in) :: &
401  compute_argument_name
402  type(kim_data_type_type), intent(out) :: data_type
403  integer(c_int), intent(out) :: ierr
404 
405  ierr = get_compute_argument_data_type(compute_argument_name, data_type)
recursive subroutine, public kim_get_compute_argument_data_type(compute_argument_name, data_type, ierr)
Get the DataType of each defined standard ComputeArgumentName.
type(kim_compute_argument_name_type), save, public, protected kim_compute_argument_name_particle_contributing
type(kim_compute_argument_name_type), save, public, protected kim_compute_argument_name_partial_virial
recursive subroutine, public kim_get_compute_argument_name(index, compute_argument_name, ierr)
Get the identity of each defined standard ComputeArgumentName.
type(kim_compute_argument_name_type), save, public, protected kim_compute_argument_name_partial_energy
type(kim_compute_argument_name_type), save, public, protected kim_compute_argument_name_partial_particle_energy
type(kim_compute_argument_name_type), save, public, protected kim_compute_argument_name_coordinates
recursive subroutine, public kim_get_number_of_compute_argument_names(number_of_compute_argument_names)
Get the number of standard ComputeArgumentName's defined by the KIM API.
type(kim_compute_argument_name_type), save, public, protected kim_compute_argument_name_partial_particle_virial
type(kim_compute_argument_name_type), save, public, protected kim_compute_argument_name_particle_species_codes
An Extensible Enumeration for the DataType's supported by the KIM API.
type(kim_compute_argument_name_type), save, public, protected kim_compute_argument_name_partial_forces
An Extensible Enumeration for the ComputeArgumentName's supported by the KIM API. ...
type(kim_compute_argument_name_type), save, public, protected kim_compute_argument_name_number_of_particles