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
33!> \brief \copybrief KIM::Collections
34!!
35!! \sa KIM::Collections, KIM_Collections
36!!
37!! \since 2.1
38module kim_collections_module
39  use, intrinsic :: iso_c_binding
40  implicit none
41  private
42
43  public &
44    ! Derived types
45    kim_collections_handle_type, &
46    ! Constants
47    KIM_COLLECTIONS_NULL_HANDLE, &
48    ! Routines
49    operator(.eq.), &
50    operator(.ne.), &
51    kim_collections_create, &
52    kim_collections_destroy, &
53    kim_get_item_type, &
54    kim_get_item_library_file_name_and_collection, &
55    kim_cache_list_of_item_metadata_files, &
56    kim_get_item_metadata_file_length, &
57    kim_get_item_metadata_file_values, &
58    kim_cache_list_of_item_names_by_type, &
59    kim_get_item_name_by_type, &
60    kim_cache_list_of_item_names_by_collection_and_type, &
61    kim_get_item_name_by_collection_and_type, &
62    kim_get_item_library_file_name_by_collection_and_type, &
63    kim_cache_list_of_item_metadata_files_by_collection_and_type, &
64    kim_get_item_metadata_file_length_by_collection_and_type, &
65    kim_get_item_metadata_file_values_by_collection_and_type, &
66    kim_get_project_name_and_sem_ver, &
67    kim_get_environment_variable_name, &
68    kim_get_configuration_file_environment_variable, &
69    kim_get_configuration_file_name, &
70    kim_cache_list_of_directory_names, &
71    kim_get_directory_name, &
72    kim_set_log_id, &
73    kim_push_log_verbosity, &
74    kim_pop_log_verbosity
75
76  !> \brief \copybrief KIM::Collections
77  !!
78  !! \sa KIM::Collections, KIM_Collections
79  !!
80  !! \since 2.1
81  type, bind(c) :: kim_collections_handle_type
82    type(c_ptr) :: p = c_null_ptr
83  end type kim_collections_handle_type
84
85  !> \brief NULL handle for use in comparisons.
86  !!
87  !! \since 2.1
88  type(kim_collections_handle_type), protected, save &
89    :: KIM_COLLECTIONS_NULL_HANDLE
90
91  !> \brief Compares kim_collections_handle_type's for equality.
92  !!
93  !! \since 2.1
94  interface operator(.eq.)
95    module procedure kim_collections_handle_equal
96  end interface operator(.eq.)
97
98  !> \brief Compares kim_collections_handle_type's for inequality.
99  !!
100  !! \since 2.1
101  interface operator(.ne.)
102    module procedure kim_collections_handle_not_equal
103  end interface operator(.ne.)
104
105  !> \brief \copybrief KIM::Collections::GetItemType
106  !!
107  !! \sa KIM::Collections::GetItemType, KIM_Collections_GetItemType
108  !!
109  !! \since 2.1
110  interface kim_get_item_type
111    module procedure kim_collections_get_item_type
112  end interface kim_get_item_type
113
114  !> \brief \copybrief KIM::Collections::GetItemLibraryFileNameAndCollection
115  !!
116  !! \sa KIM::Collections::GetItemLibraryFileNameAndCollection,
117  !! KIM_Collections_GetItemLibraryFileNameAndCollection
118  !!
119  !! \since 2.1
120  interface kim_get_item_library_file_name_and_collection
121    module procedure kim_collections_get_item_library_file_name_and_collection
122  end interface kim_get_item_library_file_name_and_collection
123
124  !> \brief \copybrief KIM::Collections::CacheListOfItemMetadataFiles
125  !!
126  !! \sa KIM::Collections::CacheListOfItemMetadataFiles,
127  !! KIM_Collections_CacheListOfItemMetadataFiles
128  !!
129  !! \since 2.1
130  interface kim_cache_list_of_item_metadata_files
131    module procedure kim_collections_cache_list_of_item_metadata_files
132  end interface kim_cache_list_of_item_metadata_files
133
134  !> \brief Get item metadata file length and determine if the file is
135  !! available as a string.
136  !!
137  !! \sa KIM::Collections::GetItemMetadataFile,
138  !! KIM_Collections_GetItemMetadataFile
139  !!
140  !! \since 2.1
141  interface kim_get_item_metadata_file_length
142    module procedure kim_collections_get_item_metadata_file_length
143  end interface kim_get_item_metadata_file_length
144
145  !> \brief Get the item's metadata file values.
146  !!
147  !! \sa KIM::Collections::GetItemMetadataFile,
148  !! KIM_Collections_GetItemMetadataFile
149  !!
150  !! \since 2.1
151  interface kim_get_item_metadata_file_values
152    module procedure kim_collections_get_item_metadata_file_values
153  end interface kim_get_item_metadata_file_values
154
155  !> \brief \copybrief KIM::Collections::CacheListOfItemNamesByType
156  !!
157  !! \sa KIM::Collections::CacheListOfItemNamesByType,
158  !! KIM_Collections_CacheListOfItemNamesByType
159  !!
160  !! \since 2.1
161  interface kim_cache_list_of_item_names_by_type
162    module procedure kim_collections_cache_list_of_item_names_by_type
163  end interface kim_cache_list_of_item_names_by_type
164
165  !> \brief \copybrief KIM::Collections::GetItemNameByType
166  !!
167  !! \sa KIM::Collections::GetItemNameByType, KIM_Collections_GetItemNameByType
168  !!
169  !! \since 2.1
170  interface kim_get_item_name_by_type
171    module procedure kim_collections_get_item_name_by_type
172  end interface kim_get_item_name_by_type
173
174  !> \brief \copybrief KIM::Collections::CacheListOfItemNamesByCollectionAndType
175  !!
176  !! \sa KIM::Collections::CacheListOfItemNamesByCollectionAndType,
177  !! KIM_Collections_CacheListOfItemNamesByCollectionAndType
178  !!
179  !! \since 2.1
180  interface kim_cache_list_of_item_names_by_collection_and_type
181    module procedure &
182      kim_collections_cache_list_of_item_names_by_collection_and_type
183  end interface kim_cache_list_of_item_names_by_collection_and_type
184
185  !> \brief \copybrief KIM::Collections::GetItemNameByCollectionAndType
186  !!
187  !! \sa KIM::Collections::GetItemNameByCollectionAndType,
188  !! KIM_Collections_GetItemNameByCollectionAndType
189  !!
190  !! \since 2.1
191  interface kim_get_item_name_by_collection_and_type
192    module procedure kim_collections_get_item_name_by_collection_and_type
193  end interface kim_get_item_name_by_collection_and_type
194
195  !> \brief \copybrief <!--
196  !! -->KIM::Collections::GetItemLibraryFileNameByCollectionAndType
197  !!
198  !! \sa KIM::Collections::GetItemLibraryFileNameByCollectionAndType,
199  !! KIM_Collections_GetItemLibraryFileNameByCollectionAndType
200  !!
201  !! \since 2.1
202  interface kim_get_item_library_file_name_by_collection_and_type
203    module procedure &
204      kim_collections_get_item_library_file_name_by_coll_and_type
205  end interface kim_get_item_library_file_name_by_collection_and_type
206
207  !> \brief \copybrief <!--
208  !! -->KIM::Collections::CacheListOfItemMetadataFilesByCollectionAndType
209  !!
210  !! \sa KIM::Collections::CacheListOfItemMetadataFilesByCollectionAndType,
211  !! KIM_Collections_CacheListOfItemMetadataFilesByCollectionAndType
212  !!
213  !! \since 2.1
214  interface kim_cache_list_of_item_metadata_files_by_collection_and_type
215    module procedure &
216      kim_colls_cache_list_of_item_metadata_files_by_coll_and_type
217  end interface kim_cache_list_of_item_metadata_files_by_collection_and_type
218
219  !> \brief Get item metadata file length and determine if the file is
220  !! available as a string.
221  !!
222  !! \sa KIM::Collections::GetItemMetadataFileByCollectionAndType,
223  !! KIM_Collections_GetItemMetadataFileByCollectionAndType
224  !!
225  !! \since 2.1
226  interface kim_get_item_metadata_file_length_by_collection_and_type
227    module procedure &
228      kim_collections_get_item_metadata_file_length_by_coll_and_type
229  end interface kim_get_item_metadata_file_length_by_collection_and_type
230
231  !> \brief Get the item's metadata file values.
232  !!
233  !! \sa KIM::Collections::GetItemMetadataFileByCollectionAndType,
234  !! KIM_Collections_GetItemMetadataFileByCollectionAndType
235  !!
236  !! \since 2.1
237  interface kim_get_item_metadata_file_values_by_collection_and_type
238    module procedure &
239      kim_collections_get_item_metadata_file_values_by_coll_and_type
240  end interface kim_get_item_metadata_file_values_by_collection_and_type
241
242  !> \brief \copybrief KIM::Collections::GetProjectNameAndSemVer
243  !!
244  !! \sa KIM::Collections::GetProjectNameAndSemVer,
245  !! KIM_Collections_GetProjectNameAndSemVer
246  !!
247  !! \since 2.1
248  interface kim_get_project_name_and_sem_ver
249    module procedure kim_collections_get_project_name_and_sem_ver
250  end interface kim_get_project_name_and_sem_ver
251
252  !> \brief \copybrief KIM::Collections::GetEnvironmentVariableName
253  !!
254  !! \sa KIM::Collections::GetEnvironmentVariableName,
255  !! KIM_Collections_GetEnvironmentVariableName
256  !!
257  !! \since 2.1
258  interface kim_get_environment_variable_name
259    module procedure kim_collections_get_environment_variable_name
260  end interface kim_get_environment_variable_name
261
262  !> \brief \copybrief KIM::Collections::GetConfigurationFileEnvironmentVariable
263  !!
264  !! \sa KIM::Collections::GetConfigurationFileEnvironmentVariable,
265  !! KIM_Collections_GetConfigurationFileEnvironmentVariable
266  !!
267  !! \since 2.1
268  interface kim_get_configuration_file_environment_variable
269    module procedure kim_collections_get_configuration_file_environment_variable
270  end interface kim_get_configuration_file_environment_variable
271
272  !> \brief \copybrief KIM::Collections::GetConfigurationFileName
273  !!
274  !! \sa KIM::Collections::GetConfigurationFileName,
275  !! KIM_Collections_GetConfigurationFileName
276  !!
277  !! \since 2.1
278  interface kim_get_configuration_file_name
279    module procedure kim_collections_get_configuration_file_name
280  end interface kim_get_configuration_file_name
281
282  !> \brief \copybrief KIM::Collections::CacheListOfDirectoryNames
283  !!
284  !! \sa KIM::Collections::CacheListOfDirectoryNames,
285  !! KIM_Collections_CacheListOfDirectoryNames
286  !!
287  !! \since 2.1
288  interface kim_cache_list_of_directory_names
289    module procedure kim_collections_cache_list_of_directory_names
290  end interface kim_cache_list_of_directory_names
291
292  !> \brief \copybrief KIM::Collections::GetDirectoryName
293  !!
294  !! \sa KIM::Collections::GetDirectoryName, KIM_Collections_GetDirectoryName
295  !!
296  !! \since 2.1
297  interface kim_get_directory_name
298    module procedure kim_collections_get_directory_name
299  end interface kim_get_directory_name
300
301  !> \brief \copybrief KIM::Collections::SetLogID
302  !!
303  !! \sa KIM::Collections::SetLogID, KIM_Collections_SetLogID
304  !!
305  !! \since 2.1
306  interface kim_set_log_id
307    module procedure kim_collections_set_log_id
308  end interface kim_set_log_id
309
310  !> \brief \copybrief KIM::Collections::PushLogVerbosity
311  !!
312  !! \sa KIM::Collections::PushLogVerbosity, KIM_Collections_PushLogVerbosity
313  !!
314  !! \since 2.1
315  interface kim_push_log_verbosity
316    module procedure kim_collections_push_log_verbosity
317  end interface kim_push_log_verbosity
318
319  !> \brief \copybrief KIM::Collections::PopLogVerbosity
320  !!
321  !! \sa KIM::Collections::, KIM_Collections_PopLogVerbosity
322  !!
323  !! \since 2.1
324  interface kim_pop_log_verbosity
325    module procedure kim_collections_pop_log_verbosity
326  end interface kim_pop_log_verbosity
327
328contains
329  !> \brief Compares kim_collections_handle_type's for equality.
330  !!
331  !! \since 2.1
332  logical recursive function kim_collections_handle_equal(lhs, rhs)
333    implicit none
334    type(kim_collections_handle_type), intent(in) :: lhs
335    type(kim_collections_handle_type), intent(in) :: rhs
336
337    if ((.not. c_associated(lhs%p)) .and. (.not. c_associated(rhs%p))) then
338      kim_collections_handle_equal = .true.
339    else
340      kim_collections_handle_equal = c_associated(lhs%p, rhs%p)
341    end if
342  end function kim_collections_handle_equal
343
344  !> \brief Compares kim_collections_handle_type's for inequality.
345  !!
346  !! \since 2.1
347  logical recursive function kim_collections_handle_not_equal(lhs, rhs)
348    implicit none
349    type(kim_collections_handle_type), intent(in) :: lhs
350    type(kim_collections_handle_type), intent(in) :: rhs
351
352    kim_collections_handle_not_equal = .not. (lhs == rhs)
353  end function kim_collections_handle_not_equal
354
355  !> \brief \copybrief KIM::Collections::Create
356  !!
357  !! \sa KIM::Collections::Create, KIM_Collections_Create
358  !!
359  !! \since 2.1
360  recursive subroutine kim_collections_create(collections_handle, ierr)
361    implicit none
362    interface
363      integer(c_int) recursive function create(collections) &
364        bind(c, name="KIM_Collections_Create")
365        use, intrinsic :: iso_c_binding
366        implicit none
367        type(c_ptr), intent(out) :: collections
368      end function create
369    end interface
370    type(kim_collections_handle_type), intent(out) :: collections_handle
371    integer(c_int), intent(out) :: ierr
372
373    type(c_ptr) :: pcollections
374
375    ierr = create(pcollections)
376    collections_handle%p = pcollections
377  end subroutine kim_collections_create
378
379  !> \brief \copybrief KIM::Collections::Destroy
380  !!
381  !! \sa KIM::Collections::Destroy, KIM_Collections_Destroy
382  !!
383  !! \since 2.1
384  recursive subroutine kim_collections_destroy(collections_handle)
385    implicit none
386    interface
387      recursive subroutine destroy(collections) &
388        bind(c, name="KIM_Collections_Destroy")
389        use, intrinsic :: iso_c_binding
390        implicit none
391        type(c_ptr), intent(inout) :: collections
392      end subroutine destroy
393    end interface
394    type(kim_collections_handle_type), intent(inout) :: collections_handle
395
396    type(c_ptr) :: pcollections
397    pcollections = collections_handle%p
398    call destroy(pcollections)
399    collections_handle%p = c_null_ptr
400  end subroutine kim_collections_destroy
401
402  !> \brief \copybrief KIM::Collections::GetItemType
403  !!
404  !! \sa KIM::Collections::GetItemType, KIM_Collections_GetItemType
405  !!
406  !! \since 2.1
407  recursive subroutine kim_collections_get_item_type(collections_handle, &
408                                                     item_name, item_type, ierr)
409    use kim_interoperable_types_module, only: kim_collections_type
410    use kim_collection_item_type_module, only: kim_collection_item_type_type
411    implicit none
412    interface
413      integer(c_int) recursive function get_item_type( &
414        collections, item_name, item_type) &
415        bind(c, name="KIM_Collections_GetItemType")
416        use, intrinsic :: iso_c_binding
417        use kim_interoperable_types_module, only: kim_collections_type
418        use kim_collection_item_type_module, only: &
419          kim_collection_item_type_type
420        implicit none
421        type(kim_collections_type), intent(in) :: collections
422        character(c_char), intent(in) :: item_name(*)
423        type(kim_collection_item_type_type), intent(out) :: item_type
424      end function get_item_type
425    end interface
426    type(kim_collections_handle_type), intent(in) :: collections_handle
427    character(len=*, kind=c_char), intent(in) :: item_name
428    type(kim_collection_item_type_type), intent(out) :: item_type
429    integer(c_int), intent(out) :: ierr
430    type(kim_collections_type), pointer :: collections
431
432    call c_f_pointer(collections_handle%p, collections)
433    ierr = get_item_type(collections, trim(item_name)//c_null_char, item_type)
434  end subroutine kim_collections_get_item_type
435
436  !> \brief \copybrief KIM::Collections::GetItemLibraryFileNameAndCollection
437  !!
438  !! \sa KIM::Collections::GetItemLibraryFileNameAndCollection,
439  !! KIM_Collections_GetItemLibraryFileNameAndCollection
440  !!
441  !! \since 2.1
442  recursive subroutine &
443    kim_collections_get_item_library_file_name_and_collection( &
444    collections_handle, item_type, item_name, file_name, collection, ierr)
445    use kim_interoperable_types_module, only: kim_collections_type
446    use kim_convert_string_module, only: kim_convert_c_char_ptr_to_string
447    use kim_collection_module, only: kim_collection_type
448    use kim_collection_item_type_module, only: kim_collection_item_type_type
449    implicit none
450    interface
451      integer(c_int) recursive function &
452        get_item_library_file_name_and_collection( &
453        collections, item_type, item_name, file_name, collection) &
454        bind(c, name="KIM_Collections_GetItemLibraryFileNameAndCollection")
455        use, intrinsic :: iso_c_binding
456        use kim_interoperable_types_module, only: kim_collections_type
457        use kim_collection_module, only: kim_collection_type
458        use kim_collection_item_type_module, only: &
459          kim_collection_item_type_type
460        implicit none
461        type(kim_collections_type), intent(in) :: collections
462        type(kim_collection_item_type_type), intent(in), value :: item_type
463        character(c_char), intent(in) :: item_name(*)
464        type(c_ptr), intent(out) :: file_name
465        type(kim_collection_type), intent(out) :: collection
466      end function get_item_library_file_name_and_collection
467    end interface
468    type(kim_collections_handle_type), intent(in) :: collections_handle
469    type(kim_collection_item_type_type), intent(in) :: item_type
470    character(len=*, kind=c_char), intent(in) :: item_name
471    character(len=*, kind=c_char), intent(out) :: file_name
472    type(kim_collection_type), intent(out) :: collection
473    integer(c_int), intent(out) :: ierr
474    type(kim_collections_type), pointer :: collections
475
476    type(c_ptr) :: pfile_name
477
478    call c_f_pointer(collections_handle%p, collections)
479    ierr = get_item_library_file_name_and_collection( &
480           collections, &
481           item_type, &
482           trim(item_name)//c_null_char, &
483           pfile_name, &
484           collection)
485    call kim_convert_c_char_ptr_to_string(pfile_name, file_name)
486  end subroutine kim_collections_get_item_library_file_name_and_collection
487
488  !> \brief \copybrief KIM::Collections::CacheListOfItemMetadataFiles
489  !!
490  !! \sa KIM::Collections::CacheListOfItemMetadataFiles,
491  !! KIM_Collections_CacheListOfItemMetadataFiles
492  !!
493  !! \since 2.1
494  recursive subroutine kim_collections_cache_list_of_item_metadata_files( &
495    collections_handle, item_type, item_name, extent, ierr)
496    use kim_interoperable_types_module, only: kim_collections_type
497    use kim_collection_item_type_module, only: kim_collection_item_type_type
498    implicit none
499    interface
500      integer(c_int) recursive function cache_list_of_item_metadata_files( &
501        collections, item_type, item_name, extent) &
502        bind(c, name="KIM_Collections_CacheListOfItemMetadataFiles")
503        use, intrinsic :: iso_c_binding
504        use kim_interoperable_types_module, only: kim_collections_type
505        use kim_collection_item_type_module, only: &
506          kim_collection_item_type_type
507        implicit none
508        type(kim_collections_type), intent(in) :: collections
509        type(kim_collection_item_type_type), intent(in), value :: item_type
510        character(c_char), intent(in) :: item_name(*)
511        integer(c_int), intent(out) :: extent
512      end function cache_list_of_item_metadata_files
513    end interface
514    type(kim_collections_handle_type), intent(in) :: collections_handle
515    type(kim_collection_item_type_type), intent(in) :: item_type
516    character(len=*, kind=c_char), intent(in) :: item_name
517    integer(c_int), intent(out) :: extent
518    integer(c_int), intent(out) :: ierr
519    type(kim_collections_type), pointer :: collections
520
521    call c_f_pointer(collections_handle%p, collections)
522    ierr = cache_list_of_item_metadata_files(collections, item_type, &
523                                             trim(item_name)//c_null_char, &
524                                             extent)
525  end subroutine kim_collections_cache_list_of_item_metadata_files
526
527  !> \brief Get item metadata file length and determine if the file is
528  !! available as a string.
529  !!
530  !! \sa KIM::Collections::GetItemMetadataFile,
531  !! KIM_Collections_GetItemMetadataFile
532  !!
533  !! \since 2.1
534  recursive subroutine kim_collections_get_item_metadata_file_length( &
535    collections_handle, index, file_length, available_as_string, ierr)
536    use kim_interoperable_types_module, only: kim_collections_type
537    implicit none
538    interface
539      integer(c_int) recursive function get_item_metadata_file( &
540        collections, index, file_name, file_length, file_raw_data, &
541        available_as_string, file_string) &
542        bind(c, name="KIM_Collections_GetItemMetadataFile_fortran")
543        use, intrinsic :: iso_c_binding
544        use kim_interoperable_types_module, only: kim_collections_type
545        implicit none
546        type(kim_collections_type), intent(in) :: collections
547        integer(c_int), intent(in), value :: index
548        type(c_ptr), intent(out) :: file_name
549        integer(c_long), intent(out) :: file_length
550        type(c_ptr), intent(out) :: file_raw_data
551        integer(c_int), intent(out) :: available_as_string
552        type(c_ptr), intent(out) :: file_string
553      end function get_item_metadata_file
554    end interface
555    type(kim_collections_handle_type), intent(in) :: collections_handle
556    integer(c_int), intent(in) :: index
557    integer(c_long), intent(out) :: file_length
558    integer(c_int), intent(out) :: available_as_string
559    integer(c_int), intent(out) :: ierr
560    type(kim_collections_type), pointer :: collections
561
562    type(c_ptr) pfile_name, pfile_raw_data, pfile_string
563
564    call c_f_pointer(collections_handle%p, collections)
565    ierr = get_item_metadata_file(collections, &
566                                  index - 1, &
567                                  pfile_name, &
568                                  file_length, &
569                                  pfile_raw_data, &
570                                  available_as_string, &
571                                  pfile_string)
572  end subroutine kim_collections_get_item_metadata_file_length
573
574  !> \brief Get the item's metadata file values.
575  !!
576  !! \sa KIM::Collections::GetItemMetadataFile,
577  !! KIM_Collections_GetItemMetadataFile
578  !!
579  !! \since 2.1
580  recursive subroutine kim_collections_get_item_metadata_file_values( &
581    collections_handle, index, file_name, file_raw_data, file_string, ierr)
582    use kim_interoperable_types_module, only: kim_collections_type
583    use kim_convert_string_module, only: kim_convert_c_char_ptr_to_string
584    implicit none
585    interface
586      integer(c_int) recursive function get_item_metadata_file( &
587        collections, index, file_name, file_length, file_raw_data, &
588        available_as_string, file_string) &
589        bind(c, name="KIM_Collections_GetItemMetadataFile_fortran")
590        use, intrinsic :: iso_c_binding
591        use kim_interoperable_types_module, only: kim_collections_type
592        implicit none
593        type(kim_collections_type), intent(in) :: collections
594        integer(c_int), intent(in), value :: index
595        type(c_ptr), intent(out) :: file_name
596        integer(c_long), intent(out) :: file_length
597        type(c_ptr), intent(out) :: file_raw_data
598        integer(c_int), intent(out) :: available_as_string
599        type(c_ptr), intent(out) :: file_string
600      end function get_item_metadata_file
601    end interface
602    type(kim_collections_handle_type), intent(in) :: collections_handle
603    integer(c_int), intent(in) :: index
604    character(len=*, kind=c_char), intent(out) :: file_name
605    integer(c_signed_char), intent(out) :: file_raw_data(:)
606    character(len=*, kind=c_char), intent(out) :: file_string
607    integer(c_int), intent(out) :: ierr
608    type(kim_collections_type), pointer :: collections
609
610    integer(c_long) file_length
611    integer(c_int) available_as_string
612    type(c_ptr) pfile_name, pfile_raw_data, pfile_string
613    integer(c_signed_char), pointer :: file_raw_data_fpointer(:)
614
615    call c_f_pointer(collections_handle%p, collections)
616    ierr = get_item_metadata_file(collections, &
617                                  index - 1, &
618                                  pfile_name, &
619                                  file_length, &
620                                  pfile_raw_data, &
621                                  available_as_string, &
622                                  pfile_string)
623    if (ierr == 0) then
624      if (size(file_raw_data) < file_length) then
625        ierr = 1
626        return
627      end if
628      if (available_as_string == 1) then
629        if (len(file_string) < file_length) then
630          ierr = 1
631          return
632        end if
633      end if
634
635      call kim_convert_c_char_ptr_to_string(pfile_name, file_name)
636      if (c_associated(pfile_raw_data)) then
637        call c_f_pointer(pfile_raw_data, file_raw_data_fpointer, [file_length])
638      else
639        nullify (file_raw_data_fpointer)
640      end if
641      file_raw_data = file_raw_data_fpointer(1:file_length)
642
643      if (available_as_string == 1) then
644        call kim_convert_c_char_ptr_to_string(pfile_string, file_string)
645      end if
646    end if
647  end subroutine kim_collections_get_item_metadata_file_values
648
649  !> \brief \copybrief KIM::Collections::CacheListOfItemNamesByType
650  !!
651  !! \sa KIM::Collections::CacheListOfItemNamesByType,
652  !! KIM_Collections_CacheListOfItemNamesByType
653  !!
654  !! \since 2.1
655  recursive subroutine kim_collections_cache_list_of_item_names_by_type( &
656    collections_handle, item_type, extent, ierr)
657    use kim_interoperable_types_module, only: kim_collections_type
658    use kim_collection_item_type_module, only: kim_collection_item_type_type
659    implicit none
660    interface
661      integer(c_int) recursive function cache_list_of_item_names_by_type( &
662        collections, item_type, extent) &
663        bind(c, name="KIM_Collections_CacheListOfItemNamesByType")
664        use, intrinsic :: iso_c_binding
665        use kim_interoperable_types_module, only: kim_collections_type
666        use kim_collection_item_type_module, only: &
667          kim_collection_item_type_type
668        implicit none
669        type(kim_collections_type), intent(in) :: collections
670        type(kim_collection_item_type_type), intent(in), value :: item_type
671        integer(c_int), intent(out) :: extent
672      end function cache_list_of_item_names_by_type
673    end interface
674    type(kim_collections_handle_type), intent(in) :: collections_handle
675    type(kim_collection_item_type_type), intent(in) :: item_type
676    integer(c_int), intent(out) :: extent
677    integer(c_int), intent(out) :: ierr
678    type(kim_collections_type), pointer :: collections
679
680    call c_f_pointer(collections_handle%p, collections)
681    ierr = cache_list_of_item_names_by_type(collections, item_type, extent)
682  end subroutine kim_collections_cache_list_of_item_names_by_type
683
684  !> \brief \copybrief KIM::Collections::GetItemNameByType
685  !!
686  !! \sa KIM::Collections::GetItemNameByType, KIM_Collections_GetItemNameByType
687  !!
688  !! \since 2.1
689  recursive subroutine kim_collections_get_item_name_by_type( &
690    collections_handle, index, item_name, ierr)
691    use kim_interoperable_types_module, only: kim_collections_type
692    use kim_convert_string_module, only: kim_convert_c_char_ptr_to_string
693    implicit none
694    interface
695      integer(c_int) recursive function get_item_name_by_type( &
696        collections, index, item_name) &
697        bind(c, name="KIM_Collections_GetItemNameByType")
698        use, intrinsic :: iso_c_binding
699        use kim_interoperable_types_module, only: kim_collections_type
700        implicit none
701        type(kim_collections_type), intent(in) :: collections
702        integer(c_int), intent(in), value :: index
703        type(c_ptr), intent(out) :: item_name
704      end function get_item_name_by_type
705    end interface
706    type(kim_collections_handle_type), intent(in) :: collections_handle
707    integer(c_int), intent(in) :: index
708    character(len=*, kind=c_char), intent(out) :: item_name
709    integer(c_int), intent(out) :: ierr
710    type(kim_collections_type), pointer :: collections
711
712    type(c_ptr) pitem_name
713
714    call c_f_pointer(collections_handle%p, collections)
715    ierr = get_item_name_by_type(collections, index - 1, pitem_name)
716    call kim_convert_c_char_ptr_to_string(pitem_name, item_name)
717  end subroutine kim_collections_get_item_name_by_type
718
719  !> \brief \copybrief KIM::Collections::CacheListOfItemNamesByCollectionAndType
720  !!
721  !! \sa KIM::Collections::CacheListOfItemNamesByCollectionAndType,
722  !! KIM_Collections_CacheListOfItemNamesByCollectionAndType
723  !!
724  !! \since 2.1
725  recursive subroutine &
726    kim_collections_cache_list_of_item_names_by_collection_and_type( &
727    collections_handle, collection, item_type, extent, ierr)
728    use kim_interoperable_types_module, only: kim_collections_type
729    use kim_collection_module, only: kim_collection_type
730    use kim_collection_item_type_module, only: kim_collection_item_type_type
731    implicit none
732    interface
733      integer(c_int) recursive function &
734        cache_list_of_item_names_by_collection_and_type( &
735        collections, collection, item_type, extent) &
736        bind(c, name="KIM_Collections_CacheListOfItemNamesByCollectionAndType")
737        use, intrinsic :: iso_c_binding
738        use kim_interoperable_types_module, only: kim_collections_type
739        use kim_collection_module, only: kim_collection_type
740        use kim_collection_item_type_module, only: &
741          kim_collection_item_type_type
742        implicit none
743        type(kim_collections_type), intent(in) :: collections
744        type(kim_collection_type), intent(in), value :: collection
745        type(kim_collection_item_type_type), intent(in), value :: item_type
746        integer(c_int), intent(out) :: extent
747      end function cache_list_of_item_names_by_collection_and_type
748    end interface
749    type(kim_collections_handle_type), intent(in) :: collections_handle
750    type(kim_collection_type), intent(in) :: collection
751    type(kim_collection_item_type_type), intent(in) :: item_type
752    integer(c_int), intent(out) :: extent
753    integer(c_int), intent(out) :: ierr
754    type(kim_collections_type), pointer :: collections
755
756    call c_f_pointer(collections_handle%p, collections)
757    ierr = cache_list_of_item_names_by_collection_and_type(collections, &
758                                                           collection, &
759                                                           item_type, &
760                                                           extent)
761  end subroutine kim_collections_cache_list_of_item_names_by_collection_and_type
762
763  !> \brief \copybrief KIM::Collections::GetItemNameByCollectionAndType
764  !!
765  !! \sa KIM::Collections::GetItemNameByCollectionAndType,
766  !! KIM_Collections_GetItemNameByCollectionAndType
767  !!
768  !! \since 2.1
769  recursive subroutine kim_collections_get_item_name_by_collection_and_type( &
770    collections_handle, index, item_name, ierr)
771    use kim_interoperable_types_module, only: kim_collections_type
772    use kim_convert_string_module, only: kim_convert_c_char_ptr_to_string
773    implicit none
774    interface
775      integer(c_int) recursive function get_item_name_by_collection_and_type( &
776        collections, index, item_name) &
777        bind(c, name="KIM_Collections_GetItemNameByCollectionAndType")
778        use, intrinsic :: iso_c_binding
779        use kim_interoperable_types_module, only: kim_collections_type
780        implicit none
781        type(kim_collections_type), intent(in) :: collections
782        integer(c_int), intent(in), value :: index
783        type(c_ptr), intent(out) :: item_name
784      end function get_item_name_by_collection_and_type
785    end interface
786    type(kim_collections_handle_type), intent(in) :: collections_handle
787    integer(c_int), intent(in) :: index
788    character(len=*, kind=c_char), intent(out) :: item_name
789    integer(c_int), intent(out) :: ierr
790    type(kim_collections_type), pointer :: collections
791
792    type(c_ptr) pitem_name
793
794    call c_f_pointer(collections_handle%p, collections)
795    ierr = get_item_name_by_collection_and_type(collections, index - 1, &
796                                                pitem_name)
797    call kim_convert_c_char_ptr_to_string(pitem_name, item_name)
798  end subroutine kim_collections_get_item_name_by_collection_and_type
799
800  !> \brief \copybrief <!--
801  !! -->KIM::Collections::GetItemLibraryFileNameByCollectionAndType
802  !!
803  !! \sa KIM::Collections::GetItemLibraryFileNameByCollectionAndType,
804  !! KIM_Collections_GetItemLibraryFileNameByCollectionAndType
805  !!
806  !! \since 2.1
807  recursive subroutine &
808    kim_collections_get_item_library_file_name_by_coll_and_type( &
809    collections_handle, collection, item_type, item_name, file_name, ierr)
810    use kim_interoperable_types_module, only: kim_collections_type
811    use kim_convert_string_module, only: kim_convert_c_char_ptr_to_string
812    use kim_collection_module, only: kim_collection_type
813    use kim_collection_item_type_module, only: kim_collection_item_type_type
814    implicit none
815    interface
816      integer(c_int) recursive function &
817        get_item_library_file_name_by_coll_and_type( &
818        collections, collection, item_type, item_name, file_name) &
819        bind(c, &
820             name="KIM_Collections_GetItemLibraryFileNameByCollectionAndType")
821        use, intrinsic :: iso_c_binding
822        use kim_interoperable_types_module, only: kim_collections_type
823        use kim_collection_module, only: kim_collection_type
824        use kim_collection_item_type_module, only: &
825          kim_collection_item_type_type
826        implicit none
827        type(kim_collections_type), intent(in) :: collections
828        type(kim_collection_type), intent(in), value :: collection
829        type(kim_collection_item_type_type), intent(in), value :: item_type
830        character(c_char), intent(in) :: item_name(*)
831        type(c_ptr), intent(out) :: file_name
832      end function get_item_library_file_name_by_coll_and_type
833    end interface
834    type(kim_collections_handle_type), intent(in) :: collections_handle
835    type(kim_collection_type), intent(in) :: collection
836    type(kim_collection_item_type_type), intent(in) :: item_type
837    character(len=*, kind=c_char), intent(in) :: item_name
838    character(len=*, kind=c_char), intent(out) :: file_name
839    integer(c_int), intent(out) :: ierr
840    type(kim_collections_type), pointer :: collections
841
842    type(c_ptr) pfile_name
843
844    call c_f_pointer(collections_handle%p, collections)
845    ierr = get_item_library_file_name_by_coll_and_type( &
846           collections, &
847           collection, &
848           item_type, &
849           trim(item_name)//c_null_char, &
850           pfile_name)
851    call kim_convert_c_char_ptr_to_string(pfile_name, file_name)
852  end subroutine kim_collections_get_item_library_file_name_by_coll_and_type
853
854  !> \brief \copybrief <!--
855  !! -->KIM::Collections::CacheListOfItemMetadataFilesByCollectionAndType
856  !!
857  !! \sa KIM::Collections::CacheListOfItemMetadataFilesByCollectionAndType,
858  !! KIM_Collections_CacheListOfItemMetadataFilesByCollectionAndType
859  !!
860  !! \since 2.1
861  recursive subroutine &
862    kim_colls_cache_list_of_item_metadata_files_by_coll_and_type( &
863    collections_handle, collection, item_type, item_name, extent, ierr)
864    use kim_interoperable_types_module, only: kim_collections_type
865    use kim_collection_module, only: kim_collection_type
866    use kim_collection_item_type_module, only: kim_collection_item_type_type
867    implicit none
868    interface
869      integer(c_int) recursive function &
870        cache_list_of_item_metadata_files_by_coll_and_type( &
871        collections, collection, item_type, item_name, extent) &
872        bind(c, &
873             name= &
874             "KIM_Collections_CacheListOfItemMetadataFilesByCollectionAndType")
875        use, intrinsic :: iso_c_binding
876        use kim_interoperable_types_module, only: kim_collections_type
877        use kim_collection_module, only: kim_collection_type
878        use kim_collection_item_type_module, only: &
879          kim_collection_item_type_type
880        implicit none
881        type(kim_collections_type), intent(in) :: collections
882        type(kim_collection_type), intent(in), value :: collection
883        type(kim_collection_item_type_type), intent(in), value :: item_type
884        character(c_char), intent(in) :: item_name(*)
885        integer(c_int), intent(out) :: extent
886      end function cache_list_of_item_metadata_files_by_coll_and_type
887    end interface
888    type(kim_collections_handle_type), intent(in) :: collections_handle
889    type(kim_collection_type), intent(in) :: collection
890    type(kim_collection_item_type_type), intent(in) :: item_type
891    character(len=*, kind=c_char), intent(in) :: item_name
892    integer(c_int), intent(out) :: extent
893    integer(c_int), intent(out) :: ierr
894    type(kim_collections_type), pointer :: collections
895
896    call c_f_pointer(collections_handle%p, collections)
897    ierr = cache_list_of_item_metadata_files_by_coll_and_type( &
898           collections, &
899           collection, &
900           item_type, &
901           trim(item_name)//c_null_char, &
902           extent)
903  end subroutine kim_colls_cache_list_of_item_metadata_files_by_coll_and_type
904
905  !> \brief \copybrief KIM::Collections::GetItemMetadataFileByCollectionAndType
906  !!
907  !! \sa KIM::Collections::GetItemMetadataFileByCollectionAndType,
908  !! KIM_Collections_GetItemMetadataFileByCollectionAndType
909  !!
910  !! \since 2.1
911  recursive subroutine &
912    kim_collections_get_item_metadata_file_length_by_coll_and_type( &
913    collections_handle, index, file_length, available_as_string, ierr)
914    use kim_interoperable_types_module, only: kim_collections_type
915    implicit none
916    interface
917      integer(c_int) recursive function &
918        get_item_metadata_file_by_coll_and_type( &
919        collections, index, &
920        file_name, &
921        file_length, &
922        file_raw_data, &
923        available_as_string, &
924        file_string) &
925        bind(c, &
926             name= &
927             "KIM_Collections_GetItemMetadataFileByCollectionAndType_fortran")
928        use, intrinsic :: iso_c_binding
929        use kim_interoperable_types_module, only: kim_collections_type
930        implicit none
931        type(kim_collections_type), intent(in) :: collections
932        integer(c_int), intent(in), value :: index
933        type(c_ptr), intent(out) :: file_name
934        integer(c_long), intent(out) :: file_length
935        type(c_ptr), intent(out) :: file_raw_data
936        integer(c_int), intent(out) :: available_as_string
937        type(c_ptr), intent(out) :: file_string
938      end function get_item_metadata_file_by_coll_and_type
939    end interface
940    type(kim_collections_handle_type), intent(in) :: collections_handle
941    integer(c_int), intent(in), value :: index
942    integer(c_long), intent(out) :: file_length
943    integer(c_int), intent(out) :: available_as_string
944    integer(c_int), intent(out) :: ierr
945    type(kim_collections_type), pointer :: collections
946
947    type(c_ptr) pfile_name, pfile_raw_data, pfile_string
948
949    call c_f_pointer(collections_handle%p, collections)
950    ierr = get_item_metadata_file_by_coll_and_type(collections, &
951                                                   index - 1, &
952                                                   pfile_name, &
953                                                   file_length, &
954                                                   pfile_raw_data, &
955                                                   available_as_string, &
956                                                   pfile_string)
957  end subroutine kim_collections_get_item_metadata_file_length_by_coll_and_type
958
959  !> \brief Get the item's metadata file values.
960  !!
961  !! \sa KIM::Collections::GetItemMetadataFileByCollectionAndType,
962  !! KIM_Collections_GetItemMetadataFileByCollectionAndType
963  !!
964  !! \since 2.1
965  recursive subroutine &
966    kim_collections_get_item_metadata_file_values_by_coll_and_type( &
967    collections_handle, index, file_name, file_raw_data, file_string, ierr)
968    use kim_interoperable_types_module, only: kim_collections_type
969    use kim_convert_string_module, only: kim_convert_c_char_ptr_to_string
970    implicit none
971    interface
972      integer(c_int) recursive function &
973        get_item_metadata_file_by_coll_and_type(collections, &
974                                                index, &
975                                                file_name, &
976                                                file_length, &
977                                                file_raw_data, &
978                                                available_as_string, &
979                                                file_string) &
980        bind(c, &
981             name= &
982             "KIM_Collections_GetItemMetadataFileByCollectionAndType_fortran")
983        use, intrinsic :: iso_c_binding
984        use kim_interoperable_types_module, only: kim_collections_type
985        implicit none
986        type(kim_collections_type), intent(in) :: collections
987        integer(c_int), intent(in), value :: index
988        type(c_ptr), intent(out) :: file_name
989        integer(c_long), intent(out) :: file_length
990        type(c_ptr), intent(out) :: file_raw_data
991        integer(c_int), intent(out) :: available_as_string
992        type(c_ptr), intent(out) :: file_string
993      end function get_item_metadata_file_by_coll_and_type
994    end interface
995    type(kim_collections_handle_type), intent(in) :: collections_handle
996    integer(c_int), intent(in) :: index
997    character(len=*, kind=c_char), intent(out) :: file_name
998    integer(c_signed_char), intent(out) :: file_raw_data(:)
999    character(len=*, kind=c_char), intent(out) :: file_string
1000    integer(c_int), intent(out) :: ierr
1001    type(kim_collections_type), pointer :: collections
1002
1003    integer(c_long) file_length
1004    integer(c_int) available_as_string
1005    type(c_ptr) pfile_name, pfile_raw_data, pfile_string
1006    integer(c_signed_char), pointer :: file_raw_data_fpointer(:)
1007
1008    call c_f_pointer(collections_handle%p, collections)
1009    ierr = get_item_metadata_file_by_coll_and_type(collections, &
1010                                                   index - 1, &
1011                                                   pfile_name, &
1012                                                   file_length, &
1013                                                   pfile_raw_data, &
1014                                                   available_as_string, &
1015                                                   pfile_string)
1016    if (ierr == 0) then
1017      if (size(file_raw_data) < file_length) then
1018        ierr = 1
1019        return
1020      end if
1021      if (available_as_string == 1) then
1022        if (len(file_string) < file_length) then
1023          ierr = 1
1024          return
1025        end if
1026      end if
1027
1028      call kim_convert_c_char_ptr_to_string(pfile_name, file_name)
1029      if (c_associated(pfile_raw_data)) then
1030        call c_f_pointer(pfile_raw_data, file_raw_data_fpointer, [file_length])
1031      else
1032        nullify (file_raw_data_fpointer)
1033      end if
1034      file_raw_data = file_raw_data_fpointer(1:file_length)
1035
1036      if (available_as_string == 1) then
1037        call kim_convert_c_char_ptr_to_string(pfile_string, file_string)
1038      end if
1039    end if
1040  end subroutine kim_collections_get_item_metadata_file_values_by_coll_and_type
1041
1042  !> \brief \copybrief KIM::Collections::GetProjectNameAndSemVer
1043  !!
1044  !! \sa KIM::Collections::GetProjectNameAndSemVer,
1045  !! KIM_Collections_GetProjectNameAndSemVer
1046  !!
1047  !! \since 2.1
1048  recursive subroutine kim_collections_get_project_name_and_sem_ver( &
1049    collections_handle, project_name, sem_ver)
1050    use kim_interoperable_types_module, only: kim_collections_type
1051    use kim_convert_string_module, only: kim_convert_c_char_ptr_to_string
1052    implicit none
1053    interface
1054      recursive subroutine get_project_name_and_sem_ver(collections, &
1055                                                        project_name, sem_ver) &
1056        bind(c, name="KIM_Collections_GetProjectNameAndSemVer")
1057        use, intrinsic :: iso_c_binding
1058        use kim_interoperable_types_module, only: kim_collections_type
1059        implicit none
1060        type(kim_collections_type), intent(in) :: collections
1061        type(c_ptr), intent(out) :: project_name
1062        type(c_ptr), intent(out) :: sem_ver
1063      end subroutine get_project_name_and_sem_ver
1064    end interface
1065    type(kim_collections_handle_type), intent(in) :: collections_handle
1066    character(len=*, kind=c_char), intent(out) :: project_name
1067    character(len=*, kind=c_char), intent(out) :: sem_ver
1068    type(kim_collections_type), pointer :: collections
1069
1070    type(c_ptr) pproject_name, psem_ver
1071
1072    call c_f_pointer(collections_handle%p, collections)
1073    call get_project_name_and_sem_ver(collections, pproject_name, psem_ver)
1074    call kim_convert_c_char_ptr_to_string(pproject_name, project_name)
1075    call kim_convert_c_char_ptr_to_string(psem_ver, sem_ver)
1076  end subroutine kim_collections_get_project_name_and_sem_ver
1077
1078  !> \brief \copybrief KIM::Collections::GetEnvironmentVariableName
1079  !!
1080  !! \sa KIM::Collections::GetEnvironmentVariableName,
1081  !! KIM_Collections_GetEnvironmentVariableName
1082  !!
1083  !! \since 2.1
1084  recursive subroutine kim_collections_get_environment_variable_name( &
1085    collections_handle, item_type, name, ierr)
1086    use kim_interoperable_types_module, only: kim_collections_type
1087    use kim_convert_string_module, only: kim_convert_c_char_ptr_to_string
1088    use kim_collection_item_type_module, only: kim_collection_item_type_type
1089    implicit none
1090    interface
1091      integer(c_int) recursive function get_environment_variable_name( &
1092        collections, item_type, name) &
1093        bind(c, name="KIM_Collections_GetEnvironmentVariableName")
1094        use, intrinsic :: iso_c_binding
1095        use kim_interoperable_types_module, only: kim_collections_type
1096        use kim_collection_item_type_module, only: &
1097          kim_collection_item_type_type
1098        implicit none
1099        type(kim_collections_type), intent(in) :: collections
1100        type(kim_collection_item_type_type), intent(in), value :: item_type
1101        type(c_ptr), intent(out) :: name
1102      end function get_environment_variable_name
1103    end interface
1104    type(kim_collections_handle_type), intent(in) :: collections_handle
1105    type(kim_collection_item_type_type), intent(in) :: item_type
1106    character(len=*, kind=c_char), intent(out) :: name
1107    integer(c_int), intent(out) :: ierr
1108    type(kim_collections_type), pointer :: collections
1109
1110    type(c_ptr) pname
1111
1112    call c_f_pointer(collections_handle%p, collections)
1113    ierr = get_environment_variable_name(collections, item_type, pname)
1114    call kim_convert_c_char_ptr_to_string(pname, name)
1115  end subroutine kim_collections_get_environment_variable_name
1116
1117  !> \brief \copybrief KIM::Collections::GetConfigurationFileEnvironmentVariable
1118  !!
1119  !! \sa KIM::Collections::GetConfigurationFileEnvironmentVariable,
1120  !! KIM_Collections_GetConfigurationFileEnvironmentVariable
1121  !!
1122  !! \since 2.1
1123  recursive subroutine &
1124    kim_collections_get_configuration_file_environment_variable( &
1125    collections_handle, name, value)
1126    use kim_interoperable_types_module, only: kim_collections_type
1127    use kim_convert_string_module, only: kim_convert_c_char_ptr_to_string
1128    implicit none
1129    interface
1130      recursive subroutine get_configuration_file_environment_variable( &
1131        collections, name, value) &
1132        bind(c, name="KIM_Collections_GetConfigurationFileEnvironmentVariable")
1133        use, intrinsic :: iso_c_binding
1134        use kim_interoperable_types_module, only: kim_collections_type
1135        implicit none
1136        type(kim_collections_type), intent(in) :: collections
1137        type(c_ptr), intent(out) :: name
1138        type(c_ptr), intent(out) :: value
1139      end subroutine get_configuration_file_environment_variable
1140    end interface
1141    type(kim_collections_handle_type), intent(in) :: collections_handle
1142    character(len=*, kind=c_char), intent(out) :: name
1143    character(len=*, kind=c_char), intent(out) :: value
1144    type(kim_collections_type), pointer :: collections
1145
1146    type(c_ptr) pname, pvalue
1147
1148    call c_f_pointer(collections_handle%p, collections)
1149    call get_configuration_file_environment_variable(collections, pname, pvalue)
1150    call kim_convert_c_char_ptr_to_string(pname, name)
1151    call kim_convert_c_char_ptr_to_string(pvalue, value)
1152  end subroutine kim_collections_get_configuration_file_environment_variable
1153
1154  !> \brief \copybrief KIM::Collections::GetConfigurationFileName
1155  !!
1156  !! \sa KIM::Collections::GetConfigurationFileName,
1157  !! KIM_Collections_GetConfigurationFileName
1158  !!
1159  !! \since 2.1
1160  recursive subroutine kim_collections_get_configuration_file_name( &
1161    collections_handle, file_name)
1162    use kim_interoperable_types_module, only: kim_collections_type
1163    use kim_convert_string_module, only: kim_convert_c_char_ptr_to_string
1164    implicit none
1165    interface
1166      recursive subroutine get_configuration_file_name(collections, file_name) &
1167        bind(c, name="KIM_Collections_GetConfigurationFileName")
1168        use, intrinsic :: iso_c_binding
1169        use kim_interoperable_types_module, only: kim_collections_type
1170        implicit none
1171        type(kim_collections_type), intent(in) :: collections
1172        type(c_ptr), intent(out) :: file_name
1173      end subroutine get_configuration_file_name
1174    end interface
1175    type(kim_collections_handle_type), intent(in) :: collections_handle
1176    character(len=*, kind=c_char), intent(out) :: file_name
1177    type(kim_collections_type), pointer :: collections
1178
1179    type(c_ptr) pfile_name
1180
1181    call c_f_pointer(collections_handle%p, collections)
1182    call get_configuration_file_name(collections, pfile_name)
1183    call kim_convert_c_char_ptr_to_string(pfile_name, file_name)
1184  end subroutine kim_collections_get_configuration_file_name
1185
1186  !> \brief \copybrief KIM::Collections::CacheListOfDirectoryNames
1187  !!
1188  !! \sa KIM::Collections::CacheListOfDirectoryNames,
1189  !! KIM_Collections_CacheListOfDirectoryNames
1190  !!
1191  !! \since 2.1
1192  recursive subroutine kim_collections_cache_list_of_directory_names( &
1193    collections_handle, collection, item_type, extent, ierr)
1194    use kim_interoperable_types_module, only: kim_collections_type
1195    use kim_collection_module, only: kim_collection_type
1196    use kim_collection_item_type_module, only: kim_collection_item_type_type
1197    implicit none
1198    interface
1199      integer(c_int) recursive function cache_list_of_directory_names( &
1200        collections, collection, item_type, extent) &
1201        bind(c, name="KIM_Collections_CacheListOfDirectoryNames")
1202        use, intrinsic :: iso_c_binding
1203        use kim_interoperable_types_module, only: kim_collections_type
1204        use kim_collection_module, only: kim_collection_type
1205        use kim_collection_item_type_module, only: &
1206          kim_collection_item_type_type
1207        implicit none
1208        type(kim_collections_type), intent(in) :: collections
1209        type(kim_collection_type), intent(in), value :: collection
1210        type(kim_collection_item_type_type), intent(in), value :: item_type
1211        integer(c_int), intent(out) :: extent
1212      end function cache_list_of_directory_names
1213    end interface
1214    type(kim_collections_handle_type), intent(in) :: collections_handle
1215    type(kim_collection_type), intent(in) :: collection
1216    type(kim_collection_item_type_type), intent(in) :: item_type
1217    integer(c_int), intent(out) :: extent
1218    integer(c_int), intent(out) :: ierr
1219    type(kim_collections_type), pointer :: collections
1220
1221    call c_f_pointer(collections_handle%p, collections)
1222    ierr = cache_list_of_directory_names(collections, collection, item_type, &
1223                                         extent)
1224  end subroutine kim_collections_cache_list_of_directory_names
1225
1226  !> \brief \copybrief KIM::Collections::GetDirectoryName
1227  !!
1228  !! \sa KIM::Collections::GetDirectoryName, KIM_Collections_GetDirectoryName
1229  !!
1230  !! \since 2.1
1231  recursive subroutine kim_collections_get_directory_name(collections_handle, &
1232                                                          index, &
1233                                                          directory_name, &
1234                                                          ierr)
1235    use kim_interoperable_types_module, only: kim_collections_type
1236    use kim_convert_string_module, only: kim_convert_c_char_ptr_to_string
1237    implicit none
1238    interface
1239      integer(c_int) recursive function get_directory_name(collections, index, &
1240                                                           directory_name) &
1241        bind(c, name="KIM_Collections_GetDirectoryName")
1242        use, intrinsic :: iso_c_binding
1243        use kim_interoperable_types_module, only: kim_collections_type
1244        implicit none
1245        type(kim_collections_type), intent(in) :: collections
1246        integer(c_int), intent(in), value :: index
1247        type(c_ptr), intent(out) :: directory_name
1248      end function get_directory_name
1249    end interface
1250    type(kim_collections_handle_type), intent(in) :: collections_handle
1251    integer(c_int), intent(in) :: index
1252    character(len=*, kind=c_char), intent(out) :: directory_name
1253    integer(c_int), intent(out) :: ierr
1254    type(kim_collections_type), pointer :: collections
1255
1256    type(c_ptr) pdirectory_name
1257
1258    call c_f_pointer(collections_handle%p, collections)
1259    ierr = get_directory_name(collections, index - 1, pdirectory_name)
1260    call kim_convert_c_char_ptr_to_string(pdirectory_name, directory_name)
1261  end subroutine kim_collections_get_directory_name
1262
1263  !> \brief \copybrief KIM::Collections::SetLogID
1264  !!
1265  !! \sa KIM::Collections::SetLogID, KIM_Collections_SetLogID
1266  !!
1267  !! \since 2.1
1268  recursive subroutine kim_collections_set_log_id(collections_handle, log_id)
1269    use kim_interoperable_types_module, only: kim_collections_type
1270    implicit none
1271    interface
1272      recursive subroutine set_log_id(collections, log_id) &
1273        bind(c, name="KIM_Collections_SetLogID")
1274        use, intrinsic :: iso_c_binding
1275        use kim_interoperable_types_module, only: kim_collections_type
1276        implicit none
1277        type(kim_collections_type), intent(in) :: collections
1278        character(c_char), intent(in) :: log_id(*)
1279      end subroutine set_log_id
1280    end interface
1281    type(kim_collections_handle_type), intent(in) :: collections_handle
1282    character(len=*, kind=c_char), intent(in) :: log_id
1283    type(kim_collections_type), pointer :: collections
1284
1285    call c_f_pointer(collections_handle%p, collections)
1286    call set_log_id(collections, trim(log_id)//c_null_char)
1287  end subroutine kim_collections_set_log_id
1288
1289  !> \brief \copybrief KIM::Collections::PushLogVerbosity
1290  !!
1291  !! \sa KIM::Collections::PushLogVerbosity, KIM_Collections_PushLogVerbosity
1292  !!
1293  !! \since 2.1
1294  recursive subroutine kim_collections_push_log_verbosity(collections_handle, &
1295                                                          log_verbosity)
1296    use kim_log_verbosity_module, only: kim_log_verbosity_type
1297    use kim_interoperable_types_module, only: kim_collections_type
1298    implicit none
1299    interface
1300      recursive subroutine push_log_verbosity(collections, log_verbosity) &
1301        bind(c, name="KIM_Collections_PushLogVerbosity")
1302        use, intrinsic :: iso_c_binding
1303        use kim_log_verbosity_module, only: kim_log_verbosity_type
1304        use kim_interoperable_types_module, only: kim_collections_type
1305        implicit none
1306        type(kim_collections_type), intent(in) :: collections
1307        type(kim_log_verbosity_type), intent(in), value :: log_verbosity
1308      end subroutine push_log_verbosity
1309    end interface
1310    type(kim_collections_handle_type), intent(in) :: collections_handle
1311    type(kim_log_verbosity_type), intent(in) :: log_verbosity
1312    type(kim_collections_type), pointer :: collections
1313
1314    call c_f_pointer(collections_handle%p, collections)
1315    call push_log_verbosity(collections, log_verbosity)
1316  end subroutine kim_collections_push_log_verbosity
1317
1318  !> \brief \copybrief KIM::Collections::PopLogVerbosity
1319  !!
1320  !! \sa KIM::Collections::, KIM_Collections_PopLogVerbosity
1321  !!
1322  !! \since 2.1
1323  recursive subroutine kim_collections_pop_log_verbosity(collections_handle)
1324    use kim_log_verbosity_module, only: kim_log_verbosity_type
1325    use kim_interoperable_types_module, only: kim_collections_type
1326    implicit none
1327    interface
1328      recursive subroutine pop_log_verbosity(collections) &
1329        bind(c, name="KIM_Collections_PopLogVerbosity")
1330        use, intrinsic :: iso_c_binding
1331        use kim_log_verbosity_module, only: kim_log_verbosity_type
1332        use kim_interoperable_types_module, only: kim_collections_type
1333        implicit none
1334        type(kim_collections_type), intent(in) :: collections
1335      end subroutine pop_log_verbosity
1336    end interface
1337    type(kim_collections_handle_type), intent(in) :: collections_handle
1338    type(kim_collections_type), pointer :: collections
1339
1340    call c_f_pointer(collections_handle%p, collections)
1341    call pop_log_verbosity(collections)
1342  end subroutine kim_collections_pop_log_verbosity
1343end module kim_collections_module
1344