kim-api  2.2.1+v2.2.1.GNU.GNU.
An Application Programming Interface (API) for the Knowledgebase of Interatomic Models (KIM).
kim_model_compute_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_model_compute_handle_type, &
46  ! Constants
48  ! Routines
49  operator(.eq.), &
50  operator(.ne.), &
51  kim_get_model_buffer_pointer, &
52  kim_log_entry, &
53  kim_to_string
54 
60  type, bind(c) :: kim_model_compute_handle_type
61  type(c_ptr) :: p = c_null_ptr
62  end type kim_model_compute_handle_type
63 
67  type(kim_model_compute_handle_type), protected, save &
69 
73  interface operator(.eq.)
74  module procedure kim_model_compute_handle_equal
75  end interface operator(.eq.)
76 
80  interface operator(.ne.)
81  module procedure kim_model_compute_handle_not_equal
82  end interface operator(.ne.)
83 
90  interface kim_get_model_buffer_pointer
91  module procedure kim_model_compute_get_model_buffer_pointer
92  end interface kim_get_model_buffer_pointer
93 
99  interface kim_log_entry
100  module procedure kim_model_compute_log_entry
101  end interface kim_log_entry
102 
108  interface kim_to_string
109  module procedure kim_model_compute_to_string
110  end interface kim_to_string
111 
112 contains
116  logical recursive function kim_model_compute_handle_equal(lhs, rhs)
117  implicit none
118  type(kim_model_compute_handle_type), intent(in) :: lhs
119  type(kim_model_compute_handle_type), intent(in) :: rhs
120 
121  if ((.not. c_associated(lhs%p)) .and. (.not. c_associated(rhs%p))) then
122  kim_model_compute_handle_equal = .true.
123  else
124  kim_model_compute_handle_equal = c_associated(lhs%p, rhs%p)
125  end if
126  end function kim_model_compute_handle_equal
127 
131  logical recursive function kim_model_compute_handle_not_equal(lhs, rhs)
132  implicit none
133  type(kim_model_compute_handle_type), intent(in) :: lhs
134  type(kim_model_compute_handle_type), intent(in) :: rhs
135 
136  kim_model_compute_handle_not_equal = .not. (lhs == rhs)
137  end function kim_model_compute_handle_not_equal
138 
145  recursive subroutine kim_model_compute_get_model_buffer_pointer( &
146  model_compute_handle, ptr)
147  use kim_interoperable_types_module, only: kim_model_compute_type
148  implicit none
149  interface
150  recursive subroutine get_model_buffer_pointer(model_compute, ptr) &
151  bind(c, name="KIM_ModelCompute_GetModelBufferPointer")
152  use, intrinsic :: iso_c_binding
153  use kim_interoperable_types_module, only: kim_model_compute_type
154  implicit none
155  type(kim_model_compute_type), intent(in) :: model_compute
156  type(c_ptr), intent(out) :: ptr
157  end subroutine get_model_buffer_pointer
158  end interface
159  type(kim_model_compute_handle_type), intent(in) :: model_compute_handle
160  type(c_ptr), intent(out) :: ptr
161  type(kim_model_compute_type), pointer :: model_compute
162 
163  call c_f_pointer(model_compute_handle%p, model_compute)
164  call get_model_buffer_pointer(model_compute, ptr)
165  end subroutine kim_model_compute_get_model_buffer_pointer
166 
172  recursive subroutine kim_model_compute_log_entry(model_compute_handle, &
173  log_verbosity, message)
174  use kim_log_verbosity_module, only: kim_log_verbosity_type
175  use kim_interoperable_types_module, only: kim_model_compute_type
176  implicit none
177  interface
178  recursive subroutine log_entry( &
179  model_compute, log_verbosity, message, line_number, file_name) &
180  bind(c, name="KIM_ModelCompute_LogEntry")
181  use, intrinsic :: iso_c_binding
182  use kim_log_verbosity_module, only: kim_log_verbosity_type
183  use kim_interoperable_types_module, only: kim_model_compute_type
184  implicit none
185  type(kim_model_compute_type), intent(in) :: model_compute
186  type(kim_log_verbosity_type), intent(in), value :: log_verbosity
187  character(c_char), intent(in) :: message(*)
188  integer(c_int), intent(in), value :: line_number
189  character(c_char), intent(in) :: file_name(*)
190  end subroutine log_entry
191  end interface
192  type(kim_model_compute_handle_type), intent(in) :: model_compute_handle
193  type(kim_log_verbosity_type), intent(in) :: log_verbosity
194  character(len=*, kind=c_char), intent(in) :: message
195  type(kim_model_compute_type), pointer :: model_compute
196 
197  call c_f_pointer(model_compute_handle%p, model_compute)
198  call log_entry(model_compute, log_verbosity, trim(message)//c_null_char, &
199  0, ""//c_null_char)
200  end subroutine kim_model_compute_log_entry
201 
207  recursive subroutine kim_model_compute_to_string(model_compute_handle, string)
208  use kim_convert_string_module, only: kim_convert_c_char_ptr_to_string
209  use kim_interoperable_types_module, only: kim_model_compute_type
210  implicit none
211  interface
212  type(c_ptr) recursive function model_compute_string(model_compute) &
213  bind(c, name="KIM_ModelCompute_ToString")
214  use, intrinsic :: iso_c_binding
215  use kim_interoperable_types_module, only: kim_model_compute_type
216  implicit none
217  type(kim_model_compute_type), intent(in) :: model_compute
218  end function model_compute_string
219  end interface
220  type(kim_model_compute_handle_type), intent(in) :: model_compute_handle
221  character(len=*, kind=c_char), intent(out) :: string
222  type(kim_model_compute_type), pointer :: model_compute
223 
224  type(c_ptr) :: p
225 
226  call c_f_pointer(model_compute_handle%p, model_compute)
227  p = model_compute_string(model_compute)
228  call kim_convert_c_char_ptr_to_string(p, string)
229  end subroutine kim_model_compute_to_string
230 end module kim_model_compute_module
type(kim_model_compute_handle_type), save, public, protected kim_model_compute_null_handle
NULL handle for use in comparisons.
static int model_compute(KIM_ModelCompute const *const modelCompute, KIM_ModelComputeArguments const *const modelComputeArguments)
recursive subroutine kim_model_compute_to_string(model_compute_handle, string)
Get a string representing the internal state of the Model object.
recursive subroutine kim_model_compute_log_entry(model_compute_handle, log_verbosity, message)
Write a log entry into the log file.
Provides the interface to a KIM API Model object for use by models within their MODEL_ROUTINE_NAME::C...
An Extensible Enumeration for the LogVerbosity's supported by the KIM API.