MONC
Functions/Subroutines | Variables
buoyancy_mod Module Reference

Calculates buoyancy terms for the SW field. More...

Functions/Subroutines

type(component_descriptor_type) function, public buoyancy_get_descriptor ()
 Provides the descriptor back to the caller and is used in component registration. More...
 
subroutine field_information_retrieval_callback (current_state, name, field_information)
 Field information retrieval callback, this returns information for a specific components published field. More...
 
subroutine field_value_retrieval_callback (current_state, name, field_value)
 Field value retrieval callback, this returns the value of a specific published field. More...
 
subroutine initialisation_callback (current_state)
 The initialisation callback sets up the buoyancy coefficient. More...
 
subroutine finalisation_callback (current_state)
 
subroutine timestep_callback (current_state)
 Called for each column per timestep this will calculate the buoyancy terms for the SW field. More...
 

Variables

real(kind=default_precision), dimension(:), allocatable w_buoyancy
 
real(kind=default_precision) g_over_2
 
integer iqv
 

Detailed Description

Calculates buoyancy terms for the SW field.

Function/Subroutine Documentation

◆ buoyancy_get_descriptor()

type(component_descriptor_type) function, public buoyancy_mod::buoyancy_get_descriptor ( )

Provides the descriptor back to the caller and is used in component registration.

Returns
The termination check component descriptor

Definition at line 29 of file buoyancy.F90.

29  buoyancy_get_descriptor%name="buoyancy"
30  buoyancy_get_descriptor%version=0.1
31  buoyancy_get_descriptor%initialisation=>initialisation_callback
32  buoyancy_get_descriptor%timestep=>timestep_callback
33  buoyancy_get_descriptor%finalisation=>finalisation_callback
34 
35  buoyancy_get_descriptor%field_value_retrieval=>field_value_retrieval_callback
36  buoyancy_get_descriptor%field_information_retrieval=>field_information_retrieval_callback
37  allocate(buoyancy_get_descriptor%published_fields(1))
38  buoyancy_get_descriptor%published_fields(1)="w_buoyancy"
Here is the call graph for this function:

◆ field_information_retrieval_callback()

subroutine buoyancy_mod::field_information_retrieval_callback ( type(model_state_type), intent(inout), target  current_state,
character(len=*), intent(in)  name,
type(component_field_information_type), intent(out)  field_information 
)
private

Field information retrieval callback, this returns information for a specific components published field.

Parameters
current_stateCurrent model state
nameThe name of the field to retrieve information for
field_informationPopulated with information about the field

Definition at line 46 of file buoyancy.F90.

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.
Here is the caller graph for this function:

◆ field_value_retrieval_callback()

subroutine buoyancy_mod::field_value_retrieval_callback ( type(model_state_type), intent(inout), target  current_state,
character(len=*), intent(in)  name,
type(component_field_value_type), intent(out)  field_value 
)
private

Field value retrieval callback, this returns the value of a specific published field.

Parameters
current_stateCurrent model state
nameThe name of the field to retrieve the value for
field_valuePopulated with the value of the field

Definition at line 63 of file buoyancy.F90.

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
Here is the caller graph for this function:

◆ finalisation_callback()

subroutine buoyancy_mod::finalisation_callback ( type(model_state_type), intent(inout), target  current_state)
private

Definition at line 94 of file buoyancy.F90.

94  type(model_state_type), target, intent(inout) :: current_state
95 
96  if (allocated(w_buoyancy)) deallocate(w_buoyancy)
Here is the caller graph for this function:

◆ initialisation_callback()

subroutine buoyancy_mod::initialisation_callback ( type(model_state_type), intent(inout), target  current_state)
private

The initialisation callback sets up the buoyancy coefficient.

Parameters
current_stateThe current model state

Definition at line 75 of file buoyancy.F90.

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))
Here is the caller graph for this function:

◆ timestep_callback()

subroutine buoyancy_mod::timestep_callback ( type(model_state_type), intent(inout), target  current_state)
private

Called for each column per timestep this will calculate the buoyancy terms for the SW field.

Parameters
current_stateThe current model state

Definition at line 102 of file buoyancy.F90.

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
Here is the caller graph for this function:

Variable Documentation

◆ g_over_2

real(kind=default_precision) buoyancy_mod::g_over_2
private

Definition at line 19 of file buoyancy.F90.

19  real(kind=DEFAULT_PRECISION) :: g_over_2

◆ iqv

integer buoyancy_mod::iqv
private

Definition at line 21 of file buoyancy.F90.

21  integer :: iqv ! Index for water vapour

◆ w_buoyancy

real(kind=default_precision), dimension(:), allocatable buoyancy_mod::w_buoyancy
private

Definition at line 17 of file buoyancy.F90.

17  real(kind=DEFAULT_PRECISION), dimension(:), allocatable :: w_buoyancy