MONC
arithmetic-operator.F90
Go to the documentation of this file.
1 
16  use logging_mod, only : log_error, log_log
18  implicit none
19 
20 #ifndef TEST_MODE
21  private
22 #endif
23 
24 
25  integer, parameter :: terminal_op=0, add_op=1, minus_op=2, mul_op=3, div_op=4, mod_op=5
26 
27 
29  character(len=STRING_LENGTH) :: variable
30  integer :: operator
31  type(arithmetic_execution_node), pointer :: left, right
33 
34 
36  type(arithmetic_execution_node), pointer :: execution_tree
37  type(list_type) :: required_fields
38  end type arithmetic_cache_item
39 
40  type(hashmap_type), volatile :: equation_cache
41  integer, volatile :: equation_cache_rwlock
42 
45 contains
46 
50  end subroutine initialise_arithmetic_operator
51 
55  end subroutine finalise_arithmetic_operator
56 
64  subroutine perform_arithmetic_operator(io_configuration, field_values, action_attributes, source_monc_location, &
65  source_monc, operator_result_values)
66  type(io_configuration_type), intent(inout) :: io_configuration
67  type(hashmap_type), intent(inout) :: field_values
68  type(map_type), intent(inout) :: action_attributes
69  integer, intent(in) :: source_monc_location, source_monc
70  real(kind=default_precision), dimension(:), allocatable, intent(inout) :: operator_result_values
71 
72  character(len=STRING_LENGTH) :: equation
73  type(arithmetic_cache_item), pointer :: cached_equation
74  integer :: data_size
75 
76  equation=get_action_attribute_string(action_attributes, "equation")
77  cached_equation=>find_or_add_equation(equation)
78  if (.not. associated(cached_equation%execution_tree)) then
79  cached_equation%execution_tree=>build_equation_tree(io_configuration, equation)
80  end if
81  data_size=get_size_of_data_being_operated_on(cached_equation, field_values)
82  allocate(operator_result_values(data_size))
83  operator_result_values=execute_equation_tree(cached_equation%execution_tree, field_values, data_size)
84  end subroutine perform_arithmetic_operator
85 
91  integer function get_size_of_data_being_operated_on(cached_equation, field_values)
92  type(arithmetic_cache_item), intent(inout) :: cached_equation
93  type(hashmap_type), intent(inout) :: field_values
94 
95  type(data_values_type), pointer :: variable_data
96  type(iterator_type) :: iterator
97  integer :: temp_size, prev_size
98 
100  if (.not. c_is_empty(cached_equation%required_fields)) then
101  iterator=c_get_iterator(cached_equation%required_fields)
102  do while (c_has_next(iterator))
103  variable_data=>get_data_value_by_field_name(field_values, c_next_string(iterator))
104 
105  if (get_size_of_data_being_operated_on == -1) then
106  get_size_of_data_being_operated_on=size(variable_data%values)
107  else
108  temp_size=size(variable_data%values)
109  if (get_size_of_data_being_operated_on .ne. temp_size) then
110  if (temp_size .gt. get_size_of_data_being_operated_on) then
113  temp_size=prev_size
114  end if
115  if (mod(get_size_of_data_being_operated_on, temp_size) .ne. 0) then
116  call log_log(log_error, &
117  "Can only perform arithmetic on variables with the same array sizes or sizes that divide evenly")
118  end if
119  end if
120  end if
121  end do
122  end if
124 
131  recursive function execute_equation_tree(equation_tree, field_values, n) result(result_value)
132  type(arithmetic_execution_node), pointer, intent(inout) :: equation_tree
133  type(hashmap_type), intent(inout) :: field_values
134  integer, intent(in) :: n
135  real(kind=default_precision), dimension(n) :: result_value
136 
137  real(kind=default_precision), dimension(n) :: left_value, right_value
138  type(data_values_type), pointer :: variable_data
139  integer :: i
140 
141  if (equation_tree%operator==terminal_op) then
142  if (conv_is_real(equation_tree%variable)) then
143  result_value=conv_to_real(equation_tree%variable)
144  else if (conv_is_integer(equation_tree%variable)) then
145  result_value=conv_to_real(conv_to_integer(equation_tree%variable))
146  else
147  variable_data=>get_data_value_by_field_name(field_values, equation_tree%variable)
148  if (size(variable_data%values) .lt. n) then
149  do i=1, n, size(variable_data%values)
150  result_value(i:i+size(variable_data%values)-1)=variable_data%values
151  end do
152  else
153  result_value=variable_data%values
154  end if
155  end if
156  else
157  left_value=execute_equation_tree(equation_tree%left, field_values, n)
158  right_value=execute_equation_tree(equation_tree%right, field_values, n)
159  if (equation_tree%operator == add_op) then
160  result_value(:)=left_value(:)+right_value(:)
161  else if (equation_tree%operator == minus_op) then
162  result_value(:)=left_value(:)-right_value(:)
163  else if (equation_tree%operator == mul_op) then
164  result_value(:)=left_value(:)*right_value(:)
165  else if (equation_tree%operator == div_op) then
166  result_value(:)=left_value(:)/right_value(:)
167  else if (equation_tree%operator == mod_op) then
168  do i=1, n
169  result_value(i)=mod(left_value(i), right_value(i))
170  end do
171  end if
172  end if
173  end function execute_equation_tree
174 
181  recursive function build_equation_tree(io_configuration, equation) result(equation_tree)
182  type(io_configuration_type), intent(inout) :: io_configuration
183  character(len=*), intent(in) :: equation
184  type(arithmetic_execution_node), pointer :: equation_tree
185 
186  integer :: split_point
187 
188  allocate(equation_tree)
189  split_point=get_location_of_least_significant_operator(equation)
190  if (split_point .gt. 0) then
191  equation_tree%operator=get_operator_representation(equation(split_point:split_point))
192  equation_tree%left=>build_equation_tree(io_configuration, equation(:split_point-1))
193  equation_tree%right=>build_equation_tree(io_configuration, equation(split_point+1:))
194  else
195  equation_tree%operator=terminal_op
196  equation_tree%variable=equation
197  call remove_character(equation_tree%variable, "(")
198  call remove_character(equation_tree%variable, ")")
199  equation_tree%variable=trim(adjustl(equation_tree%variable))
200  if (equation_tree%variable(1:1) .eq. "{" .and. &
201  equation_tree%variable(len_trim(equation_tree%variable):len_trim(equation_tree%variable)) .eq. "}") then
202  equation_tree%variable=conv_to_string(options_get_real(&
203  io_configuration%options_database, equation_tree%variable(2:len_trim(equation_tree%variable)-1)))
204  end if
205  end if
206  end function build_equation_tree
207 
211  subroutine remove_character(raw_string, c)
212  character(len=*), intent(inout) :: raw_string
213  character, intent(in) :: c
214 
215  integer :: brace_index
216 
217  brace_index=index(raw_string, c)
218  do while (brace_index .gt. 0)
219  raw_string(brace_index:brace_index)=" "
220  brace_index=index(raw_string, c)
221  end do
222  end subroutine remove_character
223 
227  character(len=*), intent(in) :: equation
228 
229  integer :: i, eq_len, location_value, op, op_val, brace_level
230 
232  location_value=999999
233  brace_level=0
234  eq_len=len(trim(equation))
235 
236  do i=eq_len, 1, -1
237  if (equation(i:i) == "(") brace_level=brace_level-1
238  if (equation(i:i) == ")") brace_level=brace_level+1
239  op=get_operator_representation(equation(i:i))
240  if (op .gt. -1) then
241  op_val=0
242  if (op == div_op) op_val=4
243  if (op == mod_op) op_val=4
244  if (op == mul_op) op_val=3
245  if (op == add_op) op_val=2
246  if (op == minus_op) op_val=1
247  op_val=op_val + (brace_level*10)
248  if (op_val .lt. location_value) then
249  location_value=op_val
251  end if
252  end if
253  end do
255 
259  integer function get_operator_representation(op_char)
260  character, intent(in) :: op_char
261 
262  if (op_char .eq. "/") then
264  else if (op_char .eq. "*") then
266  else if (op_char .eq. "-") then
268  else if (op_char .eq. "+") then
270  else if (op_char .eq. "%") then
272  else
274  end if
275  end function get_operator_representation
276 
280  type(list_type) function arithmetic_operator_get_required_fields(action_attributes)
281  type(map_type), intent(inout) :: action_attributes
282 
283  character(len=STRING_LENGTH) :: equation
284  type(arithmetic_cache_item), pointer :: cached_equation
285 
286  equation=get_action_attribute_string(action_attributes, "equation")
287  cached_equation=>find_or_add_equation(equation)
288  if (c_is_empty(cached_equation%required_fields)) then
289  cached_equation%required_fields=process_equation_to_get_required_fields(equation)
290  end if
291  arithmetic_operator_get_required_fields=cached_equation%required_fields
293 
298  type(list_type) function process_equation_to_get_required_fields(equation)
299  character(len=*), intent(in) :: equation
300 
301  character(len=STRING_LENGTH) :: str_to_write
302  character :: c
303  integer :: i, eq_length, starting_len
304 
305  eq_length=len(trim(equation))
306 
307  starting_len=1
308  do i=1, eq_length
309  c=equation(i:i)
310  if (c .eq. "/" .or. c .eq. "*" .or. c .eq. "-" .or. c .eq. "+" .or. c .eq. "(" .or. c .eq. ")" .or. c .eq. "%") then
311  if (starting_len .lt. i) then
312  str_to_write=equation(starting_len: i-1)
313  if (.not. (conv_is_real(str_to_write) .or. conv_is_integer(str_to_write) .or. str_to_write(1:1) .eq. "{")) then
314  call c_add_string(process_equation_to_get_required_fields, str_to_write)
315  end if
316  end if
317  starting_len=i+1
318  end if
319  end do
320  if (starting_len .le. eq_length) then
321  str_to_write=equation(starting_len: i-1)
322  if (.not. (conv_is_real(str_to_write) .or. conv_is_integer(str_to_write))) then
323  call c_add_string(process_equation_to_get_required_fields, str_to_write)
324  end if
325  end if
327 
332  function find_or_add_equation(equation)
333  character(len=*), intent(in) :: equation
335 
336  class(*), pointer :: generic
337 
338  find_or_add_equation=>find_equation(equation, .true.)
339  if (.not. associated(find_or_add_equation)) then
340  call check_thread_status(forthread_rwlock_wrlock(equation_cache_rwlock))
341  find_or_add_equation=>find_equation(equation, .false.)
342  if (.not. associated(find_or_add_equation)) then
343  allocate(find_or_add_equation)
344  find_or_add_equation%execution_tree=>null()
345  generic=>find_or_add_equation
346  call c_put_generic(equation_cache, equation, generic, .false.)
347  end if
348  call check_thread_status(forthread_rwlock_unlock(equation_cache_rwlock))
349  end if
350  end function find_or_add_equation
351 
356  function find_equation(equation, dolock)
357  character(len=*), intent(in) :: equation
358  type(arithmetic_cache_item), pointer :: find_equation
359  logical, intent(in) :: dolock
360 
361  class(*), pointer :: generic
362 
363  if (dolock) call check_thread_status(forthread_rwlock_rdlock(equation_cache_rwlock))
364  generic=>c_get_generic(equation_cache, equation)
365  if (dolock) call check_thread_status(forthread_rwlock_unlock(equation_cache_rwlock))
366  if (associated(generic)) then
367  select type(generic)
368  type is (arithmetic_cache_item)
369  find_equation=>generic
370  end select
371  else
372  find_equation=>null()
373  end if
374  end function find_equation
375 end module arithmetic_operator_mod
logging_mod::log_error
integer, parameter, public log_error
Only log ERROR messages.
Definition: logging.F90:11
conversions_mod
Conversion between common inbuilt FORTRAN data types.
Definition: conversions.F90:5
collections_mod::map_type
Map data structure that holds string (length 20 maximum) key value pairs.
Definition: collections.F90:86
collections_mod::c_is_empty
Returns whether a collection is empty.
Definition: collections.F90:437
arithmetic_operator_mod::perform_arithmetic_operator
subroutine, public perform_arithmetic_operator(io_configuration, field_values, action_attributes, source_monc_location, source_monc, operator_result_values)
Executes this arithmetic operator by attempting to retrieved the cached equation (and creates one if ...
Definition: arithmetic-operator.F90:66
collections_mod::c_put_generic
Puts a generic key-value pair into the map.
Definition: collections.F90:305
conversions_mod::conv_to_integer
Converts data types to integers.
Definition: conversions.F90:49
data_utils_mod
Contains functionality for managing and extracting data from the raw data dumps that the IO server re...
Definition: datautils.F90:3
arithmetic_operator_mod::arithmetic_execution_node
Definition: arithmetic-operator.F90:28
collections_mod
Collection data structures.
Definition: collections.F90:7
collections_mod::c_get_string
Gets a specific string element out of the list, stack, queue or map with the corresponding key.
Definition: collections.F90:388
optionsdatabase_mod::options_get_integer
integer function, public options_get_integer(options_database, key, index)
Retrieves an integer value from the database that matches the provided key.
Definition: optionsdatabase.F90:217
arithmetic_operator_mod::minus_op
integer, parameter minus_op
Definition: arithmetic-operator.F90:25
arithmetic_operator_mod::equation_cache
type(hashmap_type), volatile equation_cache
Definition: arithmetic-operator.F90:40
collections_mod::c_has_next
Definition: collections.F90:586
arithmetic_operator_mod::execute_equation_tree
recursive real(kind=default_precision) function, dimension(n) execute_equation_tree(equation_tree, field_values, n)
Executes an equation tree by doing a post order traversal of the tree. If a node is a terminal then e...
Definition: arithmetic-operator.F90:132
collections_mod::hashmap_type
A hashmap structure, the same as a map but uses hashing for greatly improved performance when storing...
Definition: collections.F90:94
forthread_mod
Definition: forthread.F90:1
logging_mod::log_log
subroutine, public log_log(level, message, str)
Logs a message at the specified level. If the level is above the current level then the message is ig...
Definition: logging.F90:75
forthread_mod::forthread_rwlock_destroy
integer function forthread_rwlock_destroy(rwlock_id)
Definition: forthread.F90:495
arithmetic_operator_mod::initialise_arithmetic_operator
subroutine, public initialise_arithmetic_operator()
Initialises this operator.
Definition: arithmetic-operator.F90:49
arithmetic_operator_mod::mod_op
integer, parameter mod_op
A specific node in the execution tree.
Definition: arithmetic-operator.F90:25
collections_mod::c_get_generic
Gets a specific generic element out of the list, stack, queue or map with the corresponding key.
Definition: collections.F90:367
optionsdatabase_mod::options_get_string
character(len=string_length) function, public options_get_string(options_database, key, index)
Retrieves a string value from the database that matches the provided key.
Definition: optionsdatabase.F90:280
arithmetic_operator_mod::remove_character
subroutine remove_character(raw_string, c)
Removes all occurances of a character from a string in situ by replacing it with whitespace.
Definition: arithmetic-operator.F90:212
threadpool_mod
This is a thread pool and the single management "main" thread will spawn out free threads in the pool...
Definition: threadpool.F90:5
threadpool_mod::check_thread_status
subroutine, public check_thread_status(ierr)
Checks the error status of any thread operation and reports an error if it failed.
Definition: threadpool.F90:229
arithmetic_operator_mod::div_op
integer, parameter div_op
Definition: arithmetic-operator.F90:25
optionsdatabase_mod::options_has_key
logical function, public options_has_key(options_database, key)
Determines whether a specific key is in the database.
Definition: optionsdatabase.F90:76
arithmetic_operator_mod::build_equation_tree
recursive type(arithmetic_execution_node) function, pointer build_equation_tree(io_configuration, equation)
Builds the equation tree, this searches for the least significant operator and then splits the equati...
Definition: arithmetic-operator.F90:182
conversions_mod::conv_to_string
Converts data types to strings.
Definition: conversions.F90:38
arithmetic_operator_mod::find_equation
type(arithmetic_cache_item) function, pointer find_equation(equation, dolock)
Finds an equation in the cache based upon its textual equation representation or returns null if none...
Definition: arithmetic-operator.F90:357
collections_mod::iterator_type
Definition: collections.F90:51
arithmetic_operator_mod::process_equation_to_get_required_fields
type(list_type) function process_equation_to_get_required_fields(equation)
Performs text processing on an equation to extract out all the required variable (fields) needed in o...
Definition: arithmetic-operator.F90:299
arithmetic_operator_mod::finalise_arithmetic_operator
subroutine, public finalise_arithmetic_operator()
Finalises this opertor.
Definition: arithmetic-operator.F90:54
conversions_mod::conv_is_real
Determines whether a data item can be represented as a real or not.
Definition: conversions.F90:91
forthread_mod::forthread_rwlock_init
integer function forthread_rwlock_init(rwlock_id, attr_id)
Definition: forthread.F90:504
configuration_parser_mod::io_configuration_type
Overall IO configuration.
Definition: configurationparser.F90:104
conversions_mod::conv_is_integer
Determines whether a data item can be represented as an integer or not.
Definition: conversions.F90:81
arithmetic_operator_mod::get_size_of_data_being_operated_on
integer function get_size_of_data_being_operated_on(cached_equation, field_values)
Retrieves the number of data elements that this will operate on. It will produce a log error if any v...
Definition: arithmetic-operator.F90:92
configuration_parser_mod::get_data_value_by_field_name
Definition: configurationparser.F90:30
arithmetic_operator_mod::get_operator_representation
integer function get_operator_representation(op_char)
Given a character representation of an operator this returns the internal numeric type representation...
Definition: arithmetic-operator.F90:260
logging_mod
Logging utility.
Definition: logging.F90:2
arithmetic_operator_mod::arithmetic_operator_get_required_fields
type(list_type) function, public arithmetic_operator_get_required_fields(action_attributes)
Retrieves the list of fields needed by this operator for a specific configuration.
Definition: arithmetic-operator.F90:281
datadefn_mod
Contains common definitions for the data and datatypes used by MONC.
Definition: datadefn.F90:2
configuration_parser_mod::data_values_type
Definition: configurationparser.F90:34
arithmetic_operator_mod::find_or_add_equation
type(arithmetic_cache_item) function, pointer find_or_add_equation(equation)
Locates an existing equation in the cache based upon the textual equation representation or creates a...
Definition: arithmetic-operator.F90:333
datadefn_mod::string_length
integer, parameter, public string_length
Default length of strings.
Definition: datadefn.F90:10
collections_mod::c_get_iterator
Definition: collections.F90:581
collections_mod::list_type
List data structure which implements a doubly linked list. This list will preserve its order.
Definition: collections.F90:60
arithmetic_operator_mod::get_location_of_least_significant_operator
integer function get_location_of_least_significant_operator(equation)
Given an equation this will retrieve the location of the least significant operator in that equation ...
Definition: arithmetic-operator.F90:227
arithmetic_operator_mod::equation_cache_rwlock
integer, volatile equation_cache_rwlock
Definition: arithmetic-operator.F90:41
arithmetic_operator_mod::arithmetic_cache_item
Definition: arithmetic-operator.F90:35
arithmetic_operator_mod::add_op
integer, parameter add_op
Definition: arithmetic-operator.F90:25
collections_mod::c_next_string
Definition: collections.F90:594
forthread_mod::forthread_rwlock_wrlock
integer function forthread_rwlock_wrlock(lock_id)
Definition: forthread.F90:532
conversions_mod::conv_to_real
Converts data types to real.
Definition: conversions.F90:60
forthread_mod::forthread_rwlock_rdlock
integer function forthread_rwlock_rdlock(lock_id)
Definition: forthread.F90:514
arithmetic_operator_mod::terminal_op
integer, parameter terminal_op
Definition: arithmetic-operator.F90:25
arithmetic_operator_mod
The arithmetic operator which allows the user to define arithmetic formulas based on fields and const...
Definition: arithmetic-operator.F90:6
collections_mod::c_add_string
Adds a string to the end of the list.
Definition: collections.F90:222
optionsdatabase_mod
Manages the options database. Contains administration functions and deduce runtime options from the c...
Definition: optionsdatabase.F90:7
configuration_parser_mod
Parses the XML configuration file to produce the io configuration description which contains the data...
Definition: configurationparser.F90:3
forthread_mod::forthread_rwlock_unlock
integer function forthread_rwlock_unlock(lock_id)
Definition: forthread.F90:550
data_utils_mod::get_action_attribute_string
character(len=string_length) function, public get_action_attribute_string(action_attributes, field_name)
Retrieves the name of a field from the attributes specified in the configuration.
Definition: datautils.F90:101
optionsdatabase_mod::options_get_real
real(kind=default_precision) function, public options_get_real(options_database, key, index)
Retrieves a real value from the database that matches the provided key.
Definition: optionsdatabase.F90:91
datadefn_mod::default_precision
integer, parameter, public default_precision
MPI communication type which we use for the prognostic and calculation data.
Definition: datadefn.F90:17
arithmetic_operator_mod::mul_op
integer, parameter mul_op
Definition: arithmetic-operator.F90:25