MONC
Functions/Subroutines
fieldcoarsener_operator_mod Module Reference

Coarsens a field by selecting data with a specific period in any number of dimensions. More...

Functions/Subroutines

integer function, public fieldcoarsener_operator_get_auto_size (io_configuration, auto_dimension, action_attributes)
 Retrieves the size of an auto dimension based upon the work that will be completed here. More...
 
subroutine, public perform_fieldcoarsener_operator (io_configuration, field_values, action_attributes, source_monc_location, source_monc, operator_result_values)
 Performs the field coarsener operator on a specific field. More...
 
integer function locate_dimension (dimension_id, list_of_dims)
 Locates a dimension in a list of dimensions or 0 if none can be found. More...
 
subroutine determine_dimension_bounds (corresponding_field_definition, registered_monc_info, dimensions_to_slice, indexes_to_slice, dim_weights, dim_periods, dim_starts, number_dims, sliced_size)
 Determines the dimension bounds which are used in the slicing. More...
 
subroutine get_dimensions_and_indexes_to_slice (str_dim_to_slice, str_index_to_slice, dimensions_to_slice, indexes_to_slice)
 Retrieves the dimensions and indexes to slice from the strings provided in configuration. More...
 
integer function get_occurances_of_character (source_str, search_char)
 Retrieves the number of occurances of a character in a source string. More...
 
type(list_type) function, public fieldcoarsener_operator_get_required_fields (action_attributes)
 Retrieves a list of the required fields for running this operator. More...
 
integer function convert_dimension_str_to_id (dim_str)
 Converts a dimension string to the corresponding numeric ID. More...
 
integer function get_entire_dimension_size (io_configuration, dimension_name)
 Looks up the global size of a dimension based upon its name. More...
 

Detailed Description

Coarsens a field by selecting data with a specific period in any number of dimensions.

Function/Subroutine Documentation

◆ convert_dimension_str_to_id()

integer function fieldcoarsener_operator_mod::convert_dimension_str_to_id ( character(len=*), intent(in)  dim_str)
private

Converts a dimension string to the corresponding numeric ID.

Parameters
dim_strThe dimension string
Returns
The corresponding numeric dimension ID

Definition at line 254 of file fieldcoarsener-operator.F90.

