MONC
randomnoise.F90
Go to the documentation of this file.
1 
6  use grids_mod, only : z_index, y_index, x_index
11 
12  implicit none
13 
14 #ifndef TEST_MODE
15  private
16 #endif
17 
18  integer, parameter :: max_size_seed_array=256, i_seed=7, isd=1
19 
21 contains
22 
26  randomnoise_get_descriptor%name="randomnoise"
27  randomnoise_get_descriptor%version=0.1
29  end function randomnoise_get_descriptor
30 
33  subroutine initialisation_callback(current_state)
34  type(model_state_type), target, intent(inout) :: current_state
35 
36  integer, dimension(MAX_SIZE_SEED_ARRAY) :: iranseed
37  real(kind=default_precision), dimension(:,:,:), allocatable :: randarr
38  real(kind=default_precision) :: random_num
39 
40  integer :: nq_rand ! The number of q fields to add noise to
41  integer :: nzq ! The number of input levels for noise
42  integer :: i,j,k,n ! loop counters
43  integer :: iq ! temporary q varible index
44 
45  real(kind=default_precision), dimension(:,:), allocatable :: f_rand_pl_q ! Random Noise node amplitude for q variables
46  real(kind=default_precision), dimension(:), allocatable :: z_rand_pl_q ! Random Noise node height values for q variables
47  real(kind=default_precision), dimension(:), allocatable :: f_rand_pl_theta ! Random Noise node amplitude for theta variable
48  real(kind=default_precision), dimension(:), allocatable :: z_rand_pl_theta ! Random Noise node height values for theta variable
49  real(kind=default_precision), dimension(:), allocatable :: f_rand_pl_w ! Random Noise node amplitude for theta variable
50  real(kind=default_precision), dimension(:), allocatable :: z_rand_pl_w ! Random Noise node height values for theta variable
51 
52  logical :: l_rand_pl_theta ! if .true. then random noise added to theta field
53  logical :: l_rand_pl_q ! if .true. then random noise added to q fields
54  logical :: l_rand_pl_w ! if .true. then random noise added to w field
55  logical :: l_rand_bit_reproducible ! if .true. then is bit reproducible between runs but domain (memory) size limited
56 
57  character(len=STRING_LENGTH), dimension(:), allocatable :: names_rand_pl_q ! names of q variables to add random noise to
58 
59  real(kind=default_precision), allocatable :: f_rand_pl_q_tmp(:) !temporary 1D storage of random noise for q field
60  real(kind=default_precision), allocatable :: zgrid(:) ! z grid to use in interpolation
61 
62  if (current_state%continuation_run) return
63 
64  allocate(zgrid(current_state%local_grid%local_domain_end_index(z_index)))
65 
66  l_rand_pl_theta=options_get_logical(current_state%options_database, "l_rand_pl_theta")
67  l_rand_pl_w=options_get_logical(current_state%options_database, "l_rand_pl_w")
68  l_rand_pl_q=options_get_logical(current_state%options_database, "l_rand_pl_q")
69  l_rand_bit_reproducible=options_get_logical(current_state%options_database, "l_rand_bit_reproducible")
70 
71  if (l_rand_bit_reproducible) then
72  allocate(randarr(current_state%global_grid%size(x_index), current_state%global_grid%size(y_index), &
73  current_state%global_grid%size(z_index)))
74  else
75  iranseed=i_seed+current_state%parallel%my_rank
76  call random_seed(put=iranseed)
77  end if
78 
79  if (l_rand_pl_q) then
80  allocate(names_rand_pl_q(options_get_array_size(current_state%options_database, "names_rand_pl_q")))
81  call options_get_string_array(current_state%options_database, "names_rand_pl_q", names_rand_pl_q)
82  end if
83 
84  if (l_rand_bit_reproducible) iranseed(1:isd)=i_seed
85 
86  if (l_rand_pl_theta)then
87  ! Get random numbers
88  if (l_rand_bit_reproducible) call random_seed(get=iranseed)
89  if (l_rand_bit_reproducible) call random_number(randarr)
90 
91  ! Get amplitude profiles
92  allocate(z_rand_pl_theta(options_get_array_size(current_state%options_database, "z_rand_pl_theta")), &
93  f_rand_pl_theta(options_get_array_size(current_state%options_database, "f_rand_pl_theta")))
94  call options_get_real_array(current_state%options_database, "z_rand_pl_theta", z_rand_pl_theta)
95  call options_get_real_array(current_state%options_database, "f_rand_pl_theta", f_rand_pl_theta)
96  zgrid=current_state%global_grid%configuration%vertical%zn(:)
97  call piecewise_linear_1d(z_rand_pl_theta(1:size(z_rand_pl_theta)), f_rand_pl_theta(1:size(f_rand_pl_theta)), zgrid, &
98  current_state%global_grid%configuration%vertical%theta_rand)
99  do i=current_state%local_grid%local_domain_start_index(x_index), current_state%local_grid%local_domain_end_index(x_index)
100  do j=current_state%local_grid%local_domain_start_index(y_index), current_state%local_grid%local_domain_end_index(y_index)
101  do k=2, current_state%local_grid%local_domain_end_index(z_index)
102  if (l_rand_bit_reproducible) then
103  current_state%th%data(k,j,i) = current_state%th%data(k,j,i) + &
104  current_state%global_grid%configuration%vertical%theta_rand(k) * 2.0 * (randarr( &
105  i-current_state%local_grid%local_domain_start_index(x_index)+current_state%local_grid%start(x_index), &
106  j-current_state%local_grid%local_domain_start_index(y_index)+current_state%local_grid%start(y_index), &
107  k)-0.5)
108  else
109  call random_number(random_num)
110  current_state%th%data(k,j,i) = current_state%th%data(k,j,i) + &
111  current_state%global_grid%configuration%vertical%theta_rand(k) * 2.0 * (random_num-0.5)
112  end if
113  end do
114  end do
115  end do
116  deallocate(z_rand_pl_theta, f_rand_pl_theta)
117  end if
118 
119  if (l_rand_pl_q)then
120  nq_rand=size(names_rand_pl_q)
121  allocate(z_rand_pl_q(options_get_array_size(current_state%options_database, "z_rand_pl_q")))
122  call options_get_real_array(current_state%options_database, "z_rand_pl_q", z_rand_pl_q)
123  nzq=size(z_rand_pl_q)
124  zgrid=current_state%global_grid%configuration%vertical%zn(:)
125  allocate(f_rand_pl_q_tmp(nq_rand*nzq))
126  call options_get_real_array(current_state%options_database, "f_rand_pl_q", f_rand_pl_q_tmp)
127  allocate(f_rand_pl_q(nzq, nq_rand))
128  f_rand_pl_q(1:nzq, 1:nq_rand)=reshape(f_rand_pl_q_tmp, (/nzq, nq_rand/))
129  do n=1,nq_rand
130  ! Get random numbers
131  if (l_rand_bit_reproducible) call random_seed(get=iranseed)
132  if (l_rand_bit_reproducible) call random_number(randarr)
133 
134  iq=get_q_index(trim(names_rand_pl_q(n)), 'random noise')
135  zgrid=current_state%global_grid%configuration%vertical%zn(:)
136  call piecewise_linear_1d(z_rand_pl_q(1:size(z_rand_pl_q)), f_rand_pl_q(1:nzq,n), zgrid, &
137  current_state%global_grid%configuration%vertical%q_rand(:,iq))
138  do i=current_state%local_grid%local_domain_start_index(x_index), current_state%local_grid%local_domain_end_index(x_index)
139  do j=current_state%local_grid%local_domain_start_index(y_index), current_state%local_grid%local_domain_end_index(y_index)
140  do k=2, current_state%local_grid%local_domain_end_index(z_index)
141  if (l_rand_bit_reproducible) then
142  current_state%q(iq)%data(k,j,i) = current_state%q(iq)%data(k,j,i) + &
143  current_state%global_grid%configuration%vertical%q_rand(k,iq) * 2.0 * (randarr( &
144  i-current_state%local_grid%local_domain_start_index(x_index)+current_state%local_grid%start(x_index), &
145  j-current_state%local_grid%local_domain_start_index(y_index)+current_state%local_grid%start(y_index), &
146  k)-0.5)
147  else
148  call random_number(random_num)
149  current_state%q(iq)%data(k,j,i) = current_state%q(iq)%data(k,j,i) + &
150  current_state%global_grid%configuration%vertical%q_rand(k,iq) * 2.0 * (random_num-0.5)
151  end if
152  end do
153  end do
154  end do
155  end do
156  deallocate(z_rand_pl_q, f_rand_pl_q_tmp, f_rand_pl_q, names_rand_pl_q)
157  end if
158 
159  if (l_rand_pl_w)then
160  ! Get random numbers
161  if (l_rand_bit_reproducible) call random_seed(get=iranseed)
162  if (l_rand_bit_reproducible) call random_number(randarr)
163 
164  ! Get amplitude profiles
165  allocate(z_rand_pl_w(options_get_array_size(current_state%options_database, "z_rand_pl_w")), &
166  f_rand_pl_w(options_get_array_size(current_state%options_database, "f_rand_pl_w")))
167  call options_get_real_array(current_state%options_database, "z_rand_pl_w", z_rand_pl_w)
168  call options_get_real_array(current_state%options_database, "f_rand_pl_w", f_rand_pl_w)
169 
170  zgrid=current_state%global_grid%configuration%vertical%zn(:)
171  call piecewise_linear_1d(z_rand_pl_w(1:size(z_rand_pl_w)), f_rand_pl_w(1:size(f_rand_pl_w)), zgrid, &
172  current_state%global_grid%configuration%vertical%w_rand)
173  do i=current_state%local_grid%local_domain_start_index(x_index), current_state%local_grid%local_domain_end_index(x_index)
174  do j=current_state%local_grid%local_domain_start_index(y_index), current_state%local_grid%local_domain_end_index(y_index)
175  do k=2, current_state%local_grid%local_domain_end_index(z_index)
176  if (l_rand_bit_reproducible) then
177  current_state%w%data(k,j,i) = current_state%w%data(k,j,i) + &
178  current_state%global_grid%configuration%vertical%w_rand(k) * (randarr( &
179  i-current_state%local_grid%local_domain_start_index(x_index)+current_state%local_grid%start(x_index), &
180  j-current_state%local_grid%local_domain_start_index(y_index)+current_state%local_grid%start(y_index), &
181  k)-0.5)
182  else
183  call random_number(random_num)
184  current_state%w%data(k,j,i) = current_state%w%data(k,j,i) + &
185  current_state%global_grid%configuration%vertical%w_rand(k) * (random_num-0.5)
186  end if
187  end do
188 #ifdef W_ACTIVE
189  current_state%w%data(current_state%local_grid%local_domain_end_index(z_index),j,i)=0.0_default_precision
190  current_state%w%data(1,j,i)=0.0_default_precision
191 #endif
192  if (current_state%use_viscosity_and_diffusion) then
193 #ifdef U_ACTIVE
194  current_state%u%data(1,j,i)=-current_state%u%data(2,j,i)
195 #endif
196 #ifdef V_ACTIVE
197  current_state%v%data(1,j,i)=-current_state%v%data(2,j,i)
198 #endif
199  else
200 #ifdef U_ACTIVE
201  current_state%u%data(1,j,i)=current_state%u%data(2,j,i)
202 #endif
203 #ifdef V_ACTIVE
204  current_state%v%data(1,j,i)=current_state%v%data(2,j,i)
205 #endif
206  end if
207  end do
208  end do
209  deallocate(z_rand_pl_w, f_rand_pl_w)
210  end if
211  deallocate(zgrid)
212  if (l_rand_bit_reproducible) deallocate(randarr)
213  end subroutine initialisation_callback
214 end module randomnoise_mod
optionsdatabase_mod::options_get_array_size
integer function, public options_get_array_size(options_database, key)
Gets the size of the array held in the options database corresponding to a specific key.
Definition: optionsdatabase.F90:342
interpolation_mod::piecewise_linear_1d
subroutine piecewise_linear_1d(zvals, vals, zgrid, field)
Does a simple 1d piecewise linear interpolation.
Definition: interpolation.F90:16
grids_mod::x_index
integer, parameter, public x_index
Definition: grids.F90:14
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
grids_mod::y_index
integer, parameter, public y_index
Definition: grids.F90:14
randomnoise_mod::max_size_seed_array
integer, parameter max_size_seed_array
Definition: randomnoise.F90:18
optionsdatabase_mod::options_get_logical_array
subroutine, public options_get_logical_array(options_database, key, array_data, from, to)
Retrieves an entire (or subset) logical array.
Definition: optionsdatabase.F90:176
monc_component_mod
Interfaces and types that MONC components must specify.
Definition: monc_component.F90:6
randomnoise_mod::randomnoise_get_descriptor
type(component_descriptor_type) function, public randomnoise_get_descriptor()
Provides the descriptor back to the caller and is used in component registration.
Definition: randomnoise.F90:26
randomnoise_mod
Add random noise into the fields.
Definition: randomnoise.F90:2
randomnoise_mod::i_seed
integer, parameter i_seed
Definition: randomnoise.F90:18
randomnoise_mod::isd
integer, parameter isd
Definition: randomnoise.F90:18
grids_mod::z_index
integer, parameter, public z_index
Grid index parameters.
Definition: grids.F90:14
q_indices_mod::standard_q_names
type(standard_q_names_type), public standard_q_names
Definition: q_indices.F90:59
state_mod::model_state_type
The ModelState which represents the current state of a run.
Definition: state.F90:39
state_mod::forward_stepping
integer, parameter, public forward_stepping
Definition: state.F90:15
randomnoise_mod::initialisation_callback
subroutine initialisation_callback(current_state)
The initialisation callback sets up the buoyancy coefficient.
Definition: randomnoise.F90:34
optionsdatabase_mod::options_get_logical
logical function, public options_get_logical(options_database, key, index)
Retrieves a logical value from the database that matches the provided key.
Definition: optionsdatabase.F90:154
q_indices_mod::get_q_index
integer function, public get_q_index(name, assigning_component)
Add in a new entry into the register if the name does not already exist or return the index of the pr...
Definition: q_indices.F90:112
datadefn_mod
Contains common definitions for the data and datatypes used by MONC.
Definition: datadefn.F90:2
datadefn_mod::string_length
integer, parameter, public string_length
Default length of strings.
Definition: datadefn.F90:10
q_indices_mod
This manages the Q variables and specifically the mapping between names and the index that they are s...
Definition: q_indices.F90:2
optionsdatabase_mod::options_get_string_array
subroutine, public options_get_string_array(options_database, key, array_data, from, to)
Retrieves an entire (or subset) string array.
Definition: optionsdatabase.F90:302
grids_mod
Functionality to support the different types of grid and abstraction between global grids and local o...
Definition: grids.F90:5
optionsdatabase_mod
Manages the options database. Contains administration functions and deduce runtime options from the c...
Definition: optionsdatabase.F90:7
interpolation_mod
Definition: interpolation.F90:2
optionsdatabase_mod::options_get_real_array
subroutine, public options_get_real_array(options_database, key, array_data, from, to)
Retrieves an entire (or subset) real array.
Definition: optionsdatabase.F90:113
monc_component_mod::component_descriptor_type
Description of a component.
Definition: monc_component.F90:42
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
state_mod
The model state which represents the current state of a run.
Definition: state.F90:2