kim-api  2.1.2+v2.1.2.GNU
An Application Programming Interface (API) for the Knowledgebase of Interatomic Models (KIM).
kim_energy_unit_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_energy_unit_type, &
47 
48  ! Constants
56 
57  ! Routines
58  kim_known, &
59  operator (.eq.), &
60  operator (.ne.), &
61  kim_from_string, &
62  kim_to_string, &
65 
66 
72  type, bind(c) :: kim_energy_unit_type
78  integer(c_int) energy_unit_id
79  end type kim_energy_unit_type
80 
86  type(kim_energy_unit_type), protected, save, &
87  bind(c, name="KIM_ENERGY_UNIT_unused") &
89 
95  type(kim_energy_unit_type), protected, save, &
96  bind(c, name="KIM_ENERGY_UNIT_amu_A2_per_ps2") &
98 
104  type(kim_energy_unit_type), protected, save, &
105  bind(c, name="KIM_ENERGY_UNIT_erg") &
107 
113  type(kim_energy_unit_type), protected, save, &
114  bind(c, name="KIM_ENERGY_UNIT_eV") &
116 
122  type(kim_energy_unit_type), protected, save, &
123  bind(c, name="KIM_ENERGY_UNIT_Hartree") &
125 
131  type(kim_energy_unit_type), protected, save, &
132  bind(c, name="KIM_ENERGY_UNIT_J") &
134 
140  type(kim_energy_unit_type), protected, save, &
141  bind(c, name="KIM_ENERGY_UNIT_kcal_mol") &
143 
149  interface kim_known
150  module procedure kim_energy_unit_known
151  end interface kim_known
152 
158  interface operator (.eq.)
159  module procedure kim_energy_unit_equal
160  end interface operator (.eq.)
161 
167  interface operator (.ne.)
168  module procedure kim_energy_unit_not_equal
169  end interface operator (.ne.)
170 
177  interface kim_from_string
178  module procedure kim_energy_unit_from_string
179  end interface kim_from_string
180 
186  interface kim_to_string
187  module procedure kim_energy_unit_to_string
188  end interface kim_to_string
189 
190 contains
196  logical recursive function kim_energy_unit_known(energy_unit)
197  implicit none
198  interface
199  integer(c_int) recursive function known(energy_unit) &
200  bind(c, name="KIM_EnergyUnit_Known")
201  use, intrinsic :: iso_c_binding
202  import kim_energy_unit_type
203  implicit none
204  type(kim_energy_unit_type), intent(in), value :: energy_unit
205  end function known
206  end interface
207  type(kim_energy_unit_type), intent(in) :: energy_unit
208 
209  kim_energy_unit_known = (known(energy_unit) /= 0)
210  end function kim_energy_unit_known
211 
217  logical recursive function kim_energy_unit_equal(lhs, rhs)
218  implicit none
219  type(kim_energy_unit_type), intent(in) :: lhs
220  type(kim_energy_unit_type), intent(in) :: rhs
221 
222  kim_energy_unit_equal &
223  = (lhs%energy_unit_id .eq. rhs%energy_unit_id)
224  end function kim_energy_unit_equal
225 
231  logical recursive function kim_energy_unit_not_equal(lhs, rhs)
232  implicit none
233  type(kim_energy_unit_type), intent(in) :: lhs
234  type(kim_energy_unit_type), intent(in) :: rhs
235 
236  kim_energy_unit_not_equal = .not. (lhs .eq. rhs)
237  end function kim_energy_unit_not_equal
238 
245  recursive subroutine kim_energy_unit_from_string(string, energy_unit)
246  implicit none
247  interface
248  type(kim_energy_unit_type) recursive function from_string(string) &
249  bind(c, name="KIM_EnergyUnit_FromString")
250  use, intrinsic :: iso_c_binding
251  import kim_energy_unit_type
252  implicit none
253  character(c_char), intent(in) :: string(*)
254  end function from_string
255  end interface
256  character(len=*, kind=c_char), intent(in) :: string
257  type(kim_energy_unit_type), intent(out) :: energy_unit
258 
259  energy_unit = from_string(trim(string)//c_null_char)
260  end subroutine kim_energy_unit_from_string
261 
267  recursive subroutine kim_energy_unit_to_string(energy_unit, string)
268  use kim_convert_string_module, only : kim_convert_c_char_ptr_to_string
269  implicit none
270  interface
271  type(c_ptr) recursive function get_string(energy_unit) &
272  bind(c, name="KIM_EnergyUnit_ToString")
273  use, intrinsic :: iso_c_binding
274  import kim_energy_unit_type
275  implicit none
276  type(kim_energy_unit_type), intent(in), value :: energy_unit
277  end function get_string
278  end interface
279  type(kim_energy_unit_type), intent(in) :: energy_unit
280  character(len=*, kind=c_char), intent(out) :: string
281 
282  type(c_ptr) :: p
283 
284  p = get_string(energy_unit)
285  call kim_convert_c_char_ptr_to_string(p, string)
286  end subroutine kim_energy_unit_to_string
287 
294  recursive subroutine kim_get_number_of_energy_units(number_of_energy_units)
295  implicit none
296  interface
297  recursive subroutine get_number_of_energy_units(number_of_energy_units) &
298  bind(c, name="KIM_ENERGY_UNIT_GetNumberOfEnergyUnits")
299  use, intrinsic :: iso_c_binding
300  integer(c_int), intent(out) :: number_of_energy_units
301  end subroutine get_number_of_energy_units
302  end interface
303  integer(c_int), intent(out) :: number_of_energy_units
304 
305  call get_number_of_energy_units(number_of_energy_units)
306  end subroutine kim_get_number_of_energy_units
307 
313  recursive subroutine kim_get_energy_unit(index, energy_unit, ierr)
314  implicit none
315  interface
316  integer(c_int) recursive function get_energy_unit(index, energy_unit) &
317  bind(c, name="KIM_ENERGY_UNIT_GetEnergyUnit")
318  use, intrinsic :: iso_c_binding
319  import kim_energy_unit_type
320  implicit none
321  integer(c_int), intent(in), value :: index
322  type(kim_energy_unit_type), intent(out) :: energy_unit
323  end function get_energy_unit
324  end interface
325  integer(c_int), intent(in) :: index
326  type(kim_energy_unit_type), intent(out) :: energy_unit
327  integer(c_int), intent(out) :: ierr
328 
329  ierr = get_energy_unit(index-1, energy_unit)
330  end subroutine kim_get_energy_unit
331 end module kim_energy_unit_module
type(kim_energy_unit_type), save, public, protected kim_energy_unit_erg
recursive subroutine, public kim_get_energy_unit(index, energy_unit, ierr)
Get the identity of each defined standard EnergyUnit.
An Extensible Enumeration for the EnergyUnit's supported by the KIM API.
type(kim_energy_unit_type), save, public, protected kim_energy_unit_amu_a2_per_ps2
type(kim_energy_unit_type), save, public, protected kim_energy_unit_unused
type(kim_energy_unit_type), save, public, protected kim_energy_unit_kcal_mol
type(kim_energy_unit_type), save, public, protected kim_energy_unit_ev
type(kim_energy_unit_type), save, public, protected kim_energy_unit_hartree
recursive subroutine, public kim_get_number_of_energy_units(number_of_energy_units)
Get the number of standard EnergyUnit's defined by the KIM API.
type(kim_energy_unit_type), save, public, protected kim_energy_unit_j