kim-api  2.1.2+v2.1.2.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--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_log_handle_type, &
47 
48  ! Constants
50 
51  ! Routines
52  operator (.eq.), &
53  operator (.ne.), &
56  kim_push_default_verbosity, &
57  kim_pop_default_verbosity, &
58  kim_get_id, &
59  kim_set_id, &
60  kim_push_verbosity, &
61  kim_pop_verbosity, &
62  kim_log_entry
63 
64 
70  type, bind(c) :: kim_log_handle_type
71  type(c_ptr) :: p = c_null_ptr
72  end type kim_log_handle_type
73 
77  type(kim_log_handle_type), protected, save &
79 
83  interface operator (.eq.)
84  module procedure kim_log_handle_equal
85  end interface operator (.eq.)
86 
90  interface operator (.ne.)
91  module procedure kim_log_handle_not_equal
92  end interface operator (.ne.)
93 
99  interface kim_push_default_verbosity
100  module procedure kim_log_push_default_verbosity
101  end interface kim_push_default_verbosity
102 
108  interface kim_pop_default_verbosity
109  module procedure kim_log_pop_default_verbosity
110  end interface kim_pop_default_verbosity
111 
117  interface kim_get_id
118  module procedure kim_log_get_id
119  end interface kim_get_id
120 
126  interface kim_set_id
127  module procedure kim_log_set_id
128  end interface kim_set_id
129 
135  interface kim_push_verbosity
136  module procedure kim_log_push_verbosity
137  end interface kim_push_verbosity
138 
144  interface kim_pop_verbosity
145  module procedure kim_log_pop_verbosity
146  end interface kim_pop_verbosity
147 
153  interface kim_log_entry
154  module procedure kim_log_log_entry
155  end interface kim_log_entry
156 
157 contains
161  logical recursive function kim_log_handle_equal(lhs, rhs)
162  implicit none
163  type(kim_log_handle_type), intent(in) :: lhs
164  type(kim_log_handle_type), intent(in) :: rhs
165 
166  if ((.not. c_associated(lhs%p)) .and. (.not. c_associated(rhs%p))) then
167  kim_log_handle_equal = .true.
168  else
169  kim_log_handle_equal = c_associated(lhs%p, rhs%p)
170  end if
171  end function kim_log_handle_equal
172 
176  logical recursive function kim_log_handle_not_equal(lhs, rhs)
177  implicit none
178  type(kim_log_handle_type), intent(in) :: lhs
179  type(kim_log_handle_type), intent(in) :: rhs
180 
181  kim_log_handle_not_equal = .not. (lhs .eq. rhs)
182  end function kim_log_handle_not_equal
183 
189  recursive subroutine kim_log_create(log_handle, ierr)
190  implicit none
191  interface
192  integer(c_int) recursive function create(log) &
193  bind(c, name="KIM_Log_Create")
194  use, intrinsic :: iso_c_binding
195  implicit none
196  type(c_ptr), intent(out) :: log
197  end function create
198  end interface
199  type(kim_log_handle_type), intent(out) :: log_handle
200  integer(c_int), intent(out) :: ierr
201 
202  type(c_ptr) :: plog
203 
204  ierr = create(plog)
205  log_handle%p = plog
206  end subroutine kim_log_create
207 
213  recursive subroutine kim_log_destroy(log_handle)
214  implicit none
215  interface
216  recursive subroutine destroy(log) bind(c, name="KIM_Log_Destroy")
217  use, intrinsic :: iso_c_binding
218  implicit none
219  type(c_ptr), intent(inout) :: log
220  end subroutine destroy
221  end interface
222  type(kim_log_handle_type), intent(inout) :: log_handle
223 
224  type(c_ptr) :: plog
225  plog = log_handle%p
226  call destroy(plog)
227  log_handle%p = c_null_ptr
228  end subroutine kim_log_destroy
229 
235  recursive subroutine kim_log_push_default_verbosity(log_verbosity)
236  use kim_log_verbosity_module, only : kim_log_verbosity_type
237  implicit none
238  interface
239  recursive subroutine push_default_verbosity(log_verbosity) &
240  bind(c, name="KIM_Log_PushDefaultVerbosity")
241  use, intrinsic :: iso_c_binding
242  use kim_log_verbosity_module, only : kim_log_verbosity_type
243  implicit none
244  type(kim_log_verbosity_type), intent(in), value :: log_verbosity
245  end subroutine push_default_verbosity
246  end interface
247  type(kim_log_verbosity_type), intent(in) :: log_verbosity
248 
249  call push_default_verbosity(log_verbosity)
250  end subroutine kim_log_push_default_verbosity
251 
257  recursive subroutine kim_log_pop_default_verbosity()
258  implicit none
259  interface
260  recursive subroutine pop_default_verbosity() &
261  bind(c, name="KIM_Log_PopDefaultVerbosity")
262  use, intrinsic :: iso_c_binding
263  implicit none
264  end subroutine pop_default_verbosity
265  end interface
266 
267  call pop_default_verbosity()
268  end subroutine kim_log_pop_default_verbosity
269 
275  recursive subroutine kim_log_get_id(log_handle, id_string)
276  use kim_convert_string_module, only : kim_convert_c_char_ptr_to_string
277  use kim_interoperable_types_module, only : kim_log_type
278  implicit none
279  interface
280  type(c_ptr) recursive function get_id(log) bind(c, name="KIM_Log_GetID")
281  use, intrinsic :: iso_c_binding
282  use kim_interoperable_types_module, only : kim_log_type
283  implicit none
284  type(kim_log_type), intent(in) :: log
285  end function get_id
286  end interface
287  type(kim_log_handle_type), intent(in) :: log_handle
288  character(len=*, kind=c_char), intent(out) :: id_string
289  type(kim_log_type), pointer :: log
290 
291  type(c_ptr) :: p
292 
293  call c_f_pointer(log_handle%p, log)
294  p = get_id(log)
295  call kim_convert_c_char_ptr_to_string(p, id_string)
296  end subroutine kim_log_get_id
297 
303  recursive subroutine kim_log_set_id(log_handle, id_string)
304  use kim_interoperable_types_module, only : kim_log_type
305  implicit none
306  interface
307  recursive subroutine set_id(log, id_string) bind(c, name="KIM_Log_SetID")
308  use, intrinsic :: iso_c_binding
309  use kim_interoperable_types_module, only : kim_log_type
310  implicit none
311  type(kim_log_type), intent(in) :: log
312  character(c_char), intent(in) :: id_string(*)
313  end subroutine set_id
314  end interface
315  type(kim_log_handle_type), intent(in) :: log_handle
316  character(len=*, kind=c_char), intent(in) :: id_string
317  type(kim_log_type), pointer :: log
318 
319  call c_f_pointer(log_handle%p, log)
320  call set_id(log, trim(id_string)//c_null_char)
321  end subroutine kim_log_set_id
322 
328  recursive subroutine kim_log_push_verbosity(log_handle, log_verbosity)
329  use kim_log_verbosity_module, only : kim_log_verbosity_type
330  use kim_interoperable_types_module, only : kim_log_type
331  implicit none
332  interface
333  recursive subroutine push_verbosity(log, log_verbosity) &
334  bind(c, name="KIM_Log_PushVerbosity")
335  use, intrinsic :: iso_c_binding
336  use kim_log_verbosity_module, only : kim_log_verbosity_type
337  use kim_interoperable_types_module, only : kim_log_type
338  implicit none
339  type(kim_log_type), intent(in) :: log
340  type(kim_log_verbosity_type), intent(in), value :: log_verbosity
341  end subroutine push_verbosity
342  end interface
343  type(kim_log_handle_type), intent(in) :: log_handle
344  type(kim_log_verbosity_type), intent(in) :: log_verbosity
345  type(kim_log_type), pointer :: log
346 
347  call c_f_pointer(log_handle%p, log)
348  call push_verbosity(log, log_verbosity)
349  end subroutine kim_log_push_verbosity
350 
356  recursive subroutine kim_log_pop_verbosity(log_handle)
357  use kim_interoperable_types_module, only : kim_log_type
358  implicit none
359  interface
360  recursive subroutine pop_verbosity(log) &
361  bind(c, name="KIM_Log_PopVerbosity")
362  use, intrinsic :: iso_c_binding
363  use kim_interoperable_types_module, only : kim_log_type
364  implicit none
365  type(kim_log_type), intent(in) :: log
366  end subroutine pop_verbosity
367  end interface
368  type(kim_log_handle_type), intent(in) :: log_handle
369  type(kim_log_type), pointer :: log
370 
371  call c_f_pointer(log_handle%p, log)
372  call pop_verbosity(log)
373  end subroutine kim_log_pop_verbosity
374 
380  recursive subroutine kim_log_log_entry(log_handle, log_verbosity, message)
381  use kim_log_verbosity_module, only : kim_log_verbosity_type
382  use kim_interoperable_types_module, only : kim_log_type
383  implicit none
384  interface
385  recursive subroutine log_entry(log, log_verbosity, message, line_number, &
386  file_name) bind(c, name="KIM_Log_LogEntry")
387  use, intrinsic :: iso_c_binding
388  use kim_log_verbosity_module, only : kim_log_verbosity_type
389  use kim_interoperable_types_module, only : kim_log_type
390  implicit none
391  type(kim_log_type), intent(in) :: log
392  type(kim_log_verbosity_type), intent(in), value :: log_verbosity
393  character(c_char), intent(in) :: message(*)
394  integer(c_int), intent(in), value :: line_number
395  character(c_char), intent(in) :: file_name(*)
396  end subroutine log_entry
397  end interface
398  type(kim_log_handle_type), intent(in) :: log_handle
399  type(kim_log_verbosity_type), intent(in) :: log_verbosity
400  character(len=*, kind=c_char), intent(in) :: message
401  type(kim_log_type), pointer :: log
402 
403  call c_f_pointer(log_handle%p, log)
404  call log_entry(log, log_verbosity, trim(message)//c_null_char, &
405  0, ""//c_null_char)
406  end subroutine kim_log_log_entry
407 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_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.
An Extensible Enumeration for the LogVerbosity's supported by the KIM API.