MONC
setfluxlook.F90
Go to the documentation of this file.
4  use grids_mod, only : z_index
8  use saturation_mod, only : qsaturation
9  use collections_mod, only : map_type
11  use netcdf, only : nf90_noerr, nf90_global, nf90_nowrite, nf90_inquire_attribute, nf90_open, nf90_strerror, &
12  nf90_inq_dimid, nf90_inquire_dimension, nf90_inq_varid, nf90_get_var, nf90_inquire, nf90_close, nf90_get_att
17 
18  implicit none
19 
20 #ifndef TEST_MODE
21  private
22 #endif
23 
24  character(len=*), parameter :: &
25  time_key = "time", & !< NetCDF data time key
26  surface_temperatures_key = "surface_temperature", &
27  surface_humidities_key = "surface_humidity", &
28  surface_shf_key = "surface_sensible_heat_flux",&
29  surface_lhf_key = "surface_latent_heat_flux"
30 
31  integer, parameter :: lookup_entries = 80
32  integer, parameter :: max_file_len=200
33  integer, parameter :: max_surface_inputs=750
35 
36  character(MAX_FILE_LEN) :: input_file
37 
38  character(len=STRING_LENGTH) :: units_surface_temp='unset' ! units of theta variable forcing
39 
41  real(kind=default_precision), allocatable :: surface_boundary_input_times(:)
42  real(kind=default_precision), allocatable :: surface_sensible_heat_flux(:)
43  real(kind=default_precision), allocatable :: surface_latent_heat_flux(:)
44  real(kind=default_precision), allocatable :: surface_temperatures(:)
45  real(kind=default_precision), allocatable :: surface_humidities(:)
46 
47  integer :: iqv ! index for vapour
48 
50 
51 contains
52 
56  setfluxlook_get_descriptor%name="setfluxlook"
57  setfluxlook_get_descriptor%version=0.1
60  end function setfluxlook_get_descriptor
61 
62  subroutine initialisation_callback(current_state)
63  type(model_state_type), intent(inout), target :: current_state
64 
65  current_state%lookup_table_entries=lookup_entries
66  call read_configuration(current_state)
67 
68  if (.not. current_state%passive_q .and. current_state%number_q_fields > 0)then
69  if (.not. allocated(current_state%cq))then
70  allocate(current_state%cq(current_state%number_q_fields))
71  current_state%cq=0.0_default_precision
72  end if
73  iqv = get_q_index(standard_q_names%VAPOUR, 'setfluxlook')
74  current_state%cq(iqv) = ratio_mol_wts-1.0
75  end if
76 
77  if (current_state%use_surface_boundary_conditions)then
78  if (current_state%type_of_surface_boundary_conditions == prescribed_surface_fluxes) then
79  if (current_state%use_time_varying_surface_values) then
80  call set_flux(current_state)
81  else
82  current_state%surface_temperature_flux=surface_sensible_heat_flux(1) &
83  /(current_state%global_grid%configuration%vertical%rho(1)*cp)
84  current_state%surface_vapour_flux = surface_latent_heat_flux(1) &
85  /(current_state%global_grid%configuration%vertical%rho(1)*rlvap)
86  end if
87 
88  current_state%fbuoy=0.
89  if(.not. current_state%passive_th) current_state%fbuoy=&
90  current_state%global_grid%configuration%vertical%buoy_co(1)*current_state%surface_temperature_flux
91  if(.not. current_state%passive_q .and. current_state%number_q_fields > 0)then
92  current_state%fbuoy=current_state%fbuoy+current_state%cq(iqv)*current_state%surface_vapour_flux*g
93  end if
94  call set_look(current_state) ! _set M-O lookup table
95  current_state%theta_surf=0.0_default_precision
96  current_state%surface_vapour_mixing_ratio=0.0_default_precision
97  !
98  else if (current_state%type_of_surface_boundary_conditions == prescribed_surface_values) then
99  !
100  ! Prescribed surface temperatures
101  if (current_state%use_time_varying_surface_values) then
102  call set_flux(current_state)
103  else
104  ! If surface_values are constant then surface_temperatures prescribed in
105  ! config and read in read_configuration but if humidity not set then
106  ! surface vapour (surface_vapour_mixing_ratio) set to saturated value (see read_config)
107  if (current_state%saturated_surface)then
108  current_state%surface_vapour_mixing_ratio = qsaturation(surface_temperatures(1),current_state%surface_pressure*0.01)
109  else
110  current_state%surface_vapour_mixing_ratio = &
111  options_get_real(current_state%options_database, "surface_vapour_mixing_ratio")
112  endif
113 
114  ! The code below copied from set_flux as these values need to be
115  ! set for both time varying and constant surface values
116  ! Set theta_v
117  current_state%theta_surf = surface_temperatures(1)*&
118  (current_state%surface_reference_pressure/current_state%surface_pressure)**r_over_cp
119  current_state%theta_virtual_surf = current_state%theta_surf
120  if (.not. current_state%passive_q .and. current_state%number_q_fields > 0) then
121  current_state%theta_virtual_surf = current_state%theta_surf + &
122  current_state%global_grid%configuration%vertical%thref(2)* &
123  current_state%cq(iqv)*current_state%surface_vapour_mixing_ratio
124  end if
125 
126  ! Finally set up new values of THVSURF dependent constants
127  current_state%cmbc=betam*current_state%global_grid%configuration%vertical%zn(2)*g*&
128  von_karman_constant/current_state%theta_virtual_surf
129  current_state%rcmbc=1.0_default_precision/current_state%cmbc
130  current_state%ellmocon=current_state%theta_virtual_surf/(g*von_karman_constant)
131  end if
132  end if
133  end if
134 
135  end subroutine initialisation_callback
136 
137  subroutine timestep_callback(current_state)
138  type(model_state_type), intent(inout), target :: current_state
139 
140  if (current_state%use_surface_boundary_conditions)then
141  if (current_state%use_time_varying_surface_values)then
142  call set_flux(current_state)
143  call change_look(current_state)
144  end if
145  end if
146  end subroutine timestep_callback
147 
148 
149  subroutine set_look(current_state)
150  type(model_state_type), intent(inout), target :: current_state
151 
152  integer I, ik, iters(current_state%lookup_table_entries) ! Loop counters
153  real(kind=default_precision) :: smth, & ! Relaxation parameter for unstable case
154  ob, x1, x0
155 
156  if (current_state%fbuoy .le. 0.0_default_precision) return
157  current_state%velmax=100.0_default_precision
158  current_state%velmin=0.1_default_precision
159  current_state%aloginv=1.0_default_precision/log(current_state%velmax/current_state%velmin)
160  smth=0.1_default_precision ! _relaxation parameter for unstable case
161  do ik=1, current_state%lookup_table_entries
162  current_state%lookup_table_velocity(ik)=current_state%velmin*(current_state%velmax/current_state%velmin)**&
163  (real(ik-1)/real(current_state%lookup_table_entries-1))
164  current_state%lookup_table_ustr(ik)=current_state%lookup_table_velocity(ik)*&
165  current_state%global_grid%configuration%vertical%vk_on_zlogm
166  if (current_state%fbuoy .gt. 0.0_default_precision) then ! _unstable
167  iters(ik)=0
168  do i=1, 30 ! @check how many iterations needed!!
169  iters(ik)=iters(ik)+1
170  ob=-current_state%lookup_table_ustr(ik)**3/(von_karman_constant*current_state%fbuoy)
171  x1=sqrt(sqrt(1.-gammam*(current_state%global_grid%configuration%vertical%zn(2)+z0)/ob))
172  x0=sqrt(sqrt(1.-gammam*z0/ob))
173  current_state%lookup_table_ustr(ik)=(1.-smth)*current_state%lookup_table_ustr(ik) + smth*&
174  (von_karman_constant*current_state%lookup_table_velocity(ik)) / &
175  (current_state%global_grid%configuration%vertical%zlogm-(2.0_default_precision*&
176  log((x1+1.0_default_precision)/(x0+1.0_default_precision)) + log((x1*x1+1.0_default_precision)/&
177  (x0*x0+1.0_default_precision)) + 2.0_default_precision*atan(x0) -2.0_default_precision*atan(x1)))
178  end do
179  end if
180  end do
181  current_state%cneut=current_state%lookup_table_ustr(current_state%lookup_table_entries)/&
182  current_state%lookup_table_velocity(current_state%lookup_table_entries)
183  current_state%cfc=current_state%lookup_table_ustr(1)*current_state%lookup_table_velocity(1)**convective_limit ! _Businger-Dyer
184  end subroutine set_look
185 
186  subroutine change_look(current_state)
187  type(model_state_type), intent(inout), target :: current_state
188 
189  real(kind=default_precision):: crelax,& ! Relaxation parameter to move to new USTR
190  dfb,& ! Iterative difference in buoyancy flux
191  rnit,& ! real number of iterations required
192  velnew,&
193  dvelustr(current_state%lookup_table_entries), ob, x1, x0
194  integer n, ik, & ! Loop counters
195  nit ! Number of iterations
196  if (current_state%fbuoynew .le. 0.0_default_precision) then
197  current_state%fbuoy=current_state%fbuoynew
198  return
199  end if
200  if (max_change_buoyancy_flux .gt. 0.0_default_precision) then
201  rnit = abs(current_state%fbuoynew-current_state%fbuoy)/max_change_buoyancy_flux
202  nit = 1+int(rnit)
203  else
204  nit=1
205  end if
206  if (nit .gt. 10 .or. (current_state%fbuoynew .gt. 0.0_default_precision .and. &
207  current_state%fbuoy .le. 0.0_default_precision)) then
208  current_state%fbuoy=current_state%fbuoynew
209  call set_look(current_state)
210  return
211  end if
212  crelax=1./sqrt(real(nit)) ! maybe better with crelax=1.
213  dfb=(current_state%fbuoynew-current_state%fbuoy)/real(nit)
214  do n=1, nit
215  current_state%fbuoy=current_state%fbuoy+dfb
216  do ik=2, current_state%lookup_table_entries-1
217  dvelustr(ik)=log(current_state%lookup_table_velocity(ik+1)/current_state%lookup_table_velocity(ik-1))&
218  /log(current_state%lookup_table_ustr(ik+1)/current_state%lookup_table_ustr(ik-1))
219  end do
220  dvelustr(1)=log(current_state%lookup_table_velocity(2)/current_state%lookup_table_velocity(1))/&
221  log(current_state%lookup_table_ustr(2)/current_state%lookup_table_ustr(1))
222  dvelustr(current_state%lookup_table_entries)=log(current_state%lookup_table_velocity(current_state%lookup_table_entries)/&
223  current_state%lookup_table_velocity(current_state%lookup_table_entries-1))/&
224  log(current_state%lookup_table_ustr(current_state%lookup_table_entries)/&
225  current_state%lookup_table_ustr(current_state%lookup_table_entries-1))
226  do ik=1, current_state%lookup_table_entries
227  ! compute new mean vel. based on old ustar and new fbuoy
228  ob=-current_state%lookup_table_ustr(ik)**3/(von_karman_constant*current_state%fbuoy)
229  x1=sqrt(sqrt(1.-gammam*(current_state%global_grid%configuration%vertical%zn(2)+z0)/ob))
230  x0=sqrt(sqrt(1.-gammam*z0/ob))
231  velnew=(current_state%lookup_table_ustr(ik)/von_karman_constant)*(current_state%global_grid%configuration%vertical%zlogm-&
232  (2.0_default_precision*log((x1+1.0_default_precision)/(x0+1.0_default_precision)) + &
233  log((x1*x1+1.0_default_precision)/(x0*x0+1.0_default_precision)) + 2.0_default_precision*atan(x0) &
234  -2.0_default_precision*atan(x1)))
235  ! relax to new ustar
236  current_state%lookup_table_ustr(ik)=current_state%lookup_table_ustr(ik)/&
237  (velnew/current_state%lookup_table_velocity(ik))**(crelax/dvelustr(ik))
238  end do
239  end do
240  current_state%cneut=current_state%lookup_table_ustr(current_state%lookup_table_entries)/&
241  current_state%lookup_table_velocity(current_state%lookup_table_entries)
242  current_state%cfc=current_state%lookup_table_ustr(1)*current_state%lookup_table_velocity(1)**convective_limit ! _Businger-Dyer
243  current_state%fbuoy=current_state%fbuoynew
244  end subroutine change_look
245 
246  subroutine set_flux(current_state)
247  type(model_state_type), intent(inout), target :: current_state
248 
249  real(kind=default_precision) :: surface_temp ! Surface temperature
250 
251  if (current_state%type_of_surface_boundary_conditions == prescribed_surface_fluxes) then ! Prescribed surface fluxes
252 
253  ! Linear interpolation of input data...
254  call interpolate_point_linear_1d(surface_boundary_input_times, &
255  surface_sensible_heat_flux/(current_state%global_grid%configuration%vertical%rho(1)*cp), &
256  current_state%time, current_state%surface_temperature_flux, &
257  extrapolate='constant')
258 
259  call interpolate_point_linear_1d(surface_boundary_input_times, &
260  surface_latent_heat_flux/(current_state%global_grid%configuration%vertical%rho(1)*rlvap), &
261  current_state%time, current_state%surface_vapour_flux, &
262  extrapolate='constant')
263 
264  ! Update buoyancy flux...
265  current_state%fbuoynew=0.0_default_precision
266  if (.not. current_state%passive_th) current_state%fbuoynew=&
267  current_state%global_grid%configuration%vertical%buoy_co(1)*current_state%surface_temperature_flux
268  if (.not. current_state%passive_q) then
269  current_state%fbuoynew=current_state%fbuoynew+current_state%cq(iqv)*current_state%surface_vapour_flux*g
270  end if
271 
272  else if (current_state%type_of_surface_boundary_conditions == prescribed_surface_values) then ! Prescribed surface temperatures
273 
274  ! Linear interpolation of input data...
275  call interpolate_point_linear_1d(surface_boundary_input_times, &
277  current_state%time, surface_temp, &
278  extrapolate='constant')
279 
280  select case(trim(units_surface_temp))
281  case(degc) ! degrees C
282  surface_temp = surface_temp + 273.15_default_precision
283  case default ! kelvin
284  end select
285 
286  if (current_state%saturated_surface)then
287  current_state%surface_vapour_mixing_ratio = qsaturation(surface_temp,current_state%surface_pressure*0.01)
288  else
289  call interpolate_point_linear_1d(surface_boundary_input_times, &
291  current_state%time, current_state%surface_vapour_mixing_ratio, &
292  extrapolate='constant')
293  end if
294 
295  ! Set theta_v
296  current_state%theta_surf = surface_temp*&
297  (current_state%surface_reference_pressure/current_state%surface_pressure)**r_over_cp
298  current_state%theta_virtual_surf = current_state%theta_surf
299  if (.not. current_state%passive_q) then
300  current_state%theta_virtual_surf = current_state%theta_surf + &
301  current_state%global_grid%configuration%vertical%thref(2)* &
302  current_state%cq(iqv)*current_state%surface_vapour_mixing_ratio
303  end if
304 
305  ! Finally set up new values of THVSURF dependent constants
306  current_state%cmbc=betam*current_state%global_grid%configuration%vertical%zn(2)*g*&
307  von_karman_constant/current_state%theta_virtual_surf
308  current_state%rcmbc=1.0_default_precision/current_state%cmbc
309  current_state%ellmocon=current_state%theta_virtual_surf/(g*von_karman_constant)
310 
311  end if
312 
313  end subroutine set_flux
314 
315  subroutine read_configuration(current_state)
316  type(model_state_type), intent(inout), target :: current_state
317 
318 
319 
320  integer :: ncid, time_dim
321  integer :: number_input_humidities
322 
323 
324  current_state%use_surface_boundary_conditions= &
325  options_get_logical(current_state%options_database, "use_surface_boundary_conditions")
326 
327  if (current_state%use_surface_boundary_conditions)then
328  current_state%type_of_surface_boundary_conditions=options_get_integer(current_state%options_database, &
329  "type_of_surface_boundary_conditions")
330  current_state%use_time_varying_surface_values=options_get_logical(current_state%options_database, &
331  "use_time_varying_surface_values")
332 
333  current_state%saturated_surface = .true. ! We will change this if we find some humidity data
334 
335  input_file=options_get_string(current_state%options_database, "surface_conditions_file")
336  ! Read in the input_file
337  if (trim(input_file)=='' .or. trim(input_file)=='None')then
338  if (current_state%use_time_varying_surface_values)then
341  call options_get_real_array(current_state%options_database, "surface_boundary_input_times", surface_boundary_input_times)
342  end if
343  if (current_state%type_of_surface_boundary_conditions == prescribed_surface_fluxes)then
346  )
349  call options_get_real_array(current_state%options_database, "surface_sensible_heat_flux", surface_sensible_heat_flux)
350  call options_get_real_array(current_state%options_database, "surface_latent_heat_flux", surface_latent_heat_flux)
351  number_input_humidities=0
352  else if (current_state%type_of_surface_boundary_conditions == prescribed_surface_values) then
355  )
358  call options_get_real_array(current_state%options_database, "surface_temperatures", surface_temperatures)
359  units_surface_temp=options_get_string(current_state%options_database, "units_surface_temp")
360 
361  call options_get_real_array(current_state%options_database, "surface_humidities", surface_humidities)
362  number_input_humidities=options_get_array_size(current_state%options_database, "surface_humidities")
363  end if
364  else
365  call check_status(nf90_open(path = trim(input_file), mode = nf90_nowrite, ncid = ncid))
366  if (log_get_logging_level() .ge. log_debug) then
367  call log_master_log(log_debug, "Reading in surface boundary conditions from:"//trim(input_file) )
368  end if
369  call read_dimensions(ncid, time_dim)
370  call read_variables(trim(input_file), ncid, time_dim, &
373  if (.not. allocated(surface_humidities))then
374  number_input_humidities=0
375  else
376  number_input_humidities=size(surface_humidities)
377  end if
378  call check_status(nf90_close(ncid))
379  end if
380  if (number_input_humidities>0)current_state%saturated_surface=.false.
381 
382  max_change_buoyancy_flux=options_get_real(current_state%options_database, "max_change_buoyancy_flux")
383  end if
384 
385  ! Allocate lookup_tables
386  allocate(current_state%lookup_table_velocity(current_state%lookup_table_entries), &
387  current_state%lookup_table_ustr(current_state%lookup_table_entries))
388 
389  end subroutine read_configuration
390 
391 ! BELOW COPIED FROM KIDREADER - WOULD BE GOOD TO MAKE THESE UTILITY FUNCTIONS...
392 
396  subroutine read_dimensions(ncid, time_dim)
397  integer, intent(in) :: ncid
398  integer, intent(out) :: time_dim
399  integer :: time_dimid
400 
401  call check_status(nf90_inq_dimid(ncid, time_key, time_dimid))
402 
403  call check_status(nf90_inquire_dimension(ncid, time_dimid, len=time_dim))
404 
405  end subroutine read_dimensions
406 
412  subroutine read_variables(filename, ncid, time_dim, time, surface_temperatures, surface_humidities, &
413  surface_latent_heat_flux, surface_sensible_heat_flux )
414  character(*), intent(in) :: filename
415  integer, intent(in) :: ncid, time_dim
416  real(kind=default_precision), dimension(:), allocatable, intent(inout) :: time
417  real(kind=default_precision), dimension(:), allocatable, intent(inout) :: surface_temperatures
418  real(kind=default_precision), dimension(:), allocatable, intent(inout) :: surface_humidities
419  real(kind=default_precision), dimension(:), allocatable, intent(inout) :: surface_latent_heat_flux
420  real(kind=default_precision), dimension(:), allocatable, intent(inout) :: surface_sensible_heat_flux
421 
422  integer :: status, variable_id
423 
424  ! Do some checking on the variable contents so that we can deal with different
425  ! variable names or missing variables
426 
427  ! time...
428  status=nf90_inq_varid(ncid, time_key, variable_id)
429  if (status==nf90_noerr)then
430  allocate(time(time_dim))
431  call read_single_variable(ncid, time_key, data1d=time)
432  else
433  call log_log(log_error, "No recognized time variable found in"//trim(filename))
434  end if
435 
436  status=nf90_inq_varid(ncid, surface_temperatures_key, variable_id)
437  if (status==nf90_noerr)then
438  allocate(surface_temperatures(time_dim))
440  end if
441 
442  status=nf90_inq_varid(ncid, surface_humidities_key, variable_id)
443  if (status==nf90_noerr)then
444  allocate(surface_humidities(time_dim))
446  end if
447 
448  status=nf90_inq_varid(ncid, surface_lhf_key, variable_id)
449  if (status==nf90_noerr)then
450  allocate(surface_latent_heat_flux(time_dim))
452  end if
453 
454  status=nf90_inq_varid(ncid, surface_shf_key, variable_id)
455  if (status==nf90_noerr)then
456  allocate(surface_sensible_heat_flux(time_dim))
458  end if
459 
460  end subroutine read_variables
461 
467  subroutine read_single_variable(ncid, key, data1d, data3d)
468  integer, intent(in) :: ncid
469  character(len=*), intent(in) :: key
470  real(kind=default_precision), dimension(:), intent(inout), optional :: data1d
471  real(kind=default_precision), dimension(:,:,:), intent(inout), optional :: data3d
472 
473  integer :: variable_id
474  real(kind=default_precision), dimension(:,:,:), allocatable :: sdata
475 
476  call check_status(nf90_inq_varid(ncid, key, variable_id))
477 
478  if (.not. present(data1d) .and. .not. present(data3d)) return
479 
480  if (present(data1d)) then
481  call check_status(nf90_get_var(ncid, variable_id, data1d))
482  else
483  ! 3D will reshape the data to take account of the column-row major C-F transposition
484  allocate(sdata(size(data3d,1),size(data3d,3), size(data3d,2)))
485  call check_status(nf90_get_var(ncid, variable_id, sdata))
486  data3d(:,:,:)=reshape(sdata(:,:,:),(/size(data3d,1),size(data3d,2),size(data3d,3)/))
487  deallocate(sdata)
488  end if
489  end subroutine read_single_variable
490 
491 
494  subroutine check_status(status)
495  integer, intent(in) :: status
496 
497  if (status /= nf90_noerr) then
498  call log_log(log_error, "NetCDF returned error code of "//trim(nf90_strerror(status)))
499  end if
500  end subroutine check_status
501 
502 end module setfluxlook_mod
logging_mod::log_error
integer, parameter, public log_error
Only log ERROR messages.
Definition: logging.F90:11
collections_mod::map_type
Map data structure that holds string (length 20 maximum) key value pairs.
Definition: collections.F90:86
setfluxlook_mod::units_surface_temp
character(len=string_length) units_surface_temp
Definition: setfluxlook.F90:38
setfluxlook_mod::change_look
subroutine change_look(current_state)
Definition: setfluxlook.F90:187
saturation_mod
Saturation physics functionality which is used throughout the code.
Definition: saturation.F90:2
logging_mod::log_warn
integer, parameter, public log_warn
Log WARNING and ERROR messages.
Definition: logging.F90:12
optionsdatabase_mod::options_get_array_size
integer function, public options_get_array_size(options_database, key)
Gets the size of the array held in the options database corresponding to a specific key.
Definition: optionsdatabase.F90:342
state_mod::prescribed_surface_values
integer, parameter, public prescribed_surface_values
Definition: state.F90:15
collections_mod
Collection data structures.
Definition: collections.F90:7
saturation_mod::qsaturation
real(kind=default_precision) function, public qsaturation(temperature, pressure)
Function to return the saturation mixing ratio over water based on tetans formular QS=3....
Definition: saturation.F90:22
setfluxlook_mod::surface_sensible_heat_flux
real(kind=default_precision), dimension(:), allocatable surface_sensible_heat_flux
Definition: setfluxlook.F90:42
optionsdatabase_mod::options_get_integer
integer function, public options_get_integer(options_database, key, index)
Retrieves an integer value from the database that matches the provided key.
Definition: optionsdatabase.F90:217
naming_conventions_mod
Definition: naming_conventions.F90:1
logging_mod::log_info
integer, parameter, public log_info
Log INFO, WARNING and ERROR messages.
Definition: logging.F90:13
interpolation_mod::interpolate_point_linear_1d
subroutine interpolate_point_linear_1d(zvals, vals, z, f, extrapolate)
Does a simple 1d linear interpolation to a point.
Definition: interpolation.F90:66
setfluxlook_mod::max_surface_inputs
integer, parameter max_surface_inputs
Specifies the maximum number of surface inputs through configuration file Inputs through netcdf files...
Definition: setfluxlook.F90:33
setfluxlook_mod::surface_lhf_key
character(len= *), parameter surface_lhf_key
NetCDF data surface_latent_heat_flux.
Definition: setfluxlook.F90:24
logging_mod::log_log
subroutine, public log_log(level, message, str)
Logs a message at the specified level. If the level is above the current level then the message is ig...
Definition: logging.F90:75
logging_mod::log_get_logging_level
integer function, public log_get_logging_level()
Retrieves the current logging level.
Definition: logging.F90:122
logging_mod::log_debug
integer, parameter, public log_debug
Log DEBUG, INFO, WARNING and ERROR messages.
Definition: logging.F90:14
setfluxlook_mod::surface_temperatures_key
character(len= *), parameter surface_temperatures_key
NetCDF data surface_temperatures.
Definition: setfluxlook.F90:24
setfluxlook_mod::set_look
subroutine set_look(current_state)
Definition: setfluxlook.F90:150
monc_component_mod
Interfaces and types that MONC components must specify.
Definition: monc_component.F90:6
optionsdatabase_mod::options_get_string
character(len=string_length) function, public options_get_string(options_database, key, index)
Retrieves a string value from the database that matches the provided key.
Definition: optionsdatabase.F90:280
setfluxlook_mod::read_dimensions
subroutine read_dimensions(ncid, time_dim)
Reads the dimensions from the NetCDF file.
Definition: setfluxlook.F90:397
setfluxlook_mod::iqv
integer iqv
Definition: setfluxlook.F90:47
setfluxlook_mod::read_single_variable
subroutine read_single_variable(ncid, key, data1d, data3d)
Reads a single variable out of a NetCDF file.
Definition: setfluxlook.F90:468
science_constants_mod
Scientific constant values used throughout simulations. Each has a default value and this can be over...
Definition: scienceconstants.F90:3
grids_mod::z_index
integer, parameter, public z_index
Grid index parameters.
Definition: grids.F90:14
setfluxlook_mod::read_variables
subroutine read_variables(filename, ncid, time_dim, time, surface_temperatures, surface_humidities, surface_latent_heat_flux, surface_sensible_heat_flux)
Reads the variables from the NetCDF KiD model file.
Definition: setfluxlook.F90:414
setfluxlook_mod::timestep_callback
subroutine timestep_callback(current_state)
Definition: setfluxlook.F90:138
setfluxlook_mod::surface_shf_key
character(len= *), parameter surface_shf_key
NetCDF data surface_sensible_heat_flux.
Definition: setfluxlook.F90:24
q_indices_mod::standard_q_names
type(standard_q_names_type), public standard_q_names
Definition: q_indices.F90:59
state_mod::model_state_type
The ModelState which represents the current state of a run.
Definition: state.F90:39
optionsdatabase_mod::options_get_logical
logical function, public options_get_logical(options_database, key, index)
Retrieves a logical value from the database that matches the provided key.
Definition: optionsdatabase.F90:154
setfluxlook_mod::max_change_buoyancy_flux
real(kind=default_precision) max_change_buoyancy_flux
Definition: setfluxlook.F90:40
setfluxlook_mod::set_flux
subroutine set_flux(current_state)
Definition: setfluxlook.F90:247
q_indices_mod::get_q_index
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
setfluxlook_mod::max_file_len
integer, parameter max_file_len
Maximum length of surface condition input filename.
Definition: setfluxlook.F90:32
setfluxlook_mod::surface_humidities_key
character(len= *), parameter surface_humidities_key
NetCDF data surface_humidities.
Definition: setfluxlook.F90:24
logging_mod
Logging utility.
Definition: logging.F90:2
setfluxlook_mod::surface_latent_heat_flux
real(kind=default_precision), dimension(:), allocatable surface_latent_heat_flux
Definition: setfluxlook.F90:43
datadefn_mod
Contains common definitions for the data and datatypes used by MONC.
Definition: datadefn.F90:2
setfluxlook_mod::setfluxlook_get_descriptor
type(component_descriptor_type) function, public setfluxlook_get_descriptor()
Descriptor of this component for registration.
Definition: setfluxlook.F90:56
state_mod::prescribed_surface_fluxes
integer, parameter, public prescribed_surface_fluxes
Definition: state.F90:15
datadefn_mod::string_length
integer, parameter, public string_length
Default length of strings.
Definition: datadefn.F90:10
setfluxlook_mod::input_file
character(max_file_len) input_file
Definition: setfluxlook.F90:36
logging_mod::log_master_log
subroutine, public log_master_log(level, message)
Will log just from the master process.
Definition: logging.F90:47
q_indices_mod
This manages the Q variables and specifically the mapping between names and the index that they are s...
Definition: q_indices.F90:2
setfluxlook_mod::surface_temperatures
real(kind=default_precision), dimension(:), allocatable surface_temperatures
Definition: setfluxlook.F90:44
setfluxlook_mod::surface_humidities
real(kind=default_precision), dimension(:), allocatable surface_humidities
Definition: setfluxlook.F90:45
setfluxlook_mod::check_status
subroutine check_status(status)
Will check a NetCDF status and write to log_log error any decoded statuses.
Definition: setfluxlook.F90:495
setfluxlook_mod::time_key
character(len= *), parameter time_key
NetCDF data time key.
Definition: setfluxlook.F90:24
setfluxlook_mod::initialisation_callback
subroutine initialisation_callback(current_state)
Definition: setfluxlook.F90:63
grids_mod
Functionality to support the different types of grid and abstraction between global grids and local o...
Definition: grids.F90:5
setfluxlook_mod
Definition: setfluxlook.F90:1
optionsdatabase_mod
Manages the options database. Contains administration functions and deduce runtime options from the c...
Definition: optionsdatabase.F90:7
interpolation_mod
Definition: interpolation.F90:2
setfluxlook_mod::surface_boundary_input_times
real(kind=default_precision), dimension(:), allocatable surface_boundary_input_times
Definition: setfluxlook.F90:41
optionsdatabase_mod::options_get_real_array
subroutine, public options_get_real_array(options_database, key, array_data, from, to)
Retrieves an entire (or subset) real array.
Definition: optionsdatabase.F90:113
setfluxlook_mod::read_configuration
subroutine read_configuration(current_state)
Definition: setfluxlook.F90:316
monc_component_mod::component_descriptor_type
Description of a component.
Definition: monc_component.F90:42
optionsdatabase_mod::options_get_real
real(kind=default_precision) function, public options_get_real(options_database, key, index)
Retrieves a real value from the database that matches the provided key.
Definition: optionsdatabase.F90:91
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
state_mod
The model state which represents the current state of a run.
Definition: state.F90:2
setfluxlook_mod::lookup_entries
integer, parameter lookup_entries
Number of entries for MO lookup tables.
Definition: setfluxlook.F90:31