FishMet: Fish feeding and appetite model, OPEN EDITION  0.1
FishMet: Fish feeding and appetite model, OPEN EDITION
m_simulate.f90 (16564)
Go to the documentation of this file.
1 !> @file m_simulate.f90
2 !! The FishMet Model: Runtime behaviour of the model.
3 
4 ! ------------------------------------------------------------------------------
5 ! Copyright notice:
6 ! Copyright (c) 2015-2024 Sergey Budaev & Ivar Rønnestad
7 ! FishMet model code is distributed according to GNU AGPL v3, see LICENSE.md
8 ! ------------------------------------------------------------------------------
9 
10 ! Notes:
11 ! This module is for running the simulation. It is called from the
12 ! user interface (CMD or GUI) modules.
13 
14 !> Module that defines the runtime behaviour of the model
15 module simulate
16 
17  use realcalc
18  use commondata
19  use base_utils, only : tostr
20  use base_strings, only : lowercase
21  use the_fish
22 
23  implicit none
24 
25  !> Flag for extended/detailed debug logging
26  logical, parameter :: is_extended_logging_debug_test = .false.
27 
28  !> Flag that defines how urinal and branchial energy loss (UE+ZE) is
29  !! calculated for model output arrays. If TRUE, UE+ZE is computed in
30  !! kJ per kg per day (default), otherwise, in O2 equivalent unit:
31  !! mg O2 / kg/hour
32  logical, parameter, private :: is_urinal_branchial_kj_day = .true.
33 
34  !> Progress bar widget ID for the GUI mode, needed to update at runtime
35  integer, public :: gui_idx_progress
36 
37  ! Model output arrays that are used to build the output plots and data
38  ! exports
39  !> This data structure keeps the output values for each time step. It should
40  !! normally be instantiated as an allocatable array of the size equal to the
41  !! total number of time steps in the model run.
42  type, public :: output_arrays_step_def
43  !> Total cumulative number of food items encountered by (provided to)
44  !! the fish.
45  integer :: food_items_encountered
46  !> Total cumulative number of food items ingested.
47  integer :: food_items_ingested_total
48  !> Total cumulative number of food items **not** ingested.
49  integer :: food_items_not_ingested_total
50  !> Number of food items in stomach
51  integer :: n_food_items_stomach
52  !> Number of food items in midgut
53  integer :: n_food_items_midgut
54  !> Overall appetite value as computed by the_fish::mid_gut::appetite().
55  real(srp) :: fish_appetite
56  !> Total mass of food in the **stomach**.
57  real(srp) :: food_mass_total_stomach
58  !> Total mass of food in the **midgut**.
59  real(srp) :: food_mass_total_midgut
60  !> Total mass of food absorped in the mid-gut
61  !! Note: not saved in output file, debug only.
62  real(srp) :: food_mass_absorb_total_midgut
63  !> Cumulative mass absorped in the midgut.
64  !! Note: not saved in output file, debug only.
65  real(srp) :: food_mass_absorb_cumulate
66  !> Instantaneour absorption rate in the midgut.
67  real(srp) :: food_mass_absorb_rate_instant
68  !> Total oxygen uptake
69  real(srp) :: oxygen_uptake_total
70  !> Baseline standard metabilic rate (SMR)
71  real(srp) :: baseline_smr
72  !> Active metabolic rate, excluding SMR
73  real(srp) :: active_amr
74  !> Branchaial and urinal metabolic rate
75  real(srp) :: branchial_ue_ze
76  !> Specific dynamic action
77  real(srp) :: digestion_cost_sda
78  !> Cumulative mass of evacuated food remains, stepwise
79  real(srp) :: mass_evacuated_cumulative
80  !> Energy balance of the fish:
81  !! the_fish::history_array_fish::energy_balance_curr
82  real(srp) :: energy_balance_total
83  !> Body mass of the fish
84  !! the_fish::history_array_fish::body_mass_current
85  real(srp) :: body_mass_dynamics
86  !> Activity of the fish calculated as
87  !! `fish%activity_baseline() * fish%activity_appetite()`
88  !! TODO: current activity is only used in fish_amr_locomotion_energy_cost()
89  !! so may need a separate `fish%activity()` function.
90  real(srp) :: current_activity
91 
92  end type output_arrays_step_def
93 
94  !> ::output_arrays instantiates the global data structure that
95  !! keeps the model output arrays.
96  type(output_arrays_step_def), dimension(:), allocatable, public :: &
98 
99  !> Overall output statistics that are output from the model.
100  !! @note Note that thesediffer from ::output_arrays_step_def in that
101  !! they are not arrays.
102  type, public :: output_stats_total_def
103  real(srp) :: total_mass_food_ingested
104  real(srp) :: total_mass_evacuated
105  end type
106 
107  !> ::output_stats instantiates non-array global data structure that keeps
108  !! total model output statistics, that are not arrays by time step.
110 
111  contains
112 
113  !> Calculate the total number of time steps in the model from the number
114  !! of hours. This in fact converts hours to seconds.
115  pure function total_timesteps(hours) result (time_steps)
116  !> Optional hours to be converted to seconds. If absent, the
117  !! default value is obtained from the global parameter
118  !! commondata::global_run_model_hours.
119  integer, optional, intent(in) :: hours
120  integer(LONG) :: time_steps
121 
122  if (present(hours)) then
123  time_steps = hours * hour
124  else
125  time_steps = global_run_model_hours * hour
126  end if
127 
128  end function total_timesteps
129 
130  !> Allocate *model output arrays* ::output_arrays
131  impure subroutine output_arrays_init( time_steps )
132  !> Optional overall number of time steps of the model
133  !! @note Note that this argument has the integer type of the kind
134  !! commondata::long. This might taint default integer values.
135  !! @note This procedure cannot be `pure` because it allocates a
136  !! global module-scope array.
137  integer(LONG), optional, intent(in) :: time_steps
138 
139  integer(LONG) :: time_steps_loc
140 
141  if (present(time_steps)) then
142  time_steps_loc = time_steps
143  else
144  time_steps_loc = total_timesteps()
145  end if
146 
147  if (.not. allocated(output_arrays)) then
148  allocate(output_arrays(time_steps_loc))
149  else
150  deallocate(output_arrays)
151  allocate(output_arrays(time_steps_loc))
152  end if
153 
154  output_arrays%food_items_encountered = 0
155  output_arrays%food_items_ingested_total = 0
156  output_arrays%food_items_not_ingested_total = 0
157  output_arrays%n_food_items_stomach = 0
158  output_arrays%n_food_items_midgut = 0
159  output_arrays%fish_appetite = missing
160  output_arrays%food_mass_total_stomach = 0.0_srp
161  output_arrays%food_mass_total_midgut = 0.0_srp
162  output_arrays%food_mass_absorb_total_midgut = 0.0_srp
163  output_arrays%food_mass_absorb_cumulate = 0.0_srp
164  output_arrays%food_mass_absorb_rate_instant = 0.0_srp
165  output_arrays%oxygen_uptake_total = 0.0_srp
166  output_arrays%baseline_smr = 0.0_srp
167  output_arrays%active_amr = 0.0_srp
168  output_arrays%branchial_ue_ze = 0.0_srp
169  output_arrays%digestion_cost_sda = 0.0_srp
170  output_arrays%mass_evacuated_cumulative = 0.0_srp
171  output_arrays%energy_balance_total = 0.0_srp
172  output_arrays%body_mass_dynamics = 0.0_srp
173  output_arrays%current_activity = 0.0_srp
174 
175  output_stats%total_mass_food_ingested = 0.0_srp
176  output_stats%total_mass_evacuated = 0.0_srp
177 
178  end subroutine output_arrays_init
179 
180  !> Update model *output arrays* ::output_arrays.
181  impure subroutine output_arrays_update_step( this_fish, time_step, temperature )
182  !> The fish that is participating in the simulation run.
183  class(fish), intent(in) :: this_fish
184  !> Optional time step, which coincides with the index of the model
185  !! output arrays. The default value used if the argument is not given
186  !! is defined by the global time step commondata::global_time_step.
187  integer(LONG), optional, intent(in) :: time_step
188  !> Optional temperature
189  real(srp), optional, intent(in) :: temperature
190 
191  ! Local copies of optionals
192  integer(LONG) :: time_step_loc
193  real(srp) :: temp_loc
194 
195  if (present(time_step)) then
196  time_step_loc = time_step
197  else
198  time_step_loc = global_time_step
199  end if
200 
201  if (present(temperature)) then
202  temp_loc = temperature
203  else
204  temp_loc = global_temperature
205  end if
206 
207  associate( aout => output_arrays(time_step_loc), &
208  foods_midgut => &
209  this_fish%food_items_midgut(1:this_fish%n_food_items_midgut) )
210 
211  aout%fish_appetite = this_fish%appetite()
212  aout%food_mass_total_stomach = this_fish%st_food_mass()
213  aout%food_mass_total_midgut = this_fish%mg_food_mass()
214  aout%n_food_items_stomach = this_fish%n_food_items_stomach
215  aout%n_food_items_midgut = this_fish%n_food_items_midgut - &
216  this_fish%n_food_items_stomach
217  aout%food_mass_absorb_total_midgut = &
218  sum( foods_midgut%absorped, foods_midgut%absorped /= missing )
219 
220  ! Update cumulative absorption in the output arrays
221  aout%food_mass_absorb_cumulate = &
222  this_fish%history%food_mass_absorb_cum(history_size)
223 
224  ! Update instantaneous absorption rate.
225  aout%food_mass_absorb_rate_instant = this_fish%absorption_rate()
226 
227  !> Update oxygen uptake, convert to mg O2 per kg of body mass per hour
228  aout%oxygen_uptake_total = &
229  hour * g2mg(this_fish%uptake_o2(temperature=temp_loc, &
230  is_mass=.true.)) / &
231  g2kg(this_fish%mass())
232 
233  !> Update baseline meabolic rate, mg O2 per kg per hour
234  aout%baseline_smr = &
235  this_fish%smr(temperature=temp_loc, is_per_hour=.true.) / &
236  g2kg(this_fish%mass())
237 
238  !> Update Active metabolic rate, mg O2 per kg per hour
239  aout%active_amr = &
240  this_fish%amr(temperature=temp_loc, &
241  is_per_hour=.true.,is_exclude_smr=.false.) /&
242  g2kg( this_fish%mass() )
243 
244  !> Update SDA, mg O2 per hour per kg
245  aout%digestion_cost_sda = &
246  ( this_fish%smr(temperature=temp_loc, is_per_hour=.true.)&
247  * this_fish%sda_fact( global_sda_absorp_rate_max, &
249  / g2kg(this_fish%mass())
250 
252  !> Update urinal and branchial energy in kJ/kg per day
253  aout%branchial_ue_ze = 24 * hour * &
254  this_fish%ue_ze(temperature=temp_loc, is_oxygen=.false.) &
255  / g2kg(this_fish%mass())
256  else
257  !> Alternatively, urinal and branchial energy is output as equivalent
258  !! mg O2 per kg per hour
259  !! @warning This makes sense only if UE+ZE is defined as factor of SMR
260  !! rather than fixed rate (see
261  !! commondata::global_is_ue_ze_fixed_rate)
262  aout%branchial_ue_ze = hour * &
263  g2mg(this_fish%ue_ze(temperature=temp_loc,is_oxygen=.true.))&
264  / g2kg(this_fish%mass())
265  end if
266 
267  ! Update cumulative evacuation, note that `this_fish%total_mass_evacuated`
268  ! keeps cumulative total, so cumulative is obtained straightforward.
269  aout%mass_evacuated_cumulative = &
270  last(this_fish%history%total_mass_evacuated)
271 
272  ! Update the energy balance from the last value of the respective
273  ! history array
274  aout%energy_balance_total = last(this_fish%history%energy_balance_curr)
275 
276  ! Update the body mass dynamics over the all simulation history
277  aout%body_mass_dynamics = last(this_fish%history%body_mass_current)
278  aout%current_activity = &
279  this_fish%activity_baseline() * this_fish%activity_appetite()
280 
281  ! Update the output stats, non-arrays
282  output_stats%total_mass_food_ingested = &
283  last(this_fish%history%total_mass_food_ingested)
284  output_stats%total_mass_evacuated = &
285  last(this_fish%history%total_mass_evacuated)
286 
287  end associate
288 
289  end subroutine output_arrays_update_step
290 
291  !> Update the cumulative count of food items ingested. This cannot normally
292  !! be done in ::output_arrays_update_step() and requires an input argument.
293  impure subroutine output_arrays_add_ingested( &
294  is_given, is_eaten, time_step, add_eaten )
295  !> Logical indicator whether a fod item is ingested at the current time
296  !! step (TRUE) or not (FALSE). The cumulative number of food items
297  !! consumed is updated (added) only if this parameter is TRUE.
298  logical, intent(in) :: is_given
299  !> Logical indicator whether a fod item is ingested at the current time
300  !! step (TRUE) or not (FALSE). The cumulative number of food items
301  !! consumed is updated (added) only if this parameter is TRUE.
302  logical, intent(in) :: is_eaten
303  !> Optional time step, which coincides with the index of the model
304  !! output arrays. The default value used if the argument is not given
305  !! is defined by the global time step commondata::global_time_step.
306  integer(LONG), optional, intent(in) :: time_step
307  !> Optional number of food items ingested, default value is 1.
308  integer, optional, intent(in) :: add_eaten
309 
310  ! Local copies of optionals
311  integer(LONG) :: time_step_loc
312  integer :: add_eaten_loc
313 
314  if (present(time_step)) then
315  time_step_loc = time_step
316  else
317  time_step_loc = global_time_step
318  end if
319 
320  if (present(add_eaten)) then
321  add_eaten_loc = add_eaten
322  else
323  add_eaten_loc = 1
324  end if
325 
326  if ( time_step_loc == 1 ) then
327  if ( is_eaten ) then
328  output_arrays(time_step_loc)%food_items_ingested_total = 1
329  else
330  output_arrays(time_step_loc)%food_items_ingested_total = 0
331  end if
332  if ( is_given .and. .not. is_eaten ) then
333  output_arrays(time_step_loc)%food_items_not_ingested_total = 1
334  else
335  output_arrays(time_step_loc)%food_items_not_ingested_total = 0
336  end if
337  output_arrays(time_step_loc)%food_items_encountered = &
338  output_arrays(time_step_loc)%food_items_ingested_total + &
339  output_arrays(time_step_loc)%food_items_not_ingested_total
340  return
341  end if
342 
343  !> ### Implementation notes ###
344  !> To update the cumulative count of food items ingested, the number of
345  !! items ingested at this time step is added to the value at the previous
346  !! time step. At the first step the counter is set to zero.
347  if ( is_eaten ) then
348  output_arrays(time_step_loc)%food_items_ingested_total = &
349  output_arrays(time_step_loc-1)%food_items_ingested_total + add_eaten_loc
350  else
351  output_arrays(time_step_loc)%food_items_ingested_total = &
352  output_arrays(time_step_loc-1)%food_items_ingested_total
353  end if
354 
355  !> To update the cumulative count of food items not ingested, the number of
356  !! items not ingested at this time step is added to the value at the
357  !! previous time step. At the first step the counter is set to zero.
358  if ( is_given .and. .not. is_eaten ) then
359  output_arrays(time_step_loc)%food_items_not_ingested_total = &
360  output_arrays(time_step_loc-1)%food_items_not_ingested_total &
361  + add_eaten_loc
362  else
363  output_arrays(time_step_loc)%food_items_not_ingested_total = &
364  output_arrays(time_step_loc-1)%food_items_not_ingested_total
365  end if
366 
367  output_arrays(time_step_loc)%food_items_encountered = &
368  output_arrays(time_step_loc)%food_items_ingested_total + &
369  output_arrays(time_step_loc)%food_items_not_ingested_total
370 
371  end subroutine output_arrays_add_ingested
372 
373  !> Save the model output arrays to a CSV data file.
374  impure subroutine output_arrays_save_csv( file_name, is_gui_dialog, &
375  is_write_error )
376 
377  use csv_io
378  !> The name of the CSV file to save the data into.
379  character(len=*), intent(in) :: file_name
380  !> Optional indicator that error should report to GUI.
381  logical, optional, intent(in) :: is_gui_dialog
382  !> Optional file error indicator flag, if TRUE, reports error
383  logical, optional, intent(out) :: is_write_error
384 
385  logical :: is_gui_dialog_loc
386 
387  !> - `handle_csv` is the CSV file handle object defining the file name,
388  !! Fortran unit and error descriptor, see HEDTOOLS manual for details.
389  type(csv_file) :: handle_csv
390  !> - `csv_record` is the temporary character string that keeps the
391  !! whole record of the file, i.e. the whole row of the spreadsheet table.
392  character(len=:), allocatable :: csv_record
393  !> - `COLUMNS` is a parameter array that keeps all column headers; its
394  !! size is equal to the total number of variables (columns) in the data
395  !! spreadsheet file.
396  !! .
397  character(len=LABEL_LEN), dimension(*), parameter :: &
398  columns = [ character(len=label_len) :: &
399  "DAY_NIGHT ", & ! 1
400  "SCHEDULE_FOOD ", & ! 2
401  "FOOD_PROVIDED ", & ! 3
402  "INGESTED_SUM ", & ! 4
403  "NOT_INGESTED ", & ! 5
404  "N_FOOD_STOM ", & ! 6
405  "N_FOOD_MIDGUT ", & ! 7
406  "APPETITE ", & ! 8
407  "STOMACH_MASS ", & ! 9
408  "MIDGUT_MASS ", & !10
409  "ABSORP_CUMUL ", & !11
410  "ABSORP_INRATE ", & !12
411  "OXYGEN_UPTAKE ", & !13
412  "SMR ", & !14
413  "AMR ", & !15
414  "SDA ", & !16
415  "UE_ZE ", & !17
416  "ENERGY_BALANCE", & !18
417  "BODY_MASS ", & !19
418  "ACTIVITY ", & !20
419  "EVACUATION " ] !21
420 
421  integer(LONG) :: step
422 
423  if (present(is_gui_dialog)) then
424  is_gui_dialog_loc = is_gui_dialog
425  else
426  is_gui_dialog_loc = .false.
427  end if
428 
429  handle_csv%name = file_name
430 
431  call csv_open_write( handle_csv )
432 
433  if ( .not. handle_csv%status ) then
434  call csv_file_error_report( handle_csv, is_gui_dialog=is_gui_dialog_loc )
435  if(present(is_write_error)) is_write_error=.true.
436  return
437  end if
438 
439  ! Prepare the character string variable `csv_record` that keeps the
440  ! whole record (row) of data in the output CSV data file. The length of
441  ! this string should be enough to fit all the record data, otherwise
442  ! the record is truncated.
443  csv_record = repeat( " ", size(columns) * len(columns(1)) )
444 
445  ! Create and write column header data
446  call csv_record_append( csv_record, columns )
447  call csv_record_write ( csv_record, handle_csv )
448 
449  ! The actual data are written to the CSV file in a loop over all the
450  ! time steps of Output_Arrays size
451  record_wrt: do step = 1, size(output_arrays)
452 
453  ! the `csv_record` character string variable is produced such
454  ! that it can fit the whole record;
455  csv_record = repeat(" ", &
456  max( csv_guess_record_length(size(columns)+2, 0.0_srp), label_len ) )
457 
458  ! Build the record: append variables (columns) one by one
459  associate( dat => output_arrays(step) )
460  if ( is_day(step) ) then
461  call csv_record_append(csv_record, "DAY") ! 1
462  else
463  call csv_record_append(csv_record, "NIGHT")
464  end if
465  call csv_record_append(csv_record, &
466  tostr(global_interval_food_pattern(step))) ! 2
467  call csv_record_append(csv_record, dat%food_items_encountered) ! 3
468  call csv_record_append(csv_record, dat%food_items_ingested_total) ! 4
469  call csv_record_append(csv_record, dat%food_items_not_ingested_total) ! 5
470  call csv_record_append(csv_record, dat%n_food_items_stomach) ! 6
471  call csv_record_append(csv_record, dat%n_food_items_midgut) ! 7
472  call csv_record_append(csv_record, dat%fish_appetite) ! 8
473  call csv_record_append(csv_record, dat%food_mass_total_stomach) ! 9
474  call csv_record_append(csv_record, dat%food_mass_total_midgut) !10
475  call csv_record_append(csv_record, dat%food_mass_absorb_cumulate ) !11
476  call csv_record_append(csv_record, dat%food_mass_absorb_rate_instant) !12
477  call csv_record_append(csv_record, dat%oxygen_uptake_total) !13
478  call csv_record_append(csv_record, dat%baseline_smr) !14
479  call csv_record_append(csv_record, dat%active_amr) !15
480  call csv_record_append(csv_record, dat%digestion_cost_sda) !16
481  call csv_record_append(csv_record, dat%branchial_ue_ze) !17
482  call csv_record_append(csv_record, dat%energy_balance_total) !18
483  call csv_record_append(csv_record, dat%body_mass_dynamics) !19
484  call csv_record_append(csv_record, dat%current_activity) !20
485  call csv_record_append(csv_record, dat%mass_evacuated_cumulative) !21
486  end associate
487 
488  ! Write the step-s data record
489  call csv_record_write( csv_record, handle_csv )
490  if ( .not. handle_csv%status ) then
491  call csv_file_error_report(handle_csv, is_gui_dialog=is_gui_dialog_loc)
492  call csv_close( handle_csv )
493  if(present(is_write_error)) is_write_error=.true.
494  return
495  end if
496 
497  end do record_wrt
498 
499  call csv_close( handle_csv )
500 
501  if(present(is_write_error)) is_write_error=.false.
502 
503  end subroutine output_arrays_save_csv
504 
505  !> Save the rate data arrays to a CSV data file.
506  impure subroutine output_arrays_save_rate_data_csv ( file_name, &
507  is_gui_dialog, &
508  is_write_error )
509  use csv_io
510  !> The name of the CSV file to save the data into.
511  character(len=*), intent(in) :: file_name
512  !> Optional indicator that error should report to GUI.
513  logical, optional, intent(in) :: is_gui_dialog
514  !> Optional file error indicator flag, if TRUE, reports error
515  logical, optional, intent(out) :: is_write_error
516 
517  logical :: is_gui_dialog_loc
518 
519  integer :: i, rate_unit_loc, raw_scale_max, rate_scale_y
520  real(srp), dimension(:), allocatable :: rows_x, &
521  y_rate_ingested, &
522  y_absorption_rate, &
523  y_growth_rate, &
524  y_specific_growth_rate
525 
526  !> - `handle_csv` is the CSV file handle object defining the file name,
527  !! Fortran unit and error descriptor, see HEDTOOLS manual for details.
528  type(csv_file) :: handle_csv
529  !> - `csv_record` is the temporary character string that keeps the
530  !! whole record of the file, i.e. the whole row of the spreadsheet table.
531  character(len=:), allocatable :: csv_record
532  character(len=LABEL_LEN), dimension(*), parameter :: &
533  columns = [ character(len=label_len) :: "INTERVAL_HOUR", & ! 1
534  "INGEST_RATE", & ! 2
535  "ABSORP_RATE", & ! 3
536  "GROWTH_RATE", & ! 4
537  "SP_GROWTH_RATE" ] ! 5
538 
539  if (present(is_gui_dialog)) then
540  is_gui_dialog_loc = is_gui_dialog
541  else
542  is_gui_dialog_loc = .false.
543  end if
544 
545  handle_csv%name = file_name
546 
547  call csv_open_write( handle_csv )
548 
549  if ( .not. handle_csv%status ) then
550  call csv_file_error_report( handle_csv, is_gui_dialog=is_gui_dialog_loc )
551  if(present(is_write_error)) is_write_error=.true.
552  return
553  end if
554 
555  ! Prepare the character string variable `csv_record` that keeps the
556  ! whole record (row) of data in the output CSV data file. The length of
557  ! this string should be enough to fit all the record data, otherwise
558  ! the record is truncated.
559  csv_record = repeat( " ", size(columns) * len(columns(1)) )
560 
561  ! Create and write column header data
562  call csv_record_append( csv_record, columns )
563  call csv_record_write ( csv_record, handle_csv )
564 
565  ! Calculate the rate data using the rate interval parameter
566  ! commondata::global_rate_interval.
567  rate_unit_loc = minute * global_rate_interval
568  raw_scale_max = size(output_arrays)
569 
570  allocate( rows_x(raw_scale_max/rate_unit_loc), &
571  y_rate_ingested(raw_scale_max/rate_unit_loc), &
572  y_absorption_rate(raw_scale_max/rate_unit_loc), &
573  y_growth_rate(raw_scale_max/rate_unit_loc), &
574  y_specific_growth_rate(raw_scale_max/rate_unit_loc) )
575 
576  rows_x = real([( 1 + (i-1), i=1,raw_scale_max/rate_unit_loc )], srp)
577  y_rate_ingested = cum2rate(output_arrays%food_items_ingested_total, &
578  rate_unit_loc)
579  y_absorption_rate = cum2rate(output_arrays%food_mass_absorb_cumulate, &
580  rate_unit_loc)
581  y_growth_rate = blockrate(output_arrays%body_mass_dynamics, rate_unit_loc)
582  y_growth_rate(1) = 0.0_srp ! quick fix for the first time interval
583 
584  y_specific_growth_rate = &
585  sgr(output_arrays%body_mass_dynamics,rate_unit_loc,rate_scale_y)
586  y_specific_growth_rate(1) = 0.0_srp
587 
588  ! Write the rate data to the output CSV file
589  record_wrt: do i=1, raw_scale_max / rate_unit_loc
590 
591  ! the `csv_record` character string variable is produced such
592  ! that it can fit the whole record;
593  csv_record = repeat(" ", &
594  max( csv_guess_record_length(size(columns)+2, 0.0_srp), label_len ) )
595  call csv_record_append( csv_record, rows_x(i)*rate_unit_loc/hour ) ! 1
596  call csv_record_append( csv_record, y_rate_ingested(i)*rate_scale_y ) ! 2
597  call csv_record_append( csv_record, y_absorption_rate(i)*rate_scale_y)! 3
598  call csv_record_append( csv_record, y_growth_rate(i)*rate_scale_y ) ! 4
599  call csv_record_append( csv_record, y_specific_growth_rate(i) ) ! 5
600 
601  ! Note: Left adjustment of the record with adjustl() is needed because
602  ! CSV_RECORD_APPEND() here produces ugly strings when mixing reals and
603  ! integers with many zeroes, the string starts with blanks. As a result,
604  ! office programs may have difficulty determining the columns in the
605  ! resulting CSV file.
606  csv_record = adjustl(csv_record)
607 
608  ! Write the step-s data record
609  call csv_record_write( csv_record, handle_csv )
610  if ( .not. handle_csv%status ) then
611  call csv_file_error_report(handle_csv, is_gui_dialog=is_gui_dialog_loc)
612  call csv_close( handle_csv )
613  if(present(is_write_error)) is_write_error=.true.
614  return
615  end if
616 
617  end do record_wrt
618 
619  call csv_close( handle_csv )
620 
621  if(present(is_write_error)) is_write_error=.false.
622 
623  end subroutine output_arrays_save_rate_data_csv
624 
625  !> Report CSV file write error.
626  impure subroutine csv_file_error_report( csv_handle, is_gui_dialog )
627  use csv_io, only : csv_file
628  use, intrinsic :: iso_fortran_env, only : error_unit
629  type(csv_file), intent(inout) :: csv_handle
630  !> Optional indicator that error should report to GUI.
631  logical, optional, intent(in) :: is_gui_dialog
632 
633  write(error_unit,"(a)") "ERROR: cannot open CSV file '" // &
634  trim(csv_handle%name) // "' for writing."
635  end subroutine csv_file_error_report
636 
637  !> Save the stomach transport data pattern for a single food item.
638  impure subroutine stomach_transport_save_csv(csv_file)
639  use csv_io, only : csv_matrix_write
640  !> The name of the CSV file is given as the argument.
641  character(len=*), intent(in) :: csv_file
642 
643  integer :: i
644  integer, parameter, dimension(*) :: plot_t = [(i,i=0,38000,10)]
645  real(srp), dimension(size(plot_t)) :: data_y
646 
647  data_y = st_food_item_mass(plot_t)
648 
649  call csv_matrix_write ( reshape( &
650  [real(plot_t, srp), &
651  data_y], &
652  [size(plot_t), 2]), &
653  csv_file, &
654  ["TIME ","FEED_VOLUME"] &
655  )
656 
657  end subroutine stomach_transport_save_csv
658 
659  !> Save the appetite function the_fish::appetite_func() pattern for plotting,
660  !! testing or analysis.
661  impure subroutine appetite_function_save_csv(csv_file)
662  use csv_io, only : csv_matrix_write
663  !> The name of the CSV file is given as the argument.
664  character(len=*), intent(in) :: csv_file
665 
666  integer :: i
667 
668  ! X grid array from 0.0 to 1.0 with increments INCR
669  real(srp), parameter :: incr = 0.01
670  real(srp), parameter, dimension(*) :: plot_x = &
671  [( incr * (i-1), i=1, floor((1.0)/incr + 1) )]
672  real(srp), dimension(size(plot_x)) :: data_y
673 
674  data_y = appetite_func( plot_x, global_appetite_logist_a, &
675  global_appetite_logist_r )
676 
677  call csv_matrix_write ( reshape( &
678  [plot_x, &
679  data_y], &
680  [size(plot_x), 2]), &
681  csv_file, &
682  ["RELATIVE_VOL","APPETITE_FAC"] &
683  )
684 
685  end subroutine appetite_function_save_csv
686 
687  !> Produce a text string containing general model output statistics.
688  !! @note Note that this procedure outputs table formatted data string for
689  !! terminal output and visual inspection.
690  pure function model_output_stats_txt () result( txt_out )
691  character(len=:), allocatable :: txt_out
692 
693  ! Fortran format speifier for `real` type output values
694  character(len=*), parameter :: rfmt = "(f10.4)", ifmt = "(i10)"
695 
696  real(srp) :: ratio_ingested, ratio_fcr
697 
698  associate( outdata => output_arrays(size(output_arrays)) )
699 
700  ratio_ingested = real(outdata%food_items_ingested_total,srp) / &
701  real(outdata%food_items_encountered,srp)
702 
703  ! calculate FCR for output F/(M-M0)
704  ratio_fcr = fcr(outdata%food_items_ingested_total*global_food_item_mass,&
705  outdata%body_mass_dynamics - &
706  output_arrays(1)%body_mass_dynamics)
707 
708  txt_out = crlf // &
709  "General model output statistics (" &
710  // svn_version_global // ")"// crlf // crlf // &
711  " - Simulation duration, hours : " // &
712  tostr(global_run_model_hours,ifmt,.false.) // crlf // &
713  " - Total N of food items ingested : " // &
714  tostr(outdata%food_items_ingested_total,ifmt,.false.) // crlf // &
715  " - The mass of food ingested (run), g: " // &
716  tostr( outdata%food_items_ingested_total* &
717  global_food_item_mass,rfmt,.false.)//crlf//&
718  " - Total mass of food ingested, g : " // &
719  tostr( output_stats%total_mass_food_ingested,rfmt,.false.)//crlf//&
720  " - Total cumulative absorption,g : " // &
721  tostr(outdata%food_mass_absorb_cumulate,rfmt,.false.) //crlf// &
722  " - Total energy intake from food, kJ : " // &
723  ! kJ g
724  tostr(feed_energy(outdata%food_mass_absorb_cumulate ) ,rfmt, &
725  .false.) //crlf// &
726  " - Total maintenance (at SMR), mg O2*: " // &
727  tostr(smr(global_body_mass, global_temperature, .true. ) &
728  * global_run_model_hours, rfmt,.false. )//crlf// &
729  " - Total maintenance energy, kJ* : " // &
730  ! kJ l g mgO2
731  tostr( energy_o2(o2vol(mg2g(smr(global_body_mass, &
732  global_temperature, .true. ) ) ) ) &
733  * global_run_model_hours, rfmt,.false. )//crlf// &
734  " - Energy budget at the end, kJ : " // &
735  tostr(outdata%energy_balance_total,rfmt,.false.) //crlf// &
736 
737  " - Body mass at the start, g : " // &
738  tostr(output_arrays(1)%body_mass_dynamics ,rfmt,.false.) //crlf// &
739  " - Body mass at the end, g : " // &
740  tostr(outdata%body_mass_dynamics,rfmt,.false.) //crlf// &
741  " - Feed conversion ratio : " // &
742  tostr(ratio_fcr,rfmt,.false.) //crlf// &
743  " - Specific growth rate (overall),%/h: " // &
744  tostr( sgr( outdata%body_mass_dynamics, &
745  output_arrays(1)%body_mass_dynamics, &
746  ! Note that time is given in hours, so rate scale is -1
747  global_run_model_hours, 0,-1),rfmt,.false. )//crlf// &
748 
749  ! DEBUG, body mass equivalent only for zero start energy
750  " - Body mass equivalent of energy, g*: " // &
751  tostr( energy2mass(outdata%energy_balance_total),rfmt,.false.)//crlf//&
752 
753  " - Total mass evacuated, g : " // &
754  tostr( output_stats%total_mass_evacuated,rfmt,.false. ) // crlf//&
755  " - Total N of food items provided : " // &
756  tostr(outdata%food_items_encountered,ifmt,.false.) // crlf // &
757  " - Ingestion ratio ingested/provided : " // &
758  tostr(ratio_ingested,rfmt,.false.) // crlf
759 
760  end associate
761 
762  end function model_output_stats_txt
763 
764  !> Produce a text string containing general model output statistics.
765  !! @note Note that this procedure outputs CSV-formatted data string for
766  !! saving in CSV output file. It does not write the csv output
767  !! file.
768  function model_output_stats_row_csv(show_header) result (txt_out)
769  use csv_io, only : csv_record_append
770  use base_utils, only : timestamp_full
771  !> Optional flag indicating that variable names header is included as
772  !! the first line of the string
773  logical, optional, intent(in) :: show_header
774  character(len=:), allocatable :: txt_out
775  character(len=:), allocatable :: csv_record, header_record
776  real(srp) :: ratio_ingested, ratio_fcr
777  logical :: show_header_loc
778  character(len=LABEL_LEN), dimension(:), &
779  allocatable :: col_time, col_par, col_out, columns
780  integer :: i
781  character(len=LABEL_LEN) :: timestamp_out
782  logical, parameter :: qte = .false.
783 
784  timestamp_out = timestamp_full()
785 
786  col_time = [ character(len=45) :: "TIMESTAMP " ] ! 1
787 
788  col_par = [ character(len=LABEL_LEN) :: &
789  !Input parameters:
790  !123456789012345678901234
791  "run_model_hours ", & ! 1
792  "daytime_hours ", & ! 2
793  "temperature ", & ! 3
794  "body_mass ", & ! 4
795  "stomach_capacity ", & ! 5
796  "midgut_capacity ", & ! 6
797  "absorption_ratio ", & ! 7
798  "ingestion_delay ", & ! 8
799  "water_uptake ", & ! 9
800  "water_uptake_a ", & !10
801  "water_uptake_r ", & !11
802  "appetite_factor_a ", & !12
803  "appetite_factor_r ", & !13
804  "appetite_threshold_stom", & !14
805  "digestion_delay ", & !15
806  "midgut_maxdur ", & !16
807  "appetite_energy_rate ", & !17
808  "appetite_energy_shift ", & !18
809  "midgut_michaelis_r_max ", & !19
810  "midgut_michaelis_k ", & !20
811  "food_item_mass ", & !21
812  "food_input_rate ", & !22
813  "feed_start_offset ", & !23
814  ! Array-based parameters
815  [("transport_pattern_t_" // & ! 1
816  tostr(i,10),i=1, &
817  size(global_transport_pattern_t))],&
818  [("transport_pattern_r_" // & ! 2
819  tostr(i,10),i=1, &
820  size(global_transport_pattern_r))],&
821  [("smr_oxygen_temp_" // & ! 3
822  tostr(i,10),i=1, &
823  size(global_oxygen_grid_x_temp))], &
824  [("smr_oxygen_o2_" // & ! 4
825  tostr(i,10),i=1, &
826  size(global_oxygen_grid_y_o2std))] ]
827 
828 
829  col_out = [ character(len=LABEL_LEN) :: &
830  ! Output variables
831  "INGESTED ", & ! 1
832  "MASS_INGESTED ", & ! 2
833  "TOTAL_MASS_INGESTED ", & ! 3
834  "ABSORP_CUMUL ", & ! 4
835  "ENERGY_FOOD ", & ! 5
836  "ENERGY_BUDGET ", & ! 6
837  "BODY_MASS_START ", & ! 7
838  "BODY_MASS_END ", & ! 8
839  "FEED_CONVERSION_RATIO ", & ! 9
840  "N_FOOD_PROVIDED ", & !10
841  "INGESTION_RATIO ", & !11
842  "EVACUATION " ] !12
843 
844  if (global_output_stats_is_long) then
845  columns = [col_time, col_par, col_out]
846  else
847  columns = col_out
848  end if
849 
850  if (present(show_header)) then
851  show_header_loc = show_header
852  else
853  show_header_loc = .false.
854  end if
855  csv_record = repeat( " ", size(columns) * len(columns(1)) )
856  header_record = csv_record
857 
858  associate( outdata => output_arrays(size(output_arrays)) )
859 
860  ratio_ingested = real(outdata%food_items_ingested_total,srp) / &
861  real(outdata%food_items_encountered,srp)
862 
863  ! calculate FCR for output F/(M-M0)
864  ratio_fcr = fcr(outdata%food_items_ingested_total*global_food_item_mass,&
865  outdata%body_mass_dynamics - &
866  output_arrays(1)%body_mass_dynamics)
867 
868  call csv_record_append(header_record, columns) ! 0
869 
870  if (global_output_stats_is_long) then
871  ! Input parameters
872  call csv_record_append(csv_record, timestamp_out ) ! 0
873 
874  call csv_record_append(csv_record, global_run_model_hours) ! 1
875  call csv_record_append(csv_record, global_hours_daytime_feeding) ! 2
876  call csv_record_append(csv_record, global_temperature) ! 3
877  call csv_record_append(csv_record, global_body_mass) ! 4
878  call csv_record_append(csv_record, global_stomach_mass) ! 5
879  call csv_record_append(csv_record, global_midgut_mass) ! 6
880  call csv_record_append(csv_record, global_absorption_ratio) ! 7
881  call csv_record_append(csv_record, global_ingestion_delay_min) ! 8
882  call csv_record_append(csv_record, global_water_uptake) ! 9
883  call csv_record_append(csv_record, global_water_uptake_a) ! 10
884  call csv_record_append(csv_record, global_water_uptake_r) ! 11
885  call csv_record_append(csv_record, global_appetite_logist_a) ! 12
886  call csv_record_append(csv_record, global_appetite_logist_r) ! 13
887  call csv_record_append(csv_record, global_appetite_stomach_threshold) ! 14
888  call csv_record_append(csv_record, global_digestion_delay_min) ! 15
889  call csv_record_append(csv_record, global_maximum_duration_midgut_min) ! 16
890  call csv_record_append(csv_record, global_energy_appetite_rate) ! 17
891  call csv_record_append(csv_record, global_energy_appetite_shift) ! 18
892  call csv_record_append(csv_record, global_mid_gut_mm_r_max) ! 19
893  call csv_record_append(csv_record, global_mid_gut_mm_k_m) ! 20
894  call csv_record_append(csv_record, global_food_item_mass) ! 21
895  call csv_record_append(csv_record, global_food_input_rate) ! 22
896  call csv_record_append(csv_record, global_run_model_feed_offset) ! 23
897  ! Array-based parameters
898  call csv_record_append(csv_record, global_transport_pattern_t) ! 1
899  call csv_record_append(csv_record, global_transport_pattern_r) ! 2
900  call csv_record_append(csv_record, global_oxygen_grid_x_temp) ! 3
901  call csv_record_append(csv_record, global_oxygen_grid_y_o2std) ! 4
902  end if
903 
904  ! Output variables
905  call csv_record_append(csv_record, outdata%food_items_ingested_total) ! 1
906  call csv_record_append(csv_record, outdata%food_items_ingested_total* & ! 2
907  global_food_item_mass)
908  call csv_record_append(csv_record, output_stats%total_mass_food_ingested) ! 3
909  call csv_record_append(csv_record, outdata%food_mass_absorb_cumulate) ! 4
910  call csv_record_append(csv_record, &
911  feed_energy(outdata%food_mass_absorb_cumulate)) ! 5
912  call csv_record_append(csv_record, outdata%energy_balance_total) ! 6
913  call csv_record_append(csv_record, output_arrays(1)%body_mass_dynamics) ! 7
914  call csv_record_append(csv_record, outdata%body_mass_dynamics) ! 8
915  call csv_record_append(csv_record, ratio_fcr) ! 9
916  call csv_record_append(csv_record, outdata%food_items_encountered) !10
917  call csv_record_append(csv_record, ratio_ingested) !11
918  call csv_record_append(csv_record, output_stats%total_mass_evacuated) !12
919 
920  end associate
921 
922  if (show_header_loc) then
923  txt_out = header_record // crlf // csv_record
924  else
925  txt_out = csv_record
926  end if
927 
928  end function model_output_stats_row_csv
929 
930  ! ============================================================================
931  ! ============================================================================
932 
933  !> The procedure below is TEMPORARY, for testing and debugging.
934  impure subroutine test_run()
935  use csv_io
936  use, intrinsic :: iso_fortran_env, only : error_unit
937  use base_random, only : random_seed_init
938 
939  !> Maximum number of food items to show, this should never be greater than
940  !! commondata::max_food_items_index.
941  integer, parameter :: max_col = min(50, max_food_items_index)
942 
943  integer(LONG) :: total_steps
944 
945  type(food_item) :: feed
946 
947  type(fish) :: fish_agent
948 
949  logical :: is_given_feed, is_eaten
950 
951  ! Flag for extended/detailed debug logging
952  logical, parameter :: is_logging_debug = is_extended_logging_debug_test
953 
954  ! File name for saving extended/detailed debug data.
955  character(len=*), parameter :: detailed_csv_file = "debug_data_steps.csv"
956 
957  ! CSV file handle
958  type(csv_file) :: detailed_csv_output_handle
959  integer :: detailed_csv_n_cols
960 
961  ! defines if the progress bar is hidden after completion.
962  ! @note Note on Intel `ifort`: Intel Fortran optimizes screen writing
963  ! so that the progress bar is not updated at each step but rather
964  ! writes out in one piece after model completion.
965  logical, parameter :: progbar_hide = .true.
966 
967  ! These four variables keep the previous and next value of the stomach
968  ! and midgut capacity, if
969  ! commondata::global_stomach_midgut_mass_is_automatic is TRUE
970  ! @note Note that these values are necessary to ensure the stomach
971  ! and midgut capacity do not shrink if the fish mass is reduced
972  ! as aresult of starvation or poor feeding.
973  real(srp) :: mass_stomach_prev_no_shrink, mass_midgut_prev_no_shrink, &
974  mass_stomach_next_no_shrink, mass_midgut_next_no_shrink
975 
976  !- - - - - - - -
977 
978  if (.NOT. is_debug) call random_seed_init()
979 
980  total_steps = total_timesteps( global_run_model_hours )
981 
982  call init_provisioning( total_steps )
983 
984  call output_arrays_init( total_steps )
985 
986  call feed%init( mass=global_food_item_mass )
987 
988  call fish_agent%new( id_num = 1 )
989  if (global_stomach_midgut_mass_is_automatic) then
990  call fish_agent%st_init(mass=salmon_stomach_capacity(global_body_mass))
991  call fish_agent%mg_init(mass=salmon_midgut_capacity(global_body_mass))
992  else
993  call fish_agent%st_init( mass=global_stomach_mass )
994  call fish_agent%mg_init( mass=global_midgut_mass )
995  end if
996 
997  debug_report_init: if (is_debug .and. verbose) then
998  write(*,"(a,f9.3)") "DEBUG_REPORT_INIT: Initialized body_mass:", &
999  fish_agent%mass()
1000  write(*,"(a,f9.3)") "DEBUG_REPORT_INIT: Initialized stomach_capacity:", &
1001  fish_agent%mass_stomach
1002  write(*,"(a,f9.3)") "DEBUG_REPORT_INIT: Initialized midgut_capacity:", &
1003  fish_agent%mass_midgut
1004  end if debug_report_init
1005 
1006  if ( is_logging_debug ) &
1007  call detailed_csv_output_open( detailed_csv_file, &
1008  detailed_csv_output_handle, &
1009  detailed_csv_n_cols )
1010 
1011  time_loop: do global_time_step = 1, total_steps
1012 
1013  debug_warn_size: if (is_debug) then
1014  if (fish_agent%mass() < fish_agent%body_mass0/2.0_srp) &
1015  write(*,*) "DEBUG_WARN_SIZE: Body mass is less than 1/2 of start mass"
1016  if (fish_agent%mass() < 10.0_srp) &
1017  write(*,*) "DEBUG_WARN_SIZE: Body mass too small: ", fish_agent%mass()
1018  end if debug_warn_size
1019 
1020  !> - Provide and schedule a food item
1021  !> - The fish decides to eat the food item scheduled
1022  call fish_agent%decide_eat( feed%schedule(is_provided=is_given_feed), &
1023  have_eaten=is_eaten )
1024 
1025  !> - Update one time step of the fish stomach and mid-gut
1026  call fish_agent%st_step()
1027  call fish_agent%mg_step()
1028  call fish_agent%energy_update()
1029  call fish_agent%do_grow()
1030 
1031  ! This block increases the stomach and midgut capacity, but only
1032  ! they do not shrink. In case the fish reduces the body mass (e.g.
1033  ! as a result of starvation), the stomach and gut capacity are
1034  ! kept constant.
1035  grow_stomach_midgut: if (global_stomach_midgut_mass_is_automatic) then
1036  ! previous values
1037  mass_stomach_prev_no_shrink = fish_agent%mass_stomach
1038  mass_midgut_prev_no_shrink = fish_agent%mass_midgut
1039  ! new values calculated from updated body mass
1040  mass_stomach_next_no_shrink = salmon_stomach_capacity(fish_agent%mass())
1041  mass_midgut_next_no_shrink = salmon_midgut_capacity(fish_agent%mass())
1042  if (mass_stomach_next_no_shrink >= mass_stomach_prev_no_shrink) &
1043  fish_agent%mass_stomach = mass_stomach_next_no_shrink
1044  if (mass_midgut_next_no_shrink >= mass_midgut_prev_no_shrink) &
1045  fish_agent%mass_midgut = mass_midgut_next_no_shrink
1046  end if grow_stomach_midgut
1047 
1048  !> - Update the output arrays, use ::output_arrays_update_step().
1049  call output_arrays_update_step( fish_agent )
1050 
1051  !> - Update the total count of food items eaten and not eaten
1052  call output_arrays_add_ingested( is_given_feed, is_eaten )
1053 
1054  debug_absorp_cumulate_mismatch: if ( is_debug ) then
1055  block
1056  real(srp) :: abs_diff
1057  ! Tolerance limit for detectable difference
1058  real(srp), parameter :: verysmall = epsilon(1.0_srp) * 10.0_srp
1059  abs_diff=abs( fish_agent%history%food_mass_absorb_cum(history_size) &
1060  - output_arrays(global_time_step)%food_mass_absorb_cumulate )
1061  if ( abs_diff > verysmall ) write(*,*) &
1062  "DEBUG_ABSORP_CUMULATE_MISMATCH: fish object absorption " // &
1063  "does not match output arrays, abs.diff =", abs_diff
1064  end block
1065  end if debug_absorp_cumulate_mismatch
1066 
1067  if ( is_logging_debug ) call &
1068  detailed_csv_output_write_record( detailed_csv_output_handle, &
1069  detailed_csv_n_cols )
1070 
1071  end do time_loop
1072 
1073  if ( is_logging_debug ) &
1074  call detailed_csv_output_close( detailed_csv_output_handle )
1075 
1076  contains ! ----------------------------------------------------------------
1077 
1078  !> **Open** the CSV output file with the detailed step-wise data. Note
1079  !! that these detailed outputs are produced if ::is_logging_debug
1080  !! parameter is set to TRUE.
1081  subroutine detailed_csv_output_open( file_name, csv_handle, total_columns )
1082  character(len=*), intent(in) :: file_name
1083  type(csv_file), intent(inout) :: csv_handle
1084  integer, intent(out) :: total_columns
1085 
1086  integer :: i
1087 
1088  ! Columns of the CSV file go in two kinds: single variable and
1089  ! array variables with numbered columns.
1090 
1091  ! Fifed columns of the first row, single variable names.
1092  character(len=LABEL_LEN), dimension(*), parameter :: &
1093  COLUMNS_FIX = [ character(len=label_len) :: &
1094  "STEP ", & ! 1
1095  "FEEDING ", & ! 2
1096  "N_INGESTED ", & ! 3
1097  "N_WASTED ", & ! 4
1098  "APPETITE_STOM ", & ! 5
1099  "APPETITE_MIDG ", & ! 6
1100 
1101  "APPETITE_ENERG", & ! 7
1102 
1103  "APPETITE_FISH ", & ! 8
1104  "STOM_FOOD_MASS", & ! 9
1105  "STOM_FOOD_REL ", & ! 10
1106  "STOM_FOOD_N ", & ! 11
1107  "MIDG_FOOD_MASS", & ! 12
1108  "MIDG_FOOD_REL ", & ! 13
1109  "MIDG_MM_RDECR ", & ! 14
1110  "MIDG_FOOD_N ", & ! 15
1111  "ABSORPED_TOTAL", & ! 16
1112  "ABSORPED_CUMUL" ] ! 17
1113 
1114  ! Numbered columns of the first row, variable names, their values are
1115  ! initialised using (implied) loops.
1116  character(len=LABEL_LEN), dimension(MAX_COL*5) :: COLUMNS_NUM
1117 
1118  ! `csv_record` is the temporary character string that keeps the
1119  ! whole record of the file, i.e. the whole row of the spreadsheet table.
1120  character(len=:), allocatable :: csv_record
1121 
1122  ! Initialise the array variables with numbered columns names.
1123  columns_num = [ character(len=LABEL_LEN) :: &
1124  [("STOM_TIME_" // TOSTR(i,10),i=1,max_col)], & ! 1
1125  [("STOM_MASS_" // tostr(i,10),i=1,max_col)], & ! 2
1126  [("MIDG_TIME_" // tostr(i,10),i=1,max_col)], & ! 3
1127  [("MIDG_MASS_" // tostr(i,10),i=1,max_col)], & ! 4
1128  [("ABSORP_" // tostr(i,10),i=1,max_col)] ] ! 5
1129 
1130  csv_handle%name = file_name
1131 
1132  total_columns = size(columns_fix) + size(columns_num)
1133 
1134  ! Open CSV file for writing.
1135  call csv_open_write( csv_handle )
1136  if ( .not. csv_handle%status ) then
1137  call csv_file_error_report( csv_handle )
1138  return
1139  end if
1140 
1141  ! Prepare the character string variable `csv_record` that keeps the
1142  ! whole record (row) of data in the output CSV data file. The length of
1143  ! this string should be enough to fit all the record data, otherwise
1144  ! the record is truncated.
1145  csv_record = repeat( " ", (size(columns_fix)+size(columns_num)) &
1146  * (label_len+4) )
1147 
1148  ! Create and write column header data
1149  call csv_record_append( csv_record, [ columns_fix, columns_num ] )
1150  call csv_record_write ( csv_record, csv_handle )
1151  if ( .not. csv_handle%status ) then
1152  call csv_file_error_report( csv_handle )
1153  call csv_close( csv_handle )
1154  return
1155  end if
1156 
1157  end subroutine detailed_csv_output_open
1158 
1159  !> **Close** the CSV output file with the detailed step-wise data. Note
1160  !! that these detailed outputs are produced if ::is_logging_debug
1161  !! parameter is set to TRUE.
1162  subroutine detailed_csv_output_close( csv_handle )
1163  type(csv_file), intent(inout) :: csv_handle
1164 
1165  call csv_close( csv_handle )
1166 
1167  end subroutine detailed_csv_output_close
1168 
1169  !> **Write** the step-wise CSV output record with the actual data. Note
1170  !! that these detailed outputs are produced if ::is_logging_debug
1171  !! parameter is set to TRUE.
1172  !! @note Note that this subroutine is called each time step, so that
1173  !! a single row of data (CSV file record)) is written each time.
1174  subroutine detailed_csv_output_write_record( csv_handle, total_columns )
1175  type(csv_file), intent(inout) :: csv_handle
1176  integer, intent(in) :: total_columns
1177 
1178  ! `csv_record` is the temporary character string that keeps the whole
1179  ! record of the file, i.e. the whole row of the spreadsheet table.
1180  character(len=:), allocatable :: csv_record
1181 
1182  ! the `csv_record` character string variable is produced such
1183  ! that it can fit the whole record;
1184  csv_record = repeat(" ", &
1185  max( csv_guess_record_length(total_columns+2, 0.0_srp), label_len ) )
1186 
1187  ! Fill the record (row) by adding variables
1188  ! - Fixed columns
1189  call csv_record_append(csv_record, global_time_step) ! 1
1190  call csv_record_append(csv_record, & ! 2
1191  tostr(global_interval_food_pattern(global_time_step)) )
1192  call csv_record_append(csv_record, & ! 3
1193  output_arrays(global_time_step)%food_items_ingested_total )
1194  call csv_record_append(csv_record, & ! 4
1195  output_arrays(global_time_step)%food_items_not_ingested_total )
1196  call csv_record_append(csv_record, fish_agent%appetite_stomach() ) ! 5
1197  call csv_record_append(csv_record, fish_agent%appetite_midgut() ) ! 6
1198 
1199  call csv_record_append(csv_record, fish_agent%appetite_energy() ) ! 7
1200 
1201  call csv_record_append(csv_record, & ! 8
1202  output_arrays(global_time_step)%fish_appetite )
1203  call csv_record_append(csv_record, fish_agent%st_food_mass() ) ! 9
1204 
1205  call csv_record_append(csv_record, fish_agent%st_food_mass() / & !10
1206  fish_agent%mass_stomach )
1207 
1208  call csv_record_append(csv_record, fish_agent%n_food_items_stomach )!11
1209  call csv_record_append(csv_record, fish_agent%mg_food_mass() ) !12
1210 
1211  call csv_record_append(csv_record, fish_agent%mg_food_mass() / & !13
1212  fish_agent%mass_midgut )
1213  call csv_record_append( & !14
1214  csv_record, &
1215  michaelis_menten(fish_agent%mg_food_mass() / &
1216  fish_agent%mass_midgut, &
1217  global_mid_gut_mm_r_max, &
1218  global_mid_gut_mm_k_m ) )
1219  call csv_record_append(csv_record, fish_agent%n_food_items_midgut ) !15
1220  call csv_record_append(csv_record, & !16
1221  output_arrays(global_time_step)%food_mass_absorb_total_midgut )
1222 
1223  call csv_record_append(csv_record, & !17
1224  output_arrays(global_time_step)%food_mass_absorb_cumulate )
1225 
1226  ! - Array columns
1227  call csv_record_append(csv_record, & ! 1
1228  fish_agent%food_items_stomach(1:max_col)%time_in_process )
1229  call csv_record_append(csv_record, & ! 2
1230  fish_agent%food_items_stomach(1:max_col)%mass )
1231  call csv_record_append(csv_record, & ! 3
1232  fish_agent%food_items_midgut(1:max_col)%time_in_process )
1233  call csv_record_append(csv_record, & ! 4
1234  fish_agent%food_items_midgut(1:max_col)%mass )
1235  call csv_record_append(csv_record, & ! 5
1236  fish_agent%food_items_midgut(1:max_col)%absorped )
1237 
1238  ! Write the step-s data record to the disk.
1239  call csv_record_write( csv_record, csv_handle )
1240  if ( .not. csv_handle%status ) then
1241  call csv_file_error_report( csv_handle )
1242  call csv_close( csv_handle )
1243  return
1244  end if
1245 
1246  end subroutine detailed_csv_output_write_record
1247 
1248  end subroutine test_run
1249 
1250  !> Initialise the food provisioning schedule / pattern
1251  impure subroutine init_provisioning( time_steps )
1252  !> Optional overall number of time steps of the model
1253  !! @note Note that this argument has the integer type of the kind
1254  !! commondata::long. This might taint default integer values.
1255  !! @note This procedure cannot be `pure` because it allocates a
1256  !! global module-scope array.
1257  integer(LONG), intent(in), optional :: time_steps
1258 
1259  logical :: is_file_readable
1260 
1261  integer(LONG) :: time_steps_loc
1262 
1263  if (present(time_steps)) then
1264  time_steps_loc = time_steps
1265  else
1266  time_steps_loc = total_timesteps()
1267  end if
1268 
1269  if ( global_food_pattern_file == "" ) then
1270  call food_provisioning_pattern_init( time_steps_loc )
1271  else
1272  ! Check if the configuration file exists, if not, exit with error.
1273  inquire( file=global_food_pattern_file, exist=is_file_readable )
1274  if ( is_file_readable ) then
1275  if (global_food_pattern_file_is_steps) then
1276  call food_provisioning_get_raw( time_steps_loc, &
1277  global_food_pattern_file, &
1278  column=255, & ! the last col is used
1279  is_single=.not. global_food_pattern_file_is_propagate )
1280  else
1281  call food_provisioning_get_file ( time_steps_loc, &
1282  global_food_pattern_file, &
1283  column=255, & ! the last col is used
1284  is_single=.not. global_food_pattern_file_is_propagate )
1285  end if
1286  else
1287  write(error_unit,*) "WARNING: ", "Food provision file ", &
1288  trim(global_food_pattern_file), " does not exist, ", &
1289  "use `food_provision_pattern`."
1290  call food_provisioning_pattern_init( time_steps_loc )
1291  end if
1292  end if
1293 
1294  end subroutine init_provisioning
1295 
1296  !> Determine the food schedule array for separate display and analysis
1297  !! The primary role of this function is to plan (produce and display) the
1298  !! food provisioning pattern before simulation in GUI
1299  impure function get_food_schedule_display() result (food_items_encountered)
1300  integer, allocatable, dimension(:) :: food_items_encountered
1301 
1302  type(food_item), target :: feed_check
1303  type(food_item), pointer :: feed_pt
1304 
1305  logical :: is_given
1306  integer(LONG) :: i, isum, istep
1307  logical :: is_given_feed
1308 
1309  allocate(food_items_encountered(global_run_model_hours * hour))
1310 
1311  food_items_encountered = 0
1312  isum = 0
1313 
1314  do i = 1, global_run_model_hours * hour
1315  feed_pt => feed_check%schedule( i, is_provided=is_given_feed )
1316  if (associated(feed_pt)) isum = isum + 1
1317  food_items_encountered(i) = isum
1318  end do
1319 
1320  end function get_food_schedule_display
1321 
1322  !> calculate the array of the consumption ratio, i.e. eaten/provided, so
1323  !! it is also easy to calculate the waste rate
1324  function get_ingestion_ratio_waste(rate_unit) result (consumption)
1325  !> Optional rate parameter, the rate is calculated per this number of
1326  !! seconds, the default is per minute
1327  integer, intent(in), optional :: rate_unit
1328  real(srp), allocatable, dimension(:) :: consumption
1329 
1330  integer :: rate_unit_loc
1331  integer(LONG) :: full_max, i, ii
1332 
1333  ! interval data
1334  integer, allocatable, dimension(:) :: int_ingested, int_provided
1335 
1336  if (present(rate_unit)) then
1337  rate_unit_loc = rate_unit
1338  else
1339  rate_unit_loc = minute
1340  end if
1341 
1342  full_max = size(output_arrays)
1343 
1344  allocate( int_ingested(full_max/rate_unit_loc), &
1345  int_provided(full_max/rate_unit_loc), &
1346  consumption(full_max/rate_unit_loc) )
1347 
1348  int_ingested = 0
1349  int_provided = 0
1350  consumption = 0.0_srp
1351  ii = 1
1352 
1353  do i = 1 + rate_unit_loc, full_max, rate_unit_loc
1354  int_ingested(ii)=output_arrays(i)%food_items_ingested_total - &
1355  output_arrays(i-rate_unit_loc)%food_items_ingested_total
1356  int_provided(ii)=output_arrays(i)%food_items_encountered - &
1357  output_arrays(i-rate_unit_loc)%food_items_encountered
1358  ii = ii + 1
1359  end do
1360 
1361  ! Calculate rate ingested / provided
1362  where(int_provided > 0)
1363  consumption = real(int_ingested,srp) / real(int_provided,srp)
1364  end where
1365 
1366  end function get_ingestion_ratio_waste
1367 
1368 
1369 end module simulate
Return the last element of a history array with optional offset.
Definition: m_common.f90:792
subroutine detailed_csv_output_write_record(csv_handle, total_columns)
Write the step-wise CSV output record with the actual data. Note that these detailed outputs are prod...
subroutine detailed_csv_output_close(csv_handle)
Close the CSV output file with the detailed step-wise data. Note that these detailed outputs are prod...
subroutine detailed_csv_output_open(file_name, csv_handle, total_columns)
Open the CSV output file with the detailed step-wise data. Note that these detailed outputs are produ...
This module defines global parameters and general-level computational utilities.
Definition: m_common.f90:13
elemental real(srp) function g2kg(g)
Convert g to kg.
Definition: m_common.f90:1885
real(srp), public global_sda_absorp_rate_max
Defines the specific dynamic action (SDA) that depends on the absorption rate. There are two paramete...
Definition: m_common.f90:554
integer, public global_run_model_hours
Default duration of the model run in hours. Note that parameter file uses hours as unit....
Definition: m_common.f90:196
integer, parameter, public hour
Global time constants, number of sec in hour and min.
Definition: m_common.f90:61
real(srp), public global_temperature
Ambient temperature Configuration file example:
Definition: m_common.f90:611
real(srp), public global_sda_factor_max
Defines the specific dynamic action (SDA) that depends on the absorption rate. There are two paramete...
Definition: m_common.f90:566
elemental real(srp) function g2mg(g)
Convert g to mg.
Definition: m_common.f90:1921
integer(long), public global_time_step
Global variable that defines the current time step.
Definition: m_common.f90:86
Module that defines the runtime behaviour of the model.
Definition: m_simulate.f90:15
impure subroutine output_arrays_update_step(this_fish, time_step, temperature)
Update model output arrays output_arrays.
Definition: m_simulate.f90:182
impure subroutine test_run()
The procedure below is TEMPORARY, for testing and debugging.
Definition: m_simulate.f90:935
impure subroutine output_arrays_init(time_steps)
Allocate model output arrays output_arrays.
Definition: m_simulate.f90:132
logical, parameter is_extended_logging_debug_test
Flag for extended/detailed debug logging.
Definition: m_simulate.f90:26
pure integer(long) function total_timesteps(hours)
Calculate the total number of time steps in the model from the number of hours. This in fact converts...
Definition: m_simulate.f90:116
impure subroutine init_provisioning(time_steps)
Initialise the food provisioning schedule / pattern.
logical, parameter, private is_urinal_branchial_kj_day
Flag that defines how urinal and branchial energy loss (UE+ZE) is calculated for model output arrays....
Definition: m_simulate.f90:32
real(srp) function, dimension(:), allocatable get_ingestion_ratio_waste(rate_unit)
calculate the array of the consumption ratio, i.e. eaten/provided, so it is also easy to calculate th...
impure subroutine output_arrays_save_csv(file_name, is_gui_dialog, is_write_error)
Save the model output arrays to a CSV data file.
Definition: m_simulate.f90:376
impure subroutine csv_file_error_report(csv_handle, is_gui_dialog)
Report CSV file write error.
Definition: m_simulate.f90:627
impure integer function, dimension(:), allocatable get_food_schedule_display()
Determine the food schedule array for separate display and analysis The primary role of this function...
integer, public gui_idx_progress
Progress bar widget ID for the GUI mode, needed to update at runtime.
Definition: m_simulate.f90:35
impure subroutine stomach_transport_save_csv(csv_file)
Save the stomach transport data pattern for a single food item.
Definition: m_simulate.f90:639
impure subroutine output_arrays_add_ingested(is_given, is_eaten, time_step, add_eaten)
Update the cumulative count of food items ingested. This cannot normally be done in output_arrays_upd...
Definition: m_simulate.f90:295
character(len=:) function, allocatable model_output_stats_row_csv(show_header)
Produce a text string containing general model output statistics.
Definition: m_simulate.f90:769
type(output_stats_total_def) output_stats
output_stats instantiates non-array global data structure that keeps total model output statistics,...
Definition: m_simulate.f90:109
impure subroutine appetite_function_save_csv(csv_file)
Save the appetite function the_fish::appetite_func() pattern for plotting, testing or analysis.
Definition: m_simulate.f90:662
type(output_arrays_step_def), dimension(:), allocatable, public output_arrays
output_arrays instantiates the global data structure that keeps the model output arrays.
Definition: m_simulate.f90:96
pure character(len=:) function, allocatable model_output_stats_txt()
Produce a text string containing general model output statistics.
Definition: m_simulate.f90:691
impure subroutine output_arrays_save_rate_data_csv(file_name, is_gui_dialog, is_write_error)
Save the rate data arrays to a CSV data file.
Definition: m_simulate.f90:509
This module defines the fish and its components. The model is discrete, time is based on time steps,...
Definition: m_fish.f90:12
integer, parameter, public history_size
The size of the history that saves the fish data back in time.
Definition: m_fish.f90:24
This data structure keeps the output values for each time step. It should normally be instantiated as...
Definition: m_simulate.f90:42
Overall output statistics that are output from the model.
Definition: m_simulate.f90:102
Defines an umbrella class for the complete fish organism An outline of the ::fish class inheritance i...
Definition: m_fish.f90:249