kim-api  2.2.1+v2.2.1.GNU.GNU.
An Application Programming Interface (API) for the Knowledgebase of Interatomic Models (KIM).
kim_log_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_log_handle_type, &
46  ! Constants
48  ! Routines
49  operator(.eq.), &
50  operator(.ne.), &
53  kim_push_default_verbosity, &
54  kim_pop_default_verbosity, &
55  kim_push_default_print_function, &
56  kim_pop_default_print_function, &
57  kim_convert_c_string, &
58  kim_get_id, &
59  kim_set_id, &
60  kim_push_verbosity, &
61  kim_pop_verbosity, &
62  kim_log_entry
63 
69  type, bind(c) :: kim_log_handle_type
70  type(c_ptr) :: p = c_null_ptr
71  end type kim_log_handle_type
72 
76  type(kim_log_handle_type), protected, save &
78 
82  interface operator(.eq.)
83  module procedure kim_log_handle_equal
84  end interface operator(.eq.)
85 
89  interface operator(.ne.)
90  module procedure kim_log_handle_not_equal
91  end interface operator(.ne.)
92 
98  interface kim_push_default_verbosity
99  module procedure kim_log_push_default_verbosity
100  end interface kim_push_default_verbosity
101 
107  interface kim_pop_default_verbosity
108  module procedure kim_log_pop_default_verbosity
109  end interface kim_pop_default_verbosity
110 
116  interface kim_push_default_print_function
117  module procedure kim_log_push_default_print_function
118  end interface kim_push_default_print_function
119 
125  interface kim_pop_default_print_function
126  module procedure kim_log_pop_default_print_function
127  end interface kim_pop_default_print_function
128 
132  interface kim_convert_c_string
133  module procedure kim_log_convert_c_string
134  end interface kim_convert_c_string
135 
141  interface kim_get_id
142  module procedure kim_log_get_id
143  end interface kim_get_id
144 
150  interface kim_set_id
151  module procedure kim_log_set_id
152  end interface kim_set_id
153 
159  interface kim_push_verbosity
160  module procedure kim_log_push_verbosity
161  end interface kim_push_verbosity
162 
168  interface kim_pop_verbosity
169  module procedure kim_log_pop_verbosity
170  end interface kim_pop_verbosity
171 
177  interface kim_log_entry
178  module procedure kim_log_log_entry
179  end interface kim_log_entry
180 
181 contains
185  logical recursive function kim_log_handle_equal(lhs, rhs)
186  implicit none
187  type(kim_log_handle_type), intent(in) :: lhs
188  type(kim_log_handle_type), intent(in) :: rhs
189 
190  if ((.not. c_associated(lhs%p)) .and. (.not. c_associated(rhs%p))) then
191  kim_log_handle_equal = .true.
192  else
193  kim_log_handle_equal = c_associated(lhs%p, rhs%p)
194  end if
195  end function kim_log_handle_equal
196 
200  logical recursive function kim_log_handle_not_equal(lhs, rhs)
201  implicit none
202  type(kim_log_handle_type), intent(in) :: lhs
203  type(kim_log_handle_type), intent(in) :: rhs
204 
205  kim_log_handle_not_equal = .not. (lhs == rhs)
206  end function kim_log_handle_not_equal
207 
213  recursive subroutine kim_log_create(log_handle, ierr)
214  implicit none
215  interface
216  integer(c_int) recursive function create(log) &
217  bind(c, name="KIM_Log_Create")
218  use, intrinsic :: iso_c_binding
219  implicit none
220  type(c_ptr), intent(out) :: log
221  end function create
222  end interface
223  type(kim_log_handle_type), intent(out) :: log_handle
224  integer(c_int), intent(out) :: ierr
225 
226  type(c_ptr) :: plog
227 
228  ierr = create(plog)
229  log_handle%p = plog
230  end subroutine kim_log_create
231 
237  recursive subroutine kim_log_destroy(log_handle)
238  implicit none
239  interface
240  recursive subroutine destroy(log) bind(c, name="KIM_Log_Destroy")
241  use, intrinsic :: iso_c_binding
242  implicit none
243  type(c_ptr), intent(inout) :: log
244  end subroutine destroy
245  end interface
246  type(kim_log_handle_type), intent(inout) :: log_handle
247 
248  type(c_ptr) :: plog
249  plog = log_handle%p
250  call destroy(plog)
251  log_handle%p = c_null_ptr
252  end subroutine kim_log_destroy
253 
259  recursive subroutine kim_log_push_default_verbosity(log_verbosity)
260  use kim_log_verbosity_module, only: kim_log_verbosity_type
261  implicit none
262  interface
263  recursive subroutine push_default_verbosity(log_verbosity) &
264  bind(c, name="KIM_Log_PushDefaultVerbosity")
265  use, intrinsic :: iso_c_binding
266  use kim_log_verbosity_module, only: kim_log_verbosity_type
267  implicit none
268  type(kim_log_verbosity_type), intent(in), value :: log_verbosity
269  end subroutine push_default_verbosity
270  end interface
271  type(kim_log_verbosity_type), intent(in) :: log_verbosity
272 
273  call push_default_verbosity(log_verbosity)
274  end subroutine kim_log_push_default_verbosity
275 
281  recursive subroutine kim_log_pop_default_verbosity()
282  implicit none
283  interface
284  recursive subroutine pop_default_verbosity() &
285  bind(c, name="KIM_Log_PopDefaultVerbosity")
286  use, intrinsic :: iso_c_binding
287  implicit none
288  end subroutine pop_default_verbosity
289  end interface
290 
291  call pop_default_verbosity()
292  end subroutine kim_log_pop_default_verbosity
293 
337  recursive subroutine kim_log_push_default_print_function(language_name, fptr)
338  use kim_language_name_module, only: kim_language_name_type
339  implicit none
340  interface
341  recursive subroutine push_default_print_function(language_name, fptr) &
342  bind(c, name="KIM_Log_PushDefaultPrintFunction")
343  use, intrinsic :: iso_c_binding
344  use kim_language_name_module, only: kim_language_name_type
345  implicit none
346  type(kim_language_name_type), intent(in), value :: language_name
347  type(c_funptr), intent(in), value :: fptr
348  end subroutine push_default_print_function
349  end interface
350  type(kim_language_name_type), intent(in) :: language_name
351  type(c_funptr), intent(in), value :: fptr ! must be left as "value"!?!
352 
353  call push_default_print_function(language_name, fptr)
354  end subroutine kim_log_push_default_print_function
355 
361  recursive subroutine kim_log_pop_default_print_function()
362  implicit none
363  interface
364  recursive subroutine pop_default_print_function() &
365  bind(c, name="KIM_Log_PopDefaultPrintFunction")
366  use, intrinsic :: iso_c_binding
367  implicit none
368  end subroutine pop_default_print_function
369  end interface
370 
371  call pop_default_print_function()
373 
383  recursive subroutine kim_log_convert_c_string(c_char_ptr, string)
384  use kim_convert_string_module, only: kim_convert_c_char_ptr_to_string
385  implicit none
386  type(c_ptr), intent(in), value :: c_char_ptr
387  character(len=*, kind=c_char), intent(out) :: string
388 
389  call kim_convert_c_char_ptr_to_string(c_char_ptr, string)
390  end subroutine kim_log_convert_c_string
391 
397  recursive subroutine kim_log_get_id(log_handle, id_string)
398  use kim_convert_string_module, only: kim_convert_c_char_ptr_to_string
399  use kim_interoperable_types_module, only: kim_log_type
400  implicit none
401  interface
402  type(c_ptr) recursive function get_id(log) bind(c, name="KIM_Log_GetID")
403  use, intrinsic :: iso_c_binding
404  use kim_interoperable_types_module, only: kim_log_type
405  implicit none
406  type(kim_log_type), intent(in) :: log
407  end function get_id
408  end interface
409  type(kim_log_handle_type), intent(in) :: log_handle
410  character(len=*, kind=c_char), intent(out) :: id_string
411  type(kim_log_type), pointer :: log
412 
413  type(c_ptr) :: p
414 
415  call c_f_pointer(log_handle%p, log)
416  p = get_id(log)
417  call kim_convert_c_char_ptr_to_string(p, id_string)
418  end subroutine kim_log_get_id
419 
425  recursive subroutine kim_log_set_id(log_handle, id_string)
426  use kim_interoperable_types_module, only: kim_log_type
427  implicit none
428  interface
429  recursive subroutine set_id(log, id_string) bind(c, name="KIM_Log_SetID")
430  use, intrinsic :: iso_c_binding
431  use kim_interoperable_types_module, only: kim_log_type
432  implicit none
433  type(kim_log_type), intent(in) :: log
434  character(c_char), intent(in) :: id_string(*)
435  end subroutine set_id
436  end interface
437  type(kim_log_handle_type), intent(in) :: log_handle
438  character(len=*, kind=c_char), intent(in) :: id_string
439  type(kim_log_type), pointer :: log
440 
441  call c_f_pointer(log_handle%p, log)
442  call set_id(log, trim(id_string)//c_null_char)
443  end subroutine kim_log_set_id
444 
450  recursive subroutine kim_log_push_verbosity(log_handle, log_verbosity)
451  use kim_log_verbosity_module, only: kim_log_verbosity_type
452  use kim_interoperable_types_module, only: kim_log_type
453  implicit none
454  interface
455  recursive subroutine push_verbosity(log, log_verbosity) &
456  bind(c, name="KIM_Log_PushVerbosity")
457  use, intrinsic :: iso_c_binding
458  use kim_log_verbosity_module, only: kim_log_verbosity_type
459  use kim_interoperable_types_module, only: kim_log_type
460  implicit none
461  type(kim_log_type), intent(in) :: log
462  type(kim_log_verbosity_type), intent(in), value :: log_verbosity
463  end subroutine push_verbosity
464  end interface
465  type(kim_log_handle_type), intent(in) :: log_handle
466  type(kim_log_verbosity_type), intent(in) :: log_verbosity
467  type(kim_log_type), pointer :: log
468 
469  call c_f_pointer(log_handle%p, log)
470  call push_verbosity(log, log_verbosity)
471  end subroutine kim_log_push_verbosity
472 
478  recursive subroutine kim_log_pop_verbosity(log_handle)
479  use kim_interoperable_types_module, only: kim_log_type
480  implicit none
481  interface
482  recursive subroutine pop_verbosity(log) &
483  bind(c, name="KIM_Log_PopVerbosity")
484  use, intrinsic :: iso_c_binding
485  use kim_interoperable_types_module, only: kim_log_type
486  implicit none
487  type(kim_log_type), intent(in) :: log
488  end subroutine pop_verbosity
489  end interface
490  type(kim_log_handle_type), intent(in) :: log_handle
491  type(kim_log_type), pointer :: log
492 
493  call c_f_pointer(log_handle%p, log)
494  call pop_verbosity(log)
495  end subroutine kim_log_pop_verbosity
496 
502  recursive subroutine kim_log_log_entry(log_handle, log_verbosity, message)
503  use kim_log_verbosity_module, only: kim_log_verbosity_type
504  use kim_interoperable_types_module, only: kim_log_type
505  implicit none
506  interface
507  recursive subroutine log_entry(log, log_verbosity, message, line_number, &
508  file_name) bind(c, name="KIM_Log_LogEntry")
509  use, intrinsic :: iso_c_binding
510  use kim_log_verbosity_module, only: kim_log_verbosity_type
511  use kim_interoperable_types_module, only: kim_log_type
512  implicit none
513  type(kim_log_type), intent(in) :: log
514  type(kim_log_verbosity_type), intent(in), value :: log_verbosity
515  character(c_char), intent(in) :: message(*)
516  integer(c_int), intent(in), value :: line_number
517  character(c_char), intent(in) :: file_name(*)
518  end subroutine log_entry
519  end interface
520  type(kim_log_handle_type), intent(in) :: log_handle
521  type(kim_log_verbosity_type), intent(in) :: log_verbosity
522  character(len=*, kind=c_char), intent(in) :: message
523  type(kim_log_type), pointer :: log
524 
525  call c_f_pointer(log_handle%p, log)
526  call log_entry(log, log_verbosity, trim(message)//c_null_char, &
527  0, ""//c_null_char)
528  end subroutine kim_log_log_entry
529 end module kim_log_module
recursive subroutine, public kim_log_create(log_handle, ierr)
Create a new KIM API Log object.
recursive subroutine kim_log_set_id(log_handle, id_string)
Set the identity of the Log object.
recursive subroutine, public kim_log_destroy(log_handle)
Destroy a previously Log::Create'd object.
Provides the logging interface for the KIM API.
type(kim_log_handle_type), save, public, protected kim_log_null_handle
NULL handle for use in comparisons.
recursive subroutine kim_log_get_id(log_handle, id_string)
Get the identity of the Log object.
An Extensible Enumeration for the LanguageName's supported by the KIM API.
recursive subroutine kim_log_pop_default_verbosity()
Pop a LogVerbosity from the KIM API global default verbosity stack.
recursive subroutine kim_log_pop_verbosity(log_handle)
Pop a LogVerbosity from the Log object's verbosity stack.
recursive subroutine kim_log_log_entry(log_handle, log_verbosity, message)
Write a log entry into the log file.
recursive subroutine kim_log_push_verbosity(log_handle, log_verbosity)
Push a new LogVerbosity onto the Log object's verbosity stack.
recursive subroutine kim_log_pop_default_print_function()
Pop a log PrintFunction from the KIM API global default log PrintFunction stack.
An Extensible Enumeration for the LogVerbosity's supported by the KIM API.