255  character(len=*), intent(in) :: dim_str
256 
257  if (dim_str .eq. "x") then
258  convert_dimension_str_to_id=x_index
259  else if (dim_str .eq. "y") then
260  convert_dimension_str_to_id=y_index
261  else if (dim_str .eq. "z") then
262  convert_dimension_str_to_id=z_index
263  else
264  call log_log(log_error, "Can not translate dimension "//trim(dim_str))
265  end if
Here is the caller graph for this function:

◆ determine_dimension_bounds()

subroutine fieldcoarsener_operator_mod::determine_dimension_bounds ( type(io_configuration_field_type), intent(in)  corresponding_field_definition,
type(io_configuration_registered_monc_type), intent(in)  registered_monc_info,
integer, dimension(:), intent(in)  dimensions_to_slice,
integer, dimension(:), intent(in)  indexes_to_slice,
integer, dimension(:), intent(out), allocatable  dim_weights,
integer, dimension(:), intent(out), allocatable  dim_periods,
integer, dimension(:), intent(out), allocatable  dim_starts,
integer, intent(out)  number_dims,
integer, intent(out)  sliced_size 
)
private

Determines the dimension bounds which are used in the slicing.

Parameters
corresponding_field_definitionThe definition of the field that is being sliced
registered_monc_infoThis specific MONC process
dimensions_to_sliceNumeric code for the dimensions that should be sliced
indexes_to_sliceThe indexes that we are slicing upon
dim_weightsOutput weight for each dimension when dealing with a 1D data
dim_periodsThe periods that we jump over in the data to grab the next source point
dim_startsThe local start point in data
number_dimsOutput number of dimensions that the field comprises of
sliced_sizeOutput overall 1D data size of the sliced array

Definition at line 126 of file fieldcoarsener-operator.F90.

128  type(io_configuration_field_type), intent(in) :: corresponding_field_definition
129  type(io_configuration_registered_monc_type), intent(in) :: registered_monc_info
130  integer, dimension(:), intent(in) :: dimensions_to_slice, indexes_to_slice
131  integer, dimension(:), allocatable, intent(out) :: dim_weights, dim_periods, dim_starts
132  integer, intent(out) :: number_dims, sliced_size
133 
134  integer :: i, j, dimension_id, amount_to_add, located_dim
135  integer, dimension(:), allocatable :: dim_sizes
136  logical, dimension(:), allocatable :: found_slice_field
137 
138  number_dims=corresponding_field_definition%dimensions
139  allocate(dim_sizes(number_dims), dim_weights(number_dims), dim_periods(number_dims), dim_starts(number_dims),&
140  found_slice_field(size(dimensions_to_slice)))
141  found_slice_field=.false.
142 
143  do i=1, number_dims
144  dimension_id=convert_dimension_str_to_id(corresponding_field_definition%dim_size_defns(i))
145  located_dim=locate_dimension(dimension_id, dimensions_to_slice)
146  if (located_dim .gt. 0) then
147  dim_periods(i)=indexes_to_slice(located_dim)
148  if (registered_monc_info%local_dim_starts(dimension_id) == 1) then
149  dim_starts(i)=1
150  else
151  dim_starts(i)=dim_periods(i) - mod(registered_monc_info%local_dim_starts(dimension_id)-2, dim_periods(i))
152  end if
153  dim_sizes(i)=ceiling(real(registered_monc_info%local_dim_sizes(dimension_id) - (dim_starts(i)-1))/&
154  real(indexes_to_slice(located_dim)))
155  found_slice_field(located_dim)=.true.
156  else
157  dim_sizes(i)=registered_monc_info%local_dim_sizes(dimension_id)
158  dim_periods(i)=1
159  dim_starts(i)=1
160  end if
161  end do
162  do i=1, size(found_slice_field)
163  if (.not. found_slice_field(i)) call log_log(log_error, "Can not find a dimension to slice in provided field")
164  end do
165  sliced_size=0
166  do i=1, number_dims
167  amount_to_add=1
168  dim_weights(i)=1
169  do j=1, i
170  if (j .lt. i) dim_weights(i)=dim_weights(i)*registered_monc_info%local_dim_sizes(j)
171  amount_to_add=amount_to_add*dim_sizes(j)
172  end do
173  sliced_size=sliced_size+amount_to_add
174  end do
175  deallocate(dim_sizes, found_slice_field)
Here is the call graph for this function:
Here is the caller graph for this function:

◆ fieldcoarsener_operator_get_auto_size()

integer function, public fieldcoarsener_operator_mod::fieldcoarsener_operator_get_auto_size ( type(io_configuration_type), intent(inout)  io_configuration,
character(len=*), intent(in)  auto_dimension,
type(map_type), intent(inout)  action_attributes 
)

Retrieves the size of an auto dimension based upon the work that will be completed here.

Parameters
io_configurationThe IO server configuration
auto_dimensionString of the auto dimension to look up
action_attributesThe XML configuration attributes
Returns
The size of an auto dimension

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

26  type(io_configuration_type), intent(inout) :: io_configuration
27  character(len=*), intent(in) :: auto_dimension
28  type(map_type), intent(inout) :: action_attributes
29 
30  integer :: auto_dim_id, index_of_match, entire_dim_size
31  integer, dimension(:), allocatable :: dimensions_to_slice, indexes_to_slice
32 
33  auto_dim_id=convert_dimension_str_to_id(auto_dimension)
34  call get_dimensions_and_indexes_to_slice(get_action_attribute_string(action_attributes, "dimension"), &
35  get_action_attribute_string(action_attributes, "period"), dimensions_to_slice, indexes_to_slice)
36  index_of_match=locate_dimension(auto_dim_id, dimensions_to_slice)
37  if (index_of_match .ne. 0) then
38  entire_dim_size=get_entire_dimension_size(io_configuration, auto_dimension)
39  fieldcoarsener_operator_get_auto_size=ceiling(real(entire_dim_size)/indexes_to_slice(index_of_match))
40  else
41  fieldcoarsener_operator_get_auto_size=-1
42  end if
43  deallocate(dimensions_to_slice, indexes_to_slice)
Here is the call graph for this function:

◆ fieldcoarsener_operator_get_required_fields()

type(list_type) function, public fieldcoarsener_operator_mod::fieldcoarsener_operator_get_required_fields ( type(map_type), intent(inout)  action_attributes)

Retrieves a list of the required fields for running this operator.

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

Definition at line 242 of file fieldcoarsener-operator.F90.

243  type(map_type), intent(inout) :: action_attributes
244 
245  character(len=STRING_LENGTH) :: field_to_slice
246 
247  field_to_slice=get_action_attribute_string(action_attributes, "field")
248  call c_add_string(fieldcoarsener_operator_get_required_fields, field_to_slice)
Here is the call graph for this function:

◆ get_dimensions_and_indexes_to_slice()

subroutine fieldcoarsener_operator_mod::get_dimensions_and_indexes_to_slice ( character(len=*), intent(in)  str_dim_to_slice,
character(len=*), intent(in)  str_index_to_slice,
integer, dimension(:), intent(out), allocatable  dimensions_to_slice,
integer, dimension(:), intent(out), allocatable  indexes_to_slice 
)
private

Retrieves the dimensions and indexes to slice from the strings provided in configuration.

Parameters
str_dim_to_sliceThe string dimensions that we are going to slice
str_index_to_sliceThe string indexes that we are going to slice
dimensions_to_sliceNumeric corresponding codes for the dimensions to slice
indexes_to_sliceNumeric corresponding codes for the indexes to slice

Definition at line 183 of file fieldcoarsener-operator.F90.

184  character(len=*), intent(in) :: str_dim_to_slice, str_index_to_slice
185  integer, dimension(:), allocatable, intent(out) :: dimensions_to_slice, indexes_to_slice
186 
187  integer :: num_dims, num_indexes, i, dim_idx, index_idx, idx
188  num_dims=get_occurances_of_character(str_dim_to_slice, ",")+1
189  num_indexes=get_occurances_of_character(str_index_to_slice, ",")+1
190  if (num_dims .ne. num_indexes) then
191  call log_log(log_error, "Coarsening number of dimensions and indexes must match")
192  end if
193  allocate(dimensions_to_slice(num_dims), indexes_to_slice(num_indexes))
194  dim_idx=1
195  index_idx=1
196  do i=1, num_dims
197  idx=index(str_dim_to_slice(dim_idx:), ",")
198  idx=idx-1
199  if (idx == -1) then
200  idx=len_trim(str_dim_to_slice)
201  else
202  idx=idx+(dim_idx-1)
203  end if
204  dimensions_to_slice(i)=convert_dimension_str_to_id(str_dim_to_slice(dim_idx:idx))
205  dim_idx=idx+2
206 
207  idx=index(str_index_to_slice(index_idx:), ",")
208  idx=idx-1
209  if (idx == -1) then
210  idx=len_trim(str_index_to_slice)
211  else
212  idx=idx+(index_idx-1)
213  end if
214  indexes_to_slice(i)=conv_to_integer(str_index_to_slice(index_idx:idx))
215  index_idx=idx+2
216  end do
Here is the call graph for this function:
Here is the caller graph for this function:

◆ get_entire_dimension_size()

integer function fieldcoarsener_operator_mod::get_entire_dimension_size ( type(io_configuration_type), intent(inout)  io_configuration,
character(len=string_length), intent(in)  dimension_name 
)
private

Looks up the global size of a dimension based upon its name.

Parameters
io_configurationThe IO server configuration
dimension_nameThe name of the dimension that we are looking up
Returns
The global size of this dimension

Definition at line 272 of file fieldcoarsener-operator.F90.

273  type(io_configuration_type), intent(inout) :: io_configuration
274  character(len=STRING_LENGTH), intent(in) :: dimension_name
275 
276  get_entire_dimension_size=c_get_integer(io_configuration%dimension_sizing, dimension_name)
Here is the caller graph for this function:

◆ get_occurances_of_character()

integer function fieldcoarsener_operator_mod::get_occurances_of_character ( character(len=*), intent(in)  source_str,
character(len=*), intent(in)  search_char 
)
private

Retrieves the number of occurances of a character in a source string.

Parameters
source_strThe source string to search
search_charThe character that we are searching for
Returns
The number of occurances

Definition at line 223 of file fieldcoarsener-operator.F90.

224  character(len=*), intent(in) :: source_str, search_char
225 
226  integer :: i, n, idx
227 
228  get_occurances_of_character=0
229  n=len_trim(source_str)
230  i=1
231  do while (i .le. n)
232  idx=index(source_str(i:), search_char)
233  if (idx == 0) exit
234  i=i+idx+1
235  get_occurances_of_character=get_occurances_of_character+1
236  end do
Here is the caller graph for this function:

◆ locate_dimension()

integer function fieldcoarsener_operator_mod::locate_dimension ( integer, intent(in)  dimension_id,
integer, dimension(:), intent(in)  list_of_dims 
)
private

Locates a dimension in a list of dimensions or 0 if none can be found.

Parameters
dimension_idThe id to look up
list_of_dimsThe list of dimensions to check
Theindex that this dimension resides at or 0 if it is not found

Definition at line 102 of file fieldcoarsener-operator.F90.

103  integer, intent(in) :: dimension_id, list_of_dims(:)
104 
105  integer :: i
106 
107  do i=1, size(list_of_dims)
108  if (list_of_dims(i) == dimension_id) then
109  locate_dimension=i
110  return
111  end if
112  end do
113  locate_dimension=0
Here is the caller graph for this function:

◆ perform_fieldcoarsener_operator()

subroutine, public fieldcoarsener_operator_mod::perform_fieldcoarsener_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 
)

