MONC
buoyancy.F90
Go to the documentation of this file.
1 
9  use grids_mod, only : z_index
12 implicit none
13 
14 #ifndef TEST_MODE
15  private
16 #endif
17  real(kind=DEFAULT_PRECISION), dimension(:), allocatable :: w_buoyancy
18 
19  real(kind=DEFAULT_PRECISION) :: g_over_2
20 
21  integer :: iqv ! Index for water vapour
22 
24 contains
25 
29  buoyancy_get_descriptor%name="buoyancy"
30  buoyancy_get_descriptor%version=0.1
34 
37  allocate(buoyancy_get_descriptor%published_fields(1))
38  buoyancy_get_descriptor%published_fields(1)="w_buoyancy"
39  end function buoyancy_get_descriptor
40 
45  subroutine field_information_retrieval_callback(current_state, name, field_information)
46  type(model_state_type), target, intent(inout) :: current_state
47  character(len=*), intent(in) :: name
48  type(component_field_information_type), intent(out) :: field_information
49 
50  ! Field description is the same regardless of the specific field being retrieved
51  field_information%field_type=component_array_field_type
52  field_information%data_type=component_double_data_type
53  field_information%number_dimensions=1
54  field_information%dimension_sizes(1)=current_state%local_grid%size(z_index)
55  field_information%enabled=.true.
57 
62  subroutine field_value_retrieval_callback(current_state, name, field_value)
63  type(model_state_type), target, intent(inout) :: current_state
64  character(len=*), intent(in) :: name
65  type(component_field_value_type), intent(out) :: field_value
66 
67  if (name .eq. "w_buoyancy") then
68  allocate(field_value%real_1d_array(size(w_buoyancy)), source=w_buoyancy)
69  end if
70  end subroutine field_value_retrieval_callback
71 
74  subroutine initialisation_callback(current_state)
75  type(model_state_type), target, intent(inout) :: current_state
76 
77  integer :: z_size
78 
79  if (.not. current_state%passive_q .and. current_state%number_q_fields > 0)then
80  if (.not. allocated(current_state%cq))then
81  allocate(current_state%cq(current_state%number_q_fields))
82  current_state%cq=0.0_default_precision
83  end if
84  iqv = get_q_index(standard_q_names%VAPOUR, 'buoyancy')
85  current_state%cq(iqv) = ratio_mol_wts-1.0
86  end if
87 
88  g_over_2 = 0.5_default_precision*g
89  z_size=current_state%global_grid%size(z_index)
90  allocate(w_buoyancy(z_size))
91  end subroutine initialisation_callback
92 
93  subroutine finalisation_callback(current_state)
94  type(model_state_type), target, intent(inout) :: current_state
95 
96  if (allocated(w_buoyancy)) deallocate(w_buoyancy)
97  end subroutine finalisation_callback
98 
101  subroutine timestep_callback(current_state)
102  type(model_state_type), target, intent(inout) :: current_state
103 
104  integer :: k, n
105 
106 #ifdef W_ACTIVE
107  if (.not. current_state%passive_th .and. current_state%th%active) then
108  do k=2,current_state%local_grid%size(z_index)-1
109  w_buoyancy(k)=(0.5_default_precision*current_state%global_grid%configuration%vertical%buoy_co(k))*&
110  (current_state%th%data(k, current_state%column_local_y, current_state%column_local_x)&
111  +current_state%th%data(k+1, current_state%column_local_y, current_state%column_local_x))
112  current_state%sw%data(k, current_state%column_local_y, current_state%column_local_x)=&
113  current_state%sw%data(k, current_state%column_local_y, current_state%column_local_x)+w_buoyancy(k)
114  end do
115  end if
116  if (.not. current_state%passive_q .and. current_state%number_q_fields .gt. 0) then
117  if (current_state%use_anelastic_equations) then
118  do n=1,current_state%number_q_fields
119  do k=2,current_state%local_grid%size(z_index)-1
120  current_state%sw%data(k, current_state%column_local_y, current_state%column_local_x)=&
121  current_state%sw%data(k, current_state%column_local_y, current_state%column_local_x)+&
122  (0.5_default_precision*current_state%global_grid%configuration%vertical%buoy_co(k))*&
123  current_state%cq(n)* (current_state%global_grid%configuration%vertical%thref(k)*&
124  current_state%q(n)%data(k, current_state%column_local_y, current_state%column_local_x)+&
125  current_state%global_grid%configuration%vertical%thref(k+1)*&
126  current_state%q(n)%data(k+1, current_state%column_local_y, current_state%column_local_x))
127  end do
128  end do
129  else
130  do n=1,current_state%number_q_fields
131  do k=2,current_state%local_grid%size(z_index)-1
132  current_state%sw%data(k, current_state%column_local_y, current_state%column_local_x)=&
133  current_state%sw%data(k, current_state%column_local_y, current_state%column_local_x)+&
134  g_over_2*current_state%cq(n)*&
135  (current_state%q(n)%data(k, current_state%column_local_y, current_state%column_local_x)+&
136  current_state%q(n)%data(k+1, current_state%column_local_y, current_state%column_local_x))
137  end do
138  end do
139  end if
140  end if
141 #endif
142  end subroutine timestep_callback
143 end module buoyancy_mod
type(component_descriptor_type) function, public buoyancy_get_descriptor()
Provides the descriptor back to the caller and is used in component registration. ...
Definition: buoyancy.F90:29
Wrapper type for the value returned for a published field from a component.
subroutine field_value_retrieval_callback(current_state, name, field_value)
Field value retrieval callback, this returns the value of a specific published field.
Definition: buoyancy.F90:63
integer, parameter, public forward_stepping
Definition: state.F90:15
type(standard_q_names_type), public standard_q_names
Definition: q_indices.F90:59
subroutine field_information_retrieval_callback(current_state, name, field_information)
Field information retrieval callback, this returns information for a specific components published fi...
Definition: buoyancy.F90:46
integer, parameter, public default_precision
MPI communication type which we use for the prognostic and calculation data.
Definition: datadefn.F90:17
integer, parameter, public z_index
Grid index parameters.
Definition: grids.F90:14
subroutine timestep_callback(current_state)
Called for each column per timestep this will calculate the buoyancy terms for the SW field...
Definition: buoyancy.F90:102
Contains common definitions for the data and datatypes used by MONC.
Definition: datadefn.F90:2
The ModelState which represents the current state of a run.
Definition: state.F90:39
logical function, public is_component_enabled(options_database, component_name)
Determines whether or not a specific component is registered and enabled.
Definition: registry.F90:334
Calculates buoyancy terms for the SW field.
Definition: buoyancy.F90:2
integer iqv
Definition: buoyancy.F90:21
integer, parameter, public component_array_field_type
Scientific constant values used throughout simulations. Each has a default value and this can be over...
This manages the Q variables and specifically the mapping between names and the index that they are s...
Definition: q_indices.F90:2
Interfaces and types that MONC components must specify.
subroutine initialisation_callback(current_state)
The initialisation callback sets up the buoyancy coefficient.
Definition: buoyancy.F90:75
Functionality to support the different types of grid and abstraction between global grids and local o...
Definition: grids.F90:5
subroutine finalisation_callback(current_state)
Definition: buoyancy.F90:94
Manages the options database. Contains administration functions and deduce runtime options from the c...
real(kind=default_precision), dimension(:), allocatable w_buoyancy
Definition: buoyancy.F90:17
real(kind=default_precision) g_over_2
Definition: buoyancy.F90:19
subroutine, public options_get_real_array(options_database, key, array_data, from, to)
Retrieves an entire (or subset) real array.
logical function, public options_has_key(options_database, key)
Determines whether a specific key is in the database.
The model state which represents the current state of a run.
Definition: state.F90:2
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
MONC component registry.
Definition: registry.F90:5
integer, parameter, public component_double_data_type