MONC
Data Types | Functions/Subroutines | Variables
arithmetic_operator_mod Module Reference

The arithmetic operator which allows the user to define arithmetic formulas based on fields and constants which are then executed BDMAS style. This works by parsing the text forumula into an execution tree which is walked in order to perform the final result. Building the tree is the potentially expensive aspect of this, so built trees are cached as it is likely that the equation will be run many times. Currently this is expressed in terms of scalars, and it will operate on all elements of the data. More...

Data Types

type  arithmetic_cache_item
 
type  arithmetic_execution_node
 

Functions/Subroutines

subroutine, public initialise_arithmetic_operator ()
 Initialises this operator. More...
 
subroutine, public finalise_arithmetic_operator ()
 Finalises this opertor. More...
 
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 not found.) If there is no execution tree it then parses the equation into an execution tree and stores it. The stored execution tree is then executed and the real result returned. More...
 
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 variable lengths are inconsistent. More...
 
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 either the variable is looked up for its value or the constant is returned. If a node is a non terminal then the operator is performed on the result value of its left and right subtrees and the value returned. More...
 
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 equation based upon that. Each sub equation is then passed to recursive calls of this function which return subtrees for these aspects. Some string manipulation is done to remove braces which would otherwise be included in the terminal characters. More...
 
subroutine remove_character (raw_string, c)
 Removes all occurances of a character from a string in situ by replacing it with whitespace. More...
 
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 or 0 if no operator is found (i.e. the string is a terminal.) This takes account of parenthesis. More...
 
integer function get_operator_representation (op_char)
 Given a character representation of an operator this returns the internal numeric type representation of it. More...
 
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. More...
 
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 order to run this equation and get the result. Note this ignores all values which are constants (reals or integers) More...
 
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 new entry and returns this one. More...
 
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 is found. More...
 

Variables

integer, parameter terminal_op =0
 
integer, parameter add_op =1
 
integer, parameter minus_op =2
 
integer, parameter mul_op =3
 
integer, parameter div_op =4
 
integer, parameter mod_op =5
 A specific node in the execution tree. More...
 
type(hashmap_type), volatile equation_cache
 
integer, volatile equation_cache_rwlock
 

Detailed Description

The arithmetic operator which allows the user to define arithmetic formulas based on fields and constants which are then executed BDMAS style. This works by parsing the text forumula into an execution tree which is walked in order to perform the final result. Building the tree is the potentially expensive aspect of this, so built trees are cached as it is likely that the equation will be run many times. Currently this is expressed in terms of scalars, and it will operate on all elements of the data.

Function/Subroutine Documentation

◆ arithmetic_operator_get_required_fields()

type(list_type) function, public arithmetic_operator_mod::arithmetic_operator_get_required_fields ( type(map_type), intent(inout)  action_attributes)

Retrieves the list of fields needed by this operator for a specific configuration.

Parameters
action_attributesThe attributes which configure the operator
Returns
A list of required fields before the operator can run

Definition at line 280 of file arithmetic-operator.F90.

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
Here is the call graph for this function:

◆ build_equation_tree()

recursive type(arithmetic_execution_node) function, pointer arithmetic_operator_mod::build_equation_tree ( type(io_configuration_type), intent(inout)  io_configuration,
character(len=*), intent(in)  equation 
)
private

Builds the equation tree, this searches for the least significant operator and then splits the equation based upon that. Each sub equation is then passed to recursive calls of this function which return subtrees for these aspects. Some string manipulation is done to remove braces which would otherwise be included in the terminal characters.

Parameters
io_configurationConfiguration of the IO server
equationThe equation to represent as a tree
Returns
The equation tree which represents the provided equation

Definition at line 181 of file arithmetic-operator.F90.

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
Here is the call graph for this function:
Here is the caller graph for this function:

◆ execute_equation_tree()

recursive real(kind=default_precision) function, dimension(n) arithmetic_operator_mod::execute_equation_tree ( type(arithmetic_execution_node), intent(inout), pointer  equation_tree,
type(hashmap_type), intent(inout)  field_values,
integer, intent(in)  n 
)
private

