63 type(model_state_type),
target,
intent(inout) :: current_state
64 character(len=*),
intent(in) :: name
65 type(component_field_information_type),
intent(out) :: field_information
69 strcomp=index(name,
"coriolis_3d_local")
70 if (strcomp .ne. 0)
then
71 field_information%field_type=component_array_field_type
72 field_information%number_dimensions=3
73 field_information%dimension_sizes(1)=current_state%local_grid%size(z_index)
74 field_information%dimension_sizes(2)=current_state%local_grid%size(y_index)
75 field_information%dimension_sizes(3)=current_state%local_grid%size(x_index)
76 field_information%data_type=component_double_data_type
78 if (name .eq.
"tend_u_coriolis_3d_local")
then
80 else if (name .eq.
"tend_v_coriolis_3d_local")
then
83 field_information%enabled=.true.
89 strcomp=index(name,
"coriolis_profile_total_local")
90 if (strcomp .ne. 0)
then
91 field_information%field_type=component_array_field_type
92 field_information%number_dimensions=1
93 field_information%dimension_sizes(1)=current_state%local_grid%size(z_index)
94 field_information%data_type=component_double_data_type
96 if (name .eq.
"tend_u_coriolis_profile_total_local")
then
98 else if (name .eq.
"tend_v_coriolis_profile_total_local")
then
101 field_information%enabled=.true.
114 type(model_state_type),
target,
intent(inout) :: current_state
115 character(len=*),
intent(in) :: name
116 type(component_field_value_type),
intent(out) :: field_value
119 if (name .eq.
"tend_u_coriolis_3d_local" .and.
allocated(
tend_3d_u))
then
121 else if (name .eq.
"tend_v_coriolis_3d_local" .and.
allocated(
tend_3d_v))
then
125 else if (name .eq.
"tend_u_coriolis_profile_total_local" .and.
allocated(
tend_pr_tot_u))
then
127 else if (name .eq.
"tend_v_coriolis_profile_total_local" .and.
allocated(
tend_pr_tot_v))
then
138 type(model_state_type),
target,
intent(inout) :: current_state
143 fcoriol=options_get_real(current_state%options_database,
"fcoriol")
144 current_state%geostrophic_wind_rate_of_change_in_x=options_get_real(current_state%options_database, &
145 "geostrophic_wind_rate_of_change_in_x")
146 current_state%geostrophic_wind_rate_of_change_in_y=options_get_real(current_state%options_database, &
147 "geostrophic_wind_rate_of_change_in_y")
148 current_state%surface_geostrophic_wind_x=options_get_real(current_state%options_database,
"surface_geostrophic_wind_x")
149 current_state%surface_geostrophic_wind_y=options_get_real(current_state%options_database,
"surface_geostrophic_wind_y")
154 do k=1,current_state%local_grid%size(z_index)
159 current_state%global_grid%configuration%vertical%zn(k)
161 current_state%global_grid%configuration%vertical%zn(k)
174 allocate(
tend_3d_u(current_state%local_grid%size(z_index), &
175 current_state%local_grid%size(y_index), &
176 current_state%local_grid%size(x_index) ) )
179 allocate(
tend_3d_v(current_state%local_grid%size(z_index), &
180 current_state%local_grid%size(y_index), &
181 current_state%local_grid%size(x_index) ) )
186 allocate(
tend_pr_tot_u(current_state%local_grid%size(z_index)) )
189 allocate(
tend_pr_tot_v(current_state%local_grid%size(z_index)) )
199 type(model_state_type),
target,
intent(inout) :: current_state
212 type(model_state_type),
target,
intent(inout) :: current_state
214 integer :: local_y, locaL_x, k, target_x_index, target_y_index
216 local_y=current_state%column_local_y
217 local_x=current_state%column_local_x
218 target_y_index=local_y-current_state%local_grid%halo_size(y_index)
219 target_x_index=local_x-current_state%local_grid%halo_size(x_index)
222 if (current_state%first_timestep_column)
then
231 if (current_state%halo_column)
then
232 if (.not. ((current_state%column_local_y == current_state%local_grid%halo_size(y_index) .and. &
233 current_state%column_local_x .le. current_state%local_grid%local_domain_end_index(x_index) .and. &
234 current_state%column_local_x .ge. current_state%local_grid%local_domain_start_index(x_index)-1) .or. &
235 (current_state%column_local_x == current_state%local_grid%halo_size(x_index) .and. &
236 current_state%column_local_y .ge. current_state%local_grid%local_domain_start_index(y_index) &
237 .and. current_state%column_local_y .le. current_state%local_grid%local_domain_end_index(y_index)) ))
return
244 do k=2,current_state%local_grid%size(z_index)
245 #if defined(U_ACTIVE) && defined(V_ACTIVE)
246 current_state%su%data(k, current_state%column_local_y, current_state%column_local_x)=&
247 current_state%su%data(k, current_state%column_local_y, current_state%column_local_x)+
fcoriol*&
248 (0.25_default_precision*(current_state%v%data(k, current_state%column_local_y, current_state%column_local_x)+&
249 current_state%v%data(k, current_state%column_local_y, current_state%column_local_x+1)+&
250 current_state%v%data(k, current_state%column_local_y-1, current_state%column_local_x)+&
251 current_state%v%data(k, current_state%column_local_y-1, current_state%column_local_x+1))+current_state%vgal-&
254 current_state%sv%data(k, current_state%column_local_y, current_state%column_local_x)=&
255 current_state%sv%data(k, current_state%column_local_y, current_state%column_local_x)-
fcoriol*&
256 (0.25_default_precision*(current_state%u%data(k, current_state%column_local_y, current_state%column_local_x)+&
257 current_state%u%data(k, current_state%column_local_y, current_state%column_local_x-1)+&
258 current_state%u%data(k, current_state%column_local_y+1, current_state%column_local_x)+&
259 current_state%u%data(k, current_state%column_local_y+1, current_state%column_local_x-1))+current_state%ugal-&
278 type(model_state_type),
target,
intent(in) :: current_state
279 integer,
intent(in) :: cxn, cyn, txn, tyn
283 tend_3d_u(:,tyn,txn)=current_state%su%data(:,cyn,cxn)
286 tend_3d_v(:,tyn,txn)=current_state%sv%data(:,cyn,cxn)
299 type(model_state_type),
target,
intent(inout) :: current_state
300 integer,
intent(in) :: cxn, cyn, txn, tyn
325 type(component_field_value_type),
intent(inout) :: field_value
326 real(kind=default_precision),
dimension(:),
optional :: real_1d_field
327 real(kind=default_precision),
dimension(:,:),
optional :: real_2d_field
328 real(kind=default_precision),
dimension(:,:,:),
optional :: real_3d_field
330 if (
present(real_1d_field))
then
331 allocate(field_value%real_1d_array(
size(real_1d_field)), source=real_1d_field)
332 else if (
present(real_2d_field))
then
333 allocate(field_value%real_2d_array(
size(real_2d_field, 1),
size(real_2d_field, 2)), source=real_2d_field)
334 else if (
present(real_3d_field))
then
335 allocate(field_value%real_3d_array(
size(real_3d_field, 1),
size(real_3d_field, 2),
size(real_3d_field, 3)), &
336 source=real_3d_field)