kim-api  2.1.2+v2.1.2.GNU
An Application Programming Interface (API) for the Knowledgebase of Interatomic Models (KIM).
kim_length_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  ! Derive types
46  kim_length_unit_type, &
47 
48  ! Constants
55 
56  ! Routines
57  kim_known, &
58  operator (.eq.), &
59  operator (.ne.), &
60  kim_from_string, &
61  kim_to_string, &
64 
65 
71  type, bind(c) :: kim_length_unit_type
77  integer(c_int) length_unit_id
78  end type kim_length_unit_type
79 
85  type(kim_length_unit_type), protected, save, &
86  bind(c, name="KIM_LENGTH_UNIT_unused") &
88 
94  type(kim_length_unit_type), protected, save, &
95  bind(c, name="KIM_LENGTH_UNIT_A") &
97 
103  type(kim_length_unit_type), protected, save, &
104  bind(c, name="KIM_LENGTH_UNIT_Bhor") &
106 
112  type(kim_length_unit_type), protected, save, &
113  bind(c, name="KIM_LENGTH_UNIT_cm") &
115 
121  type(kim_length_unit_type), protected, save, &
122  bind(c, name="KIM_LENGTH_UNIT_m") &
124 
130  type(kim_length_unit_type), protected, save, &
131  bind(c, name="KIM_LENGTH_UNIT_nm") &
133 
139  interface kim_known
140  module procedure kim_length_unit_known
141  end interface kim_known
142 
148  interface operator (.eq.)
149  module procedure kim_length_unit_equal
150  end interface operator (.eq.)
151 
157  interface operator (.ne.)
158  module procedure kim_length_unit_not_equal
159  end interface operator (.ne.)
160 
167  interface kim_from_string
168  module procedure kim_length_unit_from_string
169  end interface kim_from_string
170 
176  interface kim_to_string
177  module procedure kim_length_unit_to_string
178  end interface kim_to_string
179 
180 contains
186  logical recursive function kim_length_unit_known(length_unit)
187  implicit none
188  interface
189  integer(c_int) recursive function known(length_unit) &
190  bind(c, name="KIM_LengthUnit_Known")
191  use, intrinsic :: iso_c_binding
192  import kim_length_unit_type
193  implicit none
194  type(kim_length_unit_type), intent(in), value :: length_unit
195  end function known
196  end interface
197  type(kim_length_unit_type), intent(in) :: length_unit
198 
199  kim_length_unit_known = (known(length_unit) /= 0)
200  end function kim_length_unit_known
201 
207  logical recursive function kim_length_unit_equal(lhs, rhs)
208  implicit none
209  type(kim_length_unit_type), intent(in) :: lhs
210  type(kim_length_unit_type), intent(in) :: rhs
211 
212  kim_length_unit_equal &
213  = (lhs%length_unit_id .eq. rhs%length_unit_id)
214  end function kim_length_unit_equal
215 
221  logical recursive function kim_length_unit_not_equal(lhs, rhs)
222  implicit none
223  type(kim_length_unit_type), intent(in) :: lhs
224  type(kim_length_unit_type), intent(in) :: rhs
225 
226  kim_length_unit_not_equal = .not. (lhs .eq. rhs)
227  end function kim_length_unit_not_equal
228 
235  recursive subroutine kim_length_unit_from_string(string, length_unit)
236  implicit none
237  interface
238  type(kim_length_unit_type) recursive function from_string(string) &
239  bind(c, name="KIM_LengthUnit_FromString")
240  use, intrinsic :: iso_c_binding
241  import kim_length_unit_type
242  implicit none
243  character(c_char), intent(in) :: string(*)
244  end function from_string
245  end interface
246  character(len=*, kind=c_char), intent(in) :: string
247  type(kim_length_unit_type), intent(out) :: length_unit
248 
249  length_unit = from_string(trim(string)//c_null_char)
250  end subroutine kim_length_unit_from_string
251 
257  recursive subroutine kim_length_unit_to_string(length_unit, string)
258  use kim_convert_string_module, only : kim_convert_c_char_ptr_to_string
259  implicit none
260  interface
261  type(c_ptr) recursive function get_string(length_unit) &
262  bind(c, name="KIM_LengthUnit_ToString")
263  use, intrinsic :: iso_c_binding
264  import kim_length_unit_type
265  implicit none
266  type(kim_length_unit_type), intent(in), value :: length_unit
267  end function get_string
268  end interface
269  type(kim_length_unit_type), intent(in) :: length_unit
270  character(len=*, kind=c_char), intent(out) :: string
271 
272  type(c_ptr) :: p
273 
274  p = get_string(length_unit)
275  call kim_convert_c_char_ptr_to_string(p, string)
276  end subroutine kim_length_unit_to_string
277 
284  recursive subroutine kim_get_number_of_length_units(number_of_length_units)
285  implicit none
286  interface
287  recursive subroutine get_number_of_length_units(number_of_length_units) &
288  bind(c, name="KIM_LENGTH_UNIT_GetNumberOfLengthUnits")
289  use, intrinsic :: iso_c_binding
290  integer(c_int), intent(out) :: number_of_length_units
291  end subroutine get_number_of_length_units
292  end interface
293  integer(c_int), intent(out) :: number_of_length_units
294 
295  call get_number_of_length_units(number_of_length_units)
296  end subroutine kim_get_number_of_length_units
297 
303  recursive subroutine kim_get_length_unit(index, length_unit, ierr)
304  implicit none
305  interface
306  integer(c_int) recursive function get_length_unit(index, length_unit) &
307  bind(c, name="KIM_LENGTH_UNIT_GetLengthUnit")
308  use, intrinsic :: iso_c_binding
309  import kim_length_unit_type
310  implicit none
311  integer(c_int), intent(in), value :: index
312  type(kim_length_unit_type), intent(out) :: length_unit
313  end function get_length_unit
314  end interface
315  integer(c_int), intent(in) :: index
316  type(kim_length_unit_type), intent(out) :: length_unit
317  integer(c_int), intent(out) :: ierr
318 
319  ierr = get_length_unit(index-1, length_unit)
320  end subroutine kim_get_length_unit
321 end module kim_length_unit_module
type(kim_length_unit_type), save, public, protected kim_length_unit_a
type(kim_length_unit_type), save, public, protected kim_length_unit_bohr
type(kim_length_unit_type), save, public, protected kim_length_unit_m
recursive subroutine, public kim_get_number_of_length_units(number_of_length_units)
Get the number of standard LengthUnit's defined by the KIM API.
type(kim_length_unit_type), save, public, protected kim_length_unit_unused
An Extensible Enumeration for the LengthUnit's supported by the KIM API.
type(kim_length_unit_type), save, public, protected kim_length_unit_nm
recursive subroutine, public kim_get_length_unit(index, length_unit, ierr)
Get the identity of each defined standard LengthUnit.
type(kim_length_unit_type), save, public, protected kim_length_unit_cm