Executes an equation tree by doing a post order traversal of the tree. If a node is a terminal then either the variable is looked up for its value or the constant is returned. If a node is a non terminal then the operator is performed on the result value of its left and right subtrees and the value returned.

Parameters
equation_treeThe equation tree to traverse
field_valuesThe variable value key value pair
Returns
A real result from traversing this equation tree

Definition at line 131 of file arithmetic-operator.F90.

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
Here is the caller graph for this function:

◆ finalise_arithmetic_operator()

subroutine, public arithmetic_operator_mod::finalise_arithmetic_operator

Finalises this opertor.

Definition at line 53 of file arithmetic-operator.F90.

54  call check_thread_status(forthread_rwlock_destroy(equation_cache_rwlock))
Here is the call graph for this function:

◆ find_equation()

type(arithmetic_cache_item) function, pointer arithmetic_operator_mod::find_equation ( character(len=*), intent(in)  equation,
logical, intent(in)  dolock 
)
private

Finds an equation in the cache based upon its textual equation representation or returns null if none is found.

Parameters
equationTextual equation that we are looking up
dolockWhether to issue a read lock which accessing the collection
Returns
Cached entry for the equation or null if none is found

Definition at line 356 of file arithmetic-operator.F90.

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
Here is the caller graph for this function:

◆ find_or_add_equation()

type(arithmetic_cache_item) function, pointer arithmetic_operator_mod::find_or_add_equation ( character(len=*), intent(in)  equation)
private

Locates an existing equation in the cache based upon the textual equation representation or creates a new entry and returns this one.

Parameters
equationTextual equation that we are looking up
Returns
Cached entry for the equation

Definition at line 332 of file arithmetic-operator.F90.

333  character(len=*), intent(in) :: equation
334  type(arithmetic_cache_item), pointer :: find_or_add_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
Here is the call graph for this function:
Here is the caller graph for this function:

◆ get_location_of_least_significant_operator()

integer function arithmetic_operator_mod::get_location_of_least_significant_operator ( character(len=*), intent(in)  equation)
private

Given an equation this will retrieve the location of the least significant operator in that equation or 0 if no operator is found (i.e. the string is a terminal.) This takes account of parenthesis.

Definition at line 226 of file arithmetic-operator.F90.

227  character(len=*), intent(in) :: equation
228 
229  integer :: i, eq_len, location_value, op, op_val, brace_level
230 
231  get_location_of_least_significant_operator=0
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
250  get_location_of_least_significant_operator=i
251  end if
252  end if
253  end do
Here is the call graph for this function:
Here is the caller graph for this function:

◆ get_operator_representation()

integer function arithmetic_operator_mod::get_operator_representation ( character, intent(in)  op_char)
private

Given a character representation of an operator this returns the internal numeric type representation of it.

Parameters
op_charThe character operator representation
Returns
The numeric internal type of this operator or -1 if none can be found

Definition at line 259 of file arithmetic-operator.F90.

260  character, intent(in) :: op_char
261 
262  if (op_char .eq. "/") then
263  get_operator_representation=div_op
264  else if (op_char .eq. "*") then
265  get_operator_representation=mul_op
266  else if (op_char .eq. "-") then
267  get_operator_representation=minus_op
268  else if (op_char .eq. "+") then
269  get_operator_representation=add_op
270  else if (op_char .eq. "%") then
271  get_operator_representation=mod_op
272  else
273  get_operator_representation=-1
274  end if
Here is the caller graph for this function:

◆ get_size_of_data_being_operated_on()

integer function arithmetic_operator_mod::get_size_of_data_being_operated_on ( type(arithmetic_cache_item), intent(inout)  cached_equation,
type(hashmap_type), intent(inout)  field_values 
)
private

Retrieves the number of data elements that this will operate on. It will produce a log error if any variable lengths are inconsistent.

Parameters
cached_equationThe cached equation information
field_valuesThe variable value key value pair
Returns
The number of data elements being operated on

