MONC
meanprofiles.F90
Go to the documentation of this file.
1 
4  use state_mod, only : model_state_type
5  use grids_mod, only : x_index, y_index, z_index
7  use mpi, only : mpi_sum, mpi_in_place
8  implicit none
9 
10 #ifndef TEST_MODE
11  private
12 #endif
13 
15 
16  real(kind=default_precision) :: rnhpts
17  real(kind=default_precision), dimension(:,:), allocatable :: bartmp
18 
20 contains
21 
25  meanprofiles_get_descriptor%name="mean_profiles"
26  meanprofiles_get_descriptor%version=0.1
30  end function meanprofiles_get_descriptor
31 
34  subroutine init_callback(current_state)
35  type(model_state_type), target, intent(inout) :: current_state
36 
37  bar_fields=0
38 
39  rnhpts=1.0_default_precision/real(current_state%global_grid%size(x_index)*current_state%global_grid%size(y_index))
40 
41  start_x=current_state%local_grid%local_domain_start_index(x_index)
42  end_x=current_state%local_grid%local_domain_end_index(x_index)
43  start_y=current_state%local_grid%local_domain_start_index(y_index)
44  end_y=current_state%local_grid%local_domain_end_index(y_index)
45 
46 #ifdef U_ACTIVE
47  if (.not. current_state%continuation_run) then
48  allocate(current_state%global_grid%configuration%vertical%olubar(current_state%local_grid%size(z_index)),&
49  current_state%global_grid%configuration%vertical%olzubar(current_state%local_grid%size(z_index)))
50  end if
52 #endif
53 #ifdef V_ACTIVE
54  if (.not. current_state%continuation_run) then
55  allocate(current_state%global_grid%configuration%vertical%olvbar(current_state%local_grid%size(z_index)),&
56  current_state%global_grid%configuration%vertical%olzvbar(current_state%local_grid%size(z_index)))
57  end if
59 #endif
60  if (current_state%th%active) then
61  if (.not. current_state%continuation_run) then
62  allocate(current_state%global_grid%configuration%vertical%olthbar(current_state%local_grid%size(z_index)),&
63  current_state%global_grid%configuration%vertical%olzthbar(current_state%local_grid%size(z_index)))
64  end if
66  end if
67  if (current_state%number_q_fields .gt. 0) then
68  bar_fields=bar_fields+(current_state%number_q_fields*2)
69  if (.not. current_state%continuation_run) then
70  allocate(current_state%global_grid%configuration%vertical%olqbar(current_state%local_grid%size(z_index), &
71  current_state%number_q_fields), current_state%global_grid%configuration%vertical%olzqbar(&
72  current_state%local_grid%size(z_index), current_state%number_q_fields))
73  end if
74  end if
75  allocate(bartmp(current_state%local_grid%size(z_index), bar_fields))
76 
77  ! Do the initial calculation for the first timestep
78  if (.not. current_state%continuation_run) call calculate_mean_profiles(current_state)
79  end subroutine init_callback
80 
83  subroutine timestep_callback(current_state)
84  type(model_state_type), target, intent(inout) :: current_state
85 
86  call calculate_mean_profiles(current_state)
87 
88  end subroutine timestep_callback
89 
92  subroutine finalisation_callback(current_state)
93  type(model_state_type), target, intent(inout) :: current_state
94 
95  if (allocated(bartmp)) deallocate(bartmp)
96  end subroutine finalisation_callback
97 
100  subroutine calculate_mean_profiles(current_state)
101  type(model_state_type), target, intent(inout) :: current_state
102 
103  integer :: bar_index, i
104 
105  call calculate_sum_profiles(current_state)
106 
107  bar_index=1
108 #ifdef U_ACTIVE
109  current_state%global_grid%configuration%vertical%olubar(:)=bartmp(:, bar_index)*rnhpts
110  current_state%global_grid%configuration%vertical%olzubar(:)=bartmp(:, bar_index+1)*rnhpts
111  bar_index=bar_index+2
112 #endif
113 #ifdef V_ACTIVE
114  current_state%global_grid%configuration%vertical%olvbar(:)=bartmp(:, bar_index)*rnhpts
115  current_state%global_grid%configuration%vertical%olzvbar(:)=bartmp(:, bar_index+1)*rnhpts
116  bar_index=bar_index+2
117 #endif
118  if (current_state%th%active) then
119  current_state%global_grid%configuration%vertical%olthbar(:)=bartmp(:, bar_index)*rnhpts
120  current_state%global_grid%configuration%vertical%olzthbar(:)=bartmp(:, bar_index+1)*rnhpts
121  bar_index=bar_index+2
122  end if
123  do i=1,current_state%number_q_fields
124  if (current_state%q(i)%active) then
125  current_state%global_grid%configuration%vertical%olqbar(:, i)=bartmp(:, bar_index)*rnhpts
126  current_state%global_grid%configuration%vertical%olzqbar(:, i)=bartmp(:, bar_index+1)*rnhpts
127  bar_index=bar_index+2
128  end if
129  end do
130 
131  end subroutine calculate_mean_profiles
132 
135  subroutine calculate_sum_profiles(current_state)
136  type(model_state_type), intent(inout) :: current_state
137 
138  integer :: k, n, bar_index, ierr
139 
140  do k=current_state%local_grid%local_domain_start_index(z_index), current_state%local_grid%local_domain_end_index(z_index)
141  bar_index=1
142 #ifdef U_ACTIVE
143  bartmp(k, bar_index)=sum(current_state%u%data(k, start_y:end_y, start_x:end_x))
144  bartmp(k, bar_index+1)=sum(current_state%zu%data(k, start_y:end_y, start_x:end_x))
145  bar_index=bar_index+2
146 #endif
147 #ifdef V_ACTIVE
148  bartmp(k, bar_index)=sum(current_state%v%data(k, start_y:end_y, start_x:end_x))
149  bartmp(k, bar_index+1)=sum(current_state%zv%data(k, start_y:end_y, start_x:end_x))
150  bar_index=bar_index+2
151 #endif
152  if (current_state%th%active) then
153  bartmp(k, bar_index)=sum(current_state%th%data(k, start_y:end_y, start_x:end_x))
154  bartmp(k, bar_index+1)=sum(current_state%zth%data(k, start_y:end_y, start_x:end_x))
155  bar_index=bar_index+2
156  end if
157  do n=1,current_state%number_q_fields
158  if (current_state%q(n)%active) then
159  bartmp(k, bar_index)=sum(current_state%q(n)%data(k, start_y:end_y, start_x:end_x))
160  bartmp(k, bar_index+1)=sum(current_state%zq(n)%data(k, start_y:end_y, start_x:end_x))
161  bar_index=bar_index+2
162  end if
163  end do
164  end do
165 
166  call mpi_allreduce(mpi_in_place, bartmp, bar_fields*current_state%local_grid%size(z_index), precision_type, mpi_sum, &
167  current_state%parallel%monc_communicator, ierr)
168  end subroutine calculate_sum_profiles
169 end module meanprofiles_mod
meanprofiles_mod::start_x
integer start_x
Definition: meanprofiles.F90:14
meanprofiles_mod::init_callback
subroutine init_callback(current_state)
Called on MONC initialisation, will allocate appropriate data structures.
Definition: meanprofiles.F90:35
meanprofiles_mod::start_y
integer start_y
Definition: meanprofiles.F90:14
grids_mod::x_index
integer, parameter, public x_index
Definition: grids.F90:14
meanprofiles_mod::finalisation_callback
subroutine finalisation_callback(current_state)
Frees up the temporary data for the bars.
Definition: meanprofiles.F90:93
grids_mod::y_index
integer, parameter, public y_index
Definition: grids.F90:14
datadefn_mod::precision_type
integer, public precision_type
Definition: datadefn.F90:19
meanprofiles_mod::timestep_callback
subroutine timestep_callback(current_state)
Will recalculate the mean profiles of each prognostic when called (for the entire local domain)
Definition: meanprofiles.F90:84
monc_component_mod
Interfaces and types that MONC components must specify.
Definition: monc_component.F90:6
meanprofiles_mod::bar_fields
integer bar_fields
Definition: meanprofiles.F90:14
meanprofiles_mod::end_y
integer end_y
Definition: meanprofiles.F90:14
meanprofiles_mod::end_x
integer end_x
Definition: meanprofiles.F90:14
meanprofiles_mod
Calculates the mean profiles of prognostic variables which are then used in smoothing and other areas...
Definition: meanprofiles.F90:2
grids_mod::z_index
integer, parameter, public z_index
Grid index parameters.
Definition: grids.F90:14
state_mod::model_state_type
The ModelState which represents the current state of a run.
Definition: state.F90:39
meanprofiles_mod::meanprofiles_get_descriptor
type(component_descriptor_type) function, public meanprofiles_get_descriptor()
Returns the component descriptor of the mean profiles module.
Definition: meanprofiles.F90:25
datadefn_mod
Contains common definitions for the data and datatypes used by MONC.
Definition: datadefn.F90:2
meanprofiles_mod::calculate_mean_profiles
subroutine calculate_mean_profiles(current_state)
Calculates the global mean profiles and stores these in the ol bar arrays.
Definition: meanprofiles.F90:101
meanprofiles_mod::rnhpts
real(kind=default_precision) rnhpts
Definition: meanprofiles.F90:16
grids_mod
Functionality to support the different types of grid and abstraction between global grids and local o...
Definition: grids.F90:5
monc_component_mod::component_descriptor_type
Description of a component.
Definition: monc_component.F90:42
meanprofiles_mod::bartmp
real(kind=default_precision), dimension(:,:), allocatable bartmp
Definition: meanprofiles.F90:17
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
meanprofiles_mod::calculate_sum_profiles
subroutine calculate_sum_profiles(current_state)
Calculates the sum profiles for the bars for each level globally.
Definition: meanprofiles.F90:136
state_mod
The model state which represents the current state of a run.
Definition: state.F90:2