Performs the field coarsener operator on a specific field.

Parameters
io_configurationThe IO server configuration
field_valuesThe field values
action_attributesAttributes associated with the running of this operator
source_monc_locationThe location in configuration data of MONC settings
source_moncProcess ID of the MONC that sent this data
operator_result_valuesThe resulting value or left unallocated if none are appropriate

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

55  type(io_configuration_type), intent(inout) :: io_configuration
56  type(hashmap_type), intent(inout) :: field_values
57  type(map_type), intent(inout) :: action_attributes
58  integer, intent(in) :: source_monc_location, source_monc
59  real(kind=default_precision), dimension(:), allocatable, intent(inout) :: operator_result_values
60 
61  character(len=STRING_LENGTH) :: field_to_slice
62  integer, dimension(:), allocatable :: dimensions_to_slice, indexes_to_slice, dim_weights, dim_periods, dim_starts, indexes
63  integer :: number_dims, sliced_size, i, j, source_dim
64  type(io_configuration_field_type) :: corresponding_field_definition
65  type(data_values_type), pointer :: field_local_values
66 
67  field_to_slice=get_action_attribute_string(action_attributes, "field")
68  ! NSE
69  if (get_prognostic_field_configuration(io_configuration, field_to_slice, "", corresponding_field_definition)) then
70  call get_dimensions_and_indexes_to_slice(get_action_attribute_string(action_attributes, "dimension"), &
71  get_action_attribute_string(action_attributes, "period"), dimensions_to_slice, indexes_to_slice)
72 
73  call determine_dimension_bounds(corresponding_field_definition, io_configuration%registered_moncs(source_monc_location), &
74  dimensions_to_slice, indexes_to_slice, dim_weights, dim_periods, dim_starts, number_dims, sliced_size)
75 
76  field_local_values=>get_data_value_by_field_name(field_values, field_to_slice)
77 
78  allocate(operator_result_values(sliced_size), indexes(number_dims))
79  indexes=dim_starts
80  do i=1, sliced_size
81  source_dim=1
82  do j=1, number_dims
83  source_dim=source_dim+(indexes(j)-1)*dim_weights(j)
84  end do
85  operator_result_values(i)=field_local_values%values(source_dim)
86  indexes(1)=indexes(1)+dim_periods(1)
87  do j=1, number_dims
88  if (indexes(j) .gt. io_configuration%registered_moncs(source_monc_location)%local_dim_sizes(j)) then
89  indexes(j)=1
90  if (j .lt. number_dims) indexes(j+1)=indexes(j+1)+dim_periods(j+1)
91  end if
92  end do
93  end do
94  deallocate(dimensions_to_slice, indexes_to_slice, dim_weights, dim_periods, indexes, dim_starts)
95  end if
Here is the call graph for this function:
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