kim-api  2.2.1+v2.2.1.GNU.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--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_energy_unit_type, &
46  ! Constants
54  ! Routines
55  kim_known, &
56  operator(.eq.), &
57  operator(.ne.), &
58  kim_from_string, &
59  kim_to_string, &
62 
68  type, bind(c) :: kim_energy_unit_type
74  integer(c_int) energy_unit_id
75  end type kim_energy_unit_type
76 
82  type(kim_energy_unit_type), protected, save, &
83  bind(c, name="KIM_ENERGY_UNIT_unused") &
85 
91  type(kim_energy_unit_type), protected, save, &
92  bind(c, name="KIM_ENERGY_UNIT_amu_A2_per_ps2") &
94 
100  type(kim_energy_unit_type), protected, save, &
101  bind(c, name="KIM_ENERGY_UNIT_erg") &
103 
109  type(kim_energy_unit_type), protected, save, &
110  bind(c, name="KIM_ENERGY_UNIT_eV") &
112 
118  type(kim_energy_unit_type), protected, save, &
119  bind(c, name="KIM_ENERGY_UNIT_Hartree") &
121 
127  type(kim_energy_unit_type), protected, save, &
128  bind(c, name="KIM_ENERGY_UNIT_J") &
130 
136  type(kim_energy_unit_type), protected, save, &
137  bind(c, name="KIM_ENERGY_UNIT_kcal_mol") &
139 
145  interface kim_known
146  module procedure kim_energy_unit_known
147  end interface kim_known
148 
154  interface operator(.eq.)
155  module procedure kim_energy_unit_equal
156  end interface operator(.eq.)
157 
163  interface operator(.ne.)
164  module procedure kim_energy_unit_not_equal
165  end interface operator(.ne.)
166 
173  interface kim_from_string
174  module procedure kim_energy_unit_from_string
175  end interface kim_from_string
176 
182  interface kim_to_string
183  module procedure kim_energy_unit_to_string
184  end interface kim_to_string
185 
186 contains
192  logical recursive function kim_energy_unit_known(energy_unit)
193  implicit none
194  interface
195  integer(c_int) recursive function known(energy_unit) &
196  bind(c, name="KIM_EnergyUnit_Known")
197  use, intrinsic :: iso_c_binding
198  import kim_energy_unit_type
199  implicit none
200  type(kim_energy_unit_type), intent(in), value :: energy_unit
201  end function known
202  end interface
203  type(kim_energy_unit_type), intent(in) :: energy_unit
204 
205  kim_energy_unit_known = (known(energy_unit) /= 0)
206  end function kim_energy_unit_known
207 
213  logical recursive function kim_energy_unit_equal(lhs, rhs)
214  implicit none
215  type(kim_energy_unit_type), intent(in) :: lhs
216  type(kim_energy_unit_type), intent(in) :: rhs
217 
218  kim_energy_unit_equal &
219  = (lhs%energy_unit_id == rhs%energy_unit_id)
220  end function kim_energy_unit_equal
221 
227  logical recursive function kim_energy_unit_not_equal(lhs, rhs)
228  implicit none
229  type(kim_energy_unit_type), intent(in) :: lhs
230  type(kim_energy_unit_type), intent(in) :: rhs
231 
232  kim_energy_unit_not_equal = .not. (lhs == rhs)
233  end function kim_energy_unit_not_equal
234 
241  recursive subroutine kim_energy_unit_from_string(string, energy_unit)
242  implicit none
243  interface
244  type(kim_energy_unit_type) recursive function from_string(string) &
245  bind(c, name="KIM_EnergyUnit_FromString")
246  use, intrinsic :: iso_c_binding
247  import kim_energy_unit_type
248  implicit none
249  character(c_char), intent(in) :: string(*)
250  end function from_string
251  end interface
252  character(len=*, kind=c_char), intent(in) :: string
253  type(kim_energy_unit_type), intent(out) :: energy_unit
254 
255  energy_unit = from_string(trim(string)//c_null_char)
256  end subroutine kim_energy_unit_from_string
257 
263  recursive subroutine kim_energy_unit_to_string(energy_unit, string)
264  use kim_convert_string_module, only: kim_convert_c_char_ptr_to_string
265  implicit none
266  interface
267  type(c_ptr) recursive function get_string(energy_unit) &
268  bind(c, name="KIM_EnergyUnit_ToString")
269  use, intrinsic :: iso_c_binding
270  import kim_energy_unit_type
271  implicit none
272  type(kim_energy_unit_type), intent(in), value :: energy_unit
273  end function get_string
274  end interface
275  type(kim_energy_unit_type), intent(in) :: energy_unit
276  character(len=*, kind=c_char), intent(out) :: string
277 
278  type(c_ptr) :: p
279 
280  p = get_string(energy_unit)
281  call kim_convert_c_char_ptr_to_string(p, string)
282  end subroutine kim_energy_unit_to_string
283 
290  recursive subroutine kim_get_number_of_energy_units(number_of_energy_units)
291  implicit none
292  interface
293  recursive subroutine get_number_of_energy_units(number_of_energy_units) &
294  bind(c, name="KIM_ENERGY_UNIT_GetNumberOfEnergyUnits")
295  use, intrinsic :: iso_c_binding
296  integer(c_int), intent(out) :: number_of_energy_units
297  end subroutine get_number_of_energy_units
298  end interface
299  integer(c_int), intent(out) :: number_of_energy_units
300 
301  call get_number_of_energy_units(number_of_energy_units)
302  end subroutine kim_get_number_of_energy_units
303 
309  recursive subroutine kim_get_energy_unit(index, energy_unit, ierr)
310  implicit none
311  interface
312  integer(c_int) recursive function get_energy_unit(index, energy_unit) &
313  bind(c, name="KIM_ENERGY_UNIT_GetEnergyUnit")
314  use, intrinsic :: iso_c_binding
315  import kim_energy_unit_type
316  implicit none
317  integer(c_int), intent(in), value :: index
318  type(kim_energy_unit_type), intent(out) :: energy_unit
319  end function get_energy_unit
320  end interface
321  integer(c_int), intent(in) :: index
322  type(kim_energy_unit_type), intent(out) :: energy_unit
323  integer(c_int), intent(out) :: ierr
324 
325  ierr = get_energy_unit(index - 1, energy_unit)
326  end subroutine kim_get_energy_unit
327 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