Definition at line 91 of file arithmetic-operator.F90.

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 
99  get_size_of_data_being_operated_on=-1
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
111  prev_size=get_size_of_data_being_operated_on
112  get_size_of_data_being_operated_on=temp_size
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
Here is the call graph for this function:
Here is the caller graph for this function:

◆ initialise_arithmetic_operator()

subroutine, public arithmetic_operator_mod::initialise_arithmetic_operator

Initialises this operator.

Definition at line 48 of file arithmetic-operator.F90.

49  call check_thread_status(forthread_rwlock_init(equation_cache_rwlock, -1))
Here is the call graph for this function:

◆ perform_arithmetic_operator()

subroutine, public arithmetic_operator_mod::perform_arithmetic_operator ( type(io_configuration_type), intent(inout)  io_configuration,
type(hashmap_type), intent(inout)  field_values,
type(map_type), intent(inout)  action_attributes,
integer, intent(in)  source_monc_location,
integer, intent(in)  source_monc,
real(kind=default_precision), dimension(:), intent(inout), allocatable  operator_result_values 
)

Executes this arithmetic operator by attempting to retrieved the cached equation (and creates one if not found.) If there is no execution tree it then parses the equation into an execution tree and stores it. The stored execution tree is then executed and the real result returned.

Parameters
io_configurationConfiguration of the IO server
field_valuesThe field values
action_attributesAttributes associated with the running of this operator
Returns
The resulting value

Definition at line 64 of file arithmetic-operator.F90.

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)
Here is the call graph for this function:

◆ process_equation_to_get_required_fields()

type(list_type) function arithmetic_operator_mod::process_equation_to_get_required_fields ( character(len=*), intent(in)  equation)
private

Performs text processing on an equation to extract out all the required variable (fields) needed in order to run this equation and get the result. Note this ignores all values which are constants (reals or integers)

Parameters
equationText equation to extract list of required fields (variables) from
Returns
A list of variables needed by this equation

Definition at line 298 of file arithmetic-operator.F90.

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
Here is the caller graph for this function:

◆ remove_character()

subroutine arithmetic_operator_mod::remove_character ( character(len=*), intent(inout)  raw_string,
character, intent(in)  c 
)
private

Removes all occurances of a character from a string in situ by replacing it with whitespace.

Parameters
raw_stringThe string to process and remove characters from in place
cThe character to search for and remove (replace by whitespace)

Definition at line 211 of file arithmetic-operator.F90.

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
Here is the caller graph for this function:

Variable Documentation

◆ add_op

integer, parameter arithmetic_operator_mod::add_op =1
private

Definition at line 25 of file arithmetic-operator.F90.

◆ div_op

integer, parameter arithmetic_operator_mod::div_op =4
private

Definition at line 25 of file arithmetic-operator.F90.

◆ equation_cache

type(hashmap_type), volatile arithmetic_operator_mod::equation_cache
private

Definition at line 40 of file arithmetic-operator.F90.

40  type(hashmap_type), volatile :: equation_cache

◆ equation_cache_rwlock

integer, volatile arithmetic_operator_mod::equation_cache_rwlock
private

Definition at line 41 of file arithmetic-operator.F90.

41  integer, volatile :: equation_cache_rwlock

◆ minus_op

integer, parameter arithmetic_operator_mod::minus_op =2
private

Definition at line 25 of file arithmetic-operator.F90.

◆ mod_op

integer, parameter arithmetic_operator_mod::mod_op =5
private

A specific node in the execution tree.

Definition at line 25 of file arithmetic-operator.F90.

◆ mul_op

integer, parameter arithmetic_operator_mod::mul_op =3
private

Definition at line 25 of file arithmetic-operator.F90.

◆ terminal_op

integer, parameter arithmetic_operator_mod::terminal_op =0
private

Definition at line 25 of file arithmetic-operator.F90.

25  integer, parameter :: TERMINAL_OP=0, add_op=1, minus_op=2, mul_op=3, div_op=4, mod_op=5
logging_mod::log_error
integer, parameter, public log_error
Only log ERROR messages.
Definition: logging.F90:11
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
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