FishMet: Fish feeding and appetite model, OPEN EDITION  0.1
FishMet: Fish feeding and appetite model, OPEN EDITION
m_fish.f90 (16601)
Go to the documentation of this file.
1 !> @file m_fish.f90
2 !! The FishMet Model: Definition of fish 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 !> This module defines the fish and its components.
11 !! The model is discrete, time is based on time steps, in s.
12 module the_fish
13 
14  use realcalc
15  use commondata
16  use base_random, only : rand_uni => rand_r4
17  use base_utils, only : cspline_scalar
18  use environ
19  use def_salmon
20 
21  implicit none
22 
23  !> The size of the history that saves the fish data back in time.
24  integer, parameter, public :: history_size = 20
25 
26  !> This *type* defines history arrays that are saved for the FISH class.
27  type, public :: history_array_fish
28  !> Total number of food items ingested
29  integer, dimension(HISTORY_SIZE) :: total_n_food_ingested
30  !> Total mass of food ingested
31  real(srp), dimension(HISTORY_SIZE) :: total_mass_food_ingested
32  !> Total mass of excrements evacuated
33  real(srp), dimension(HISTORY_SIZE) :: total_mass_evacuated
34  !> Instantaneous absorption history, midgut
35  real(srp), dimension(HISTORY_SIZE) :: food_mass_absorb_curr
36  !> Cumulativa absorption history, midgut
37  real(srp), dimension(HISTORY_SIZE) :: food_mass_absorb_cum
38  !> Current energy balance of the fish, history
39  real(srp), dimension(HISTORY_SIZE) :: energy_balance_curr
40  !> Current body mass, with latest history dynamics.
41  real(srp), dimension(HISTORY_SIZE) :: body_mass_current
42  end type
43 
44  !> This defines the root type for the FISH *class*.
45  !! @dot
46  !! digraph{
47  !! edge [arrowhead = "empty"]
48  !! node [shape = "record", fontname=Arial]
49  !! FISH_SKEL [ label = "{FISH_SKEL|| new() }" ]
50  !! STOMACH [ label = "{STOMACH|| + st_step() }" ]
51  !! MIDGUT [ label = "{MIDGUT|| + mg_step() }" ]
52  !! FISH [ label = "{FISH|| + decide_eat() }" ]
53  !! FISH -> MIDGUT -> STOMACH -> FISH_SKEL
54  !! }
55  !! @enddot
56  type, public :: fish_skel
57  !> ID number of the fish
58  integer :: idnum
59  !> A limited history of past indicators (of size ::history_array_fish)
60  type(history_array_fish) :: history
61 
62  ! Energetics parameters (maybe ti a separate class?)
63  !> Body mass of the fish, g
64  real(srp) :: body_mass0
65 
66  contains
67  !> Initialise an empty fish base. See the fish::fish_init_new_zero().
68  procedure, public :: new => fish_init_new_zero
69  !> Calculate SMR, see the_fish::fish_skel::smr() and the_fish::smr().
71  !> Calculate whole body energy of the fish,
72  !! see the_fish::fish_whole_body_energy_trout()
73  procedure, public :: body_energy => fish_whole_body_energy_trout
74  !> Get the current body mass of the fish, note that this function is
75  !! a shortcut to obtain the last body mass from the history array
76  !! (the_fish::fish_skel::history::body_mass_current).
77  !! See the_fish::fish_body_mass_current_get().
78  procedure, public :: mass => fish_body_mass_current_get
79  end type fish_skel
80 
81  !> Calculate SMR, with generic interface to non-object oriented procedure
82  !> @note Using both the_fish::fish_skel::smr() and the_fish::smr() allows
83  !! to call the same `smr` function with both the_fish::fish class
84  !! objects (e.g. `fish_agent%smr(18.0_SRP)`) and raw data
85  !! (e.g. `smr(6560.0_SRP, 18.0_SRP)`).
86  interface smr
89  end interface
90 
91  !> Calculate stress pattern based on cubic spline interpolation over
92  !! the grid defined by commondata::global_stress_factor_hour and
93  !! commondata::global_stress_fact_suppress.
94  interface stress_factor
95  module procedure stress_suppress_factor_s
96  module procedure stress_suppress_factor_v
97  end interface stress_factor
98 
99  ! This type defines a food items that is within the fish stomach
100  type, public, extends(food_item) :: food_item_eaten
101  !> The time that the food item has spent in the fish stomach
102  integer :: time_in_process
103  !> Ingestion delay in s (time steps) between ingestion of the food item
104  !! by the fish end the start of its ingestion. Water uptake occurs during
105  !! this period.
106  integer :: ingestion_delay
107 
108  contains
109  !> Initialise an **empty** food item when it got eaten by the fish
110  !! See the_fish::food_item_eaten_set_zero_init_state().
111  procedure, public :: zero => food_item_eaten_set_zero_init_state
112  !> Initialise a food item when it got eaten by the fish
113  !! See the_fish::food_item_eaten_eat_init_at_ingest().
114  procedure, public :: init_ingest => food_item_eaten_eat_init_at_ingest
115  !> Update the time a food item spent in the fish gastrointestinal tract.
116  !! See the_fish::food_item_eaten_update_age_in_stomach().
117  procedure, public :: time_update => food_item_eaten_update_age_in_stomach
118  !> Check if the food item in the stomach shrunk to zero mass and
119  !! disappears.
120  !! See the_fish::food_item_eaten_check_destruct().
121  procedure, public :: check_disappear => food_item_eaten_check_destruct
122  end type food_item_eaten
123 
124  type, public, extends(food_item_eaten) :: food_item_eaten_mg
125  !> The starting mass of the food item at the point it is ingested.
126  real(srp) :: mass_0
127  !> The cumulative mass processed (absorbed) in midgut.
128  real(srp) :: absorped
129  !> Duration of the time the food item was in the midgut.
130  integer :: time_in_mg
131  !> Duration of the time since full absorption occurred.
132  integer :: time_absorbed
133  contains
134  procedure, public :: zero => food_item_eaten_mg_set_zero_init_state
135 
136  procedure, public :: is_absorbed_full => food_item_eaten_is_absorbed_full
137 
138  procedure, public :: check_disappear => food_item_eaten_mg_check_destruct
139 
140  procedure, public :: is_evacuate => &
142 
143  end type food_item_eaten_mg
144 
145  !> Defines the stomach of the fish
146  type, public, extends(fish_skel) :: stomach
147  !> Total mass capacity of fish stomach.
148  real(srp) :: mass_stomach
149  !> Number of food items within the stomach of the fish.
150  !! @note Note that commondata::max_food_items_index parameter that
151  !! define the size of the array keeping all food items should be
152  !! big enough to fit all food items.
153  integer :: n_food_items_stomach
154  !> An array of ::food_item_eaten objects representing food items in the
155  !! stomach
156  type(food_item_eaten),dimension(MAX_FOOD_ITEMS_INDEX) :: food_items_stomach
157 
158  contains
159  !> Initialise an empty fish stomach object.
160  !! See the_fish::fish_stomach_init().
161  procedure, public :: st_init => fish_stomach_init
162  !> Update one time step (s) in the fish stomach life cycle.
163  !! See the_fish::fish_stomach_update_step().
164  procedure, public :: st_step => fish_stomach_update_step
165  !> Calculate total mass of food in the fish stomach.
166  !! the_fish::fish_stomach_total_mass_food().
167  procedure, public :: st_food_mass => fish_stomach_total_mass_food
168  !> Calculate the fish appetite factor based on relative stomach fullness.
169  !! the_fish::fish_appetite_factor_stomach().
170  procedure, public :: appetite_stomach => fish_appetite_factor_stomach
171  !> Object-oriented frontend for ::stomach_emptying_time(): Calculate the
172  !! stomach emptying time for a fish with specific body mass at a specific
173  !! temperature. Calculation is based on spline interpolation of
174  !! experimental data.
175  !! See the_fish::fish_stomach_emptying_time().
176  procedure, public :: emptying => fish_stomach_emptying_time
177 
178  end type stomach
179 
180  !> Defines the midgut of the fish
181  type, public, extends(stomach) :: midgut
182  !> Total mass capacity of the fish midgut
183  real(srp) :: mass_midgut
184  !> Number of food items within the midgut of the fish.
185  !! @note Note that commondata::max_food_items_index parameter that
186  !! define the size of the array keeping all food items should be
187  !! big enough to fit all food items.
188  integer :: n_food_items_midgut
189  !> An array of ::food_item_eaten objects representing food items in the
190  !! midgut
191  type(food_item_eaten_mg),dimension(MAX_FOOD_ITEMS_INDEX)::food_items_midgut
192 
193  contains
194  !> Initialise an empty fish stomach object.
195  !! See the_fish::fish_midgut_init().
196  procedure, public :: mg_init => fish_midgut_init
197  !> Update the time the food item spent in the **midgut** of the fish.
198  !! See the_fish::fish_midgut_update_from_stomach().
199  procedure, public :: mg_step => fish_midgut_update_from_stomach
200  !> Calculate the cumulative history of absorption in midgut
201  !! See the_fish::fish_midgut_history_update()
202  procedure, public :: history_update => fish_midgut_history_update
203  !> Calculate the total mass of food in the fish midgut.
204  !! See the_fish::fish_midgut_total_mass_food().
205  procedure, public :: mg_food_mass => fish_midgut_total_mass_food
206  !> Shift food items in the midgut after a new food item is ingested and
207  !! therefore food items are shifted in stomach adding the new item.
208  !! See the_fish::fish_midgut_shift_items_after_new_ingest().
209  procedure, public :: add_midgut=>fish_midgut_shift_items_after_new_ingest
210  !> Calculate the fish appetite factor based on relative midgut fullness.
211  !! See the_fish::fish_appetite_factor_midgut().
212  procedure, public :: appetite_midgut => fish_appetite_factor_midgut
213  !> Calculate instantaneous absorption rate.
214  !! See the_fish::fish_midgut_absorption_rate().
215  procedure, public :: absorption_rate => fish_midgut_absorption_rate
216  !> Appetite factor multiplier based on the total absorption rate.
217  !! See the_fish::fish_midgut_absorption_factor().
218  procedure, public :: absorption_factor => fish_midgut_absorption_factor
219  !> Determine the index of the latest absorption item in the history
220  !! stack array. Note that in most cases the function should return
221  !! commondata::history_size as the history stack is filled with previous
222  !! values. See the_fish::midgut_absorp_history_last_past_idx()
223  procedure, public :: absorp_last_i => midgut_absorp_history_last_past_idx
224  !> Calculate the total mass of food evacuated from the midgut
225  !!see the_fish::fish_midgut_total_mass_evacuated_step()
226  procedure, public :: evacuated_step=>fish_midgut_total_mass_evacuated_step
227  !> Calculate the number of the total mass of food evacuated from the
228  !! midgut after full absorption and evacuation delay (see
229  !! commondata:global_maximum_duration_midgut_min) that occurs at
230  !! one time step.
231  !! See the_fish::fish_midgut_n_evacuated_step()
232  procedure, public :: evacuated_n => fish_midgut_n_evacuated_step
233 
234  end type midgut
235 
236  !> Defines an umbrella class for the complete fish organism
237  !! An outline of the ::fish class inheritance is presented below
238  !! @dot
239  !! digraph{
240  !! edge [arrowhead = "empty"]
241  !! node [shape = "record", fontname=Arial]
242  !! FISH_SKEL [ label = "{FISH_SKEL|| + new() }" ]
243  !! STOMACH [ label = "{STOMACH|| + st_step() }" ]
244  !! MIDGUT [ label = "{MIDGUT|| + mg_step() }" ]
245  !! FISH [ label = "{FISH|| + decide_eat() }" ]
246  !! FISH -> MIDGUT -> STOMACH -> FISH_SKEL
247  !! }
248  !! @enddot
249  type, public, extends(midgut) :: fish
250  contains
251  !> Calculate the baseline locomotor activity of the fish, it is fixed
252  !! to the values of commondata::global_baseline_activity_day and
253  !! commondata::global_baseline_activity_night for day and night
254  !! respectively
255  !! See the_fish::fish_activity_baseline_component().
256  procedure, public :: activity_baseline => fish_activity_baseline_component
257 
258  procedure, public :: activity_appetite => fish_activity_appetite_factor
259 
260  !> Calculate AMR, see the_fish::fish_amr_locomotion_energy_cost()
261  procedure, public :: amr => fish_amr_locomotion_energy_cost
262  !> Calculate and update the current energy balance of the fish.
263  !! See the_fish::fish_energy_balance_update()
264  procedure, public :: energy_update => fish_energy_balance_update
265  !> Calculate energy energy expenditures and O2 uptake
266  !! See the_fish::fish_energy_consumption_step() and
267  !! the_fish::fish_oxygen_consumption_step())
268  procedure, public :: uptake_energy => fish_energy_consumption_step
269  !> Calculate osygen consumption (l) of the fish depending on
270  !! temperature (O2 = O2_SMR + O2_AMR + O2_SDA)
271  !! See the_fish::fish_oxygen_consumption_step()
272  procedure, public :: uptake_o2 => fish_oxygen_consumption_step
273  !> Calculate the scaling factor for SDA (specific dynamic action) that
274  !! depends on the absorption rate. See the_fish::fish_energy_sda_factor()
275  procedure, public :: sda_fact => fish_energy_sda_factor
276  !> Calculate bronchial and urine energy
277  !! see the_fish::fish_energy_branchial_step()
278  procedure, public :: ue_ze => fish_energy_branchial_step
279  !> Calculate appetite factor that depends on the energy balance
280  !! See the_fish::fish_appetite_factor_energy_balance()
281  procedure, public :: appetite_energy=>fish_appetite_factor_energy_balance
282  !> Calculate the overall appetite of the fish, which defines the
283  !! probability to ingest any food item.
284  !! See the_fish::fish_appetite_probability_ingestion().
285  procedure, public :: appetite => fish_appetite_probability_ingestion
286  !> Making decision to eat a single food item that is available.
287  !> See the_fish::fish_decide_eat_food_item_ptr().
288  !! @warning This method must be applied to the top-level object
289  !! hierarchy.
290  procedure, public :: decide_eat => fish_decide_eat_food_item_ptr
291  !> The fish does eat a single food item.
292  !> See the_fish::fish_ingest_food_item().
293  procedure, public :: do_ingest => fish_ingest_food_item
294  !> Grow the fish body mass: increment mass based on energy
295  !! See the_fish::fish_grow_increment_energy()
296  procedure, public :: do_grow => fish_grow_increment_energy
297 
298  end type fish
299 
300  contains !--------------------------------------------------------------------
301 
302  !> Calculate the stomach volume (ml) based on the fish body mass (g)
303  !! using Salgado, A., Salgado, I., & Valdebenito, I. (2018). A direct and
304  !! straightforward method for measurement real maximum fish stomach volume
305  !! to improve aquaculture feeding research. Latin American Journal of
306  !! Aquatic Research, 46(5), 880–889.
307  !! https://doi.org/10.3856/vol46-issue5-fulltext-3
308  elemental function stomach_vol( mass ) result (stomach)
309  !> fish body mass
310  real(srp), intent(in) :: mass
311  real(srp) :: stomach
312 
313  stomach = 0.0007_srp * mass ** 1.829_srp
314 
315  end function stomach_vol
316 
317  !> Initialise an empty ::fish object to an empty zero state.
318  elemental subroutine fish_init_new_zero(this, id_num)
319  class(fish_skel), intent(inout) :: this
320  !> Optional ID number of the fish, default is commondata::unknown
321  integer, optional, intent(in) :: id_num
322  !> Optional appetite factor level of the fish. Default is
323  !! commondata::missing
324 
325  if (present(id_num)) then
326  this%idnum = id_num
327  else
328  this%idnum = unknown
329  end if
330 
331  this%history%food_mass_absorb_curr = missing
332  this%history%food_mass_absorb_cum = missing
333  this%history%energy_balance_curr = missing
334  this%history%body_mass_current = missing
335 
336  this%history%total_n_food_ingested = 0
337  this%history%total_mass_food_ingested = 0.0_srp
338  this%history%total_mass_evacuated = 0.0_srp
339 
340  this%body_mass0 = global_body_mass
341  call add_to_history(this%history%body_mass_current,this%body_mass0)
342 
343  end subroutine fish_init_new_zero
344 
345  !> SMR calculation from Evans 1992 data, *scalar* version
346  pure function fish_smr_temp_bodymass_evan1990_scalar(this, temperature, &
347  is_per_hour, time_step) result(smr_out)
348  class(fish_skel), intent(in) :: this
349  !> Ambient temperature ºC
350  real(srp), intent(in) :: temperature
351  !> Optional flag if calculation is done per hour (default FALSE,
352  !! meaning per one time step, second)
353  logical, optional, intent(in) :: is_per_hour
354  !! Time step, optional parameter.
355  integer(LONG), optional, intent(in) :: time_step
356  !> Standard metabolic rate (SMR) in mg O2 / kg per unit time (s or h)
357  real(srp) :: smr_out
358 
359  logical :: is_hour_loc
360  integer(LONG) :: step_loc
361 
362  if (present(is_per_hour)) then
363  is_hour_loc = is_per_hour
364  else
365  is_hour_loc = .false.
366  end if
367 
368  if (present(time_step)) then
369  step_loc = time_step
370  else
371  step_loc = global_time_step
372  end if
373 
374  smr_out=fish_smr_temp_bodymass_evan1990_value( this%mass(), &
375  temperature, &
376  is_hour_loc, step_loc )
377 
379 
380  !> SMR calculation from Evans 1992 data, *non-object scalar* version
381  pure function fish_smr_temp_bodymass_evan1990_value(body_mass, temperature, &
382  is_per_hour, time_step) result(smr_out)
383  !> Body mass of the fish, kg
384  real(srp), intent(in) :: body_mass
385  !> Ambient temperature ºC
386  real(srp), intent(in) :: temperature
387  !> Optional flag if calculation is done per hour (default FALSE, per
388  !! second)
389  logical, optional, intent(in) :: is_per_hour
390  !! Time step, optional parameter.
391  integer(LONG), optional, intent(in) :: time_step
392  !> Standard metabolic rate (SMR) in mg O2 / kg per unit time (s or h)
393  real(srp) :: smr_out
394 
395  logical :: is_hour_loc
396  integer(LONG) :: step_loc
397 
398  if (present(is_per_hour)) then
399  is_hour_loc = is_per_hour
400  else
401  is_hour_loc = .false.
402  end if
403 
404  if (present(time_step)) then
405  step_loc = time_step
406  else
407  step_loc = global_time_step
408  end if
409 
410  if ( is_hour_loc ) then
411  ! mg O2 kg
412  smr_out = oxygen_rate_std(temperature)*g2kg(body_mass)
413  else
414  ! mg O2 kg per s
415  smr_out = oxygen_rate_std(temperature)*g2kg(body_mass) / real(hour, srp)
416  end if
417 
418  if (is_stress_enable) &
419  smr_out = smr_out + &
420  smr_out * global_stress_cost_smr * stress_suppress(step_loc)
421 
423 
424  !> Calculate the active metabolic rate of fish in units of oxygen
425  !! consumption **per hour**.
426  !! @f[ AMR = a M^{b} U^{c} @f]
427  !!
428  !! See Ohlberger, J., Staaks, G., Van Dijk, P. L. M., & Hölker, F. (2005).
429  !! Modelling energetic costs of fish swimming. Journal of Experimental
430  !! Zoology Part A: Comparative Experimental Biology, 303, 657–664.
431  elemental function amr_swim_basic(fish_mass,swimming_speed,time_unit) &
432  result(amr_h_out)
433  !> Fish mass, g
434  real(srp), intent(in) :: fish_mass
435  !> Fish swimming speed cm/s
436  real(srp), intent(in) :: swimming_speed
437  !> Optional time unit, e.g. commondata::minute or commondata::hour
438  !! The default value is s 1/60 of commondata:::minute
439  integer, intent(in), optional :: time_unit
440  !> Active metabolic rate, mg O2 per `time_unit`
441  !! (equation default commondata::hour)
442  real(srp) :: amr_h_out
443 
444  integer :: time_unit_loc
445 
446  ! default parameters of the AMR model
447  ! TODO: Set new parameters
448  real(srp), parameter :: a = 0.24_srp
449  real(srp), parameter :: b = 0.80_srp
450  real(srp), parameter :: c = 0.60_srp
451 
452  if (present(time_unit)) then
453  time_unit_loc = time_unit
454  else
455  time_unit_loc = 1
456  end if
457 
458  associate( m => fish_mass, u => swimming_speed, amr => amr_h_out )
459 
460  amr = a * m**b * u**c
461 
462  end associate
463 
464  ! We need to adjust the AMR according to the time_unit as the equation
465  ! (with the empirical parameters) calculates per hour
466  amr_h_out = time_unit_loc * amr_h_out/hour
467 
468  end function amr_swim_basic
469 
470  !> Calculate the active metabolic rate. This can be based on
471  !! ::amr_swim_basic() or def_salmon::salmon_oxygen_consumption().
472  elemental function fish_amr_locomotion_energy_cost(this, &
473  temperature, is_exclude_smr, is_per_hour) result (amr_out)
474  class(fish), intent(in) :: this
475  !> Ambient temperature, C
476  real(srp), optional, intent(in) :: temperature
477  !> Opional flag to force exclude SMR (if SMR is included into the equation
478  !! making this function essentially SMR + AMR function).
479  !! Note that SMR and AMR are added in the_fish::fish::energy_update().
480  !! The default value is FALSE.
481  logical, optional, intent(in) :: is_exclude_smr
482  !> Optional flag if calculation is done per hour (default FALSE,
483  !! meaning per one time step, second)
484  logical, optional, intent(in) :: is_per_hour
485  !> Active metabolic rate (AMR), mg O2 / s
486  real(srp) :: amr_out
487 
488  logical :: is_exclude_smr_loc, is_per_hour_loc
489  real(srp) :: current_activity, temp_loc
490 
491  if (present(is_exclude_smr)) then
492  is_exclude_smr_loc = is_exclude_smr
493  else
494  is_exclude_smr_loc = .false.
495  end if
496 
497  if (present(is_per_hour)) then
498  is_per_hour_loc = is_per_hour
499  else
500  is_per_hour_loc = .false.
501  end if
502 
503  if (present(temperature)) then
504  temp_loc = temperature
505  else
506  temp_loc = global_temperature
507  end if
508 
509  current_activity = this%activity_baseline() * this%activity_appetite()
510 
511  if (is_per_hour_loc) then
512  amr_out = salmon_oxygen_consumption( &
513  g2kg(this%mass()), temp_loc, current_activity, &
514  time_unit=hour )
515  else
516  amr_out = salmon_oxygen_consumption( &
517  g2kg(this%mass()), temp_loc, current_activity )
518  end if
519 
520  if (is_exclude_smr_loc) amr_out = amr_out - this%smr(temp_loc)
521 
523 
524  !> Calculate the whole body energy content.
525  elemental function fish_whole_body_energy_trout(this) result (energy_out)
526  class(fish_skel), intent(in) :: this
527  !> Energy content of the body, kJ per whole fish
528  real(srp) :: energy_out
529  ! %% kJ/g
530  real(srp), parameter :: protein_cont=0.15_srp, protein_energy=24.0_srp, &
531  fat_cont =0.23_srp, fat_energy =35.0_srp
532 
533  real(srp) :: protein_fish, fat_fish ! kJ/fish
534 
535  !> @f$ E = M P_c P_e + M F_c F_e @f$
536  protein_fish = this%mass() * protein_cont * protein_energy
537  fat_fish = this%mass() * fat_cont * fat_energy
538 
539  energy_out = protein_fish + fat_fish
540 
541  end function fish_whole_body_energy_trout
542 
543  !> Calculate the body mass from whole body energy.
544  !! @note Note that this procedure is the reverse of
545  !! the_fish::fish_whole_body_energy_trout().
546  elemental function energy2mass( body_energy ) result (mass_get)
547  !> Whole body energy of the fish, kJ
548  real(srp), intent(in) :: body_energy
549  !> Body mass, g
550  real(srp) :: mass_get
551  ! %% kJ/g
552  real(srp), parameter :: protein_cont=0.15_srp, protein_energy=24.0_srp, &
553  fat_cont =0.23_srp, fat_energy =35.0_srp
554 
555  !> @f$ M = \frac {E} { P_c P_e + F_c F_e } @f$
556  mass_get = body_energy / &
557  ( protein_cont * protein_energy + fat_cont * fat_energy )
558 
559  end function energy2mass
560 
561  !> Initialise an empty food item as ingested by the fish. Cleanup and set
562  !! zero state.
563  !! @warning This procedure is by default used as a **destructor**, it sets
564  !! the food item an undefined state (missing, unknown).
565  elemental subroutine food_item_eaten_set_zero_init_state(this, &
566  mass, start_mass, delay)
567  class(food_item_eaten), intent(inout) :: this
568  !> Optional mass of the food item, default is set to
569  !! commondata::global_food_item_mass
570  real(srp), optional, intent(in) :: mass
571 
572  !> Optional starting reference mass of the food item.
573  !! @note Not used here
574  real(srp), optional, intent(in) :: start_mass
575 
576  !> Optional ingestion delay, default is set from the parameter
577  !! commondata::global_ingestion_delay
578  integer, optional, intent(in) :: delay
579 
580  if (present(mass)) then
581  call this%init( mass )
582  else
583  call this%init( missing )
584  end if
585 
586  this%time_in_process = 0
587 
588  if (present(delay)) then
589  this%ingestion_delay = delay
590  else
591  this%ingestion_delay = global_ingestion_delay_min * minute
592  end if
593 
595 
596  !> Initialise an empty food item as ingested by the fish. Cleanup and set
597  !! zero state.
598  !! @warning This procedure is by default used as a **destructor**, it sets
599  !! the food item an undefined state (missing, unknown).
600  elemental subroutine food_item_eaten_mg_set_zero_init_state(this, &
601  mass, start_mass, delay)
602  class(food_item_eaten_mg), intent(inout) :: this
603  !> Optional mass of the food item, default is set to
604  !! commondata::global_food_item_mass
605  real(srp), optional, intent(in) :: mass
606 
607  !> Optional starting reference mass of the food item.
608  real(srp), optional, intent(in) :: start_mass
609 
610  !> Optional ingestion delay, default is set from the parameter
611  !! commondata::global_ingestion_delay
612  integer, optional, intent(in) :: delay
613 
614  ! Local copies of optionals.
615  real(srp) :: mass_loc
616  integer :: delay_loc
617 
618  if (present(mass)) then
619  mass_loc = mass
620  else
621  mass_loc = missing
622  end if
623 
624  if (present(delay)) then
625  delay_loc = delay
626  else
627  delay_loc = global_digestion_delay_min * minute
628  end if
629 
630  ! initialise the stomach components
631  call food_item_eaten_set_zero_init_state(this,mass_loc,missing,delay_loc)
632  !call this%zero(mass_loc, MISSING, delay_loc) ! segmentation fault
633 
634  if (present(start_mass)) then
635  this%mass_0 = start_mass
636  else
637  this%mass_0 = this%mass
638  end if
639 
640  this%absorped = 0.0_srp
641 
642  this%time_in_mg = 0
643 
644  this%time_absorbed = 0
645 
647 
648  !> Initialise a single food item as it is ingested by the fish.
649  !! Note that the ingested food item is copied from the external food item
650  !! environ::food_item that comes as the input argument.
651  elemental subroutine food_item_eaten_eat_init_at_ingest(this, food_item_in, &
652  ingest_delay)
653  class(food_item_eaten), intent(inout) :: this
654  !> The food item object (class) being ingested by the fish.
655  class(food_item), intent(in) :: food_item_in
656  !> Optional ingestion delay, if not provided the default value is
657  !! commondata::global_ingestion_delay.
658  !! @note Ingestion delay is assumed a property of the fish
659  !! gastrointestinal system rather than the food item.
660  integer, optional, intent(in) :: ingest_delay
661 
662  !> - copy all data components from the input argument `food_item_in`
663  !! to `this`. Note that class assignment operator overloading is used
664  !! for `=` assignment with backend defined in
665  !! environ::food_item_copy_assign_to().
666  ! @note The code is equivalent to ` this%mass = food_item_in%mass `
667  ! see notes on ::copy().
668  call this%copy( food_item_in )
669 
670  !> - The time counter of the food item within the gastrointestinal tract
671  !! of the fish is set to zero.
672  !! .
673  this%time_in_process = 0
674 
675  if (present(ingest_delay)) then
676  this%ingestion_delay = ingest_delay
677  else
678  this%ingestion_delay = global_ingestion_delay_min * minute
679  end if
680 
682 
683  !> This procedure updates the time the food item spent in the
684  !! **stomach** of the fish.
685  elemental subroutine food_item_eaten_update_age_in_stomach(this, t_increment)
686  class(food_item_eaten), intent(inout) :: this
687  !> Optional time step increment, default value is 1.
688  integer, optional, intent(in) :: t_increment
689 
690  integer :: inc_loc
691 
692  if (present(t_increment)) then
693  inc_loc = t_increment
694  else
695  inc_loc = 1
696  end if
697 
698  this%time_in_process = this%time_in_process + inc_loc
699 
701 
702  !> Check if the food item mass shrunk to near-zero and destruct it.
703  elemental subroutine food_item_eaten_check_destruct( this, &
704  is_destructed, tolerance, max_time )
705  class(food_item_eaten), intent(inout) :: this
706  !> Optional logical indicator that is set to TRUE if the food item was
707  !! actually destructed.
708  logical, optional, intent(out) :: is_destructed
709  !> Optional numerical tolerance, the smallest value of the food item mass
710  !! that counts as non-zero. Default is set by commondata::min_vol_toler.
711  real(srp), optional, intent(in) :: tolerance
712 
713  !> Maximum time parameter, not used here, for compatibility with the
714  !! respective midgut method
715  integer, optional, intent(in) :: max_time
716 
717  ! Local copy of optional
718  real(srp) :: toler_loc
719 
720  if (present(tolerance)) then
721  toler_loc = tolerance
722  else
723  toler_loc = min_mass_toler
724  end if
725 
726  if ( this%mass < toler_loc ) then
727  call this%zero()
728  if (present(is_destructed)) is_destructed = .true.
729  else
730  if (present(is_destructed)) is_destructed = .false.
731  end if
732 
733  end subroutine food_item_eaten_check_destruct
734 
735  !> Check if the food item has been processed for more than
736  !! commondata::global_maximum_duration_midgut s time in the midgut.
737  elemental subroutine food_item_eaten_mg_check_destruct( this, &
738  is_destructed, tolerance, max_time )
739  class(food_item_eaten_mg), intent(inout) :: this
740  !> Optional logical indicator that is set to TRUE if the food item was
741  !! actually destructed.
742  logical, optional, intent(out) :: is_destructed
743  !> Optional numerical tolerance parameter. Note that it is not used here
744  !! but needed for compatibility with the food_item_eaten::zero() method
745  !! implemented for the base type the_fish::food_item_eaten.
746  real(srp), optional, intent(in) :: tolerance
747 
748  !> Maximum time processed in the midgut, by default all food items that
749  !! have been in the process of absorption for more than this time will
750  !! destructed from midgut and evacuated.
751  integer, optional, intent(in) :: max_time
752 
753  integer :: max_time_loc
754 
755  if (present(max_time)) then
756  max_time_loc = max_time
757  else
758  max_time_loc = global_maximum_duration_midgut_min * minute
759  end if
760 
761  if ( this%is_evacuate(max_time_loc) ) then
762  !> The food item is destructed with the food_item_eaten_mg::zero()
763  !! function.
764  call this%zero()
765  if (present(is_destructed)) is_destructed = .true.
766  else
767  if (present(is_destructed)) is_destructed = .false.
768  end if
769 
770  end subroutine food_item_eaten_mg_check_destruct
771 
772  !> Check if the food item in the midgut has spent for more than the maximum
773  !! time in the midgut after full absorption and should be destructed and
774  !! evacuated (TRUE).
776  max_time) result(is_destruct)
777  class(food_item_eaten_mg), intent(in) :: this
778  !> Maximum time processed in the midgut, by default all food items that
779  !! have been in the process of absorption for more than this time will
780  !! destructed from midgut and evacuated.
781  !! Default value is based on commondata::global_maximum_duration_midgut_min.
782  integer, optional, intent(in) :: max_time
783 
784  logical :: is_destruct
785 
786  integer :: max_time_loc
787 
788  if (present(max_time)) then
789  max_time_loc = max_time
790  else
791  max_time_loc = global_maximum_duration_midgut_min * minute
792  end if
793 
794  if ( this%time_absorbed >= max_time_loc ) then
795  is_destruct = .true.
796  else
797  is_destruct = .false.
798  end if
799 
801 
802  !> Check if the food item has been absorbed to the maximum possible mass
803  elemental function food_item_eaten_is_absorbed_full(this, max_absorb) &
804  result(is_absorbed)
805  class(food_item_eaten_mg), intent(in) :: this
806 
807  real(srp), optional, intent(in) :: max_absorb
808 
809  logical :: is_absorbed
810 
811  real(srp) :: max_absorb_loc
812 
813  check_invalid: if (this%mass_0==missing.or.this%absorped==0.0_srp) then
814  is_absorbed = .false.
815  return
816  end if check_invalid
817 
818  if (present(max_absorb)) then
819  max_absorb_loc = max_absorb
820  else
821  max_absorb_loc = this%mass_0 * global_absorption_ratio
822  end if
823 
824  if ( this%absorped <= max_absorb_loc - min_mass_toler ) then
825  is_absorbed = .false.
826  else
827  is_absorbed = .true.
828  end if
829 
831 
832  !-----------------------------------------------------------------------------
833  !> This function defines the mass of a single food item as it passes
834  !! through the fish stomach.
835  elemental function st_food_item_mass ( time_in_process, dry_mass, &
836  ingestion_delay, water_uptake, rescale ) result (volume_out)
837  !> The time since the food item has been ingested by the fish
838  integer, intent(in) :: time_in_process
839  !> Optional dry mass of the food item, if absent the default value
840  !! commondata::global_food_item_mass is used.
841  real(srp), optional, intent(in) :: dry_mass
842  !> Ingestion delay: the time duration from ingestion of the food item
843  !! until it starts transport into midgut. Water uptake occurs during
844  !! the ingestion delay. Default is commondata::global_ingestion_delay.
845  integer, optional, intent(in) :: ingestion_delay
846  !> The relative mass of water added to the food item after ingestion
847  !! during the ingestion delay. Default is commondata::global_water_uptake.
848  real(srp), optional, intent(in) :: water_uptake
849  !> Optional time rescaling parameter for the stomach transport array
850  real(srp), optional, intent(in) :: rescale
851  !> Returns the mass of the food item.
852  real(srp) :: volume_out
853 
854  ! Local copies of optional arguments
855  real(srp) :: dry_mass_loc, water_uptake_loc, rescale_loc
856  integer :: ingestion_delay_loc
857 
858  ! maximum mass of the food item after water uptake
859  real(srp) :: max_vol
860 
861  ! Process optional parameters, default values are set is absent.
862  if (present(dry_mass)) then
863  dry_mass_loc = dry_mass
864  else
865  dry_mass_loc = global_food_item_mass
866  end if
867 
868  if (present(ingestion_delay)) then
869  ingestion_delay_loc = ingestion_delay
870  else
871  ingestion_delay_loc = global_ingestion_delay_min * minute
872  end if
873 
874  if (present(water_uptake)) then
875  water_uptake_loc = water_uptake
876  else
877  water_uptake_loc = global_water_uptake
878  end if
879 
880  if (present(rescale)) then
881  rescale_loc = rescale
882  else
883  rescale_loc = 1.0_srp
884  end if
885 
886  !> ### Implementation notes ###
887  !> In stomach, the feed that is ingested is passed through two stages:
888  !! - ingestion delay (commondata::global_ingestion_delay) when water
889  !! uptake occurs and the mass of the food item **increases**:
890  !! - passage to midgut where the mass of the food item **decreases**.
891  !! .
892  !!
893  !> The food item is subjected to water uptake. The pattern of water
894  !! uptake over time, the maximum the_fish::food_item_eaten::ingestion_delay
895  !! seconds, is defined by a commondata::logistic() equation:
896  !! @f[ v_t = c_{max} + \frac{c_{max}-c_{0}}{1+a \cdot e^{-r \cdot x}} @f]
897  !! where @f$ c_{0} @f$ is the dry mass of the food item, as defined by
898  !! the parameter commondata::global_food_item_mass, @f$ c_{max} @f$
899  !! is the asymptotic maximum mass of the food item after water intake,
900  !! @f$ a @f$ and @f$ r @f$ are logistic function parameters (see
901  !! commondata::logistic()).
902  !!
903  !> - The asymptotic maximum mass of the food item after water uptake
904  !! @f$ c_{max} @f$ is defined by
905  !! @f[ c_{max} = c_{0} + c_{0} \cdot u @f]
906  !! where @f$ u @f$ is the water uptake parameter
907  !! commondata::global_water_uptake.
908  !! .
909  max_vol = dry_mass_loc + dry_mass_loc * water_uptake_loc
910 
911  !> The value of the function is calculated as follows.
912  !> - If the time the food item spend in the stomach is smaller than the
913  !! ingestion delay (commondata::global_ingestion_delay), its mass
914  !! **increases** through water uptake up to the `max_vol` value
915  !! @f$ c_{max} @f$.
916  if ( time_in_process <= 0 ) then
917  volume_out = global_food_item_mass
918  else if ( time_in_process < ingestion_delay_loc ) then
919  associate( t => real(time_in_process, srp), &
920  cm => max_vol, c0 => dry_mass_loc, &
921  a => global_water_uptake_a, &
922  r => global_water_uptake_r )
923  volume_out = c0 + logistic( t, a, cm-c0, r )
924  end associate
925  !> - If the time the food item spent in stomach is longer than the
926  !! ingestion delay, its mass **decreases** (from the maximum mass
927  !! after water intake) as determined by the interpolation function that
928  !! is determined by the grid:
929  !! - abscissa: commondata::global_transport_pattern_t;
930  !! - ordinate: commondata::global_transport_pattern_r.
931  !! .
932  !! given the time after water intake completed (ingestion delay
933  !! commondata::global_ingestion_delay).
934  !! .
935  else
936  volume_out = &
937  max_vol * &
938  cspline_scalar( real(global_transport_pattern_t, srp)*rescale_loc,&
939  global_transport_pattern_r, &
940  real(time_in_process - ingestion_delay_loc, srp) )
941  end if
942 
943  end function st_food_item_mass
944 
945  !> Initialise an empty fish stomach object.
946  !! @warning Note that the fish itself is not initialised here, it should be
947  !! done with the ::fish::new() method.
948  elemental subroutine fish_stomach_init(this, mass)
949  class(stomach), intent(inout) :: this
950 
951  real(srp), optional, intent(in) :: mass
952 
953  if(present(mass)) then
954  this%mass_stomach = mass
955  else
956  this%mass_stomach = global_stomach_mass
957  end if
958 
959  this%n_food_items_stomach = 0
960 
961  !> Note that at the init, all food items in the stomach are destructed
962  !! with the ::food_item_eaten::zero() method.
963  call this%food_items_stomach%zero()
964 
965  end subroutine fish_stomach_init
966 
967  !> Update one time step of the fish stomach life cycle
968  impure subroutine fish_stomach_update_step(this)
969  class(stomach), intent(inout) :: this
970 
971  ! Note: Fixed array sized to object is not allowed in elemental procedure:
972  ! `logical, dimension( this%n_food_items_stomach ) :: is_destruct`
973  logical, allocatable, dimension(:) :: is_destruct
974 
975  debug_check_max_stom: if (is_debug) then
976  if (this%n_food_items_stomach > &
977  max_food_items_index * debug_warn_level ) then
978  write(*,*) "DEBUG_CHECK_MAX_STOM: N of food items in stomach ", &
979  this%n_food_items_stomach," exceeds ", &
980  nint(max_food_items_index * debug_warn_level)
981  end if
982  if (this%n_food_items_stomach > max_food_items_index) then
983  write(*,*) "DEBUG_CHECK_MAX_STOM: N of food items in stomach ", &
984  this%n_food_items_stomach," exceeds MAX_FOOD_ITEMS_INDEX=",&
985  max_food_items_index
986  stop
987  end if
988  end if debug_check_max_stom
989 
990  allocate( is_destruct(this%n_food_items_stomach) )
991 
992  is_destruct = .false.
993 
994  !> ### Implementation notes ###
995  associate( stom_foods &
996  => this%food_items_stomach(1:this%n_food_items_stomach) )
997 
998  !> First, the time counter for each of the existing (non-zero)
999  !! `n_food_items_stomach` food item (`time_in_process`) is updated, by
1000  !! default incremented by 1.
1001  call stom_foods%time_update()
1002 
1003  !> Second, the mass of each food item in stomach is recalculated
1004  !! according to its individual `time_in_process` counter.
1005  stom_foods%mass = st_food_item_mass( stom_foods%time_in_process, rescale=stomach_adjust() )
1006 
1007  !> Check if the food items shrunk below the minimum size and should then
1008  !! disappear (be destructed). The `is_destruct` boolean indicators show
1009  !! how many food items should be destructed
1010  call stom_foods%check_disappear(is_destructed=is_destruct)
1011  this%n_food_items_stomach = this%n_food_items_stomach - count(is_destruct)
1012 
1013  end associate
1014 
1015  !> In the debug mode, also check and fix counter for negative values.
1016  if (is_debug) then
1017  if ( this%n_food_items_stomach < 0 ) this%n_food_items_stomach = 0
1018  if ( this%n_food_items_stomach >= max_food_items_index ) &
1019  this%n_food_items_stomach = max_food_items_index
1020  end if
1021 
1022  end subroutine fish_stomach_update_step
1023 
1024  !> This procedure shows what happens when the fish eats a single food item.
1025  elemental subroutine fish_ingest_food_item(this, food_item_ingested)
1026  class(fish), intent(inout) :: this
1027  !> An environ::food_item class object that represents the food item
1028  !! being ingested.
1029  class(food_item), intent(in) :: food_item_ingested
1030 
1031  type(food_item_eaten) :: new_food_item_in
1032 
1033  !> - Individual totals are updated: N of food items ingested and the
1034  !! total mass of food ingested.
1035  call add_to_history( this%history%total_n_food_ingested, &
1036  last(this%history%total_n_food_ingested) + 1 )
1037 
1038  call add_to_history( this%history%total_mass_food_ingested, &
1039  last(this%history%total_mass_food_ingested) + &
1040  food_item_ingested%mass )
1041 
1042  !> - The newly ingested food item object is initialised, data structure
1043  !! is copied from the input argument food_item object. Ingestion delay
1044  !! is set default.
1045  call new_food_item_in%init_ingest( food_item_ingested )
1046 
1047  !> - The food item is then added to the stack array of the fish
1048  !! stomach. It takes the first place shifting all other food items in
1049  !! sequence.
1050  this%food_items_stomach(2:this%n_food_items_stomach+1) = &
1051  this%food_items_stomach(1:this%n_food_items_stomach)
1052 
1053  this%food_items_stomach(1) = new_food_item_in
1054 
1055  !> - The food items counter is incremented.
1056  this%n_food_items_stomach = this%n_food_items_stomach + 1
1057 
1058  !> - Finally, whenever the food is eaten, initialise it in the midgut.
1059  call this%add_midgut( food_item_ingested )
1060 
1061  end subroutine fish_ingest_food_item
1062 
1063  !> Calculate the total mass of food in the fish stomach.
1064  elemental function fish_stomach_total_mass_food(this, tolerance) &
1065  result(total_mass)
1066  class(stomach), intent(in) :: this
1067  !> Optional numerical tolerance, the smallest value of the food item mass
1068  !! that counts as non-zero. Default is set by commondata::min_vol_toler.
1069  real(srp), optional, intent(in) :: tolerance
1070  !> Total mass of food in the stomach.
1071  real(srp) :: total_mass
1072 
1073  ! Local copy of optional
1074  real(srp) :: toler_loc
1075 
1076  if (present(tolerance)) then
1077  toler_loc = tolerance
1078  else
1079  toler_loc = min_mass_toler
1080  end if
1081 
1082  !> The total value is calculated as an array sum to the total number of
1083  !! food items being kept in the stomach (`this%n_food_items_stomach`).
1084  associate( foods_stomach &
1085  => this%food_items_stomach(1:this%n_food_items_stomach) )
1086  total_mass = sum( foods_stomach%mass, &
1087  foods_stomach%mass > toler_loc .and. &
1088  foods_stomach%mass /= missing )
1089  end associate
1090 
1091  end function fish_stomach_total_mass_food
1092 
1093  !> Calculate the fish appetite factor based on the relative stomach fullness.
1094  !! Appetite factor is equivalent to the probability of consuming any food
1095  !! item.
1096  elemental function fish_appetite_factor_stomach(this, fcapacity) &
1097  result(appetite)
1098  class(stomach), intent(in) :: this
1099  real(srp), optional, intent(in) :: fcapacity
1100  real(srp) :: appetite
1101 
1102  real(srp) :: fcapacity_loc
1103 
1104  real(srp) :: mass_relative
1105 
1106  if (present(fcapacity)) then
1107  fcapacity_loc = fcapacity
1108  else
1109  fcapacity_loc = global_stomach_mass
1110  end if
1111 
1112  !> ### Implementation notes ###
1113  !! The appetite factor ranges between (0 and 1) and is based on the
1114  !! relative filling capacity. Here relative filling capacity @f$ c_r @f$
1115  !! is calculated as the ratio of the total mass of food in the stomach
1116  !! @f$ c_{max} @f$ to the maximum filling capacity @f$ c_t @f$
1117  !! @f[ c_r = \frac{c_t}{c_{max}} @f]
1118  mass_relative = this%st_food_mass()/fcapacity_loc
1119 
1120  !> Given the relative filling capacity @f$ c_r @f$, appetite factor
1121  !! that ranges from 0 to 1 is calculated as logistic function
1122  !! ::appetite_func().
1123  !!
1124  !! The @f$ a @f$ and @f$ r @f$ logistic parameters are defined by the
1125  !! commondata::global_appetite_logist_a and
1126  !! commondata::global_appetite_logist_r parameters.
1127  !!
1128  !! *gnuplot code:*
1129  !! @verbatim
1130  !! set xrange [0:1]
1131  !! plot 1 - 1/(1+500000*exp(-20*x))
1132  !! @endverbatim
1133  appetite = appetite_func( mass_relative, global_appetite_logist_a, &
1134  global_appetite_logist_r )
1135 
1136  end function fish_appetite_factor_stomach
1137 
1138 
1139  !> Initialise an empty fish midgut object.
1140  !! @warning Note that the fish itself is not initialised here, it should be
1141  !! done with the ::fish::new() method.
1142  elemental subroutine fish_midgut_init(this, mass)
1143  class(midgut), intent(inout) :: this
1144 
1145  real(srp), optional, intent(in) :: mass
1146 
1147  if(present(mass)) then
1148  this%mass_midgut = mass
1149  else
1150  this%mass_midgut = global_midgut_mass
1151  end if
1152 
1153  this%n_food_items_midgut = 0
1154 
1155  !> Note that at the init, all food items in the stomach are destructed
1156  !! with the ::food_item_eaten::zero() method.
1157  call this%food_items_midgut%zero()
1158 
1159  end subroutine fish_midgut_init
1160 
1161  !> This procedure processes the food item in the **midgut** of the fish.
1162  impure subroutine fish_midgut_update_from_stomach(this,dry_mass,t_increment)
1163  class(midgut), intent(inout) :: this
1164  !> Optional dry mass of the food item, if absent the default value
1165  !! commondata::global_food_item_mass is used.
1166  real(srp), optional, intent(in) :: dry_mass
1167  !> Optional time step increment, default value is 1.
1168  integer, optional, intent(in) :: t_increment
1169 
1170  ! Local copies of optional arguments
1171  real(srp) :: dry_mass_loc
1172  integer :: inc_loc
1173 
1174  integer :: i
1175 
1176  ! Absorption variables: absorption increment and the mass of the food
1177  ! prior to absorption
1178  real(srp) :: absorbed_i , mass_0
1179 
1180  ! Minimum mass of a food item at transferred to the midgut when the
1181  ! timer counting the duration of the time spent in the midgut starts.
1182  ! See commondata::min_vol_toler for details.
1183  real(srp), parameter :: threshold_min_vol = min_mass_toler
1184 
1185  ! An array of food item volumes that transits to midgut from stomach at
1186  ! the current time step, the delta
1187  real(srp), dimension(MAX_FOOD_ITEMS_INDEX) :: delta_vol
1188 
1189  ! Note: Fixed array sized to object is not allowed in elemental procedure:
1190  ! `logical, dimension( this%n_food_items_stomach ) :: is_destruct`
1191  logical, allocatable, dimension(:) :: is_destruct
1192 
1193  ! This debugging check is conducted to make sure the maximum number
1194  ! of food items in the gastrointestinal system is never exceeded.
1195  ! Whenever it exceeds commondata::debug_warn_level of the maximum, a
1196  ! warning message is issued.
1197  debug_check_max_midgut: if (is_debug) then
1198  if (this%n_food_items_midgut > &
1199  max_food_items_index * debug_warn_level ) then
1200  write(*,"(a,i4,a,i4)") &
1201  "DEBUG_CHECK_MAX_MIDGUT: N of food items in midgut ", &
1202  this%n_food_items_midgut," exceeds ", &
1203  nint(max_food_items_index * debug_warn_level)
1204  end if
1205  if (this%n_food_items_midgut > max_food_items_index) then
1206  write(*,"(a,i4,a,i4)") &
1207  "DEBUG_CHECK_MAX_MIDGUT: N of food items in midgut ", &
1208  this%n_food_items_midgut, " exceeds MAX_FOOD_ITEMS_INDEX=",&
1209  max_food_items_index
1210  stop
1211  end if
1212  end if debug_check_max_midgut
1213 
1214  allocate( is_destruct(this%n_food_items_midgut) )
1215  is_destruct = .false.
1216  delta_vol = missing
1217 
1218  ! Process optional parameters, default values are set is absent.
1219  if (present(dry_mass)) then
1220  dry_mass_loc = dry_mass
1221  else
1222  dry_mass_loc = global_food_item_mass
1223  end if
1224 
1225  if (present(t_increment)) then
1226  inc_loc = t_increment
1227  else
1228  inc_loc = 1
1229  end if
1230 
1231  !> ### Implementation notes ###
1232  !> #### Transfer to midgut ####
1233  !> Each food item smoothly transfers from the stomach to the midgut, which
1234  !! is implemented as removing a small proportion if its mass with
1235  !! simultaneous addition of the same mass to the linked midgut data
1236  !! component.
1237  !!
1238  !! First, for each valid food item in the stomach, calculate the difference
1239  !! between mass of the food item in stomach at the previous time step
1240  !! *t-1* and the current step *t*: @f$ \Delta v_{i} @f$ (`delta_vol`).
1241  !! @f[ \Delta v_{i} = S_{i-1} - S_{i} @f]
1242  !! where @f$ S_{i} @f$ is the mass of the *i*-th food item in the stomach.
1243  !! This difference is equal to the mass increment that transfers to
1244  !! the midgut.
1245  !!
1246  !! This increment is set to zero for all food items that stayed in the
1247  !! stomach for less than the `ingestion_delay` duration (this period is
1248  !! water uptake, no transfer, see stomach::st_step()).
1249  associate(stom_foods => &
1250  this%food_items_stomach(1:this%n_food_items_stomach))
1251 
1252  where ( stom_foods%time_in_process > stom_foods%ingestion_delay .and. &
1253  stom_foods%time_in_process /= unknown )
1254  delta_vol(1:this%n_food_items_stomach) = &
1255  st_food_item_mass(stom_foods%time_in_process-1, dry_mass_loc, rescale=stomach_adjust() ) - &
1256  st_food_item_mass(stom_foods%time_in_process, dry_mass_loc, rescale=stomach_adjust() )
1257  elsewhere
1258  delta_vol(1:this%n_food_items_stomach) = 0.0_srp
1259  end where
1260 
1261  end associate
1262 
1263  !> The increment @f$ \Delta v_{i} @f$ (`delta_vol`) is here also set
1264  !! to zero for all food items that have transferred fully from the
1265  !! stomach to midgut.
1266  delta_vol(this%n_food_items_stomach+1:this%n_food_items_midgut) = 0.0_srp
1267 
1268  !> Second, the mass of each food item already in the midgut is
1269  !! augmented by the respective increment @f$ \Delta v_{i} @f$.
1270  !! @f[ V_{i} + \Delta v_{i} @f]
1271  !! The age of each food item (`time_in_process` data component) in the
1272  !! midgut is also incremented by one (i.e. discretization period, s).
1273  associate( midgut_foods => &
1274  this%food_items_midgut(1:this%n_food_items_midgut) )
1275 
1276  midgut_foods%mass = midgut_foods%mass + &
1277  delta_vol(1:this%n_food_items_midgut)
1278  midgut_foods%time_in_process = midgut_foods%time_in_process + inc_loc
1279 
1280  !> The timer for the duration spent in the midgut is also incremented.
1281  where ( midgut_foods%mass >= threshold_min_vol .and. &
1282  delta_vol > 0.0_srp )
1283  midgut_foods%time_in_mg = midgut_foods%time_in_mg + 1
1284  end where
1285 
1286  end associate
1287 
1288  !> #### Absorption ####
1289  !> The **absorption** processis this: certain proportion of the mass of
1290  !! each food item in the midgut is subtracted following the equation:
1291  !! @f[ V_{i} - V_{i} \frac{r_{max} \sum V{i}}{K_{MM} + \sum V{i}} @f]
1292  !! where @f$ r_{max} @f$ and @f$ K_{MM} @f$ are the Michaelis-Menten
1293  !! equation parameters: the maximum rate and the K constant
1294  !! (see commondata::michaelis_menten() for more details). Here
1295  !! @f$ \sum V{i} @f$ is the total mass of food in the midgut.
1296  !!
1297  !! Only the food items that stay in the midgut for more than the
1298  !! duration defined by commondata::global_digestion_delay_min are subject
1299  !! to absorption. Also, there is a maximum limit on the absorption set
1300  !! by the commondata::global_absorption_ratio model parameter. This limit
1301  !! is checked in the food_item_eaten_mg::is_absorbed_full() method.
1302  !!
1303  !! @note Note that each food item in the midgut is subjected to
1304  !! Michaelis-Menten absorption depending on the **total** mass
1305  !! of food in the midgut @f$ \sum V{i} @f$.
1306  do_absorp: do i=this%n_food_items_stomach+1, this%n_food_items_midgut
1307 
1308  associate( midgut_foods => this%food_items_midgut(i), &
1309  r => this%mg_food_mass() / this%mass_midgut, &
1310  rmax => global_mid_gut_mm_r_max, &
1311  km => global_mid_gut_mm_k_m )
1312 
1313  ! Time counter in midgut is incremented for all absorping food items
1314  midgut_foods%time_in_mg = midgut_foods%time_in_mg + 1
1315 
1316  debug_check_full_midgut_delta: if (is_debug) then
1317  if ( delta_vol(i) > 0.0_srp ) then
1318  write(*,*) "DEBUG_CHECK_FULL_MIDGUT_DELTA: `delta_vol` nonzero [",&
1319  i, "], ", delta_vol(i), ", certainly eror"
1320  end if
1321  end if debug_check_full_midgut_delta
1322 
1323  if ( (midgut_foods%time_in_mg > midgut_foods%ingestion_delay) .and. &
1324  (.not. midgut_foods%is_absorbed_full()) ) then
1325 
1326  mass_0 = midgut_foods%mass
1327  absorbed_i = mass_0 * michaelis_menten( r, rmax, km )
1328 
1329  midgut_foods%mass = midgut_foods%mass - absorbed_i * &
1330  midgut_temp_factor(global_temperature)
1331 
1332  if ( midgut_foods%mass < midgut_foods%mass_0 - &
1333  midgut_foods%mass_0 * global_absorption_ratio ) then
1334 
1335  midgut_foods%mass = midgut_foods%mass_0 - &
1336  midgut_foods%mass_0 * global_absorption_ratio
1337 
1338  midgut_foods%absorped = midgut_foods%mass_0*global_absorption_ratio
1339 
1340  else
1341 
1342  midgut_foods%absorped = &
1343  min( midgut_foods%mass_0 * global_absorption_ratio, &
1344  midgut_foods%absorped + &
1345  ( mass_0 - midgut_foods%mass ) )
1346  end if
1347 
1348  end if
1349 
1350  end associate
1351 
1352  end do do_absorp
1353 
1354  debug_digest_checks: if (is_debug) then
1355  associate( midgut_foods => &
1356  this%food_items_midgut(1:this%n_food_items_midgut) )
1357  if (any(midgut_foods%ingestion_delay/=global_digestion_delay_min &
1358  * minute)) then
1359  write(*,*) "DEBUG_DIGEST_CHECKS: midgut digestion delay mismatch: ",&
1360  global_digestion_delay_min, midgut_foods%ingestion_delay
1361  stop 255
1362  end if
1363  if ( any(midgut_foods%absorped > &
1364  midgut_foods%mass_0 * global_absorption_ratio ) ) then
1365  write(*,*) "DEBUG_DIGEST_CHECKS: exceed absorption MAX ratio at ", &
1366  global_time_step , " step, count ", &
1367  count(midgut_foods%absorped > &
1368  midgut_foods%mass_0 * global_absorption_ratio ), &
1369  ", total Ns ", this%n_food_items_stomach, "/", &
1370  this%n_food_items_midgut, " stomach/midgut"
1371  end if
1372  end associate
1373  end if debug_digest_checks
1374 
1375  !> Finally, the food_item_eaten_mg::check_disappear() method is called for
1376  !! each food item in the midgut that has fully transferred from
1377  !! the stomach. This checks if the item has been processed in the midgut
1378  !! or more than commondata::global_maximum_duration_midgut_min. Those food
1379  !! items are deleted from the midgut and are excreted.
1380  associate( foods_midgut_not_stom => &
1381  this%food_items_midgut( &
1382  this%n_food_items_stomach+1:this%n_food_items_midgut) )
1383 
1384  !> The time counter for the time since full absorption (`time_absorbed`
1385  !! data component) also updates (incremented by 1) for all food items
1386  !! that are fully absorbed.
1387  where ( foods_midgut_not_stom%is_absorbed_full() )
1388  foods_midgut_not_stom%time_absorbed = &
1389  foods_midgut_not_stom%time_absorbed + 1
1390  end where
1391 
1392  debug_digest_disappear: if ( is_debug ) then
1393  if ( any( foods_midgut_not_stom%time_absorbed > &
1394  global_maximum_duration_midgut_min * minute ) ) then
1395  write(*,*) "DEBUG_DIGEST_DISAPPEAR: must remove ", &
1396  count( foods_midgut_not_stom%time_absorbed > &
1397  global_maximum_duration_midgut_min * minute ),&
1398  " at time ", global_time_step
1399  end if
1400  end if debug_digest_disappear
1401 
1402  !> Update the individual totals for the mass of food evacuated.
1403  call add_to_history( this%history%total_mass_evacuated, &
1404  last(this%history%total_mass_evacuated) + &
1405  this%evacuated_step() )
1406 
1407 
1408  !> Check if the food items must be evacuated from the midgut, disappear
1409  call foods_midgut_not_stom%check_disappear( is_destructed=is_destruct )
1410 
1411  !> The count of the food items in the midgut is updated after reduction
1412  !! at the previous step.
1413  this%n_food_items_midgut = this%n_food_items_midgut-count( is_destruct )
1414 
1415  debug_check_subzero_food: if (is_debug) then
1416  if ( any( foods_midgut_not_stom%mass < 0.00000001_srp .and. &
1417  foods_midgut_not_stom%mass /= missing ) ) then
1418  write(*,*) "DEBUG_CHECK_SUBZERO_FOOD: midgut food items are " // &
1419  "suspiciously small"
1420  write(*,*) " ", foods_midgut_not_stom%mass
1421  end if
1422 
1423  end if debug_check_subzero_food
1424 
1425  end associate
1426 
1427  ! Calculate the cumulative history of absorption in midgut
1428  call this%history_update()
1429 
1430  end subroutine fish_midgut_update_from_stomach
1431 
1432  !> Calculate and update the current energy balance of the fish. Note that
1433  !! the energy balance is kept in the history array
1434  !! the_fish::fish_skel::history::energy_balance_curr.
1435  elemental subroutine fish_energy_balance_update (this, temperature, start_value)
1436  class(fish), intent(inout) :: this
1437  !> Optional current ambient temperature, if the parameter absent, use
1438  !! the global default commondata::global_temperature.
1439  real(srp), optional, intent(in) :: temperature
1440  !> Optional start value of the energy balance, if the parameter is absent,
1441  !! the nefault value oz zero is used
1442  real(srp), optional, intent(in) :: start_value
1443 
1444  integer :: hist_length, absorb_last_item
1445  real(srp) :: absorp_increment
1446 
1447  real(srp) :: temp_loc, start_loc
1448 
1449  real(srp), parameter :: balance_start = 0.0_srp ! starting energy balance
1450  real(srp) :: balance_current
1451 
1452  if (present(temperature)) then
1453  temp_loc = temperature
1454  else
1455  temp_loc = global_temperature
1456  end if
1457 
1458  if (present(start_value)) then
1459  start_loc = start_value
1460  else
1461  start_loc = balance_start
1462  end if
1463 
1464  balance_current = temp_loc
1465 
1466  hist_length = size(this%history%food_mass_absorb_cum) ! HISTORY_SIZE
1467 
1468  ! The history is initialized to commondata::missing values, so it is easy
1469  ! to determine what is the last valid item in the history stack array.
1470  absorb_last_item = this%absorp_last_i()
1471 
1472  !> ### Implementation notes
1473  !!
1474  !! @f[ E_{i+1} = E_{i} + F(\Delta a) - E_{SMR} - E_{AMR} , @f]
1475  !! where @f$ E_{i} @f$ is the energy balance of the fish at time @f$ i @f$
1476  !! (history array: the_fish::history_array_fish::energy_balance_curr),
1477  !! @f$ \Delta a @f$ is the energy that came from increment in the food
1478  !! absorption @f$ a @f$, @f$ E_{SMR} @f$ is the energetic equivalent
1479  !! of the standard metabolic rate based on the_fish::fish_skel::smr(),
1480  !! and @f$ E_{AMR} @f$ is the energetic equivalent of the active metabolic
1481  !! rate bsed on the_fish::fish_skel::amr().
1482  if ( absorb_last_item == 1 ) then
1483  call add_to_history(this%history%energy_balance_curr, start_loc - &
1484  energy_o2(o2vol(mg2g( this%smr(temp_loc) ))) )
1485  else
1486  ! Cumulative absorption increment is obtained from history stack
1487  absorp_increment = this%history%food_mass_absorb_cum(hist_length) - &
1488  this%history%food_mass_absorb_cum(hist_length-1)
1489 
1490  balance_current = this%history%energy_balance_curr(hist_length) &
1491  + feed_energy(absorp_increment) &
1492  - this%uptake_energy(temp_loc)
1493 
1494  call add_to_history( this%history%energy_balance_curr, balance_current )
1495  end if
1496 
1497  end subroutine fish_energy_balance_update
1498 
1499  !> Calculate urinal (UE) and branchial energy (ZE) as a proportion of
1500  !! the SMR
1501  elemental function fish_energy_branchial_step(this, temperature, is_oxygen) &
1502  result(ue_ze)
1503  class(fish), intent(in) :: this
1504  !> Optional current ambient temperature, if the parameter absent, use
1505  !! the global default commondata::global_temperature.
1506  real(srp), optional, intent(in) :: temperature
1507  !> Optional logical flag that defines that oxygen consumption (mass, g)
1508  !! rather than energy is output, default is FALSE (energy is calculated)
1509  !! @note Note that oxygen consumption in case of `is_oxygen=TRUE` is
1510  !! output as mass in g, NOT volume.
1511  logical, optional, intent(in) :: is_oxygen
1512  real(srp) :: ue_ze
1513 
1514  real(srp) :: temp_loc
1515  logical :: set_is_oxygen
1516 
1517  if (present(temperature)) then
1518  temp_loc = temperature
1519  else
1520  temp_loc = global_temperature
1521  end if
1522 
1523  if (present(is_oxygen)) then
1524  set_is_oxygen = is_oxygen
1525  else
1526  set_is_oxygen = .false.
1527  end if
1528 
1529  if (set_is_oxygen) then
1530  ue_ze = mg2g(this%smr(temp_loc)) * global_ue_ze_factor
1531  else
1532  if (global_is_ue_ze_fixed_rate) then
1533  ! Test fixed N mass based on Forsberg 1996: 36 mg TAN kg fish day
1534  ! Forsberg, O.I., 1997. The impact of varying feeding regimes on
1535  ! oxygen consumption and excretion of carbon dioxide and nitrogen in
1536  ! post-smolt Atlantic salmon Salmo salar L. Aquac Research 28, 29–41.
1537  ! https://doi.org/10.1046/j.1365-2109.1997.00826.x
1538  !ue_ze=
1539  ! branchial_nitrogen_to_energy(0.036_SRP*g2kg(this%mass())/(HOUR*24))
1540  ue_ze = &
1542  nitrogen_mass( &
1543  from_micro(global_ue_ze_ammonia_excretion) ) &
1544  *this%mass()/hour )
1545  else
1546  ue_ze = energy_o2(o2vol(mg2g(this%smr(temp_loc)))) * global_ue_ze_factor
1547  end if
1548  end if
1549 
1550  end function fish_energy_branchial_step
1551 
1552  !> Calculate the mass of ammonia, mol to g
1553  elemental function nitrogen_mass(mol, is_ammonia) result(gram)
1554  real(srp), parameter :: ammonia_molar_mass=17.03052_srp ! 17.03052 g/mol
1555  real(srp), parameter :: nitrogen_molar_mass=14.006747_srp ! 14.006747 g/mol
1556  !> Amount in mol
1557  real(srp), intent(in) :: mol
1558  !> Optional flag indicating that
1559  logical, intent(in), optional :: is_ammonia
1560  real(srp) :: gram
1561  logical :: use_ammonia
1562 
1563  if (present(is_ammonia)) then
1564  use_ammonia = is_ammonia
1565  else
1566  use_ammonia = .false.
1567  end if
1568 
1569  if (use_ammonia) then
1570  gram = mol * ammonia_molar_mass
1571  else
1572  gram = mol * nitrogen_molar_mass
1573  end if
1574 
1575  end function nitrogen_mass
1576 
1577  !> Calculate the branchal and urinary energy loss from branchial and
1578  !! urinary nitrogen loss.
1579  !! See Bureau, D.P., Kaushik, S.J., Cho, C.Y. (2002) Bioenergetics.
1580  !! In Hardy, R.W., Halver, J.E., eds. Fish Nutrition, 3 ed
1581  !! Academic Press, San Diego, CA, USA (pp 1–59):
1582  !!
1583  !! <<Because most nitrogen losses are as ammonia, and the difference in
1584  !! the amount of energy loss per gram of nitrogen between ammonia and
1585  !! urea is small, it has been proposed that the loss of1gofnitrogen by
1586  !! fish under normal conditions can be equated to an energy loss
1587  !! of 24.9 kJ.>> (p.21)
1588  !!
1589  !! see also
1590  !! Saravanan, S., Schrama, J. W., Figueiredo-Silva, A. C.,
1591  !! Kaushik, S. J., Verreth, J. A. J., & Geurden, I. (2012). Constraints on
1592  !! Energy Intake in Fish: The Link between Diet Composition, Energy
1593  !! Metabolism, and Energy Intake in Rainbow Trout. PLoS ONE, 7(4), e34743.
1594  !! https://doi.org/10.1371/journal.pone.0034743
1595  elemental function branchial_nitrogen_to_energy(excreted_nitrogen, is_kg) &
1596  result(bue)
1597  !> Branchial and urinary nitrogen loss, g
1598  real(srp), intent(in) :: excreted_nitrogen
1599  !> Optional flag indicating that excreted nitrogen loss is given in kg
1600  logical, optional, intent(in) :: is_kg
1601  !> Energy loss kJ
1602  real(srp) :: bue
1603  logical :: is_kg_loc
1604  !> Energy equivalent kJ of 1 g excreted nitrogen NH3-N
1605  real(srp), parameter :: energ_g_nitro = 24.85_srp
1606 
1607  if (present(is_kg)) then
1608  is_kg_loc = is_kg
1609  else
1610  is_kg_loc = .false.
1611  end if
1612 
1613  bue = excreted_nitrogen * energ_g_nitro
1614 
1615  if (is_kg_loc) bue = bue / 1000.0_srp
1616 
1617  end function branchial_nitrogen_to_energy
1618 
1619  !> Calculate *total energy, kJ consumption* of the fish depending on the
1620  !! temperature E = SMR + AMR + (UE+ZE) + SDA
1621  !! Public interface: the_fish::uptake_energy().
1622  !!
1623  !! @note This function should be adapted together with the oxygen
1624  !! consumption code ::fish_oxygen_consumption_step().
1625  elemental function fish_energy_consumption_step(this, temperature, sda_off) &
1626  result(kj_out)
1627  class(fish), intent(in) :: this
1628  real(srp), optional, intent(in) :: temperature
1629  !> Optional logical switch that sets SDA component OFF, by default FALSE,
1630  !! intended for use mainly for debugging and testing.
1631  logical, optional, intent(in) :: sda_off
1632  real(srp) :: kj_out
1633 
1634  real(srp) :: temp_loc
1635  logical :: sda_off_debug
1636 
1637  if (present(temperature)) then
1638  temp_loc = temperature
1639  else
1640  temp_loc = global_temperature
1641  end if
1642 
1643  if (present(sda_off)) then
1644  sda_off_debug = sda_off
1645  else
1646  sda_off_debug = .false.
1647  end if
1648 
1649  !! @f[ e = E_{SMR} + E_{AMR} + (E_{UE}+E_{ZE}) + E_{SDA} , @f]
1650  kj_out = energy_o2(o2vol(mg2g(this%smr(temp_loc)))) + & ! SMR
1651  energy_o2(o2vol(mg2g(this%amr(temp_loc)))) + & ! AMR
1652  this%ue_ze(temp_loc) ! UE+ZE
1653 
1654  if (.NOT. sda_off_debug) then
1655  kj_out = kj_out + &
1656  energy_o2(o2vol(mg2g(this%smr(temp_loc)))) * & ! SDA
1657  this%sda_fact(global_sda_absorp_rate_max, &
1658  global_sda_factor_max)
1659  end if
1660 
1661  end function fish_energy_consumption_step
1662 
1663  !> Calculate *total oxygen consumption* (l) of the fish depending on the
1664  !! temperature O2 = O2_SMR + O2_AMR + O2_{UE+ZE} O2_SDA
1665  !! @note This function should be adapted together with the energy
1666  !! consumption code ::fish_energy_consumption_step().
1667  elemental function fish_oxygen_consumption_step(this, temperature, &
1668  is_mass, sda_off) result (o2_out)
1669  class(fish), intent(in) :: this
1670  real(srp), optional, intent(in) :: temperature
1671  !> Optional logical switch, if TRUE, determining that oxygen consumption is
1672  !! calculated as mass (g), the default is volume (l)
1673  logical, optional, intent(in) :: is_mass
1674  !> Optional logical switch that sets SDA component OFF, by default FALSE,
1675  !! intended for use mainly for debugging and testing.
1676  logical, optional, intent(in) :: sda_off
1677  real(srp) :: o2_out
1678 
1679  ! Is UE+ZE equivalent O2 included in consumption, default is NO
1680  ! The value TRUE only makes sense if Global_IS_UE_ZE_Fixed_Rate is FALSE
1681  logical, parameter :: is_include_ue_ze = .false.
1682 
1683  real(srp) :: temp_loc
1684  logical :: is_mass_g, sda_off_debug
1685 
1686  if (present(temperature)) then
1687  temp_loc = temperature
1688  else
1689  temp_loc = global_temperature
1690  end if
1691 
1692  if (present(sda_off)) then
1693  sda_off_debug = sda_off
1694  else
1695  sda_off_debug = .false.
1696  end if
1697 
1698  if (present(is_mass)) then
1699  is_mass_g = is_mass
1700  else
1701  is_mass_g = .false.
1702  end if
1703 
1704  if (is_mass_g) then
1705  !! @f[ e = E_{SMR} + E_{AMR} + E_{UE+ZE} + E_{SDA} , @f]
1706  o2_out = mg2g(this%smr(temp_loc)) + & ! SMR
1707  mg2g(this%amr(temp_loc)) ! AMR
1708 
1709  if (is_include_ue_ze) &
1710  o2_out=o2_out+this%ue_ze(temp_loc, is_oxygen=.true.) ! UE+ZE
1711  if (.NOT. sda_off_debug) then
1712  o2_out = o2_out + mg2g(this%smr(temp_loc)) * & ! SDA
1713  this%sda_fact(global_sda_absorp_rate_max, &
1714  global_sda_factor_max)
1715  end if
1716  else
1717  !! @f[ e = E_{SMR} + E_{AMR} + E_{UE+ZE} + E_{SDA} , @f]
1718  o2_out = o2vol(mg2g(this%smr(temp_loc))) + & ! SMR
1719  o2vol(mg2g(this%amr(temp_loc))) ! AMR
1720  if (is_include_ue_ze) &
1721  o2_out=o2_out+o2vol(this%ue_ze(temp_loc, is_oxygen=.true.)) ! UE+ZE
1722  if (.NOT. sda_off_debug) then
1723  o2_out = o2_out + o2vol(mg2g(this%smr(temp_loc))) * & ! SDA
1724  this%sda_fact(global_sda_absorp_rate_max, &
1725  global_sda_factor_max)
1726  end if
1727  end if
1728 
1729  end function fish_oxygen_consumption_step
1730 
1731  !> Calculate the relative SDA (specific dynamic action) factor for SMR unit
1732  !! of energy uptake. SDA depends on the absorption rate up th the
1733  !! maxmum cap value max_sda that is achieved at the absorption rate `max_ap`
1734  !!
1735  !! The relative SDA factor is based on a linear relationship defined by
1736  !! the maximum absorption rate `max_ap` and max SDA factor `max_sda`.
1737  !!
1738  !! @verbatim
1739  !! max_sda + * 2,0 :: SDA = 2.0 x SMR
1740  !! | * . y = k x + b
1741  !! | * . ? =0
1742  !! | * .
1743  !! 0 +-------+
1744  !! 0 max_ap = 0.0007
1745  !! @endverbatim
1746  elemental function fish_energy_sda_factor(this, max_ap, max_sda, is_limit) &
1747  result(ap_fact)
1748  use base_utils, only : solve_line
1749  class(fish), intent(in) :: this
1750  !> Maximum (absolute) absorption rate when the maximum value of SDA
1751  !! (`max_sda`) is achieved
1752  real(srp), intent(in) :: max_ap
1753  !> Maximum value of SDA achieved at the maximum absorption rate (`max_ap`)
1754  real(srp), intent(in) :: max_sda
1755  logical, optional, intent(in) :: is_limit
1756  real(srp) :: ap_fact
1757  real(srp), parameter :: max_ultimate = 24.0_srp ! maximum limit for SDA
1758 
1759  real(srp) :: k, b
1760 
1761  call solve_line(k, b, 0.0_srp, 0.0_srp, max_ap, max_sda)
1762 
1763  ap_fact = k * this%absorption_rate() + b
1764 
1765  if (present(is_limit)) then
1766  if (is_limit) ap_fact = within(ap_fact, 0.0_srp, max_sda)
1767  else
1768  ap_fact = within(ap_fact, 0.0_srp, max_ultimate)
1769  end if
1770 
1771  end function fish_energy_sda_factor
1772 
1773  !> Grow the fish body mass: increment mass based on energy.
1774  elemental subroutine fish_grow_increment_energy(this)
1775  class(fish), intent(inout) :: this
1776 
1777  real(srp) :: updated_mass, last_ebal, prev_ebal
1778 
1779  last_ebal = missing
1780  prev_ebal = missing
1781 
1782  ! Note that the first time step is covered by the_fish::fish:skel:new()
1783  ! method
1784  if (global_time_step > 1) then
1785 
1786  last_ebal = last(this%history%energy_balance_curr)
1787  prev_ebal = this%history%energy_balance_curr( &
1788  size(this%history%energy_balance_curr)-1 )
1789 
1790  !> ### Implementation details ###
1791  !! The current body mass is incremented as
1792  !! @f$ M_{i+1} = M_{i} + \Delta M @f$ by the mass equivalent
1793  !! @f$ \Delta M @f$ of the energy increment for the time step
1794  !! calculated using the_fish::energy2mass().
1795  updated_mass = last(this%history%body_mass_current) + &
1796  energy2mass( last_ebal - prev_ebal )
1797 
1798  call add_to_history( this%history%body_mass_current, updated_mass )
1799 
1800  end if
1801 
1802  end subroutine fish_grow_increment_energy
1803 
1804  !> Calculate the increment of the total mass of food evacuated from the
1805  !! midgut after full absorption and evacuation delay (see
1806  !! commondata:global_maximum_duration_midgut_min) that occurs at
1807  !! one time step.
1808  !! @warning Note that this method should be called before
1809  !! the_fish::food_item_eaten_mg::check_disappear() so that all food
1810  !! itemsthat should be evacuated have not yet been evacuated.
1811  elemental function fish_midgut_total_mass_evacuated_step(this,max_time) &
1812  result(volume_out)
1813  class(midgut), intent(in) :: this
1814  real(srp) :: volume_out
1815  !> Maximum time processed in the midgut, by default all food items that
1816  !! have been in the process of absorption for more than this time will
1817  !! destructed from midgut and evacuated.
1818  !! Default value is based on commondata::global_maximum_duration_midgut_min.
1819  integer, optional, intent(in) :: max_time
1820 
1821  integer :: i
1822  integer :: max_time_loc
1823 
1824  if (present(max_time)) then
1825  max_time_loc = max_time
1826  else
1827  max_time_loc = global_maximum_duration_midgut_min * minute
1828  end if
1829 
1830  volume_out = 0.0_srp
1831 
1832  associate( foods_midgut_not_stom => &
1833  this%food_items_midgut( &
1834  this%n_food_items_stomach+1:this%n_food_items_midgut) )
1835 
1836  do i = 1, size(foods_midgut_not_stom)
1837  if ( foods_midgut_not_stom(i)%is_evacuate(max_time_loc) ) then
1838  volume_out = volume_out + foods_midgut_not_stom(i)%mass_0 - &
1839  foods_midgut_not_stom(i)%absorped
1840  end if
1841  end do
1842 
1843  end associate
1844 
1846 
1847  !> Calculate the number of the total mass of food evacuated from the
1848  !! midgut after full absorption and evacuation delay (see
1849  !! commondata:global_maximum_duration_midgut_min) that occurs at
1850  !! one time step.
1851  !! @warning Note that this method should be called before
1852  !! the_fish::food_item_eaten_mg::check_disappear() so that all food
1853  !! itemsthat should be evacuated have not yet been evacuated.
1854  elemental function fish_midgut_n_evacuated_step(this, max_time) result(n_out)
1855  class(midgut), intent(in) :: this
1856  integer :: n_out
1857  !> Maximum time processed in the midgut, by default all food items that
1858  !! have been in the process of absorption for more than this time will
1859  !! destructed from midgut and evacuated.
1860  !! Default value is based on commondata::global_maximum_duration_midgut_min.
1861  integer, optional, intent(in) :: max_time
1862 
1863  integer :: max_time_loc
1864 
1865  if (present(max_time)) then
1866  max_time_loc = max_time
1867  else
1868  max_time_loc = global_maximum_duration_midgut_min * minute
1869  end if
1870 
1871  associate( foods_midgut_not_stom => &
1872  this%food_items_midgut( &
1873  this%n_food_items_stomach+1:this%n_food_items_midgut) )
1874  n_out = count( foods_midgut_not_stom%is_evacuate(max_time_loc) )
1875  end associate
1876 
1877  end function fish_midgut_n_evacuated_step
1878 
1879  !> Update the history stack arrays for the fish, ::midgut class.
1880  elemental subroutine fish_midgut_history_update(this)
1881  class(midgut), intent(inout) :: this
1882 
1883  integer :: absorb_last_item
1884  real(srp) :: absorp_prev, absorp_total, absorp_diff, absorp_cumulate
1885 
1886  ! The history is initialized to commondata::missing values, so it is easy
1887  ! to determine what is the last valid item in the history stack array.
1888  absorb_last_item = this%absorp_last_i()
1889 
1890  ! If the whole history stack is composed of commondata::missing, this
1891  ! means it is the first time step, then all historical values are zero.
1892  ! Alternatively, if all history stack items are non-commondata::missing,
1893  ! the last value is the latest history.
1894  if ( absorb_last_item == 0 ) then
1895  absorp_prev = 0.0_srp
1896  absorp_total = 0.0_srp
1897  absorp_cumulate = 0.0_srp
1898  else
1899  absorp_prev = this%history%food_mass_absorb_cum(absorb_last_item)
1900  absorp_total = &
1901  sum( this%food_items_midgut(1:this%n_food_items_midgut)%absorped, &
1902  this%food_items_midgut(1:this%n_food_items_midgut)%absorped &
1903  /= missing )
1904  ! Note: It is important that absorp_diff subtracts current
1905  ! instantaneous absorption value, not cumulative value
1906  ! from the history stack array. Otherwise cumulative
1907  ! absorption is wrongly calculated.
1908  absorp_diff = absorp_total - &
1909  this%history%food_mass_absorb_curr( absorb_last_item )
1910  if ( absorp_diff > 0.0_srp ) then
1911  absorp_cumulate = absorp_prev + absorp_diff
1912  else
1913  absorp_cumulate = absorp_prev
1914  end if
1915  end if
1916 
1917  call add_to_history( this%history%food_mass_absorb_curr, absorp_total )
1918  call add_to_history( this%history%food_mass_absorb_cum, absorp_cumulate )
1919 
1920  end subroutine fish_midgut_history_update
1921 
1922  !> Determine the index of the latest absorption item in the history
1923  !! stack array. If the whole array is commondata::missing, this means the
1924  !! history stack is empty, then the function returns zero. Note that in
1925  !! most cases the function should return commondata::history_size as the
1926  !! history stack is filled with previous values.
1927  elemental function midgut_absorp_history_last_past_idx(this) result(inum)
1928  class(midgut), intent(in) :: this
1929  integer :: inum
1930  integer :: absorb_last_item
1931 
1932  ! The history is initialized to commondata::missing values, so it is easy
1933  ! to determine what is the last valid item in the history stack array.
1934  absorb_last_item = count( this%history%food_mass_absorb_cum == missing )
1935 
1936  inum = history_size - absorb_last_item
1937 
1939 
1940  !> Calculate the total mass of food in the fish midgut.
1941  elemental function fish_midgut_total_mass_food(this, tolerance) &
1942  result(total_mass)
1943  class(midgut), intent(in) :: this
1944  !> Optional numerical tolerance, the smallest value of the food item mass
1945  !! that counts as non-zero. Default is set by commondata::min_vol_toler.
1946  real(srp), optional, intent(in) :: tolerance
1947  !> Total mass of food in the midgut.
1948  real(srp) :: total_mass
1949 
1950  ! Local copy of optional
1951  real(srp) :: toler_loc
1952 
1953  if (present(tolerance)) then
1954  toler_loc = tolerance
1955  else
1956  toler_loc = min_mass_toler
1957  end if
1958 
1959  !> The total value is calculated as an array sum to the total number of
1960  !! food items being kept in the stomach (`this%n_food_items_stomach`).
1961  associate( foods_midgut &
1962  => this%food_items_midgut(1:this%n_food_items_midgut) )
1963  total_mass = &
1964  sum( foods_midgut%mass, &
1965  foods_midgut%mass > toler_loc .and. &
1966  foods_midgut%mass /= missing )
1967  end associate
1968 
1969  end function fish_midgut_total_mass_food
1970 
1971  !> Calculate the fish appetite factor based on the relative midgut fullness.
1972  !! Appetite factor is equivalent to the probability of consuming any food
1973  !! item.
1974  !! @note Note that the parameters of the appetite function are identical for
1975  !! both the **stomach** and **midgut** appetite factors:
1976  !! - stomach::appetite_stomach
1977  !! - midgut::
1978  !! .
1979  elemental function fish_appetite_factor_midgut(this, fcapacity) &
1980  result(appetite)
1981  class(midgut), intent(in) :: this
1982  real(srp), optional, intent(in) :: fcapacity
1983  real(srp) :: appetite
1984 
1985  real(srp) :: fcapacity_loc
1986 
1987  real(srp) :: mass_relative, correction_fac
1988 
1989  if (present(fcapacity)) then
1990  fcapacity_loc = fcapacity
1991  else
1992  fcapacity_loc = this%mass_midgut
1993  end if
1994 
1995  !> ### Implementation notes ###
1996  !! The appetite factor ranges between (0 and 1) and is based on the
1997  !! relative filling capacity. Here relative filling capacity @f$ c_r @f$
1998  !! is calculated as the ratio of the total mass of food in the midgut
1999  !! @f$ c_{max} @f$ to the maximum filling capacity @f$ c_t @f$
2000  !! @f[ c_r = \frac{c_t}{c_{max}} @f]
2001  mass_relative = this%mg_food_mass()/fcapacity_loc
2002 
2003  !> Correction factor is introduced to take account of the fact that
2004  !! the capacity of the midgut is bigger than stomach but basically the
2005  !! same amount of food is coming from stomach (in case of one meal).
2006  correction_fac = this%mass_midgut / this%mass_stomach
2007 
2008  !> Given the relative filling capacity @f$ c_r @f$, appetite factor
2009  !! that ranges from 0 to 1 is calculated as logistic function
2010  !! ::appetite_func().
2011  !!
2012  !! The @f$ a @f$ and @f$ r @f$ logistic parameters are defined by the
2013  !! commondata::global_appetite_logist_a and
2014  !! commondata::global_appetite_logist_r parameters.
2015  !!
2016  !! *gnuplot code:*
2017  !! @verbatim
2018  !! set xrange [0:1]
2019  !! plot 1 - 1/(1+500000*exp(-20*x))
2020  !! @endverbatim
2021  appetite = appetite_func( mass_relative * correction_fac, &
2022  global_appetite_logist_a, &
2023  global_appetite_logist_r )
2024 
2025  end function fish_appetite_factor_midgut
2026 
2027  !> Calculate instantaneous absorption rate based on the current absorption
2028  !! data and previous absorption saved in Output Arrays
2029  elemental function fish_midgut_absorption_rate(this) result (out_rate)
2030  class(midgut), intent(in) :: this
2031  real(srp) :: out_rate
2032 
2033  if( global_time_step == 1 .or. this%absorp_last_i()<history_size/2 ) then
2034  out_rate = 0.0_srp
2035  return
2036  end if
2037 
2038  ! It is assumed that the history stack already includes the current
2039  ! absorption value as the last value, so previous is taken as n-1.
2040  ! History stack array for absorption is updated in ::mg_step().
2041  out_rate = this%history%food_mass_absorb_cum( this%absorp_last_i() ) - &
2042  this%history%food_mass_absorb_cum( this%absorp_last_i()-1 )
2043 
2044  end function fish_midgut_absorption_rate
2045 
2046  !> Appetite factor multiplier based on the total absorption rate.
2047  elemental function fish_midgut_absorption_factor(this) result (out_factor)
2048  class(midgut), intent(in) :: this
2049  real(srp) :: out_factor
2050 
2051  real(srp) :: absorp_rate
2052 
2053  real(srp), dimension(*), parameter :: grid_test_x = [0.0_srp, 0.00003_srp],&
2054  grid_test_y = [0.0_srp, 1.0_srp]
2055 
2056 
2057  absorp_rate = this%absorption_rate()
2058 
2059  if ( absorp_rate >= grid_test_x(1) .and. &
2060  absorp_rate <= grid_test_x(size(grid_test_x)) ) then
2061  out_factor = cspline_scalar( grid_test_x, grid_test_y, absorp_rate )
2062  else if ( absorp_rate < grid_test_x(1) ) then
2063  out_factor = grid_test_y(1)
2064  else
2065  out_factor = grid_test_y(size(grid_test_y))
2066  end if
2067 
2068  end function fish_midgut_absorption_factor
2069 
2070  !> Shift food items in the midgut after a new food item is ingested and
2071  !! therefore food items are shifted in stomach adding the new item.
2072  elemental subroutine fish_midgut_shift_items_after_new_ingest( this, &
2073  food_item_pass)
2074  class(midgut), intent(inout) :: this
2075  !> Optional food item that is ingested by the fish (environ::food_item) or
2076  !! any extension class. This food mass is used only to set the reference
2077  !! start mass of the food item.
2078  class(food_item), optional, intent(in) :: food_item_pass
2079 
2080  ! Local copy of the start mass of the food item
2081  real(srp) :: food_item_pass_start_mass_loc
2082 
2083  if (present(food_item_pass)) then
2084  select type ( food_item_pass )
2085  type is (food_item)
2086  food_item_pass_start_mass_loc = food_item_pass%mass
2087  type is (food_item_eaten)
2088  food_item_pass_start_mass_loc = food_item_pass%mass
2089  type is (food_item_eaten_mg)
2090  food_item_pass_start_mass_loc = food_item_pass%mass_0
2091  class default
2092  food_item_pass_start_mass_loc = food_item_pass%mass
2093  end select
2094  else
2095  food_item_pass_start_mass_loc = global_food_item_mass
2096  end if
2097 
2098  !> - The food item is then added to the stack array of the fish
2099  !! stomach. It takes the first place shifting all other food items in
2100  !! sequence.
2101  this%food_items_midgut(2:this%n_food_items_midgut+1) = &
2102  this%food_items_midgut(1:this%n_food_items_midgut)
2103 
2104  !> - The first food item in the stack is then obtained from the input
2105  !! parameter **food_item_pass**. But note that at this stage, its actual
2106  !! environ::food_item::mass is set to zero, the starting mass
2107  !! food_item_eaten::mass_0 is obtained from the input item's actual
2108  !! mass. The food_item_eaten::time_in_process is set to zero. All
2109  !! this is done via the food_item_eaten::zero() method.
2110  !! .
2111  call this%food_items_midgut(1)%zero( &
2112  mass=0.0_srp, &
2113  start_mass=food_item_pass_start_mass_loc )
2114 
2115  this%n_food_items_midgut = this%n_food_items_midgut + 1
2116 
2118 
2119  !> Computational backend for the appetite function.
2120  !! Appetite is calculated as
2121  !! @f[ \alpha = 1 - \frac{1}{1+a \cdot e^{-r \cdot c_r}} @f]
2122  !! where @f$ c_r @f$ is the relative filling capacity (range 0 to 1) of
2123  !! the fish stomach, @f$ a @f$ and @f$ r @f$ are logistic function
2124  !! parameters.
2125  !!
2126  !! *gnuplot code:*
2127  !! @verbatim
2128  !! set xrange [0:1]
2129  !! plot 1-1/(1+500000*exp(-20*x))
2130  !! @endverbatim
2131  !!
2132  !! @note Note that m_ifcmd::save_appetite_function_data() saves the appetite
2133  !! factor data for plotting, testing and analysis.
2134  elemental function appetite_func( mass_relative, A, R ) result(value_out)
2135  !> The mass of food in the stomach relative to the filling capacity.
2136  real(srp), intent(in) :: mass_relative
2137  !> Parameters of the logistic function @f$ a @f$.
2138  real(srp), intent(in) :: a
2139  !> Parameters of the logistic function @f$ r @f$.
2140  real(srp), intent(in) :: r
2141  !> Returns the appetite factor value that ranges from 0 to 1.
2142  real(srp) :: value_out
2143 
2144  value_out = 1.0_srp - logistic( mass_relative, a, 1.0_srp, r )
2145 
2146  end function appetite_func
2147 
2148  !> Calculate the overall appetite of the fish, which defines the
2149  !! probability to ingest any food item.
2150  elemental function fish_appetite_probability_ingestion(this, time_step) &
2151  result(appetite)
2152  class(fish), intent(in) :: this
2153  !> Time step, optional parameter
2154  integer(LONG), optional, intent(in) :: time_step
2155  real(srp) :: appetite
2156  integer(LONG) :: step_loc
2157 
2158  !> Fish appetite at night is near-zero
2159  if ( .not. is_day() .and. global_appetite_fish_night >= 0.0_srp ) then
2160  appetite = global_appetite_fish_night
2161  return
2162  end if
2163 
2164  if(present(time_step)) then
2165  step_loc = time_step
2166  else
2167  step_loc = global_time_step
2168  end if
2169 
2170  !> The overall appetite is a function of individual appetite factors:
2171  !! - appetite factor for stomach the_fish::stomach::appetite_stomach()
2172  !! - appetite factor for midgut the_fish::midgut::appetite_midgut()
2173  !! - appetite factor for energy balance the_fish::fish::appetite_energy()
2174  !! .
2175  !!
2176  !!
2177  !! *Version 1* multiplication rule: @f$ A = A_{stomach} A_{midgut} @f$
2178  !! probability of a combination of events events.
2179  !appetite = this%appetite_stomach() * this%appetite_midgut()
2180  !----------------------
2181  !> *Version 2* maximum/competition rule:
2182  !! @f[
2183  !! \left\{\begin{matrix} A = A_{stomach}, A_{stomach} < 0.2 \\
2184  !! max( A_{stomach}, A_{midgut},A_{energy} )
2185  !! \end{matrix}\right.
2186  !! @f]
2187  if ( this%appetite_stomach() < global_appetite_stomach_threshold ) then
2188  appetite = this%appetite_stomach()
2189  else
2190  appetite = maxval( [ this%appetite_stomach(), this%appetite_midgut(), &
2191  this%appetite_energy() ] )
2192  end if
2193 
2194  ! Suppress appetite by stress (if enabled compile-time)
2195  if (is_stress_enable) &
2196  appetite = appetite - appetite*stress_suppress(step_loc)
2197 
2199 
2200  !> Calculate suppression factor for appetite caused by stress intervention
2201  !! at time `time`: generic interface is ::stress_factor().
2202  !! This is the scalar version, vector -based version is
2203  !!::stress_suppress_factor_v().
2204  !!
2205  !! @verbatim
2206  !! +**
2207  !! F | ***
2208  !! | **
2209  !! +-------*--
2210  !! ^ time_step_incr
2211  !! A-F
2212  !! @endverbatim
2213  pure function stress_suppress_factor_s(time_step_incr, is_force) result (fout)
2214  use base_utils, only : cspline_scalar
2215  !> Time step increment from the moment stress intervention has occurred
2216  integer, intent(in) :: time_step_incr
2217  !> optional flag to force calculation of the function even if stress
2218  !! is disabled
2219  logical, optional, intent(in) :: is_force
2220  real(srp) :: fout
2221 
2222  logical :: is_force_loc
2223 
2224  if (present(is_force)) then
2225  is_force_loc = is_force
2226  else
2227  is_force_loc = .false.
2228  end if
2229 
2230  if ( is_stress() .or. is_force_loc ) then
2231  fout = cspline_scalar( hour * global_stress_factor_hour, &
2232  global_stress_fact_suppress, &
2233  real(time_step_incr, srp) )
2234  else
2235  fout = 0.0_srp
2236  end if
2237 
2238  end function stress_suppress_factor_s
2239 
2240  !> Vector-based version of the stress-based suppression function
2241  !! ::stress_factor(). There is a scalar version of the same function
2242  !! ::stress_suppress_factor_s.
2243  pure function stress_suppress_factor_v(time_step_incr, is_force) result (fout)
2244  use base_utils, only : cspline_vector
2245  !> Time step increment from the moment stress intervention has occurred
2246  integer, dimension(:), intent(in) :: time_step_incr
2247  !> optional flag to force calculation of the function even if stress
2248  !! is disabled
2249  logical, optional, intent(in) :: is_force
2250  real(srp), allocatable, dimension(:) :: fout
2251 
2252  logical :: is_force_loc
2253 
2254  if (present(is_force)) then
2255  is_force_loc = is_force
2256  else
2257  is_force_loc = .false.
2258  end if
2259 
2260  if (.NOT. allocated(fout)) allocate(fout(size(time_step_incr)))
2261 
2262  if ( is_stress() .or. is_force_loc ) then
2263  fout = cspline_vector( hour * global_stress_factor_hour, &
2264  global_stress_fact_suppress, &
2265  real(time_step_incr, srp) )
2266  else
2267  fout = 0.0_srp
2268  end if
2269 
2270  end function stress_suppress_factor_v
2271 
2272  !> Calculate real stress suppression factor for a specific time step
2273  !! given the configured stress intervention pattern. This is a high-level
2274  !! interface to ::stress_factor().
2275  !! @verbatim
2276  !! 1** 2**
2277  !! F | *** | ***
2278  !! | ** | **
2279  !! --#-------+-------*----+-----#--*---
2280  !! ^ ^
2281  !! F=0 +<---># time_over
2282  !! ^
2283  !! A-F
2284  !! @endverbatim
2285  pure function stress_suppress(time_step) result (fout)
2286  !> Current time step
2287  integer(LONG), intent(in), optional :: time_step
2288  real(srp) :: fout
2289 
2290  integer :: i, last_stress, time_over
2291  integer(LONG) :: time_loc
2292 
2293  fout = 0.0_srp
2294 
2295  if (.not. is_stress() ) then
2296  return
2297  end if
2298 
2299  if (present(time_step)) then
2300  time_loc = time_step
2301  else
2302  time_loc = global_time_step
2303  end if
2304 
2305  last_stress = unknown
2306 
2307  ! get current stress intervention number
2308  do i = 1, size(global_stress_intervention_time)
2309  if ( time_loc >= global_stress_intervention_time(i) ) then
2310  last_stress = i
2311  end if
2312  end do
2313 
2314  ! If the current time step is before the first stress intervention,
2315  ! zero suppression of appetite
2316  if (last_stress == unknown) then
2317  fout = 0.0_srp
2318  return
2319  end if
2320 
2321  ! time difference over the last stress intervention
2322  time_over = time_loc - global_stress_intervention_time(last_stress)
2323 
2324  if (time_over <= last(global_stress_factor_hour)*hour) then
2325  fout = stress_factor(time_over)
2326  else
2327  fout = 0.0_srp
2328  end if
2329 
2330  if (fout <= small ) fout = 0.0_srp
2331 
2332  end function stress_suppress
2333 
2334  !> Get the current body mass of the fish. Note that this is the shortcut to
2335  !! obtain the last value from the body mass history array
2336  !! the_fish::fish_skel::history::body_mass_current.
2337  elemental function fish_body_mass_current_get(this) result (current_mass_get)
2338  class(fish_skel), intent(in) :: this
2339  real(srp) :: current_mass_get
2340 
2341  current_mass_get = last( this%history%body_mass_current )
2342 
2343  end function fish_body_mass_current_get
2344 
2345  !> Calculate appetite factor that depends on the energy balance
2346  elemental function fish_appetite_factor_energy_balance(this) &
2347  result(appetite_factor)
2348  class(fish), intent(in) :: this
2349  real(srp) :: appetite_factor
2350 
2351  integer :: hist_len
2352  real(hrp) :: ebal_older, ebal_newer ! average past energy balance components
2353  real(hrp) :: ebal_diff
2354  integer, parameter :: block_size = 4
2355  real(hrp) :: delta_e, appetite_hg
2356 
2357  hist_len = size(this%history%energy_balance_curr) ! HISTORY_SIZE
2358 
2359  ! If simulation is just started and the history is empty, exit with zero
2360  if (global_time_step < block_size*2 ) then
2361  appetite_factor = 0.0_srp
2362  return
2363  end if
2364 
2365  associate( e_hist => this%history%energy_balance_curr )
2366 
2367  if (block_size < 4 .or. hist_len < block_size*2) then
2368  ebal_older = e_hist(hist_len-1)
2369  ebal_newer = e_hist(hist_len)
2370  else
2371  !array older ::
2372  ebal_older = average(e_hist(hist_len-2*block_size+1:hist_len-block_size), &
2373  undef_ret_null=.true.)
2374  !array newer ::
2375  ebal_newer = average(e_hist(hist_len-block_size+1:hist_len), &
2376  undef_ret_null=.true.)
2377  end if
2378 
2379  ! Absolute difference in the past energy balance
2380  ebal_diff = ebal_newer - ebal_older
2381 
2382  end associate
2383 
2384  !> ### Implementation notes ###
2385  !!
2386  !! The energy component of the appetite is defined by the following
2387  !! formula:
2388  !! @f[ \alpha_E = \frac{1}{1 + e^{-r_E \cdot (- \Delta_E - b_E )}} @f]
2389  !! @verbatim
2390  !! gnuplot> set xrange [-1:1]
2391  !! gnuplot> plot 1 / (1+2.718**(-40*(-x-0.2)) )
2392  !! @endverbatim
2393  associate( r_e => real(global_energy_appetite_rate,hrp), &
2394  b_e => real(global_energy_appetite_shift,hrp) )
2395 
2396  delta_e = ebal_diff/this%smr(global_temperature)
2397  ! Guard against extreme values of the basic difference:
2398  ! Note that the validity range values are chosen because the f(x)
2399  ! lie within [0,1] asympotically for all x<-1 and x>1, seegnuplot
2400  ! code
2401  if (delta_e < 10.0_hrp * tiny(1.0_srp)) delta_e = 0.0_hrp
2402  if (delta_e > 10.0_hrp) delta_e = 10.0_hrp
2403 
2404  appetite_hg = 1.0_hrp / (1.0_hrp + exp(-r_e * (-delta_e-b_e)))
2405  appetite_factor = real(appetite_hg, srp)
2406 
2407  end associate
2408 
2410 
2411  !> This procedure determines if the fish decides to consume the food item
2412  !! and if yes, ingests it using the ::do_ingest() method.
2413  !! @important This version accepts **raw food item**. Generic
2414  !! interface linking both raw and pointer versions is ambiguous.
2415  !! @note This cannot be pure due to random operation
2416  impure subroutine fish_decide_eat_food_item(this, food_item_in, have_eaten )
2417  class(fish), intent(inout) :: this
2418  !> The food item that is available for decision and consumption.
2419  class(food_item), intent(in) :: food_item_in
2420  !> Optional indicator showing if the fish have actually eaten the food
2421  !! item (returns TRUE).
2422  logical, optional, intent(out) :: have_eaten
2423 
2424  if (present(have_eaten)) have_eaten = .false.
2425 
2426  if ( rand_uni() < this%appetite() ) then
2427  call this%do_ingest( food_item_in )
2428  if (present(have_eaten)) have_eaten = .true.
2429  end if
2430 
2431  end subroutine fish_decide_eat_food_item
2432 
2433  !> This procedure determines if the fish decides to consume the food item
2434  !! and if yes, ingests it using the ::do_ingest() method.
2435  !! @important This version accepts **pointer** to food item. Generic
2436  !! interface linking both raw and pointer versions is ambiguous.
2437  !! @note This cannot be pure due to random operation
2438  impure subroutine fish_decide_eat_food_item_ptr(this,food_item_in,have_eaten)
2439  class(fish), intent(inout) :: this
2440  !> The food item that is available for decision and consumption.
2441  class(food_item), pointer, intent(in) :: food_item_in
2442  !> Optional indicator showing if the fish have actually eaten the food
2443  !! item (returns TRUE).
2444  logical, optional, intent(out) :: have_eaten
2445 
2446  if (present(have_eaten)) have_eaten = .false.
2447 
2448  if ( .NOT. associated(food_item_in) ) return
2449 
2450  if ( rand_uni() < this%appetite() ) then
2451  call this%do_ingest( food_item_in )
2452  if (present(have_eaten)) have_eaten = .true.
2453  end if
2454 
2455  end subroutine fish_decide_eat_food_item_ptr
2456 
2457  !> Calculate the baseline activity of the fish.
2458  !!
2459  !> Global baseline locomotor activity pattern (swimming speed) for each
2460  !! time step consists of two components:
2461  !! - baseline that differs at day ::global_baseline_activity_day and
2462  !! night ::global_baseline_activity_night
2463  !! - feeding activity increment defined by feeding activity factor
2464  !! ::global_feeding_activity_factor
2465  !! .
2466  !!
2467  !! This is illustrated by the following diagram:
2468  !!
2469  !! @verbatim
2470  !! +----+ feeding activity multiplier
2471  !! | |
2472  !! +--+ - -+----------------+
2473  !! | | baseline
2474  !! -------------------+ +-------------------> activity
2475  !! -night-------------+-day--------------------+-night------------->
2476  !! @endverbatim
2477  elemental function fish_activity_baseline_component(this, time_step) &
2478  result(act_out)
2479  class(fish), intent(in) :: this
2480  !> Optional time step of the model, default value is
2481  !! commondata::global_time_step
2482  integer(LONG), optional, intent(in) :: time_step
2483 
2484  real(srp) :: act_out
2485 
2486  integer(LONG) :: time_step_loc, i
2487 
2488  if (present(time_step)) then
2489  time_step_loc = time_step
2490  else
2491  time_step_loc = global_time_step
2492  end if
2493 
2494  if ( is_day(time_step_loc) ) then
2495  act_out = global_baseline_activity_day
2496  else
2497  act_out = global_baseline_activity_night
2498  end if
2499 
2500  if (is_stress_enable) &
2501  act_out = act_out - &
2502  act_out * global_stress_activity_decr * &
2503  stress_suppress(time_step_loc)
2504 
2506 
2507  !> Calculate activity factor linked to appetite.
2508  !! Appetite factor has a linear relationship with the fish appetite
2509  !! !> @f$ l_{A} = k_{a} A + 1 @f$, here @f$ k_{a} + 1 @f$ is the maximum
2510  !! value of the appetite activity factor when appetite value is
2511  !! maximum @f$ A = 1 @f$. Note that the appetite activity factor works
2512  !! as a multiplier for the baseline actvity
2513  !! the_fish::fish::activity_baseline(), see
2514  !! ::fish_amr_locomotion_energy_cost().
2515  !!
2516  !! Gnuplot commands for plotting:
2517  !!
2518  !! @verbatim
2519  !! set xrange [0:1]
2520  !! set yrange [0:5]
2521  !! plot 0.5*x + 1
2522  !! @endverbatim
2523  elemental function fish_activity_appetite_factor(this) result (act_out)
2524  class(fish), intent(in) :: this
2525  real(srp) :: act_out
2526 
2527  act_out = global_appetite_activity_factor * this%appetite() + 1.0_srp
2528 
2529  end function fish_activity_appetite_factor
2530 
2531  !> Calculate the adjustment factor for the transformation of the stomach
2532  !! transport pattern Time scale commondata::global_transport_pattern_t
2533  !! for a different temperature or fish size.
2534  elemental function stomach_adjust(target_emptying_time) result (adj_out)
2535  real(srp) :: adj_out
2536  !> Optional maximum stomach emptying time for a different target
2537  !! temperature, default value is calculated by ::stomach_emptying_time().
2538  integer, optional, intent(in) :: target_emptying_time
2539  real(srp), parameter :: min_diff = 0.00001
2540  integer :: i
2541 
2542  integer :: target_empty_loc
2543 
2544  if (present(target_emptying_time)) then
2545  target_empty_loc = target_emptying_time
2546  else
2547  target_empty_loc = &
2548  stomach_emptying_time(global_body_mass, global_temperature)
2549  end if
2550 
2551  do i=1, global_transport_dim
2552  if ( global_transport_pattern_r(i) < min_diff ) then
2553  adj_out = &
2554  real(target_empty_loc,srp)/real(Global_Transport_Pattern_T(i),srp)
2555  exit
2556  end if
2557  end do
2558  end function stomach_adjust
2559 
2560  !> Calculate the stomach emptying time for a fish with specific body mass
2561  !! at a specific temperature. Calculation is based on spline interpolation
2562  !! of experimental data.
2563  elemental function stomach_emptying_time(fish_mass, temperature) &
2564  result(empty_time_raw)
2565  !> Optional fish mass, default value is commondata::global_body_mass
2566  real(srp), optional, intent(in) :: fish_mass
2567  !> Optional temperature, default value is commondata::global_temperature
2568  real(srp), optional, intent(in) :: temperature
2569  integer :: empty_time_raw
2570 
2571  integer :: temp_size, i
2572  real(srp) :: mass_loc, temperature_loc
2573 
2574  real(srp), &
2575  dimension(size(Global_Stomach_Emptying_Pattern%grid_temperature)) :: x_t
2576 
2577  if (present(fish_mass)) then
2578  mass_loc = fish_mass
2579  else
2580  mass_loc = global_body_mass
2581  end if
2582 
2583  if (present(temperature)) then
2584  temperature_loc = temperature
2585  else
2586  temperature_loc = global_temperature
2587  end if
2588 
2589  temp_size = size(global_stomach_emptying_pattern%grid_temperature)
2590 
2591  do i = 1, temp_size
2592  x_t(i) = cspline_scalar( &
2593  global_stomach_emptying_pattern%grid_mass, &
2594  real(global_stomach_emptying_pattern%emptying_time(:,i),srp), &
2595  mass_loc )
2596  end do
2597 
2598  empty_time_raw = nint( cspline_scalar( &
2599  global_stomach_emptying_pattern%grid_temperature, &
2600  x_t, temperature_loc ) )
2601 
2602  end function stomach_emptying_time
2603 
2604  !> Object-oriented frontend for ::stomach_emptying_time(): Calculate the
2605  !! stomach emptying time for a fish with specific body mass at a specific
2606  !! temperature. Calculation is based on spline interpolation of experimental
2607  !! data.
2608  elemental function fish_stomach_emptying_time(this, temperature) &
2609  result(empty_time_raw)
2610  class(stomach), intent(in) :: this
2611  integer :: empty_time_raw
2612  !> Optional temperature, if absent use commondata::global_temperature
2613  !! parameter.
2614  real(srp), optional, intent(in) :: temperature
2615 
2616  real(srp) :: temp_loc
2617 
2618  if (present(temperature)) then
2619  temp_loc = temperature
2620  else
2621  temp_loc = global_temperature
2622  end if
2623 
2624  empty_time_raw = stomach_emptying_time(this%mass(), temperature)
2625 
2626  end function fish_stomach_emptying_time
2627 
2628  !> Get the stomach emptying time base matrix from a CSV input data file.
2629  !!
2630  !! File structure:
2631  !! @verbatim
2632  !! | 50.00 100.00 300.00 500.00
2633  !! ---------+------------------------------------
2634  !! 5.00 | 24.00 35.00 75.00 100.00
2635  !! 10.00 | 15.00 20.00 50.00 75.00
2636  !! 15.00 | 9.00 15.00 40.00 50.00
2637  !! 20.00 | 5.00 10.00 30.00 35.00
2638  !! 22.00 | 4.00 8.00 29.00 33.00
2639  !! @endverbatim
2640  impure function get_stomach_emptying_matrix_csv(csv_file) result (pattern_out)
2641  use csv_io , only: csv_matrix_read
2642  !> Input file name
2643  character(len=*), intent(in) :: csv_file
2644  type(stomach_emptying_pattern) :: pattern_out
2645 
2646  real(srp), allocatable, dimension(:,:) :: raw_data_csv
2647  logical :: is_success
2648 
2649  raw_data_csv = transpose( &
2650  csv_matrix_read( csv_file, csv_file_status=is_success, &
2651  missing_code=missing ) )
2652 
2653  ! First row is mass grid
2654  pattern_out%grid_mass = raw_data_csv(2:,1)
2655  ! First column is temperature grid
2656  pattern_out%grid_temperature = raw_data_csv(1,2:)
2657  ! Remaining data is stomach emptying time
2658  pattern_out%emptying_time = nint(raw_data_csv(2:,2:)) * hour
2659 
2660  end function get_stomach_emptying_matrix_csv
2661 
2662 
2663 end module the_fish
Simple history stack function, add to the end of the stack. We need only to add components on top (en...
Definition: m_common.f90:785
Function calculating standard oxygen consumption in rainbow trout based on the curve from Fig....
Definition: m_common.f90:805
Calculate SMR, with generic interface to non-object oriented procedure.
Definition: m_fish.f90:86
Calculate stress pattern based on cubic spline interpolation over the grid defined by commondata::glo...
Definition: m_fish.f90:94
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_body_mass
Fish body mass, g, at the start of the simulation Configuration file example:
Definition: m_common.f90:226
real(srp), public global_stress_cost_smr
Maximum value of the metabolic cost of stress in units of resting metabolic rate (SMR)....
Definition: m_common.f90:374
logical, parameter, public is_stress_enable
Compile-time logical flag that defines if stress effects described by global_stress_factor_hour,...
Definition: m_common.f90:45
integer, parameter, public hour
Global time constants, number of sec in hour and min.
Definition: m_common.f90:61
integer(long), public global_time_step
Global variable that defines the current time step.
Definition: m_common.f90:86
Module defining the environment.
Definition: m_env.f90:12
This module defines the fish and its components. The model is discrete, time is based on time steps,...
Definition: m_fish.f90:12
impure subroutine fish_decide_eat_food_item_ptr(this, food_item_in, have_eaten)
This procedure determines if the fish decides to consume the food item and if yes,...
Definition: m_fish.f90:2439
elemental real(srp) function fish_stomach_total_mass_food(this, tolerance)
Calculate the total mass of food in the fish stomach.
Definition: m_fish.f90:1066
elemental real(srp) function nitrogen_mass(mol, is_ammonia)
Calculate the mass of ammonia, mol to g.
Definition: m_fish.f90:1554
elemental real(srp) function fish_midgut_absorption_factor(this)
Appetite factor multiplier based on the total absorption rate.
Definition: m_fish.f90:2048
elemental integer function fish_stomach_emptying_time(this, temperature)
Object-oriented frontend for stomach_emptying_time(): Calculate the stomach emptying time for a fish ...
Definition: m_fish.f90:2610
elemental subroutine fish_grow_increment_energy(this)
Grow the fish body mass: increment mass based on energy.
Definition: m_fish.f90:1775
elemental real(srp) function fish_amr_locomotion_energy_cost(this, temperature, is_exclude_smr, is_per_hour)
Calculate the active metabolic rate. This can be based on amr_swim_basic() or def_salmon::salmon_oxyg...
Definition: m_fish.f90:474
elemental real(srp) function fish_body_mass_current_get(this)
Get the current body mass of the fish. Note that this is the shortcut to obtain the last value from t...
Definition: m_fish.f90:2338
elemental integer function fish_midgut_n_evacuated_step(this, max_time)
Calculate the number of the total mass of food evacuated from the midgut after full absorption and ev...
Definition: m_fish.f90:1855
elemental real(srp) function fish_energy_consumption_step(this, temperature, sda_off)
Calculate total energy, kJ consumption of the fish depending on the temperature E = SMR + AMR + (UE+Z...
Definition: m_fish.f90:1627
pure real(srp) function fish_smr_temp_bodymass_evan1990_value(body_mass, temperature, is_per_hour, time_step)
SMR calculation from Evans 1992 data, non-object scalar version.
Definition: m_fish.f90:383
elemental real(srp) function fish_oxygen_consumption_step(this, temperature, is_mass, sda_off)
Calculate total oxygen consumption (l) of the fish depending on the temperature O2 = O2_SMR + O2_AMR ...
Definition: m_fish.f90:1669
pure real(srp) function stress_suppress(time_step)
Calculate real stress suppression factor for a specific time step given the configured stress interve...
Definition: m_fish.f90:2286
pure real(srp) function, dimension(:), allocatable stress_suppress_factor_v(time_step_incr, is_force)
Vector-based version of the stress-based suppression function ::stress_factor(). There is a scalar ve...
Definition: m_fish.f90:2244
elemental real(srp) function stomach_vol(mass)
Calculate the stomach volume (ml) based on the fish body mass (g) using Salgado, A....
Definition: m_fish.f90:309
elemental subroutine fish_midgut_init(this, mass)
Initialise an empty fish midgut object.
Definition: m_fish.f90:1143
elemental logical function food_item_eaten_mg_exceed_max_is_to_destruct(this, max_time)
Check if the food item in the midgut has spent for more than the maximum time in the midgut after ful...
Definition: m_fish.f90:777
elemental subroutine food_item_eaten_check_destruct(this, is_destructed, tolerance, max_time)
Check if the food item mass shrunk to near-zero and destruct it.
Definition: m_fish.f90:705
elemental real(srp) function fish_activity_appetite_factor(this)
Calculate activity factor linked to appetite. Appetite factor has a linear relationship with the fish...
Definition: m_fish.f90:2524
elemental subroutine fish_stomach_init(this, mass)
Initialise an empty fish stomach object.
Definition: m_fish.f90:949
elemental real(srp) function amr_swim_basic(fish_mass, swimming_speed, time_unit)
Calculate the active metabolic rate of fish in units of oxygen consumption per hour.
Definition: m_fish.f90:433
impure subroutine fish_midgut_update_from_stomach(this, dry_mass, t_increment)
This procedure processes the food item in the midgut of the fish.
Definition: m_fish.f90:1163
elemental integer function midgut_absorp_history_last_past_idx(this)
Determine the index of the latest absorption item in the history stack array. If the whole array is c...
Definition: m_fish.f90:1928
elemental subroutine fish_midgut_shift_items_after_new_ingest(this, food_item_pass)
Shift food items in the midgut after a new food item is ingested and therefore food items are shifted...
Definition: m_fish.f90:2074
elemental real(srp) function fish_appetite_probability_ingestion(this, time_step)
Calculate the overall appetite of the fish, which defines the probability to ingest any food item.
Definition: m_fish.f90:2152
elemental subroutine food_item_eaten_update_age_in_stomach(this, t_increment)
This procedure updates the time the food item spent in the stomach of the fish.
Definition: m_fish.f90:686
elemental real(srp) function fish_activity_baseline_component(this, time_step)
Calculate the baseline activity of the fish.
Definition: m_fish.f90:2479
integer, parameter, public history_size
The size of the history that saves the fish data back in time.
Definition: m_fish.f90:24
elemental subroutine food_item_eaten_mg_check_destruct(this, is_destructed, tolerance, max_time)
Check if the food item has been processed for more than commondata::global_maximum_duration_midgut s ...
Definition: m_fish.f90:739
pure real(srp) function stress_suppress_factor_s(time_step_incr, is_force)
Calculate suppression factor for appetite caused by stress intervention at time time: generic interfa...
Definition: m_fish.f90:2214
elemental subroutine food_item_eaten_mg_set_zero_init_state(this, mass, start_mass, delay)
Initialise an empty food item as ingested by the fish. Cleanup and set zero state.
Definition: m_fish.f90:602
elemental real(srp) function fish_midgut_total_mass_evacuated_step(this, max_time)
Calculate the increment of the total mass of food evacuated from the midgut after full absorption and...
Definition: m_fish.f90:1813
elemental real(srp) function branchial_nitrogen_to_energy(excreted_nitrogen, is_kg)
Calculate the branchal and urinary energy loss from branchial and urinary nitrogen loss....
Definition: m_fish.f90:1597
elemental subroutine fish_ingest_food_item(this, food_item_ingested)
This procedure shows what happens when the fish eats a single food item.
Definition: m_fish.f90:1026
elemental integer function stomach_emptying_time(fish_mass, temperature)
Calculate the stomach emptying time for a fish with specific body mass at a specific temperature....
Definition: m_fish.f90:2565
elemental real(srp) function fish_midgut_total_mass_food(this, tolerance)
Calculate the total mass of food in the fish midgut.
Definition: m_fish.f90:1943
elemental subroutine fish_init_new_zero(this, id_num)
Initialise an empty ::fish object to an empty zero state.
Definition: m_fish.f90:319
elemental real(srp) function fish_whole_body_energy_trout(this)
Calculate the whole body energy content.
Definition: m_fish.f90:526
elemental subroutine food_item_eaten_eat_init_at_ingest(this, food_item_in, ingest_delay)
Initialise a single food item as it is ingested by the fish. Note that the ingested food item is copi...
Definition: m_fish.f90:653
elemental real(srp) function fish_energy_branchial_step(this, temperature, is_oxygen)
Calculate urinal (UE) and branchial energy (ZE) as a proportion of the SMR.
Definition: m_fish.f90:1503
elemental real(srp) function fish_appetite_factor_midgut(this, fcapacity)
Calculate the fish appetite factor based on the relative midgut fullness. Appetite factor is equivale...
Definition: m_fish.f90:1981
elemental real(srp) function fish_appetite_factor_stomach(this, fcapacity)
Calculate the fish appetite factor based on the relative stomach fullness. Appetite factor is equival...
Definition: m_fish.f90:1098
elemental real(srp) function fish_midgut_absorption_rate(this)
Calculate instantaneous absorption rate based on the current absorption data and previous absorption ...
Definition: m_fish.f90:2030
impure subroutine fish_decide_eat_food_item(this, food_item_in, have_eaten)
This procedure determines if the fish decides to consume the food item and if yes,...
Definition: m_fish.f90:2417
elemental subroutine food_item_eaten_set_zero_init_state(this, mass, start_mass, delay)
Initialise an empty food item as ingested by the fish. Cleanup and set zero state.
Definition: m_fish.f90:567
pure real(srp) function fish_smr_temp_bodymass_evan1990_scalar(this, temperature, is_per_hour, time_step)
SMR calculation from Evans 1992 data, scalar version.
Definition: m_fish.f90:348
elemental real(srp) function st_food_item_mass(time_in_process, dry_mass, ingestion_delay, water_uptake, rescale)
This function defines the mass of a single food item as it passes through the fish stomach.
Definition: m_fish.f90:837
elemental real(srp) function fish_energy_sda_factor(this, max_ap, max_sda, is_limit)
Calculate the relative SDA (specific dynamic action) factor for SMR unit of energy uptake....
Definition: m_fish.f90:1748
elemental real(srp) function appetite_func(mass_relative, A, R)
Computational backend for the appetite function. Appetite is calculated as.
Definition: m_fish.f90:2135
elemental subroutine fish_energy_balance_update(this, temperature, start_value)
Calculate and update the current energy balance of the fish. Note that the energy balance is kept in ...
Definition: m_fish.f90:1436
elemental subroutine fish_midgut_history_update(this)
Update the history stack arrays for the fish, ::midgut class.
Definition: m_fish.f90:1881
elemental logical function food_item_eaten_is_absorbed_full(this, max_absorb)
Check if the food item has been absorbed to the maximum possible mass.
Definition: m_fish.f90:805
impure subroutine fish_stomach_update_step(this)
Update one time step of the fish stomach life cycle.
Definition: m_fish.f90:969
elemental real(srp) function fish_appetite_factor_energy_balance(this)
Calculate appetite factor that depends on the energy balance.
Definition: m_fish.f90:2348
elemental real(srp) function energy2mass(body_energy)
Calculate the body mass from whole body energy.
Definition: m_fish.f90:547
elemental real(srp) function stomach_adjust(target_emptying_time)
Calculate the adjustment factor for the transformation of the stomach transport pattern Time scale co...
Definition: m_fish.f90:2535
impure type(stomach_emptying_pattern) function get_stomach_emptying_matrix_csv(csv_file)
Get the stomach emptying time base matrix from a CSV input data file.
Definition: m_fish.f90:2641
Defines the food item.
Definition: m_env.f90:20
This defines the root type for the FISH class.
Definition: m_fish.f90:56
Defines an umbrella class for the complete fish organism An outline of the ::fish class inheritance i...
Definition: m_fish.f90:249
This type defines history arrays that are saved for the FISH class.
Definition: m_fish.f90:27
Defines the midgut of the fish.
Definition: m_fish.f90:181
Defines the stomach of the fish.
Definition: m_fish.f90:146