34     type(model_state_type), 
target, 
intent(inout) :: current_state
 
   36     integer, 
dimension(MAX_SIZE_SEED_ARRAY) :: iranseed
 
   37     real(kind=default_precision), 
dimension(:,:,:), 
allocatable :: randarr
 
   38     real(kind=default_precision) :: random_num
 
   45     real(kind=default_precision), 
dimension(:,:), 
allocatable :: f_rand_pl_q   
 
   46     real(kind=default_precision), 
dimension(:), 
allocatable :: z_rand_pl_q     
 
   47     real(kind=default_precision), 
dimension(:), 
allocatable :: f_rand_pl_theta 
 
   48     real(kind=default_precision), 
dimension(:), 
allocatable :: z_rand_pl_theta 
 
   49     real(kind=default_precision), 
dimension(:), 
allocatable :: f_rand_pl_w     
 
   50     real(kind=default_precision), 
dimension(:), 
allocatable :: z_rand_pl_w     
 
   52     logical :: l_rand_pl_theta 
 
   53     logical :: l_rand_pl_q     
 
   54     logical :: l_rand_pl_w     
 
   55     logical :: l_rand_bit_reproducible 
 
   57     character(len=STRING_LENGTH), 
dimension(:), 
allocatable :: names_rand_pl_q 
 
   59     real(kind=default_precision), 
allocatable :: f_rand_pl_q_tmp(:) 
 
   60     real(kind=default_precision), 
allocatable :: zgrid(:)  
 
   62     if (current_state%continuation_run) 
return 
   64     allocate(zgrid(current_state%local_grid%local_domain_end_index(z_index)))
 
   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")
 
   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)))
 
   75       iranseed=
i_seed+current_state%parallel%my_rank
 
   76       call random_seed(put=iranseed)
 
   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)
 
   84     if (l_rand_bit_reproducible) iranseed(1:
isd)=
i_seed 
   86     if (l_rand_pl_theta)
then 
   88       if (l_rand_bit_reproducible) 
call random_seed(get=iranseed)
 
   89       if (l_rand_bit_reproducible) 
call random_number(randarr)
 
   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), &
 
  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)
 
  116       deallocate(z_rand_pl_theta, f_rand_pl_theta)
 
  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/))
 
  131         if (l_rand_bit_reproducible) 
call random_seed(get=iranseed)
 
  132         if (l_rand_bit_reproducible) 
call random_number(randarr)
 
  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), &
 
  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)
 
  156       deallocate(z_rand_pl_q, f_rand_pl_q_tmp, f_rand_pl_q, names_rand_pl_q)
 
  161       if (l_rand_bit_reproducible) 
call random_seed(get=iranseed)
 
  162       if (l_rand_bit_reproducible) 
call random_number(randarr)
 
  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)
 
  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), &
 
  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)
 
  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
 
  192           if (current_state%use_viscosity_and_diffusion) 
then 
  194             current_state%u%data(1,j,i)=-current_state%u%data(2,j,i)
 
  197             current_state%v%data(1,j,i)=-current_state%v%data(2,j,i)
 
  201             current_state%u%data(1,j,i)=current_state%u%data(2,j,i)
 
  204             current_state%v%data(1,j,i)=current_state%v%data(2,j,i)
 
  209       deallocate(z_rand_pl_w, f_rand_pl_w)
 
  212     if (l_rand_bit_reproducible) 
deallocate(randarr)