The AHA Model  Revision: 12809
Reference implementation 04 (HEDG02_04)
m_behav.f90
Go to the documentation of this file.
1 !> @file m_behav.f90
2 !! The behaviour architecture of the AHA Model.
3 !! @author Sergey Budaev <sergey.budaev@uib.no>
4 !! @author Jarl Giske <jarl.giske@uib.no>
5 !! @date 2016-2017
6 
7 !-------------------------------------------------------------------------------
8 ! $Id: m_behav.f90 8322 2019-05-23 20:47:11Z sbu062 $
9 !-------------------------------------------------------------------------------
10 
11 !-------------------------------------------------------------------------------
12 !> @brief Definition of high level behavioural architecture
13 !> @section the_neurobio_module THE_BEHAVIOUR module
14 !> This module defines the behavioural architecture of the agent, extending
15 !! the starting neutobiology defined in @ref the_neurobio. Various behavioural
16 !! actions are implemented that form the behavioural repertoire of the agent.
18 
19  use commondata
20  use the_environment
21  use the_body
22  use the_neurobio
23 
24  implicit none
25 
26  character (len=*), parameter, private :: modname = "(THE_BEHAVIOUR)"
27 
28  !. . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . .
29  ! Define the components of the **behavioural repertoire** of the agent.
30  !. . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . .
31 
32  !> Root behaviour abstract type. Several different discrete behaviours
33  !! encompass the @ref aha_buildblocks_behaviour "behavioural repertoire" of
34  !! the agent. This is the base root type from which all other behaviours
35  !! are obtained by inheritance/extension.
36  type, abstract, public :: behaviour_base
37  !> Label for the behaviour type.
38  character(len=LABEL_LENGTH), private :: label
39  !> Logical flag indicating that this behaviour is activated (executed).
40  !! @warning Only one behaviour unit can be executed at a time.
41  logical :: is_active
42  !> Each behavioural type within the whole repertoire has
43  !! **expectancies** that set how each of the GOS motivational components
44  !! is affected by its execution.
45  type(motivation) :: expectancy
46  !> An expectation of the arousal level. It is the maximum weighted
47  !! value among all motivation components. This value is actually
48  !! minimised -- those behaviour which would result in the lowest
49  !! `arousal_expected` is finally executed.
50  real(srp) :: arousal_expected
51  contains
52  !> Abstract **init** function that has to be overriden by each object
53  !! that extends the root behaviour component class.
54  procedure(behaviour_init_root), public, deferred :: init
55  !> Get the execution status of the behaviour unit.
56  !! See `the_behaviour::behaviour_root_get_is_executed()`.
57  procedure, public :: is_executed => behaviour_root_get_is_executed
58  !> `gos_expected` is an accessor get-function that returns the final GOS
59  !! expectation from `expectancies_calculate`. Once we get this value for
60  !! all the possible behaviours, we choose what behaviour to execute by
61  !! minimising `gos_expected`.
62  !! See `the_behaviour::behaviour_root_gos_expectation()`.
63  procedure, public :: gos_expected => behaviour_root_gos_expectation
64  !> `attention_transfer` transfers attention weights from the actor
65  !! agent to this behaviour expectancy objects.
66  !! See `the_behaviour::behaviour_root_attention_weights_transfer()`.
67  procedure, public :: attention_transfer => &
69 
70  end type behaviour_base
71 
72  !> Abstract interface for the deferred **init** function that
73  !! has to be overriden by each object that extends the basic behavioural
74  !! component class.
75  abstract interface
76  elemental subroutine behaviour_init_root(this)
77  import :: behaviour_base
78  class(behaviour_base), intent(inout) :: this
79  end subroutine behaviour_init_root
80  end interface
81 
82  !> Movement is an umbrella abstract type linked with spatial movement.
83  type, abstract, public, extends(behaviour_base) :: move
84  !> Movement is described by its absolute distance.
85  !> @note Note that the expected cost of movement is implemented
86  !! separately in each derived class because calculations
87  !! of the movement cost are specific to each (derived)
88  !! behavioural component (e.g. the_behaviour::freeze and
89  !! the_behaviour::go_down_depth.
90  real(srp) :: distance
91  contains
92  !> The the_behaviour::move::init() is a deferred function that is
93  !! overriden by each extension object `init` method.
94  procedure(move_init_root), public, deferred :: init
95  end type move
96 
97  !> Abstract interface for the deferred **init** function that
98  !! has to be overriden by each object that extends the basic behavioural
99  !! component class.
100  abstract interface
101  elemental subroutine move_init_root(this)
102  import :: move
103  class(move), intent(inout) :: this
104  end subroutine move_init_root
105  end interface
106 
107  !- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
108  ! Specific behavioural units that are part of the behavioural repertoire
109  ! follow...
110 
111  !> **Eat food** is consuming food item(s) perceived.
112  type, public, extends(behaviour_base) :: eat_food
113  !> Increment of the agent's stomach content that results from eating a single
114  !! specific food item.
115  real(srp) :: stomach_increment_from_food
116  !> Increment of the agent's body mass that results from eating a single
117  !! specific food item.
118  real(srp) :: mass_increment_from_food
119  contains
120  !> `init` inits the behaviour element object.
121  !! See `the_behaviour::eat_food_item_init_zero()`.
122  procedure, public :: init => eat_food_item_init_zero
123  !> `do_this` performs the agent's action without changing the agent or the
124  !! environment.
125  !! @warning `do_this` is **not** intended to be called directly, only
126  !! from within `expectancies_calculate` and `execute`.
127  !! See `the_behaviour::eat_food_item_do_this()`.
128  procedure, public :: do_this => eat_food_item_do_this
129  !> `expectancies_calculate` is a subroutine (re)calculating motivations
130  !! from fake expected perceptions following from `do_this`.
131  !! @note Note that this is the computational engine to assess the
132  !! expected GOS of the behaviour, it is called from within
133  !! the base root behaviour class-bound polymorphic `gos_expect`.
134  !! See `the_behaviour::eat_food_item_motivations_expect()`.
135  procedure, public :: expectancies_calculate => &
137  !> `execute`performs the action fully, **changing the state** of the agent
138  !! and the environment.
139  !! See `the_behaviour::eat_food_item_do_execute()`.
140  procedure, public :: execute => eat_food_item_do_execute
141  end type eat_food
142 
143  !> *Reproduce* is do a single reproduction.
144  type, public, extends(behaviour_base) :: reproduce
145  !> Decrement of the agent's current reproductive factor (sex-specific sex
146  !! steroids level): testosterone
147  real(srp) :: reprfact_decrement_testosterone
148  !> Decrement of the agent's current reproductive factor (sex-specific sex
149  !! steroids level): estrogen
150  real(srp) :: reprfact_decrement_estrogen
151  !> Decrement of the agent's body mass resulting from this reproduction
152  !! event object. The objective value is calculated via the
153  !! `appraisal::probability_reproduction()` method.
154  real(srp) :: decrement_mass
155  contains
156  !> Initialise reproduce behaviour object.
157  !! See `the_behaviour::reproduce_init_zero()`.
158  procedure, public :: init => reproduce_init_zero
159  !> Do reproduce by `this_agent` (the actor agent) given the specific
160  !! probability of successful reproduction.
161  !! See `the_behaviour::reproduce_do_this()`.
162  procedure, public :: do_this => reproduce_do_this
163  !> `expectancies_calculate` is a subroutine (re)calculating
164  !! motivations from fake expected perceptions following from
165  !! `reproduce::do_this()` => `the_behaviour::reproduce_do_this()`
166  !! procedure. See implementation in
167  !! `the_behaviour::reproduce_motivations_expect()`.
168  procedure, public :: expectancies_calculate => &
170  !> Execute this behaviour component "reproduce" by the `this_agent` agent.
171  !! See `the_behaviour::reproduce_do_execute()`.
172  procedure, public :: execute => reproduce_do_execute
173  end type reproduce
174 
175  !> **Walk_random** is a single step of a Gaussian random walk.
176  type, public, extends(move) :: walk_random
177  !> Coefficient of variation for the Gaussian random walk.
178  real(srp) :: distance_cv
179  !> The body mass cost of movement; depends on the distance.
180  real(srp) :: expected_cost_moving
181  !> The expected food gain (for body mass increment) is determined from
182  !! the past history for the random walk.
183  real(srp) :: expected_food_gain
184  !> The expected direct food perception in the novel target habitat.
185  real(srp) :: expected_food_dir
186  !> The expected direct predation risk is zero for random walk.
187  real(srp) :: expected_pred_dir_risk
188  !> The expected general predation risk, i.e. the risk depending on the
189  !! current number of predators in both the perception and memory stack.
190  real(srp) :: expected_predation_risk
191  contains
192  !> Initialise the **walk_random** behaviour component to a zero state.
193  !! See `the_behaviour::walk_random_init_zero()`.
194  procedure, public :: init => walk_random_init_zero
195  !> The "do" procedure component of the behaviour element performs the
196  !! behaviour without affecting the actor agent (the_agent) and the world
197  !! (here food_item_eaten) which have intent(in), so it only can change
198  !! the internal representation of the behaviour (the type to which this
199  !! procedure is bound to, here `the_behaviour::walk_random`).
200  !! See `the_behaviour::walk_random_do_this()`.
201  procedure, public :: do_this => walk_random_do_this
202  !> `the_behaviour::walk_random::motivations_expect()` (re)calculates
203  !! motivations from fake expected perceptions following from the procedure
204  !! `walk_random::do_this()` => `the_behaviour::walk_random_do_this()`.
205  !! See `the_behaviour::walk_random_motivations_expect()`.
206  procedure, public :: expectancies_calculate => &
208  !> Execute this behaviour component "random walk" by `this_agent` agent.
209  !! See `the_behaviour::walk_random_do_execute()`.
210  procedure, public :: execute => walk_random_do_execute
211  end type walk_random
212 
213  !> **Freeze** is stop any locomotion completely.
214  type, public, extends(move) :: freeze
215  !> The expected food gain (body mass increment) is always zero for
216  !! freezing. Although energy costs are also zero.
217  real(srp) :: expected_food_gain
218  !> The expected direct predation risk is small and near-zero due to
219  !! the function the_environment::predator::risk_fish() getting low
220  !! values with is_freezing=TRUE.
221  real(srp) :: expected_pred_dir_risk
222  !> The expected general predation risk, i.e. the risk depending on the
223  !! current number of predators in both the perception and memory stack.
224  !! The expected risk assumes that a freezing predator is not easily
225  !! noticed by the roaming predators. So the subjective number of
226  !! predators in the perception is zero in the predation_risk_backend()
227  !! function.
228  real(srp) :: expected_predation_risk
229  contains
230  !> Initialise the **freeze** behaviour component to a zero state.
231  !! Freeze is a special type of move to a zero distance.
232  !! See `the_behaviour::freeze_init_zero()`.
233  procedure, public :: init => freeze_init_zero
234  !> Do freeze by `this_agent` (the actor agent). Subjective assessment
235  !! of the motivational value for this is based on the number of food
236  !! items, conspecifics and predators in the perception object.
237  !! See `the_behaviour::freeze_do_this()`.
238  procedure, public :: do_this => freeze_do_this
239  !> `the_behaviour::freeze::motivations_expect()` is a subroutine
240  !! (re)calculating motivations from fake expected perceptions from
241  !! the procedure `freeze::do_this()` => `the_behaviour::freeze_do_this()`.
242  !! See `the_behaviour:: freeze_motivations_expect()`.
243  procedure, public ::expectancies_calculate => freeze_motivations_expect
244  !> Execute this behaviour component "freeze" by `this_agent` agent.
245  !! See `the_behaviour::freeze_do_execute()`.
246  procedure, public :: execute => freeze_do_execute
247  end type freeze
248 
249  !> **Escape dart** is a very fast long distance movement, normally in
250  !! response to a direct predation threat.
251  type, public, extends(move) :: escape_dart
252  !> The expected food gain (body mass increment) is always **null** for
253  !! active escape.
254  real(srp) :: expected_food_gain
255  !> Expected body mass cost of movement; depends on the distance.
256  !! Distance, in turn, should be calculated based on the visual range
257  !! detectability of the predator for the agent, in the do_this procedure.
258  real(srp) :: expected_cost_moving
259  !> The expected direct predation risk is zero for active escape.
260  real(srp) :: expected_pred_dir_risk
261  !> The expected general predation risk, i.e. the risk depending on the
262  !! current number of predators in both the perception and memory stack.
263  !! The expected risk assumes that a escape moves the agent fully out of
264  !! reach of any direct predation risk.
265  real(srp) :: expected_predation_risk
266  contains
267  !> Initialise the **escape dart** behaviour component to a zero state.
268  !! Dart is a quick high speed active escape.
269  !! See `the_behaviour::escape_dart_init_zero()`.
270  procedure, public :: init => escape_dart_init_zero
271  !> Do active escape dart by `this_agent` (the actor agent). Subjective
272  !! assessment of the motivational value for this is based on the
273  !! distance of escape (in turn, dependent on the visibility of the
274  !! predator).
275  !! See `the_behaviour::escape_dart_do_this()`.
276  procedure, public :: do_this => escape_dart_do_this
277  !> `escape_dart::motivations_expect()` is a subroutine (re)calculating
278  !! motivations from fake expected perceptions following from
279  !! `escape_dart::do_this()` => `the_behaviour::escape_dart_do_this()`.
280  !! See `the_behaviour::escape_dart_motivations_expect()
281  procedure, public :: expectancies_calculate => &
283  !> Execute this behaviour component "escape" by `this_agent` agent.
284  !! See `the_behaviour::escape_dart_do_execute()`.
285  procedure, public :: execute => escape_dart_do_execute
286  end type escape_dart
287 
288  !> **Approach an arbitrary spatial object** is a directed movement to an
289  !! arbitrary the_environment::spatial class target object.
290  type, public, extends(move) :: approach
291  !> The body mass cost of movement; depends on the distance.
292  !> @note Note that such class attributes as `expected_food_gain`,
293  !! `expected_food_gain` `expected_pred_dir_risk`
294  !! `expected_predation_risk` should be implemented in specific
295  !! derived subclasses of the_behaviour::approach, e.g.
296  !! the_behaviour::approach_conspec.
297  real(srp) :: expected_cost_moving
298  contains
299  !> Initialise the **approach** behaviour component to a zero state.
300  !! Approach is a generic type but not abstract.
301  !! See `the_behaviour::approach_spatial_object_init_zero()`.
302  procedure, public :: init => approach_spatial_object_init_zero
303  !> The "do" procedure component of the behaviour element performs the
304  !! behaviour without affecting the actor agent (the_agent) and the world
305  !! which have intent(in), so it only can change the internal
306  !! representation of the behaviour (the type to which this procedure is
307  !! bound to, here the_environment::approach).
308  !! See `the_behaviour::approach_do_this()`.
309  procedure, public :: do_this => approach_do_this
310  !> `the_behaviour::approach::expectancies_calculate()` (re)calculates
311  !! motivations from fake expected perceptions following from the
312  !! procedure `approach::do_this()` => `the_behaviour::approach_do_this()`.
313  !! See `the_behaviour::approach_motivations_expect()`.
314  procedure, public :: expectancies_calculate => approach_motivations_expect
315  !> Execute this behaviour component "approach" by `this_agent` agent.
316  !! See `the_behaviour::approach_do_execute()`.
317  procedure, public :: execute => approach_do_execute
318  end type approach
319 
320  !> **Approach conspecifics** is directed movement towards a conspecific.
321  !> @note The `execute` method for the_behaviour::approach_conspec uses
322  !! the base class the_behaviour::approach::execute() method.
323  type, public, extends(approach) :: approach_conspec
324  !> The expected food gain (body mass increment) is always **null** for
325  !! active escape.
326  real(srp) :: expected_food_gain
327  !> The expected direct predation risk, from the nearest predator.
328  real(srp) :: expected_pred_dir_risk
329  !> The expected general predation risk, i.e. the risk depending on the
330  !! current number of predators in both the perception and memory stack.
331  real(srp) :: expected_predation_risk
332  contains
333  !> Initialise the **approach conspecific** behaviour to a zero state.
334  !! Approach conspecific is a special extension of the generic
335  !! `the_behaviour::approach` behaviour.
336  !! See `the_behaviour::approach_conspecifics_init_zero()`.
337  procedure, public :: init => approach_conspecifics_init_zero
338  !> The "do" procedure component of the behaviour element performs the
339  !! behaviour without affecting the actor agent (the_agent) and the world
340  !! which have intent(in), so it only can change the internal
341  !! representation of the behaviour (the type to which this
342  !! procedure is bound to, here `APPROACH_CONSPES`).
343  !! See `the_behaviour::approach_conspecifics_do_this()`.
344  procedure, public :: do_this => approach_conspecifics_do_this
345  !> `the_behaviour::approach_conspec::expectancies_calculate()` (re)calculates
346  !! motivations from fake expected perceptions following from the procedure
347  !! approach_conspec::do_this().
348  !! See `the_behaviour::approach_conspecifics_motivations_expect()`.
349  procedure, public :: expectancies_calculate => &
351 
352  end type approach_conspec
353 
354  !> **Migrate** is move quickly directing to the other habitat
355  type, public, extends(move) :: migrate
356  !> Target point (with offset) for migration into the target environment.
357  type(spatial) :: target_point
358  !> The body mass cost of movement; depends on the distance.
359  real(srp) :: expected_cost_moving
360  !> The expected food gain (for body mass increment).
361  real(srp) :: expected_food_gain
362  !> The expected direct food perception in the novel target habitat.
363  real(srp) :: expected_food_dir
364  !> The expected number of conspecifics at the layer below. This value is
365  !! based on the number of conspecifics below the agent's current horizon
366  integer :: expected_consp_number
367  !> The expected direct predation risk is zero for random walk.
368  real(srp) :: expected_pred_dir_risk
369  !> The expected general predation risk, i.e. the risk depending on the
370  !! current number of predators in both the perception and memory stack.
371  real(srp) :: expected_predation_risk
372  contains
373  !> Initialise the **migrate** behaviour component to a zero state.
374  !! See `the_behaviour::migrate_init_zero()`.
375  procedure, public :: init => migrate_init_zero
376  !> The "do" procedure component of the behaviour element performs the
377  !! behaviour without affecting the actor agent (the_agent) and the world
378  !! (here food_item_eaten) which have intent(in), so it only can change
379  !! the internal representation of the behaviour (the type to which this
380  !! procedure is bound to, here `MIGRATE`).
381  !! See `the_behaviour::migrate_do_this()`.
382  procedure, public :: do_this => migrate_do_this
383  !> `the_behaviour::migrate::expectancies_calculate()` (re)calculates
384  !! motivations from fake expected perceptions following from the procedure
385  !! `migrate::do_this()` => `the_behaviour::migrate_do_this()`.
386  !! See `the_behaviour::migrate_motivations_expect()`.
387  procedure, public :: expectancies_calculate => migrate_motivations_expect
388  !> Execute this behaviour component "migrate" by `this_agent` agent.
389  !! See `the_behaviour::migrate_do_execute()`.
390  procedure, public :: execute => migrate_do_execute
391  end type migrate
392 
393  !> *Go down* dive deeper.
394  type, public, extends(move) :: go_down_depth
395  !> The cost of the swimming downwards. Should be relatively low, much
396  !! smaller than the cost of active locomotion to the same distance (in
397  !! terms of the body length as set by condition_cost_swimming_burst()).
398  !! This is because it is assumed to be based on the hydrodynamic
399  !! (swimbladder) volume manipulation rather than active propulsion.
400  real(srp) :: decrement_mass_cost
401  !> The expected food gain (body mass increment) from the food items deeper
402  !! than the actor agent. This value is based on the number and average
403  !! mass of food items below the agent's current horizon.
404  real(srp) :: expected_food_gain
405  !> The expected number of conspecifics at the layer below. This value is
406  !! based on the number of conspecifics below the agent's current horizon
407  integer :: expected_consp_number
408  !> The expected predation risk at the layer below. This value is based on
409  !! the number of predators below the agent's current horizon.
410  real(srp) :: expected_predation_risk
411  contains
412  !> Initialise the **go down to a deeper spatial layer** behaviour
413  !! component to a zero state.
414  !! See `the_behaviour::go_down_depth_init_zero()`.
415  procedure, public :: init => go_down_depth_init_zero
416  !> `do_this` performs the agent's action without changing the agent
417  !! or the environment.
418  procedure, public :: do_this => go_down_do_this
419  !> `expectancies_calculate` is a subroutine (re)calculating motivations
420  !! from fake expected perceptions following from `do_this`.
421  !! @note Note that this is the computational engine to assess the
422  !! expected GOS of the behaviour, it is called from within
423  !! the base root behaviour class-bound polymorphic `gos_expect`.
424  !! See `the_behaviour::go_down_motivations_expect()`.
425  procedure, public :: expectancies_calculate => go_down_motivations_expect
426  !> Execute this behaviour component "go down" by `this_agent` agent.
427  !! See `the_behaviour::go_down_do_execute()`.
428  procedure, public :: execute => go_down_do_execute
429  end type go_down_depth
430 
431  !> *Go up* raise to a smaller depth.
432  !! TODO: abstract type linking both Up and Down.
433  type, public, extends(move) :: go_up_depth
434  !> The cost of the swimming downwards. Should be relatively low, much
435  !! smaller than the cost of active locomotion to the same distance (in
436  !! terms of the body length as set by condition_cost_swimming_burst()).
437  !! This is because it is assumed to be based on the hydrodynamic
438  !! (swimbladder) volume manipulation rather than active propulsion.
439  real(srp) :: decrement_mass_cost
440  !> The expected food gain (body mass increment) from the food items deeper
441  !! than the actor agent. This value is based on the number and average
442  !! mass of food items below the agent's current horizon.
443  real(srp) :: expected_food_gain
444  !> The expected number of conspecifics at the layer below. This value is
445  !! based on the number of conspecifics below the agent's current horizon
446  integer :: expected_consp_number
447  !> The expected predation risk at the layer below. This value is based on
448  !! the number of predators below the agent's current horizon.
449  real(srp) :: expected_predation_risk
450  contains
451  !> Initialise the **go up to a shallower spatial layer** behaviour
452  !! component to a zero state.
453  !! See `the_behaviour::go_up_depth_init_zero()`.
454  procedure, public :: init => go_up_depth_init_zero
455  !> `do_this` performs the agent's action without changing the agent
456  !! or the environment.
457  !! See `the_behaviour::go_up_do_this()`.
458  procedure, public :: do_this => go_up_do_this
459  !> `expectancies_calculate` is a subroutine (re)calculating motivations
460  !! from fake expected perceptions following from `do_this`.
461  !! @note Note that this is the computational engine to assess the
462  !! expected GOS of the behaviour, it is called from within
463  !! the base root behaviour class-bound polymorphic `gos_expect`.
464  !! See `the_behaviour::go_up_motivations_expect()`.
465  procedure, public :: expectancies_calculate => go_up_motivations_expect
466  !> Execute this behaviour component "go up" by `this_agent` agent.
467  !! See `the_behaviour::go_up_do_execute()`.
468  procedure, public :: execute => go_up_do_execute
469  end type go_up_depth
470 
471  !> This is a test fake behaviour unit that is used only for debugging.
472  !! It cannot be "execute"'d, but the expectancy can be calculated (normally
473  !! in the @ref intro_debug_mode "debug mode").
474  type, private, extends(behaviour_base) :: debug_base
475  contains
476  procedure, public :: init => debug_base_init_zero
477  procedure, public ::expectancies_calculate => &
479  end type debug_base
480 
481  !-----------------------------------------------------------------------------
482  !> The behaviour of the agent is defined by the the_behaviour::behaviour
483  !! class. This class defines the *behavioural repertoire* of the agent.
484  !! Each of the components of the behavioural repertoire (behaviour object)
485  !! is defined as a separate independent class with its own *self* parameter.
486  !! However, the agent which performs the behaviour (the *actor agent*) is
487  !! included as the first non-self parameter into the behaviour component
488  !! methods.
489  !!
490  !! For example, there is a behaviour component the_behaviour::eat_food that
491  !! defines the feeding behaviour of the agent. The method that calculates
492  !! the basic (and expected) outputs from this behaviour (i.e. "does" it)
493  !! the_behaviour::eat_food::do_this() includes the actor agent as the first
494  !! non-self (non-`this`) parameter. The same is true for all other methods
495  !! of the the_behaviour::eat_food class:
496  !! the_behaviour::eat_food::expectancies_calculate() and
497  !! the_behaviour::execute().
498  !!
499  !! Thus, the many individual classes define the behavioural repertoire:
500  !! - the_behaviour::eat_food;
501  !! - the_behaviour::reproduce;
502  !! - the_behaviour::walk_random;
503  !! - the_behaviour::freeze;
504  !! - the_behaviour::escape_dart;
505  !! - the_behaviour::approach;
506  !! - the_behaviour::approach_conspec;
507  !! - the_behaviour::migrate;
508  !! - the_behaviour::go_down_depth;
509  !! - the_behaviour::go_up_depth.
510  !! .
511  !! However the_behaviour::behaviour unites all these classes together and
512  !! plugs them into the agent class hierarchy. An overview of the behavioural
513  !! repertoire is found @ref aha_buildblocks_behaviour "here".
514  type, public, extends(gos_global) :: behaviour
515  !> Parameters that set the parameters of the behaviours and
516  !! their **expectancies** (perceived consequences).
517  type(eat_food) :: eat
520  type(freeze) :: freeze
522  type(approach) :: approach_spatial
524  type(migrate) :: migrate
525  type(go_down_depth) :: depth_down
526  type(go_up_depth) :: depth_up
528  !> Overall label of the behaviour being executed. It is used
529  !! only for outputs.
530  character(len=LABEL_LENGTH) :: behaviour_label
531  !> @name Indicator and debugging variables.
532  !! @anchor behav_debug_indicators
533  !> @{
534  !> A history stack of behaviours (labels) that have been executed.
535  character(len=LABEL_LENGTH), dimension(HISTORY_SIZE_BEHAVIOURS) :: &
536  history_behave
537  !> An indicator showing the cumulative count of the_behaviour::eat_food
538  !! attempts (notwithstanding successful or failures).
539  integer :: n_eats_all_indicator
540  !> An indicator showing the cumulative count of the food items eaten.
541  integer :: n_eaten_indicator
542  !> An indicator showing the cumulative mass of the food items eaten.
543  real(srp) :: mass_eaten_indicator
544  !> @}
545  !> The subroutines contained define what the agent really does, i.e.
546  !! implements the actual behavioural repertoire components.
547  contains
548  !> Initialise the behaviour components of the agent, the
549  !! the_behaviour::behaviour class. See
550  !! `the_behaviour::behaviour_whole_agent_init()`.
551  procedure, public :: init_behaviour => behaviour_whole_agent_init
552  !> Cleanup the behaviour history stack for the agent.
553  !! See `the_behaviour::behaviour_cleanup_history()`.
554  procedure, public :: cleanup_behav_history => behaviour_cleanup_history
555  !> Deactivate all behaviour units that compose the behaviour repertoire
556  !! of the agent. See `the_behaviour::behaviour_whole_agent_deactivate()`.
557  procedure, public :: deactivate => behaviour_whole_agent_deactivate
558  !> Obtain the label of the currently executing behaviour for the `this`
559  !! agent. See `the_behaviour::behaviour_get_behaviour_label_executing()`.
560  procedure, public :: behaviour_is => &
562  !> Select the optimal food item among (possibly) several ones that are
563  !! available in the **perception object** of the agent.
564  !! See `the_behaviour::behaviour_select_food_item()`.
565  procedure, public :: food_item_select => behaviour_select_food_item
566  !> Select the optimal conspecific among (possibly) several ones that are
567  !! available in the **perception object** of the agent.
568  !! See `the_behaviour::behaviour_select_conspecific()`.
569  procedure, public :: consp_select => behaviour_select_conspecific
570  !> Select the nearest food item among (possibly) several ones that are
571  !! available in the perception object.
572  !! See `the_behaviour::behaviour_select_food_item_nearest()`.
573  procedure, public :: food_item_select_nearest => &
575  !> Select the nearest conspecific among (possibly) several ones that are
576  !! available in the perception object.
577  !! See `the_behaviour::behaviour_select_conspecific_nearest()`.
578  procedure, public :: consp_select_nearest => &
580 
581  !> Eat a food item(s) that are found in the perception object.
582  !! See `the_behaviour::behaviour_do_eat_food_item()`.
583  procedure, public :: do_eat_food_item => behaviour_do_eat_food_item
584  !> Reproduce based on the `this` agent's current state.
585  !! See `the_behaviour::behaviour_do_reproduce()`.
586  procedure, public :: do_reproduce => behaviour_do_reproduce
587  !> Perform a random Gaussian walk to a specific average distance with
588  !! certain variance (set by the CV).
589  !! See `the_behaviour::behaviour_do_walk()`.
590  procedure, public :: do_walk => behaviour_do_walk
591  !> Perform (execute) the the_behaviour::freeze behaviour.
592  !! See `the_behaviour::behaviour_do_freeze()`.
593  procedure, public :: do_freeze => behaviour_do_freeze
594  !> Perform (execute) the the_behaviour::escape_dart behaviour.
595  !! See `the_behaviour::behaviour_do_escape_dart()`.
596  procedure, public :: do_escape => behaviour_do_escape_dart
597  !> Approach a specific the_environment::spatial class target, i.e. execute
598  !! the the_behaviour::approach behaviour.
599  !! See `the_behaviour::behaviour_do_approach()`.
600  procedure, public :: do_approach => behaviour_do_approach
601  !> Perform (execute) the the_behaviour::migrate (migration) behaviour.
602  !! See `the_behaviour::behaviour_do_migrate()`.
603  procedure, public :: do_migrate => behaviour_do_migrate
604  !> Perform a simplistic random migration. If the agent is within a specific
605  !! distance to the target environment, it emigrates there with a specific
606  !! fixed probability.
607  !! See `the_behaviour::behaviour_try_migrate_random()`.
608  procedure, public :: migrate_random => behaviour_try_migrate_random
609  !> Perform (execute) the the_behaviour::go_down_depth (go down) behaviour.
610  !! See `the_behaviour::behaviour_do_go_down()`.
611  procedure, public :: do_go_down => behaviour_do_go_down
612  !> Perform (execute) the the_behaviour::go_up_depth (go up) behaviour.
613  !! See `the_behaviour::behaviour_do_go_up()`.
614  procedure, public :: do_go_up => behaviour_do_go_up
615  !> Select and execute the optimal behaviour, i.e. the behaviour which
616  !! minimizes the expected GOS arousal.
617  !! See `the_behaviour::behaviour_select_optimal()`.
618  !! - There is a different behaviour selection backend procedure that
619  !! depends on the current GOS:
620  !! `the_behaviour::behaviour_select_fixed_from_gos()`. This procedure
621  !! selects a specific fixed behaviour unit at specific GOS.
622  !! .
623  procedure, public :: do_behave => behaviour_select_optimal
624  end type behaviour
625 
626  !> This type is an "umbrella" for all the lower-level classes.
627  type, public, extends(behaviour) :: architecture_neuro
628  contains
629  private
630  !> Initialise neuro-biological architecture.
631  !! See `the_behaviour::neurobio_init_components()` for implementation.
632  procedure, public :: init_neurobio => neurobio_init_components
633  end type architecture_neuro
634 
635  ! Implementation procedures for all "init" methods are private.
637 
638 contains ! ........ implementation of procedures for this level ................
639 
640  !+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
641  ! Functions linked with BEHAVIOURAL COMPONENTS and their expectancies.
642  ! base root behavioural (abstract) class.
643  !+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
644 
645  !-----------------------------------------------------------------------------
646  !> Transfer attention weights from the actor agent to the behaviour's
647  !! GOS expectancy object. At this stage, attention weights for **this**
648  !! behaviour's expectancy motivational state components are copied from
649  !! the actor agent's (`this_agent`) main motivational components' attention
650  !! weights.
651  !! @note The `associate` construct makes it easier to write all possible
652  !! combinations, so there is little need to implement motivation-state
653  !! specific attention transfer functions separately. Here in the below
654  !! `associate` constructs `EX` is the this **expectancy** class root
655  !! and `AG` is the **actor agent** class root.
656  !! @note Attention transfer routine cannot be conveniently placed into the
657  !! `STATE_MOTIVATION_BASE` because specific motivation states
658  !! (hunger,...) are still unavailable at this level, but
659  !! we are intended to get access to specific motivational state
660  !! of the actor agent. The `state_motivation_attention_weights_transfer`
661  !! procedure in `STATE_MOTIVATION_BASE` class just implements attention
662  !! weights transfer across two **motivation state** root class objects.
663  !! Even so, we still would need this function here calling specific
664  !! motivation object-bound versions. However, this is more complicated
665  !! than just a single subroutine as implemented here for the
666  !! `BEHAVIOUR_BASE`. Anyway, we only really copy attention weights for
667  !! all motivation states in a single batch here and never need it
668  !! elsewhere.
669  pure subroutine behaviour_root_attention_weights_transfer (this, this_agent)
670  class(behaviour_base), intent(inout) :: this
671  class(appraisal), intent(in) :: this_agent
672 
673  !> @note We have to include all the motivation state components that
674  !! are found in the `MOTIVATION` class, hunger, fear_defence etc.
675 
676  !> Transfer attention weights for **hunger**.
677  !! @note The `STATE_MOTIVATION_BASE` bound procedure that implements this
678  !! attention transfer is:
679  !! `call this%expectancy%hunger%attention_copy( &
680  !! this_agent%motivations%hunger)`
681  hunger: associate( ex=>this%expectancy%hunger%attention_weight, &
682  ag=>this_agent%motivations%hunger%attention_weight )
683  ex%light = ag%light
684  ex%depth = ag%depth
685  ex%food_dir = ag%food_dir
686  ex%food_mem = ag%food_mem
687  ex%conspec = ag%conspec
688  ex%pred_dir = ag%pred_dir
689  ex%predator = ag%predator
690  ex%stomach = ag%stomach
691  ex%bodymass = ag%bodymass
692  ex%energy = ag%energy
693  ex%age = ag%age
694  ex%reprfac = ag%reprfac
695  end associate hunger
696 
697  !> Transfer attention weights for **fear_defence**.
698  !! @note The `STATE_MOTIVATION_BASE` bound procedure that implements this
699  !! attention transfer is:
700  !! `call this%expectancy%fear_defence%attention_copy( &
701  !! this_agent%motivations%fear_defence)`
702  a_active: associate( ex=>this%expectancy%fear_defence%attention_weight, &
703  ag=>this_agent%motivations%fear_defence%attention_weight )
704  ex%light = ag%light
705  ex%depth = ag%depth
706  ex%food_dir = ag%food_dir
707  ex%food_mem = ag%food_mem
708  ex%conspec = ag%conspec
709  ex%pred_dir = ag%pred_dir
710  ex%predator = ag%predator
711  ex%stomach = ag%stomach
712  ex%bodymass = ag%bodymass
713  ex%energy = ag%energy
714  ex%age = ag%age
715  ex%reprfac = ag%reprfac
716  end associate a_active
717 
718  !> Transfer attention weights for **reproduction**.
719  !! @note The `STATE_MOTIVATION_BASE` bound procedure that implements this
720  !! attention transfer is:
721  !! `call this%expectancy%reproduction%attention_copy( &
722  !! this_agent%motivations%reproduction)`
723  reprod: associate( ex=>this%expectancy%reproduction%attention_weight, &
724  ag=>this_agent%motivations%reproduction%attention_weight )
725  ex%light = ag%light
726  ex%depth = ag%depth
727  ex%food_dir = ag%food_dir
728  ex%food_mem = ag%food_mem
729  ex%conspec = ag%conspec
730  ex%pred_dir = ag%pred_dir
731  ex%predator = ag%predator
732  ex%stomach = ag%stomach
733  ex%bodymass = ag%bodymass
734  ex%energy = ag%energy
735  ex%age = ag%age
736  ex%reprfac = ag%reprfac
737  end associate reprod
738 
740 
741  !-----------------------------------------------------------------------------
742  !> Accessor get-function for the final expected GOS arousal from this
743  !! behaviour. All calculations for are done in `expectancies_calculate` for
744  !! the specific behaviour unit.
745  elemental function behaviour_root_gos_expectation(this) result (gos_expected)
746  class(behaviour_base), intent(in) :: this !< @param this self.
747  !< @returns Expected GOS arousal level if **this** behaviour is executed.
748  real(srp) :: gos_expected
749 
750  gos_expected = this%arousal_expected
751 
752  end function behaviour_root_gos_expectation
753 
754  !-----------------------------------------------------------------------------
755  !> Get the execution status of the behaviour unit. If TRUE, the unit is
756  !! currently active and is being executed. This is the "getter" for
757  !! the_behaviour::behaviour_base::is_active
758  elemental function behaviour_root_get_is_executed(this) result (is_exec)
759  class(behaviour_base), intent(in) :: this
760  !> @return TRUE, the behaviour unit is currently active and is being
761  !! executed; FALSE otherwise.
762  logical :: is_exec
763 
764  is_exec = this%is_active
765 
766  end function behaviour_root_get_is_executed
767 
768  !+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
769  ! Functions linked with SPECIFIC BEHAVIOURAL COMPONENTS.
770  !+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
771 
772  !-----------------------------------------------------------------------------
773  !> Initialise the **eat food item** behaviour component to a zero state.
774  elemental subroutine eat_food_item_init_zero(this)
775  class(eat_food), intent(inout) :: this
776 
777  !> First init components from the base root class
778  !! `the_behaviour::behaviour_base`:
779  !! Mandatory label component that should be read-only.
780  this%label = "EAT_FOOD"
781  !> The execution status is always FALSE, can be reset to TRUE only when
782  !! the behaviour unit is called to execution.
783  this%is_active = .false.
784 
785  !> And the *expectancy* type components.
786  call this%expectancy%init()
787  !> And init the expected arousal data component.
788  this%arousal_expected = 0.0_srp
789 
790  !> Second, init components of this specific behaviour (`EAT_FOOD`)
791  !! component extended class.
792  !! @note Note that we initialise increments to 0.0, not MISSING as
793  !! increments will be later added. And several items can be added
794  !! consecutively.
795  this%stomach_increment_from_food = 0.0_srp
796  this%mass_increment_from_food = 0.0_srp
797 
798  end subroutine eat_food_item_init_zero
799 
800  !-----------------------------------------------------------------------------
801  !> Initialise the **walk_random** behaviour component to a zero state.
802  elemental subroutine walk_random_init_zero(this)
803  class(walk_random), intent(inout) :: this
804 
805  !> First, initialise components from the base root class
806  !! `the_behaviour::behaviour_base`.
807  !> Mandatory label component that should be read-only.
808  this%label = "WALK_RANDOM"
809  !> The execution status is always FALSE, can be reset to TRUE only when
810  !! the behaviour unit is called to execution.
811  this%is_active = .false.
812 
813  !> And the *expectancy* components.
814  call this%expectancy%init()
815  this%arousal_expected = 0.0_srp
816 
817  !> Abstract `MOVE` component.
818  this%distance = missing
819 
820  !> Second, init components of this specific behaviour (`WALK_RANDOM`).
821  this%distance_cv = missing
822  this%expected_cost_moving = missing
823  this%expected_food_gain = missing
824  this%expected_food_dir = missing
825  this%expected_pred_dir_risk = missing
826  this%expected_predation_risk = missing
827 
828  end subroutine walk_random_init_zero
829 
830  !-----------------------------------------------------------------------------
831  !> Initialise the **freeze** behaviour component to a zero state.
832  !! Freeze is a special type of move to a zero distance / zero speed.
833  elemental subroutine freeze_init_zero(this)
834  class(freeze), intent(inout) :: this
835 
836  !> First init components from the base root class
837  !! `the_behaviour::behaviour_base`.
838  !> Mandatory label component that should be read-only.
839  this%label = "FREEZE"
840  !> The execution status is always FALSE, can be reset to TRUE only when
841  !! the behaviour unit is called to execution.
842  this%is_active = .false.
843 
844  !> And the *expectancy* components.
845  call this%expectancy%init()
846  this%arousal_expected = 0.0_srp
847 
848  !> Abstract `MOVE` component.
849  this%distance = 0.0_srp
850 
851  !> Second, init components of this specific behaviour (`FREEZE`).
852  this%expected_food_gain = 0.0_srp
853  this%expected_pred_dir_risk = missing
854  this%expected_predation_risk = missing
855 
856  end subroutine freeze_init_zero
857 
858  !-----------------------------------------------------------------------------
859  !> Do freeze by `this_agent` (the actor agent). Subjective assessment of the
860  !! motivational value for this is based on the number of food items,
861  !! conspecifics and predators in the perception object.
862  subroutine freeze_do_this(this, this_agent)
863  !> @param[inout] this the object itself.
864  class(freeze), intent(inout) :: this
865  !> @param[in] this_agent is the actor agent which goes down.
866  class(appraisal), intent(in) :: this_agent
867 
868  ! **WEIGHT_DIRECT** is the relative weight given to the immediate
869  ! perception of predators over the predators counts in the memory stack.
870  ! Obtained from global parameters
871  ! (`commondata::predation_risk_weight_immediate`).
872  real(SRP), parameter :: WEIGHT_DIRECT = predation_risk_weight_immediate
873 
874  ! **MEM_WIND** is the size of the memory window when assessing the
875  ! predator risk, only this number of the latest elements from the memory
876  ! stack is taken into account. So we further weight the direct threat
877  ! over the background risk when making the decision.
878  ! @note Note that we take into account the whole memory size
879  ! (commondata::history_size_perception).
880  integer, parameter :: MEM_WIND = history_size_perception
881 
882  !> ### Implementation details ###
883  !> The expected food gain for freezing is zero as immobile agent
884  !! does not eat.
885  this%expected_food_gain = 0.0_srp
886 
887  !> Calculate the expected direct risk of predation that is based on the
888  !! distance to the nearest predator. However, a version of the
889  !! the_neurobio::perception::risk_pred() procedure for freezing/immobile
890  !! agent is used here.
891  this%expected_pred_dir_risk = this_agent%risk_pred( is_freezing=.true. )
892 
893  !> Calculate the expected predation risk for the immobile agent. It is
894  !! assumed that predators that are roaming nearby cannot easily detect an
895  !! immobile/freezing agent as long as it does not move (freezing here has
896  !! significant similarity with sheltering). Therefore, the expectancy is
897  !! based on a (subjective) **zero** count of the number of predators in
898  !! the agent's perception object and normal risk component based on the
899  !! predators in the memory stack. The calculation is done by the standard
900  !! `the_neurobio::predation_risk_backend()` function.
901  !! Thus, the resulting general risk is calculated as:
902  !! @f[ R = 0 + r_{id} \cdot (1 - \omega) , @f]
903  !! where @f$ r_{id} @f$) is the average number of predators in the latest
904  !! memory stack and @f$ \omega @f$ is the weighting factor for the actual
905  !! number of predators (that is zero in this case).
906  this%expected_predation_risk = &
907  predation_risk_backend( &
908  pred_count=0, &
909  pred_memory_mean=this_agent%memory_stack%get_pred_mean(mem_wind), &
910  weight_direct=weight_direct )
911 
912  end subroutine freeze_do_this
913 
914  !-----------------------------------------------------------------------------
915  !> `the_behaviour::freeze::motivations_expect()` (re)calculates
916  !! motivations from fake expected perceptions following from the procedure
917  !! `freeze::do_this()` => `the_behaviour::freeze_do_this()`.
918  subroutine freeze_motivations_expect(this, this_agent, &
919  time_step_model, rescale_max_motivation)
920  !> @param[inout] this the object itself.
921  class(freeze), intent(inout) :: this
922  !> @param[in] this_agent is the actor agent which does freezing.
923  class(appraisal), intent(in) :: this_agent
924  !> @param [in] time_step_model optional time step of the model,
925  !! **overrides** the value calculated from the spatial data.
926  integer, optional, intent(in) :: time_step_model
927  !> @param[in] rescale_max_motivation optional maximum motivation value for
928  !! rescaling all motivational components for comparison
929  !! across all motivation and perceptual components and behaviour
930  !! units.
931  real(SRP), optional, intent(in) :: rescale_max_motivation
932 
933  ! Local copy of optional model time step
934  integer :: time_step_model_here
935 
936  ! Local variables
937  real(SRP) :: max_motivation ! Local max. over all motivation components.
938 
939  ! The actor agent's current stomach contents.
940  real(SRP) :: agent_stomach
941 
942  !> ### Notable local variables ###
943  !> #### Perception overrides ####
944  !> - **expect_pred_dir** is the expected direct predation risk; it is zero.
945  real(SRP) :: expect_pred_dir
946  !> - **expect_predator** is the expected general predation risk, that is
947  !! based on a weighting of the current predation and predation risk
948  !! from the memory stack.
949  real(SRP) :: expect_predator
950  !> - **expect_stomach** is the expected stomach contents as a consequence
951  !! of freezing. Note that there is no food consumption while freezing.
952  real(SRP) :: expect_stomach
953  !> - **expect_bodymass** is the expected body mass as a consequence of
954  !! freezing. Notably, it subtracts a small living cost component.
955  real(SRP) :: expect_bodymass
956  !> - **expect_energy** is the expected energy reserves as a consequence
957  !! of the freezing. Calculated from the body mass and weight.
958  !! .
959  real(SRP) :: expect_energy
960 
961  ! PROCNAME is the procedure name for logging and debugging
962  character(len=*), parameter :: PROCNAME = &
963  "(freeze_motivations_expect)"
964 
965  !> #### Checks and preparations ####
966  !> Check optional time step parameter. If not provided, use global
967  !! parameter value from commondata::global_time_step_model_current.
968  if (present(time_step_model)) then
969  time_step_model_here = time_step_model
970  else
971  time_step_model_here = global_time_step_model_current
972  end if
973 
974  !> #### Call do_this ####
975  !> As the first step, we use the **do**-procedure `freeze::do_this()`
976  !! => `the_behaviour::freeze_do_this()` to perform the behaviour desired
977  !! without changing either the agent or its environment, obtaining the
978  !! **subjective** values of the `this` behaviour components that later feed
979  !! into the motivation **expectancy** functions:
980  !! - `perception_override_pred_dir`
981  !! - `perception_override_predator`
982  !! - `perception_override_stomach`
983  !! - `perception_override_bodymass`
984  !! - `perception_override_energy`
985  !! .
986  call this%do_this(this_agent = this_agent)
987 
988  !> #### Calculate expected (fake) perceptions ####
989  !> First, calculate the expected stomach contents, body mass and energy
990  !! reserves out of the fixed zero food gain that is returned from the
991  !! `do_this` procedure.
992  !> - Obtain the agent's current stomach contents.
993  agent_stomach = this_agent%get_stom_content()
994 
995  !> - Calculate the expected stomach content, which is decremented by the
996  !! expected digestion value (the_body::stomach_emptify_backend()).
997  expect_stomach = max( zero, &
998  agent_stomach - &
999  stomach_emptify_backend(agent_stomach) )
1000 
1001  !> - Calculate the expected body mass of the agent as a consequence of
1002  !! freezing. The body mass is decremented by a small value of the
1003  !! living cost (the_body::body_mass_calculate_cost_living_step()).
1004  expect_bodymass = max( zero, &
1005  this_agent%get_mass() - this_agent%living_cost() )
1006 
1007  !> - The expected energy reserves are calculated from the fake
1008  !! perceptions of the body mass and the current length (it does not
1009  !! change as food intake is zero in case of freezing) using
1010  !! the_body::energy_reserve() function.
1011  !! .
1012  expect_energy = energy_reserve( expect_bodymass, this_agent%length() )
1013 
1014  !> Second, transfer the predation risk expectancies from the freezing
1015  !! class object to the dedicated override perception variables (their
1016  !! final values are calculated in `do_this`).
1017  expect_pred_dir = this%expected_pred_dir_risk
1018  expect_predator = this%expected_predation_risk
1019 
1020  !> #### Calculate motivation expectancies ####
1021  !> The next step is to calculate the motivational expectancies using the
1022  !! fake perceptions to override the default (actual agent's) values.
1023  !> At this stage, first, calculate motivation values resulting from the
1024  !! behaviour done (`freeze::do_this()` ) at the previous steps: what
1025  !! would be the motivation values *if* the agent does perform
1026  !! FREEZE? Technically, this is done by calling the **neuronal
1027  !! response function**, `percept_components_motiv::motivation_components()`
1028  !! method, for each of the motivational states with `perception_override_`
1029  !! dummy parameters overriding the default values.
1030  !! Here is the list of the fake overriding perceptions for the
1031  !! FREEZE behaviour:
1032  !! - `perception_override_pred_dir`
1033  !! - `perception_override_predator`
1034  !! - `perception_override_stomach`
1035  !! - `perception_override_bodymass`
1036  !! - `perception_override_energy`
1037  !! .
1038  ! @note **Expectancy** assessment for **hunger** motivation, using
1039  ! `PERCEPT_COMPONENTS_MOTIV`-bound procedure with intent[in] for
1040  ! `this_agent` now.
1041  call this%expectancy%hunger%percept_component%motivation_components &
1042  (this_agent, &
1043  ! Parameters:: Boolean G x P matrices:
1044  param_gp_matrix_light = light_hunger_genotype_neuronal, &
1045  param_gp_matrix_depth = depth_hunger_genotype_neuronal, &
1046  param_gp_matrix_food_dir = foodcount_hunger_genotype_neuronal, &
1047  param_gp_matrix_food_mem = food_mem_hunger_genotype_neuronal, &
1048  param_gp_matrix_conspec = conspcount_hunger_genotype_neuronal, &
1049  param_gp_matrix_pred_dir = pred_direct_hunger_genotype_neuronal, &
1050  param_gp_matrix_predator = pred_meancount_hunger_genotype_neuronal, &
1051  param_gp_matrix_stomach = stom_hunger_genotype_neuronal, &
1052  param_gp_matrix_bodymass = bodymass_hunger_genotype_neuronal, &
1053  param_gp_matrix_energy = energy_hunger_genotype_neuronal, &
1054  param_gp_matrix_age = age_hunger_genotype_neuronal, &
1055  param_gp_matrix_reprfac = reprfac_hunger_genotype_neuronal, &
1056  ! Parameters :: G x P variances:
1057  param_gerror_cv_light = light_hunger_genotype_neuronal_gerror_cv, &
1058  param_gerror_cv_depth = depth_hunger_genotype_neuronal_gerror_cv, &
1059  param_gerror_cv_food_dir = foodcount_hunger_genotype_neuronal_gerror_cv,&
1060  param_gerror_cv_food_mem = food_mem_hunger_genotype_neuronal_gerror_cv, &
1061  param_gerror_cv_conspec = conspcount_hunger_genotype_neuronal_gerror_cv,&
1062  param_gerror_cv_pred_dir = pred_direct_hunger_genotype_neuronal_gerror_cv,&
1063  param_gerror_cv_predator = pred_meancount_hunger_genotype_neuronal_gerror_cv,&
1064  param_gerror_cv_stomach = stom_hunger_genotype_neuronal_gerror_cv, &
1065  param_gerror_cv_bodymass = bodymass_hunger_genotype_neuronal_gerror_cv, &
1066  param_gerror_cv_energy = energy_hunger_genotype_neuronal_gerror_cv, &
1067  param_gerror_cv_age = age_hunger_genotype_neuronal_gerror_cv, &
1068  param_gerror_cv_reprfac = reprfac_hunger_genotype_neuronal_gerror_cv, &
1069  ! Real agent perception components are now substituted by the *fake*
1070  ! values resulting from executing this behaviour (`do_this` method).
1071  ! This is repeated for all the motivations: *hunger*,
1072  ! *fear state* etc.
1073  perception_override_pred_dir = expect_pred_dir, &
1074  perception_override_predator = expect_predator, &
1075  perception_override_stomach = expect_stomach, &
1076  perception_override_bodymass = expect_bodymass, &
1077  perception_override_energy = expect_energy &
1078  )
1079  !> Real agent perception components are now substituted by the *fake*
1080  !! values resulting from executing this behaviour (`reproduce::do_this()`
1081  !! => `the_behaviour::reproduce_do_this()` method). This is repeated for
1082  !! all the motivations: *hunger*, *fear state* etc. These optional
1083  !! **override parameters** are substituted by the "fake" values.
1084 
1085  ! @note **Expectancy** assessment for **fear_defence** motivation,
1086  ! using `PERCEPT_COMPONENTS_MOTIV`-bound procedure with intent[in]
1087  ! for `this_agent` now.
1088  call this%expectancy%fear_defence%percept_component%motivation_components &
1089  (this_agent, &
1090  ! Parameters:: Boolean G x P matrices:
1091  param_gp_matrix_light = light_actv_avoid_genotype_neuronal, &
1092  param_gp_matrix_depth = depth_actv_avoid_genotype_neuronal, &
1093  param_gp_matrix_food_dir = foodcount_actv_avoid_genotype_neuronal, &
1094  param_gp_matrix_food_mem = food_mem_actv_avoid_genotype_neuronal, &
1095  param_gp_matrix_conspec = conspcount_actv_avoid_genotype_neuronal, &
1096  param_gp_matrix_pred_dir = pred_direct_actv_avoid_genotype_neuronal, &
1097  param_gp_matrix_predator = pred_meancount_actv_avoid_genotype_neuronal, &
1098  param_gp_matrix_stomach = stom_actv_avoid_genotype_neuronal, &
1099  param_gp_matrix_bodymass = bodymass_actv_avoid_genotype_neuronal, &
1100  param_gp_matrix_energy = energy_actv_avoid_genotype_neuronal, &
1101  param_gp_matrix_age = age_actv_avoid_genotype_neuronal, &
1102  param_gp_matrix_reprfac = reprfac_actv_avoid_genotype_neuronal, &
1103  ! Parameters :: G x P variances:
1104  param_gerror_cv_light = light_actv_avoid_genotype_neuronal_gerror_cv, &
1105  param_gerror_cv_depth = depth_actv_avoid_genotype_neuronal_gerror_cv, &
1106  param_gerror_cv_food_dir = foodcount_actv_avoid_genotype_neuronal_gerror_cv,&
1107  param_gerror_cv_food_mem = food_mem_actv_avoid_genotype_neuronal_gerror_cv, &
1108  param_gerror_cv_conspec = conspcount_actv_avoid_genotype_neuronal_gerror_cv,&
1109  param_gerror_cv_pred_dir = pred_direct_actv_avoid_genotype_neuronal_gerror_cv,&
1110  param_gerror_cv_predator = pred_meancount_actv_avoid_genotype_neuronal_gerror_cv,&
1111  param_gerror_cv_stomach = stom_actv_avoid_genotype_neuronal_gerror_cv, &
1112  param_gerror_cv_bodymass = bodymass_actv_avoid_genotype_neuronal_gerror_cv,&
1113  param_gerror_cv_energy = energy_actv_avoid_genotype_neuronal_gerror_cv,&
1114  param_gerror_cv_age = age_actv_avoid_genotype_neuronal_gerror_cv, &
1115  param_gerror_cv_reprfac = reprfac_actv_avoid_genotype_neuronal_gerror_cv,&
1116  ! @note Real agent perception components are now **substituted**
1117  ! by the **fake** values resulting from executing this
1118  ! behaviour (`do_this` method).
1119  perception_override_pred_dir = expect_pred_dir, &
1120  perception_override_predator = expect_predator, &
1121  perception_override_stomach = expect_stomach, &
1122  perception_override_bodymass = expect_bodymass, &
1123  perception_override_energy = expect_energy &
1124  )
1125 
1126  ! @note **Expectancy** assessment for **reproduction** motivation,
1127  ! using `PERCEPT_COMPONENTS_MOTIV`-bound procedure with intent[in]
1128  ! for `this_agent` now.
1129  call this%expectancy%reproduction%percept_component%motivation_components &
1130  (this_agent, &
1131  ! Parameters:: Boolean G x P matrices:
1132  param_gp_matrix_light = light_reproduce_genotype_neuronal, &
1133  param_gp_matrix_depth = depth_reproduce_genotype_neuronal, &
1134  param_gp_matrix_food_dir = foodcount_reproduce_genotype_neuronal, &
1135  param_gp_matrix_food_mem = food_mem_reproduce_genotype_neuronal, &
1136  param_gp_matrix_conspec = conspcount_reproduce_genotype_neuronal, &
1137  param_gp_matrix_pred_dir = pred_direct_reproduce_genotype_neuronal, &
1138  param_gp_matrix_predator = pred_meancount_reproduce_genotype_neuronal, &
1139  param_gp_matrix_stomach = stom_reproduce_genotype_neuronal, &
1140  param_gp_matrix_bodymass = bodymass_reproduce_genotype_neuronal, &
1141  param_gp_matrix_energy = energy_reproduce_genotype_neuronal, &
1142  param_gp_matrix_age = age_reproduce_genotype_neuronal, &
1143  param_gp_matrix_reprfac = reprfac_reproduce_genotype_neuronal, &
1144  ! Parameters :: G x P variances:
1145  param_gerror_cv_light = light_reproduce_genotype_neuronal_gerror_cv, &
1146  param_gerror_cv_depth = depth_reproduce_genotype_neuronal_gerror_cv, &
1147  param_gerror_cv_food_dir = foodcount_reproduce_genotype_neuronal_gerror_cv,&
1148  param_gerror_cv_food_mem = food_mem_reproduce_genotype_neuronal_gerror_cv, &
1149  param_gerror_cv_conspec = conspcount_reproduce_genotype_neuronal_gerror_cv,&
1150  param_gerror_cv_pred_dir = pred_direct_reproduce_genotype_neuronal_gerror_cv,&
1151  param_gerror_cv_predator = pred_meancount_reproduce_genotype_neuronal_gerror_cv,&
1152  param_gerror_cv_stomach = stom_reproduce_genotype_neuronal_gerror_cv, &
1153  param_gerror_cv_bodymass = bodymass_reproduce_genotype_neuronal_gerror_cv,&
1154  param_gerror_cv_energy = energy_reproduce_genotype_neuronal_gerror_cv,&
1155  param_gerror_cv_age = age_reproduce_genotype_neuronal_gerror_cv, &
1156  param_gerror_cv_reprfac = reprfac_reproduce_genotype_neuronal_gerror_cv,&
1157  ! @note Real agent perception components are now **substituted**
1158  ! by the **fake** values resulting from executing this
1159  ! behaviour (`do_this` method).
1160  perception_override_pred_dir = expect_pred_dir, &
1161  perception_override_predator = expect_predator, &
1162  perception_override_stomach = expect_stomach, &
1163  perception_override_bodymass = expect_bodymass, &
1164  perception_override_energy = expect_energy &
1165  )
1166 
1167  !> #### Calculate primary and final motivations ####
1168  !> Next, from the perceptual components calculated at the previous
1169  !! step we can obtain the **primary** and **final motivation** values by
1170  !! weighed summing.
1171  if (present(rescale_max_motivation)) then
1172  !> Here we can use global maximum motivation across all behaviours and
1173  !! perceptual components if it is provided, for rescaling.
1174  max_motivation = rescale_max_motivation
1175  else
1176  !> Or can rescale using local maximum value for this behaviour only.
1177  max_motivation = this%expectancy%max_perception()
1178  end if
1179 
1180  !> Transfer attention weights from the actor agent `this_agent` to the
1181  !! `this` behaviour component. So, we will now use the updated modulated
1182  !! attention weights of the agent rather than their default parameter
1183  !! values.
1184  call this%attention_transfer(this_agent)
1185 
1186  !> So the primary motivation values are calculated.
1187  call this%expectancy%motivation_primary_calc(max_motivation)
1188 
1189  !> Primary motivations are logged in the @ref intro_debug_mode "debug mode".
1190  call log_dbg( ltag_info // "Primary motivations: " // &
1191  "hunger: " // &
1192  tostr(this%expectancy%hunger%motivation_prim) // &
1193  ", fear_defence: " // &
1194  tostr(this%expectancy%fear_defence%motivation_prim) // &
1195  ", reproduce: " // &
1196  tostr(this%expectancy%reproduction%motivation_prim), &
1197  procname, modname )
1198 
1199  !> There is **no modulation** at this stage, so the final motivation
1200  !! values are the same as primary motivations.
1201  call this%expectancy%modulation_none()
1202 
1203  !> #### Calculate motivation expectancies ####
1204  !> Finally, calculate the finally **expected arousal level for this
1205  !! behaviour**. As in the GOS, the overall arousal is the maximum value
1206  !! among all motivation components.
1207  this%arousal_expected = this%expectancy%max_final()
1208 
1209  !> Log also the final expectancy value in the @ref intro_debug_mode
1210  !! "debug mode".
1211  call log_dbg( ltag_info // "Expectancy: " // tostr(this%arousal_expected),&
1212  procname, modname )
1213 
1214  !> Now as we know the expected arousal, we can choose the behaviour which
1215  !! would minimise this arousal level.
1216 
1217  end subroutine freeze_motivations_expect
1218 
1219  !-----------------------------------------------------------------------------
1220  !> Execute this behaviour component "freeze" by `this_agent` agent.
1221  subroutine freeze_do_execute(this, this_agent)
1222  class(freeze), intent(inout) :: this
1223  !> @param[in] this_agent is the actor agent which goes down.
1224  class(appraisal), intent(inout) :: this_agent
1225 
1226  !> ### Implementation details ###
1227  !> #### Step 1: do_this ####
1228  !> As the first step, we use the **do**-procedure `freeze::do_this()`
1229  !! to perform the behaviour desired. As a result, the following values
1230  !! are obtained:
1231  !! - expected zero food gain
1232  !! - expected zero direct predation risk
1233  !! - expected general predation risk, assuming no direct threat.
1234  !! .
1235  !!
1236  !> However, because freezing does not incur any specific behavioural costs
1237  !! and does not change any environmental objects, calling `do_this()` is
1238  !! really **unnecessary**. It is therefore only called in the DEBUG mode to
1239  !! log and check the resulting perception values.
1240  if (is_debug) then
1241  call this%do_this(this_agent = this_agent)
1242  call log_dbg(ltag_info // "Executed FREEZING; Perception values: " // &
1243  "Food gain: " // tostr(this%expected_food_gain) // &
1244  ", Direct risk: " // tostr(this%expected_pred_dir_risk) // &
1245  ", Indirect risk: " // tostr(this%expected_predation_risk) )
1246  end if
1247 
1248  !> #### Step 2: Change the agent ####
1249  !> Freezing results in some small cost, equal to a single piece of the the
1250  !! cost of living. However, it is much smaller than the cost of locomotion.
1251  !! Also, no food can be obtained while freezing but digestion still occurs,
1252  !! so the value of the stomach contents is reduced by a fixed fraction.
1253  !! However, freezing, unlike other behaviour components, does not incur any
1254  !! specific cost or change of the agent. Cost of living and digestion
1255  !! subtractions are updated for every time step for every other
1256  !! behaviours anyway. Therefore, it is **not** done here.
1257 
1258  !> #### Step 3: Change the environment ####
1259  !> Freezing does not affect the environmental objects.
1260 
1261  end subroutine freeze_do_execute
1262 
1263  !-----------------------------------------------------------------------------
1264  !> Initialise the **escape dart** behaviour component to a zero state.
1265  !! Dart is a quick high speed active escape.
1266  elemental subroutine escape_dart_init_zero(this)
1267  class(escape_dart), intent(inout) :: this
1268 
1269  !> First init components from the base root class
1270  !! `the_behaviour::behaviour_base`.
1271  !> Mandatory label component that should be read-only.
1272  this%label = "ESCAPE_DART"
1273  !> The execution status is always FALSE, can be reset to TRUE only when
1274  !! the behaviour unit is called to execution.
1275  this%is_active = .false.
1276 
1277  !> And the *expectancy* components.
1278  call this%expectancy%init()
1279  this%arousal_expected = 0.0_srp
1280 
1281  !> Abstract `MOVE` component.
1282  this%distance = missing
1283 
1284  !> Second, init components of this specific behaviour (`ESCAPE_DART`).
1285  this%expected_food_gain = 0.0_srp
1286  this%expected_cost_moving = missing
1287  this%expected_pred_dir_risk = missing
1288  this%expected_predation_risk = missing
1289 
1290  end subroutine escape_dart_init_zero
1291 
1292  !-----------------------------------------------------------------------------
1293  !> Do active escape dart by `this_agent` (the actor agent). Subjective
1294  !! assessment of the motivational value for this is based on the distance of
1295  !! escape (in turn, dependent on the visibility of the predator).
1296  subroutine escape_dart_do_this(this, this_agent, predator_object, &
1297  dist_is_stochastic, time_step_model)
1298  class(escape_dart), intent(inout) :: this
1299  !> @param[in] this_agent is the actor agent which goes down.
1300  class(appraisal), intent(in) :: this_agent
1301  !> @param[in] predator_object optional predator object, if present, it is
1302  !! assumed the actor agent tries to actively escape from this
1303  !! specific predator.
1304  class(spatial), optional, intent(in) :: predator_object
1305  !> @param[in] dist_is_stochastic Logical flag, if set to TRUE, the escape
1306  !! distance is stochastic in the expectancy engine; this can
1307  !! define an internal expectation uncertainty.
1308  logical, optional, intent(in) :: dist_is_stochastic
1309  !> @param[in] time_step_model optional time step of the model, overrides
1310  !! the value calculated from the spatial data.
1311  integer, optional, intent(in) :: time_step_model
1312 
1313  ! **WEIGHT_DIRECT** is the relative weight given to the immediate
1314  ! perception of predators over the predators counts in the memory stack.
1315  ! Obtained from global parameters
1316  ! (`commondata::predation_risk_weight_immediate`).
1317  real(SRP), parameter :: WEIGHT_DIRECT = predation_risk_weight_immediate
1318 
1319  ! **MEM_WIND** is the size of the memory window when assessing the
1320  ! predator risk, only this number of the latest elements from the memory
1321  ! stack is taken into account. So we further weight the direct threat
1322  ! over the background risk when making the decision.
1323  ! @note Note that we take into account the whole memory size
1324  ! (commondata::history_size_perception).
1325  integer, parameter :: MEM_WIND = history_size_perception
1326 
1327  ! Local copy of the time step parameter.
1328  integer :: time_step_model_here
1329 
1330  ! Local maximum visibility distance (visual range) to the predator.
1331  real(SRP) :: visibility_range_predator
1332 
1333  !> ### Implementation details ###
1334  !> #### Checks and preparations ####
1335  !> Check optional time step parameter. If unset, use global
1336  !! `commondata::global_time_step_model_current`.
1337  if (present(time_step_model)) then
1338  time_step_model_here = time_step_model
1339  else
1340  time_step_model_here = global_time_step_model_current
1341  end if
1342 
1343  !> #### Calculate expected food gain ####
1344  !> The expected food gain for active escape is zero as the agent cannot
1345  !! eat at this time.
1346  this%expected_food_gain = 0.0_srp
1347 
1348  !> #### Calculate cost of fast escape movement ####
1349  !! First, calculate the distance of escape. The escape distance, in turn,
1350  !! depends on the visibility distance of the predator object: it should
1351  !! exceed this distance, so the actor agent could not see the predator
1352  !! any more.
1353  !> ##### Visibility range of the predator #####
1354  if (present(predator_object)) then
1355  !> First, check if the predator object is provided. If the predator
1356  !! object is provided as a dummy parameter, visibility range can be
1357  !! assessed using its size. However, the calculations depend on the
1358  !! exact type of the predator object because it can be
1359  !! the_environment::predator or the_neurobio::spatialobj_percept_comp
1360  !! (in predator perception: the_neurobio::percept_predator) or perhaps
1361  !! even just any extension of the the_environment::spatial class.
1362  !! Fortran `select type` construct is used here.
1363  select type (predator_object)
1364  !> - If the type of the object is the_environment::predator, then
1365  !! visibility benefits from the object-bound function
1366  !! the_environment::predator::visibility().
1367  type is (predator)
1368  visibility_range_predator = &
1369  predator_object%visibility( &
1370  time_step_model = time_step_model_here)
1371  !> - If the object type is the_neurobio::spatialobj_percept_comp
1372  !! (as in perception objects), the visibility is calculated
1373  !! using the object bound function
1374  !! the_neurobio::spatialobj_percept_comp::visibility() with the
1375  !! default object type (`object_area` parameter is not provided),
1376  !! so the object area is calculated for *fish* (see
1377  !! the_neurobio::spatialobj_percept_visibility_visual_range()).
1378  type is (spatialobj_percept_comp)
1379  ! @warning The named parameter `time_step_model` is mandatory here
1380  ! because `visibility()` function first non-self parameter
1381  ! is `object_area`, not `time_step_model`.
1382  visibility_range_predator = &
1383  predator_object%visibility( &
1384  time_step_model = time_step_model_here)
1385  !> - If the object type is the default class the_environment::spatial,
1386  !! e.g. the_environment::spatial_moving, its size may not be
1387  !! available; the visibility is calculated manually
1388  !! using the_environment::visual_range() function assuming
1389  !! default predator size set by the commondata::predator_body_size
1390  !! parameter.
1391  !! .
1392  class default
1393  visibility_range_predator = &
1394  m2cm( &
1395  visual_range( irradiance= &
1396  predator_object%illumination( &
1397  time_step_model_here), &
1398  prey_area= &
1399  length2sidearea_fish( &
1400  cm2m( predator_body_size ) ), &
1401  prey_contrast=preycontrast_default ) )
1402 
1403  end select
1404  else
1405  !> If the predator object is not provided as a dummy parameter,
1406  !! visibility range is assessed using the default size of the predator
1407  !! commondata::predator_body_size and the ambient illumination at the
1408  !! actor agent's depth.
1409  visibility_range_predator = &
1410  m2cm( &
1411  visual_range( irradiance= &
1412  this_agent%illumination(time_step_model_here),&
1413  prey_area= &
1414  length2sidearea_fish( &
1415  cm2m( predator_body_size ) ), &
1416  prey_contrast=preycontrast_default ) )
1417  end if
1418 
1419  !> ##### Exact escape distance #####
1420  !> Knowing the visibility range of the predator, one can calculate the
1421  !! escape distance. Namely, the escape distance is obtained by multiplying
1422  !! the visibility range by the
1423  !! commondata::escape_dart_distance_default_factor parameter constant.
1424  !!
1425  !! This constant should normally exceed 1.0. In such a case, the escape
1426  !! distance exceeds the visibility of the predator. However, it should not
1427  !! be too long to avoid extra energetic cost.
1428  !!
1429  !! If the `dist_is_stochastic` optional parameter is TRUE, the escape
1430  !! distance is stochastic with the mean as above and the coefficient of
1431  !! variation set by the commondata::escape_dart_distance_default_stoch_cv
1432  !! parameter. Stochastic distance can define *uncertainty* in the escape
1433  !! behaviour expectancy.
1434  if (present(dist_is_stochastic)) then
1435  if (dist_is_stochastic) then
1436  this%distance = &
1437  rnorm(visibility_range_predator*escape_dart_distance_default_factor,&
1438  cv2variance(escape_dart_distance_default_stoch_cv, &
1439  visibility_range_predator* &
1440  escape_dart_distance_default_factor))
1441  else
1442  ! Non-stochastic escape distance.
1443  this%distance = visibility_range_predator * &
1444  escape_dart_distance_default_factor
1445  end if
1446  else
1447  ! Non-stochastic escape distance.
1448  this%distance = visibility_range_predator * &
1449  escape_dart_distance_default_factor
1450  end if
1451 
1452  !> ##### Cost of movement #####
1453  !> Knowing the movement distance, it is possible to calculate the cost
1454  !! of movement to this distance using the
1455  !! the_body::condition_cost_swimming_burst() method assuming the
1456  !! swimming is turbulent (so the exponent parameter takes the
1457  !! commondata::swimming_cost_exponent_turbulent value).
1458  this%expected_cost_moving = &
1459  this_agent%cost_swim( distance=this%distance, &
1460  exponent=swimming_cost_exponent_turbulent)
1461 
1462  !> #### Calculate the direct and general risk of predation ####
1463  !> The expected direct risk of predation is assumed to be commondata::zero.
1464  this%expected_pred_dir_risk = zero
1465 
1466  !> Accordingly, the general risk of predation taking account both the
1467  !! number of predators in the perception object and the average number
1468  !! of predators in the memory stack is calculated using the
1469  !! the_neurobio::predation_risk_backend() method, assuming there are no
1470  !! predators in perception.
1471  this%expected_predation_risk = &
1472  predation_risk_backend( &
1473  pred_count = 0, &
1474  pred_memory_mean = &
1475  this_agent%memory_stack%get_pred_mean(mem_wind), &
1476  weight_direct = weight_direct )
1477 
1478  end subroutine escape_dart_do_this
1479 
1480  !-----------------------------------------------------------------------------
1481  !> `escape_dart::motivations_expect()` is a subroutine (re)calculating
1482  !! motivations from fake expected perceptions following from the procedure
1483  !! `escape_dart::do_this()` => `the_behaviour::escape_dart_do_this()`.
1484  subroutine escape_dart_motivations_expect(this, this_agent, predator_object,&
1485  time_step_model, rescale_max_motivation )
1486  class(escape_dart), intent(inout) :: this
1487  !> @param[in] this_agent is the actor agent which goes down.
1488  class(appraisal), intent(in) :: this_agent
1489  !> @param[in] predator_object optional predator object, if present, it is
1490  !! assumed the actor agent tries to actively escape from this
1491  !! specific predator.
1492  class(spatial), optional, intent(in) :: predator_object
1493  !> @param[in] time_step_model optional time step of the model, overrides
1494  !! the value calculated from the spatial data.
1495  integer, optional, intent(in) :: time_step_model
1496  !> @param[in] rescale_max_motivation maximum motivation value for
1497  !! rescaling all motivational components for comparison
1498  !! across all motivation and perceptual components and behaviour
1499  !! units.
1500  real(SRP), optional, intent(in) :: rescale_max_motivation
1501 
1502  ! Local copy of optional model time step
1503  integer :: time_step_model_here
1504 
1505  ! Local variables
1506  real(SRP) :: max_motivation ! Local max. over all motivation components.
1507 
1508  !> ### Notable local variables ###
1509  !> #### Perception overrides ####
1510  !> - **expect_pred_dir** is the expected direct predation risk; it is zero.
1511  real(SRP) :: expect_pred_dir
1512  !> - **expect_predator** is the expected general predation risk, that is
1513  !! based on a weighting of the current predation and predation risk
1514  !! from the memory stack.
1515  real(SRP) :: expect_predator
1516  !> - **expect_stomach** is the expected stomach contents as a consequence
1517  !! of escape movement. Note that there is no food consumption during
1518  !! escape.
1519  real(SRP) :: expect_stomach
1520  !> - **expect_bodymass** is the expected body mass as a consequence of
1521  !! the escape movement. Notably, it subtracts the cost of the escape
1522  !! movement.
1523  real(SRP) :: expect_bodymass
1524  !> - **expect_energy** is the expected energy reserves as a consequence
1525  !! of the escape movement. Calculated from the body mass and weight.
1526  !! .
1527  real(SRP) :: expect_energy
1528 
1529  ! PROCNAME is the procedure name for logging and debugging
1530  character(len=*), parameter :: PROCNAME = &
1531  "(escape_dart_motivations_expect)"
1532 
1533  !> ### Implementation details ###
1534  !> #### Checks and preparations ####
1535  !> Check optional time step parameter. If not provided, use global
1536  !! parameter value from commondata::global_time_step_model_current.
1537  if (present(time_step_model)) then
1538  time_step_model_here = time_step_model
1539  else
1540  time_step_model_here = global_time_step_model_current
1541  end if
1542 
1543  !> #### Call do_this ####
1544  !> As the first step, we use the **do**-procedure `go_down_depth::do_this()`
1545  !! => `the_behaviour::go_down_do_this()` to perform the behaviour desired
1546  !! without changing either the agent or its environment, obtaining the
1547  !! **subjective** values of the `this` behaviour components that later feed
1548  !! into the motivation **expectancy** functions:
1549  !! - `perception_override_pred_dir`
1550  !! - `perception_override_predator`
1551  !! - `perception_override_stomach`
1552  !! - `perception_override_bodymass`
1553  !! - `perception_override_energy`
1554  !! .
1555  if (present(predator_object)) then
1556  call this%do_this( this_agent = this_agent, &
1557  predator_object = predator_object, &
1558  dist_is_stochastic = .false., &
1559  time_step_model = time_step_model_here )
1560  else
1561  call this%do_this( this_agent = this_agent, &
1562  dist_is_stochastic = .false., &
1563  time_step_model = time_step_model_here )
1564  end if
1565 
1566  !> #### Calculate expected (fake) perceptions ####
1567  !> First, calculate the expected **stomach content**, which is decremented
1568  !! by the expected digestion value (the_body::stomach_emptify_backend()).
1569  expect_stomach = max( zero, &
1570  this_agent%get_stom_content() - &
1571  stomach_emptify_backend( &
1572  this_agent%get_stom_content() ) )
1573 
1574  !> Second, calculate the expected **body mass** of the agent as a consequence
1575  !! of the escape movement. The body mass is decremented by the cost of
1576  !! movement to the this\%distance and the cost of living
1577  !! (the_body::condition::living_cost()).
1578  expect_bodymass = max( zero, &
1579  this_agent%get_mass() - &
1580  this%expected_cost_moving - &
1581  this_agent%living_cost() )
1582 
1583  !> The expected **energy reserves** are calculated from the fake
1584  !! perceptions of the body mass and the current length (length does not
1585  !! change as food intake is zero in case of escape) using the
1586  !! the_body::energy_reserve() function.
1587  expect_energy = energy_reserve( expect_bodymass, this_agent%length() )
1588 
1589  !> The expected **direct predation risk** is transferred from the this
1590  !! object (the_behaviour::escape_dart).
1591  expect_pred_dir = this%expected_pred_dir_risk
1592 
1593  !> The expected **general predation risk** is also transferred from the
1594  !! this object (the_behaviour::escape_dart).
1595  expect_predator = this%expected_predation_risk
1596 
1597  !> #### Calculate motivation expectancies ####
1598  !> The next step is to calculate the motivational expectancies using the
1599  !! fake perceptions to override the default (actual agent's) values.
1600  !> At this stage, first, calculate motivation values resulting from the
1601  !! behaviour done (`the_behaviour::escape_dart::do_this()`) at the previous
1602  !! steps: what would be the motivation values *if* the agent does perform
1603  !! escape? Technically, this is done by calling the **neuronal
1604  !! response function**, `percept_components_motiv::motivation_components()`
1605  !! method, for each of the motivational states with `perception_override_`
1606  !! dummy parameters overriding the default values.
1607  !! Here is the list of the fake overriding perceptions for the
1608  !! `ESCAPE_DART` behaviour:
1609  !! - `perception_override_pred_dir`
1610  !! - `perception_override_predator`
1611  !! - `perception_override_stomach`
1612  !! - `perception_override_bodymass`
1613  !! - `perception_override_energy`
1614  !! .
1615  ! @note **Expectancy** assessment for **hunger** motivation, using
1616  ! `PERCEPT_COMPONENTS_MOTIV`-bound procedure with intent[in] for
1617  ! `this_agent` now.
1618  call this%expectancy%hunger%percept_component%motivation_components &
1619  (this_agent, &
1620  ! Parameters:: Boolean G x P matrices:
1621  param_gp_matrix_light = light_hunger_genotype_neuronal, &
1622  param_gp_matrix_depth = depth_hunger_genotype_neuronal, &
1623  param_gp_matrix_food_dir = foodcount_hunger_genotype_neuronal, &
1624  param_gp_matrix_food_mem = food_mem_hunger_genotype_neuronal, &
1625  param_gp_matrix_conspec = conspcount_hunger_genotype_neuronal, &
1626  param_gp_matrix_pred_dir = pred_direct_hunger_genotype_neuronal, &
1627  param_gp_matrix_predator = pred_meancount_hunger_genotype_neuronal, &
1628  param_gp_matrix_stomach = stom_hunger_genotype_neuronal, &
1629  param_gp_matrix_bodymass = bodymass_hunger_genotype_neuronal, &
1630  param_gp_matrix_energy = energy_hunger_genotype_neuronal, &
1631  param_gp_matrix_age = age_hunger_genotype_neuronal, &
1632  param_gp_matrix_reprfac = reprfac_hunger_genotype_neuronal, &
1633  ! Parameters :: G x P variances:
1634  param_gerror_cv_light = light_hunger_genotype_neuronal_gerror_cv, &
1635  param_gerror_cv_depth = depth_hunger_genotype_neuronal_gerror_cv, &
1636  param_gerror_cv_food_dir = foodcount_hunger_genotype_neuronal_gerror_cv,&
1637  param_gerror_cv_food_mem = food_mem_hunger_genotype_neuronal_gerror_cv, &
1638  param_gerror_cv_conspec = conspcount_hunger_genotype_neuronal_gerror_cv,&
1639  param_gerror_cv_pred_dir = pred_direct_hunger_genotype_neuronal_gerror_cv,&
1640  param_gerror_cv_predator = pred_meancount_hunger_genotype_neuronal_gerror_cv,&
1641  param_gerror_cv_stomach = stom_hunger_genotype_neuronal_gerror_cv, &
1642  param_gerror_cv_bodymass = bodymass_hunger_genotype_neuronal_gerror_cv, &
1643  param_gerror_cv_energy = energy_hunger_genotype_neuronal_gerror_cv, &
1644  param_gerror_cv_age = age_hunger_genotype_neuronal_gerror_cv, &
1645  param_gerror_cv_reprfac = reprfac_hunger_genotype_neuronal_gerror_cv, &
1646  ! Real agent perception components are now substituted by the *fake*
1647  ! values resulting from executing this behaviour (`do_this` method).
1648  ! This is repeated for all the motivations: *hunger*,
1649  ! *passive avoidance,* *fear state* etc.
1650  perception_override_pred_dir = expect_pred_dir, &
1651  perception_override_predator = expect_predator, &
1652  perception_override_stomach = expect_stomach, &
1653  perception_override_bodymass = expect_bodymass, &
1654  perception_override_energy = expect_energy &
1655  )
1656  !> Real agent perception components are now substituted by the *fake*
1657  !! values resulting from executing this behaviour (`reproduce::do_this()`
1658  !! => `the_behaviour::reproduce_do_this()` method). This is repeated for
1659  !! all the motivations: *hunger*, *passive avoidance,* *active
1660  !! avoidance* etc. These optional **override parameters** are
1661  !! substituted by the "fake" values.
1662 
1663  ! @note **Expectancy** assessment for **fear_defence** motivation,
1664  ! using `PERCEPT_COMPONENTS_MOTIV`-bound procedure with intent[in]
1665  ! for `this_agent` now.
1666  call this%expectancy%fear_defence%percept_component%motivation_components &
1667  (this_agent, &
1668  ! Parameters:: Boolean G x P matrices:
1669  param_gp_matrix_light = light_actv_avoid_genotype_neuronal, &
1670  param_gp_matrix_depth = depth_actv_avoid_genotype_neuronal, &
1671  param_gp_matrix_food_dir = foodcount_actv_avoid_genotype_neuronal, &
1672  param_gp_matrix_food_mem = food_mem_actv_avoid_genotype_neuronal, &
1673  param_gp_matrix_conspec = conspcount_actv_avoid_genotype_neuronal, &
1674  param_gp_matrix_pred_dir = pred_direct_actv_avoid_genotype_neuronal, &
1675  param_gp_matrix_predator = pred_meancount_actv_avoid_genotype_neuronal, &
1676  param_gp_matrix_stomach = stom_actv_avoid_genotype_neuronal, &
1677  param_gp_matrix_bodymass = bodymass_actv_avoid_genotype_neuronal, &
1678  param_gp_matrix_energy = energy_actv_avoid_genotype_neuronal, &
1679  param_gp_matrix_age = age_actv_avoid_genotype_neuronal, &
1680  param_gp_matrix_reprfac = reprfac_actv_avoid_genotype_neuronal, &
1681  ! Parameters :: G x P variances:
1682  param_gerror_cv_light = light_actv_avoid_genotype_neuronal_gerror_cv, &
1683  param_gerror_cv_depth = depth_actv_avoid_genotype_neuronal_gerror_cv, &
1684  param_gerror_cv_food_dir = foodcount_actv_avoid_genotype_neuronal_gerror_cv,&
1685  param_gerror_cv_food_mem = food_mem_actv_avoid_genotype_neuronal_gerror_cv, &
1686  param_gerror_cv_conspec = conspcount_actv_avoid_genotype_neuronal_gerror_cv,&
1687  param_gerror_cv_pred_dir = pred_direct_actv_avoid_genotype_neuronal_gerror_cv,&
1688  param_gerror_cv_predator = pred_meancount_actv_avoid_genotype_neuronal_gerror_cv,&
1689  param_gerror_cv_stomach = stom_actv_avoid_genotype_neuronal_gerror_cv, &
1690  param_gerror_cv_bodymass = bodymass_actv_avoid_genotype_neuronal_gerror_cv,&
1691  param_gerror_cv_energy = energy_actv_avoid_genotype_neuronal_gerror_cv,&
1692  param_gerror_cv_age = age_actv_avoid_genotype_neuronal_gerror_cv, &
1693  param_gerror_cv_reprfac = reprfac_actv_avoid_genotype_neuronal_gerror_cv,&
1694  ! @note Real agent perception components are now **substituted**
1695  ! by the **fake** values resulting from executing this
1696  ! behaviour (`do_this` method).
1697  perception_override_pred_dir = expect_pred_dir, &
1698  perception_override_predator = expect_predator, &
1699  perception_override_stomach = expect_stomach, &
1700  perception_override_bodymass = expect_bodymass, &
1701  perception_override_energy = expect_energy &
1702  )
1703 
1704  ! @note **Expectancy** assessment for **reproduction** motivation,
1705  ! using `PERCEPT_COMPONENTS_MOTIV`-bound procedure with intent[in]
1706  ! for `this_agent` now.
1707  call this%expectancy%reproduction%percept_component%motivation_components &
1708  (this_agent, &
1709  ! Parameters:: Boolean G x P matrices:
1710  param_gp_matrix_light = light_reproduce_genotype_neuronal, &
1711  param_gp_matrix_depth = depth_reproduce_genotype_neuronal, &
1712  param_gp_matrix_food_dir = foodcount_reproduce_genotype_neuronal, &
1713  param_gp_matrix_food_mem = food_mem_reproduce_genotype_neuronal, &
1714  param_gp_matrix_conspec = conspcount_reproduce_genotype_neuronal, &
1715  param_gp_matrix_pred_dir = pred_direct_reproduce_genotype_neuronal, &
1716  param_gp_matrix_predator = pred_meancount_reproduce_genotype_neuronal, &
1717  param_gp_matrix_stomach = stom_reproduce_genotype_neuronal, &
1718  param_gp_matrix_bodymass = bodymass_reproduce_genotype_neuronal, &
1719  param_gp_matrix_energy = energy_reproduce_genotype_neuronal, &
1720  param_gp_matrix_age = age_reproduce_genotype_neuronal, &
1721  param_gp_matrix_reprfac = reprfac_reproduce_genotype_neuronal, &
1722  ! Parameters :: G x P variances:
1723  param_gerror_cv_light = light_reproduce_genotype_neuronal_gerror_cv, &
1724  param_gerror_cv_depth = depth_reproduce_genotype_neuronal_gerror_cv, &
1725  param_gerror_cv_food_dir = foodcount_reproduce_genotype_neuronal_gerror_cv,&
1726  param_gerror_cv_food_mem = food_mem_reproduce_genotype_neuronal_gerror_cv, &
1727  param_gerror_cv_conspec = conspcount_reproduce_genotype_neuronal_gerror_cv,&
1728  param_gerror_cv_pred_dir = pred_direct_reproduce_genotype_neuronal_gerror_cv,&
1729  param_gerror_cv_predator = pred_meancount_reproduce_genotype_neuronal_gerror_cv,&
1730  param_gerror_cv_stomach = stom_reproduce_genotype_neuronal_gerror_cv, &
1731  param_gerror_cv_bodymass = bodymass_reproduce_genotype_neuronal_gerror_cv,&
1732  param_gerror_cv_energy = energy_reproduce_genotype_neuronal_gerror_cv,&
1733  param_gerror_cv_age = age_reproduce_genotype_neuronal_gerror_cv, &
1734  param_gerror_cv_reprfac = reprfac_reproduce_genotype_neuronal_gerror_cv,&
1735  ! @note Real agent perception components are now **substituted**
1736  ! by the **fake** values resulting from executing this
1737  ! behaviour (`do_this` method).
1738  perception_override_pred_dir = expect_pred_dir, &
1739  perception_override_predator = expect_predator, &
1740  perception_override_stomach = expect_stomach, &
1741  perception_override_bodymass = expect_bodymass, &
1742  perception_override_energy = expect_energy &
1743  )
1744 
1745  !> #### Calculate primary and final motivations ####
1746  !> Next, from the perceptual components calculated at the previous
1747  !! step we can obtain the **primary** and **final motivation** values by
1748  !! weighed summing.
1749  if (present(rescale_max_motivation)) then
1750  !> Here we can use global maximum motivation across all behaviours and
1751  !! perceptual components if it is provided, for rescaling.
1752  max_motivation = rescale_max_motivation
1753  else
1754  !> Or can rescale using local maximum value for this behaviour only.
1755  max_motivation = this%expectancy%max_perception()
1756  end if
1757 
1758  !> Transfer attention weights from the actor agent `this_agent` to the
1759  !! `this` behaviour component. So, we will now use the updated modulated
1760  !! attention weights of the agent rather than their default parameter
1761  !! values.
1762  call this%attention_transfer(this_agent)
1763 
1764  !> So the primary motivation values are calculated.
1765  call this%expectancy%motivation_primary_calc(max_motivation)
1766 
1767  !> Primary motivations are logged in the @ref intro_debug_mode "debug mode".
1768  call log_dbg( ltag_info // "Primary motivations: " // &
1769  "hunger: " // &
1770  tostr(this%expectancy%hunger%motivation_prim) // &
1771  ", fear_defence: " // &
1772  tostr(this%expectancy%fear_defence%motivation_prim) // &
1773  ", reproduce: " // &
1774  tostr(this%expectancy%reproduction%motivation_prim), &
1775  procname, modname )
1776 
1777  !> There is **no modulation** at this stage, so the final motivation
1778  !! values are the same as primary motivations.
1779  call this%expectancy%modulation_none()
1780 
1781  !> #### Calculate motivation expectancies ####
1782  !> Finally, calculate the finally **expected arousal level for this
1783  !! behaviour**. As in the GOS, the overall arousal is the maximum value
1784  !! among all motivation components.
1785  this%arousal_expected = this%expectancy%max_final()
1786 
1787  !> Log also the final expectancy value in the @ref intro_debug_mode
1788  !! "debug mode".
1789  call log_dbg( ltag_info // "Expectancy: " // tostr(this%arousal_expected),&
1790  procname, modname )
1791 
1792  !> Now as we know the expected arousal, we can choose the behaviour which
1793  !! would minimise this arousal level.
1794 
1795  end subroutine escape_dart_motivations_expect
1796 
1797  !-----------------------------------------------------------------------------
1798  !> Execute this behaviour component "escape" by `this_agent` agent.
1799  subroutine escape_dart_do_execute(this, this_agent, predator_object, &
1800  environment_limits)
1801  class(escape_dart), intent(inout) :: this
1802  !> @param[in] this_agent is the actor agent which goes down.
1803  class(appraisal), intent(inout) :: this_agent
1804  !> @param[in] predator_object optional predator object, if present, it is
1805  !! assumed the actor agent tries to actively escape from this
1806  !! specific predator.
1807  class(spatial), optional, intent(in) :: predator_object
1808  !> @param environment_limits Limits of the environment area available for
1809  !! the random walk. The moving object cannot get beyond this limit.
1810  !! If this parameter is not provided, the environmental limits are
1811  !! obtained automatically from the global array
1812  !! the_environment::global_habitats_available.
1813  class(environment), intent(in), optional :: environment_limits
1814 
1815  ! Number of iterations in Gaussian correlated random walk, mainly for debug.
1816  integer :: iter_debug
1817 
1818  !> ### Implementation details ###
1819  !> #### Step 1: do_this ####
1820  !> As the first step, we use the **do**-procedure
1821  !! `the_behaviour::escape_dart::do_this()` to perform the behaviour
1822  !! desired. As a result, the following values are obtained:
1823  !! - **escape distance**;
1824  !! - expected (zero) food gain;
1825  !! - expected **stomach contents, body mass and energy reserves**, assuming
1826  !! nonzero cost of movement and lack of feeding while escaping (i.e.
1827  !! zero food gain).
1828  !! - the estimates of the predation risk are not used here, they only
1829  !! are used in the subjective evaluation phase, when the agent computes
1830  !! expectancies.
1831  !! .
1832  if (present(predator_object)) then
1833  call this%do_this( this_agent = this_agent, &
1834  predator_object = predator_object, &
1835  dist_is_stochastic = .false. )
1836  else
1837  call this%do_this( this_agent = this_agent, &
1838  dist_is_stochastic = .false. )
1839  end if
1840 
1841  !> In the @ref intro_debug_mode "debug mode", checking and logging the
1842  !! perception values.
1843  call log_dbg(ltag_info // "Executed ESCAPE; Perception values: " // &
1844  "Escape distance: " // tostr(this%distance) // &
1845  ", Food gain: " // tostr(this%expected_food_gain) // &
1846  ", Direct risk: " // tostr(this%expected_pred_dir_risk) // &
1847  ", Indirect risk: " // tostr(this%expected_predation_risk) )
1848 
1849  !> #### Step 2: Change the agent ####
1850  !> Escape involves a random walk. Thus, the first thing is the agent
1851  !! *displacement*:
1852  if (present(predator_object)) then
1853  !> - If the predator is present, the agent does a correlated Gaussian
1854  !! random walk the_environment::spatial_moving::corwalk() in a
1855  !! direction roughly opposite to the predator position.
1856  ! TODO: DISPLACEMENT NON-IMPLEMENTED SO FAR -- NEED IMPLEMENT
1857  ! MOVE OPPOSITE FOR SPATIAL_MOVING
1858  if (present(environment_limits)) then
1859  call this_agent%corwalk( &
1860  target=predator_object, &
1861  meanshift=this%distance, &
1862  cv_shift=escape_dart_distance_default_stoch_cv, &
1863  is_away=.true., &
1864  environment_limits=environment_limits, &
1865  debug_reps = iter_debug )
1866  else
1867  call this_agent%corwalk( &
1868  target=predator_object, &
1869  meanshift=this%distance, &
1870  cv_shift=escape_dart_distance_default_stoch_cv, &
1871  is_away=.true., &
1872  environment_limits=global_habitats_available( &
1873  this_agent%find_environment( &
1874  global_habitats_available) ), &
1875  debug_reps = iter_debug )
1876  end if
1877  else
1878  !> - If the predator is not present, the agent performs a Gaussian
1879  !! walk, to a distance equal to the this\%distance data component
1880  !! and the CV set by the parameter
1881  !! commondata::escape_dart_distance_default_stoch_cv.
1882  !! @note Note that the escape involves a full 3D walk
1883  !! with a single set of distance and CV parameters
1884  !! (i.e. no separate depth walk parameters).
1885  !! .
1886  if (present(environment_limits)) then
1887  call this_agent%rwalk( &
1888  meanshift=this%distance, &
1889  cv_shift=escape_dart_distance_default_stoch_cv, &
1890  environment_limits=environment_limits )
1891  else
1892  call this_agent%rwalk( &
1893  meanshift=this%distance, &
1894  cv_shift=escape_dart_distance_default_stoch_cv, &
1895  environment_limits=global_habitats_available( &
1896  this_agent%find_environment( &
1897  global_habitats_available) ) )
1898  end if
1899  end if
1900 
1901  !> Escape movement results a *cost* that is defined by the actual distance
1902  !! travelled, the_environment::spatial_moving::way() which is subtracted
1903  !! here. Call `the_body::condition::set_mass()` for this.
1904  !! @note Note that the_body::condition::cost_swim() calculates the cost
1905  !! of the latest way passed (the_environment::spatial_moving::way()
1906  !! if the distance parameter is not provided.
1907  call this_agent%set_mass( value_set = this_agent%get_mass() - &
1908  this_agent%cost_swim(exponent= &
1909  swimming_cost_exponent_turbulent), &
1910  update_history = .true. )
1911 
1912  !> Additionally, also call the `the_body::condition::set_length()` method
1913  !! to update the body length history stack. However, the value_set
1914  !! parameter here is just the current value. This fake re-setting of the
1915  !! body length is done to keep both mass and length synchronised in their
1916  !! history stack arrays (there is no procedure for only updating history).
1917  call this_agent%set_length( value_set = this_agent%get_length(), &
1918  update_history = .true. )
1919 
1920  !> After resetting the body mass, update energy reserves of the agent, that
1921  !! depend on both the length and the mass.
1922  call this_agent%energy_update()
1923 
1924  !> Check if the agent is starved to death. If yes, the agent can
1925  !! die without going any further.
1926  if (this_agent%starved_death()) call this_agent%dies()
1927 
1928  !> #### Step 3: Change the environment ####
1929  !> Escape movement itself does not affect the environmental objects.
1930 
1931  end subroutine escape_dart_do_execute
1932 
1933  !-----------------------------------------------------------------------------
1934  !> Initialise the **approach** behaviour component to a zero state.
1935  !! Approach is a generic type but not abstract.
1936  elemental subroutine approach_spatial_object_init_zero(this)
1937  class(approach), intent(inout) :: this
1938 
1939  !> First init components from the base root class
1940  !! `the_behaviour::behaviour_base`.
1941  !> Mandatory label component that should be read-only.
1942  this%label = "APPROACH"
1943  !> The execution status is always FALSE, can be reset to TRUE only when
1944  !! the behaviour unit is called to execution.
1945  this%is_active = .false.
1946 
1947  !> And the *expectancy* components.
1948  call this%expectancy%init()
1949  this%arousal_expected = 0.0_srp
1950 
1951  !> Abstract `MOVE` component.
1952  this%distance = missing
1953 
1954  !> Then init components of this specific behaviour component extended class.
1955  this%expected_cost_moving = missing
1956 
1957  end subroutine approach_spatial_object_init_zero
1958 
1959  !-----------------------------------------------------------------------------
1960  !> The "do" procedure component of the behaviour element performs the
1961  !! behaviour without affecting the actor agent (the_agent) and the world
1962  !! (here food_item_eaten) which have intent(in), so it only can change
1963  !! the internal representation of the behaviour (the type to which this
1964  !! procedure is bound to, here `APPROACH`).
1965  subroutine approach_do_this(this, this_agent, target_object, target_offset, &
1966  predict_window_food, time_step_model )
1967  class(approach), intent(inout) :: this
1968  !> @param[in] this_agent is the actor agent which eats the food item.
1969  class(appraisal), intent(in) :: this_agent
1970  !> @param[in] target_object is the spatial target object the actor agent
1971  !! is going to approach.
1972  class(spatial), intent(in) :: target_object
1973  !> @param[in] target_offset is an optional offset for the target, so that
1974  !! the target position of the approaching agent does not
1975  !! coincide with the target object. If absent, a default value
1976  !! set by the commondata::approach_offset_default is used.
1977  real(SRP), optional, intent(in) :: target_offset
1978  !> @param[in] predict_window_food the size of the prediction window, i.e.
1979  !! how many steps back in memory are used to calculate the
1980  !! predicted food gain. This parameter is limited by the maximum
1981  !! commondata::history_size_perception value of the perception
1982  !! memory history size.
1983  !! @note This parameter is not used here and is placed only to make
1984  !! derived class subroutine make the same argument list.
1985  integer, optional, intent(in) :: predict_window_food
1986  !> @param[in] time_step_model optional time step of the model, overrides
1987  !! the value calculated from the spatial data.
1988  !! This parameter is not used for this class, it is here only
1989  !! to allow placement of this parameter for higher-order derived
1990  !! classes.
1991  integer, optional, intent(in) :: time_step_model
1992 
1993 
1994  ! Local copy of the body length of the agent
1995  real(SRP) :: agent_length
1996 
1997  ! Local copy of optional target offset
1998  real(SRP) :: target_offset_here
1999 
2000  ! PROCNAME is the procedure name for logging and debugging.
2001  character(len=*), parameter :: PROCNAME = "(approach_do_this)"
2002 
2003  !> ### Implementation details ###
2004  !> Check the optional parameter for the target offset and set the default
2005  !! one if offset is not provided.
2006  if (present(target_offset)) then
2007  target_offset_here = target_offset
2008  else
2009  target_offset_here = approach_offset_default
2010  end if
2011 
2012  ! Agent length is local variable to avoid multiple calls to get_length().
2013  agent_length = this_agent%get_length()
2014 
2015  !> #### Proximity check ####
2016  !> The agent approaches the conspecific but to a nonzero distance equal
2017  !! to the target offset value (`target_offset`). A check is done if the
2018  !! distance between the agent and the conspecific target object is
2019  !! actually smaller than the target offset.
2020  !! - If so, the agent is already in close proximity to the target and
2021  !! there is no need to do an approach movement.
2022  in_proximity: if ( this_agent%distance( target_object ) <= &
2023  target_offset_here ) then
2024  !> - The approach distance is set to zero.
2025  this%distance = 0.0_srp
2026  !> - The expected cost of approach movement is also zero.
2027  !! .
2028  this%expected_cost_moving = 0.0_srp
2029 
2030  !> - If the agent is currently at a distance exceeding the target
2031  !! offset, the approach distance towards the target position of
2032  !! the actor agent is calculated as the true distance towards the
2033  !! target conspecific minus the offset value `target_offset`.
2034  !! (Note that whenever the default target offset is set, i.e. an average
2035  !! of the agent and target body sizes, the approach distance depends
2036  !! on the body sizes of both parties; it is also symmetric, i.e. the
2037  !! same if a large agent approaches a small target conspecific or
2038  !! *vice versa*.)
2039  else in_proximity
2040  this%distance = this_agent%distance( target_object ) - target_offset_here
2041  !> - Check if the distance to the target object exceeds the
2042  !! migration travel maximum value, set as
2043  !! commondata::migrate_dist_max_step body sizes of the agent. This
2044  !! case should never occur if the maximum distance is sufficiently
2045  !! large so that the target object is beyond the agent's visual range.
2046  !! So, nothing is done here except logging a possible error.
2047  if (this%distance > agent_length * migrate_dist_max_step ) then
2048  call log_msg( ltag_warn // "Approach travel distance exceeds big " // &
2049  "threshold in " // procname // " for the agent " // &
2050  this_agent%individ_label() // ". Agent length: " // &
2051  tostr(agent_length) // ", migration distance: " // &
2052  tostr(this%distance) )
2053  end if
2054  !> - Calculate expected cost of the swimming. The expected cost of
2055  !! swimming in the approach walk step depends on the above approach
2056  !! distance and is calculated using the_body::condition::cost_swim()
2057  !! method assuming *laminar* flow (laminar flow is due to normal
2058  !! relatively slow swimming pattern).
2059  !! .
2060  !! .
2061  this%expected_cost_moving = &
2062  this_agent%cost_swim( distance=this%distance, &
2063  exponent=swimming_cost_exponent_laminar)
2064  end if in_proximity
2065 
2066  end subroutine approach_do_this
2067 
2068  !-----------------------------------------------------------------------------
2069  !> `the_behaviour::approach::expectancies_calculate()` (re)calculates
2070  !! motivations from fake expected perceptions following from the procedure
2071  !! `approach::do_this()` => `the_behaviour::approach_do_this()`.
2072  subroutine approach_motivations_expect( this, this_agent, target_object, &
2073  target_offset, time_step_model, &
2074  rescale_max_motivation )
2075  class(approach), intent(inout) :: this
2076  !> @param[in] this_agent is the actor agent which does approach.
2077  class(appraisal), intent(in) :: this_agent
2078  !> @param[in] target_object is the spatial target object the actor agent
2079  !! is going to approach.
2080  class(spatial), optional, intent(in) :: target_object
2081  !> @param[in] target_offset is an optional offset for the target, so that
2082  !! the target position of the approaching agent does not
2083  !! coincide with the target object. If absent, a default value
2084  !! set by the commondata::approach_offset_default is used.
2085  real(SRP), optional, intent(in) :: target_offset
2086  !> @param[in] time_step_model optional time step of the model, overrides
2087  !! the value calculated from the spatial data.
2088  !! This parameter is not used for this class, it is here only
2089  !! to allow placement of this parameter for higher-order derived
2090  !! classes.
2091  integer, optional, intent(in) :: time_step_model
2092  !> @param[in] rescale_max_motivation optional maximum motivation value for
2093  !! rescaling all motivational components for comparison
2094  !! across all motivation and perceptual components and behaviour
2095  !! units.
2096  real(SRP), optional, intent(in) :: rescale_max_motivation
2097 
2098  ! Local variables
2099  real(SRP) :: max_motivation ! Local max. over all motivation components.
2100 
2101  ! Local copy of optional target offset
2102  real(SRP) :: target_offset_here
2103 
2104  !> ### Notable local variables ###
2105  !> #### Perception overrides ####
2106  !> - **perception_override_bodymass** is the expected body mass as a
2107  !! consequence of the approach movement.
2108  real(SRP) :: perception_override_bodymass
2109  !> - **perception_override_energy** is the expected energy reserves
2110  !! as a consequence of the escape movement. Calculated from the body
2111  !! mass and weight.
2112  !! .
2113  real(SRP) :: perception_override_energy
2114 
2115  ! PROCNAME is the procedure name for logging and debugging
2116  character(len=*), parameter :: PROCNAME = &
2117  "(approach_motivations_expect)"
2118 
2119  ! Check the optional parameter for the target offset and set the default
2120  ! one if offset is not provided.
2121  if (present(target_offset)) then
2122  target_offset_here = target_offset
2123  else
2124  target_offset_here = approach_offset_default
2125  end if
2126 
2127  !> ### Implementation details ###
2128  !> #### Call do_this ####
2129  !> As the first step, we use the **do**-procedure `walk_random::do_this()`
2130  !! => the_behaviour::walk_random_do_this() to perform the behaviour desired
2131  !! without changing either the agent or its environment, obtaining the
2132  !! **subjective** values of the `this` behaviour components that later feed
2133  !! into the motivation **expectancy** functions:
2134  !! - `perception_override_bodymass`
2135  !! - `perception_override_energy`
2136  !! .
2137  call this%do_this( this_agent = this_agent, &
2138  target_object = target_object, &
2139  target_offset = target_offset_here )
2140 
2141  !> #### Calculate expected (fake) perceptions ####
2142  !> **Body mass**: the **body mass** perception override is obtained by
2143  !! subtracting the approach movement cost and the
2144  !! the_body::condition::living_cost() from the current mass.
2145  perception_override_bodymass = max( this_agent%get_mass() - &
2146  this%expected_cost_moving - &
2147  this_agent%living_cost(), &
2148  zero )
2149 
2150  !> **Energy**: The fake perception values for the energy reserves
2151  !! (`perception_override_energy`) using the `the_body::energy_reserve()`
2152  !! procedure.
2153  perception_override_energy = energy_reserve( perception_override_bodymass,&
2154  this_agent%length() )
2155 
2156  !> #### Calculate motivation expectancies ####
2157  !> The next step is to calculate the motivational expectancies using the
2158  !! fake perceptions to override the default (actual agent's) values.
2159  !> At this stage, first, calculate motivation values resulting from the
2160  !! behaviour done (`walk_random::do_this()` ) at the previous steps: what
2161  !! would be the motivation values *if* the agent does perform
2162  !! APPROACH? Technically, this is done by calling the **neuronal
2163  !! response function**, `percept_components_motiv::motivation_components()`
2164  !! method, for each of the motivational states with `perception_override_`
2165  !! dummy parameters overriding the default values.
2166  !! Here is the list of the fake overriding perceptions for the
2167  !! `APPROACH` behaviour:
2168  !! - `perception_override_bodymass`
2169  !! - `perception_override_energy`
2170  !! .
2171  ! @note **Expectancy** assessment for **hunger** motivation, using
2172  ! `PERCEPT_COMPONENTS_MOTIV`-bound procedure with intent[in] for
2173  ! `this_agent` now.
2174  call this%expectancy%hunger%percept_component%motivation_components &
2175  (this_agent, &
2176  ! Parameters:: Boolean G x P matrices:
2177  param_gp_matrix_light = light_hunger_genotype_neuronal, &
2178  param_gp_matrix_depth = depth_hunger_genotype_neuronal, &
2179  param_gp_matrix_food_dir = foodcount_hunger_genotype_neuronal, &
2180  param_gp_matrix_food_mem = food_mem_hunger_genotype_neuronal, &
2181  param_gp_matrix_conspec = conspcount_hunger_genotype_neuronal, &
2182  param_gp_matrix_pred_dir = pred_direct_hunger_genotype_neuronal, &
2183  param_gp_matrix_predator = pred_meancount_hunger_genotype_neuronal, &
2184  param_gp_matrix_stomach = stom_hunger_genotype_neuronal, &
2185  param_gp_matrix_bodymass = bodymass_hunger_genotype_neuronal, &
2186  param_gp_matrix_energy = energy_hunger_genotype_neuronal, &
2187  param_gp_matrix_age = age_hunger_genotype_neuronal, &
2188  param_gp_matrix_reprfac = reprfac_hunger_genotype_neuronal, &
2189  ! Parameters :: G x P variances:
2190  param_gerror_cv_light = light_hunger_genotype_neuronal_gerror_cv, &
2191  param_gerror_cv_depth = depth_hunger_genotype_neuronal_gerror_cv, &
2192  param_gerror_cv_food_dir = foodcount_hunger_genotype_neuronal_gerror_cv,&
2193  param_gerror_cv_food_mem = food_mem_hunger_genotype_neuronal_gerror_cv, &
2194  param_gerror_cv_conspec = conspcount_hunger_genotype_neuronal_gerror_cv,&
2195  param_gerror_cv_pred_dir = pred_direct_hunger_genotype_neuronal_gerror_cv,&
2196  param_gerror_cv_predator = pred_meancount_hunger_genotype_neuronal_gerror_cv,&
2197  param_gerror_cv_stomach = stom_hunger_genotype_neuronal_gerror_cv, &
2198  param_gerror_cv_bodymass = bodymass_hunger_genotype_neuronal_gerror_cv, &
2199  param_gerror_cv_energy = energy_hunger_genotype_neuronal_gerror_cv, &
2200  param_gerror_cv_age = age_hunger_genotype_neuronal_gerror_cv, &
2201  param_gerror_cv_reprfac = reprfac_hunger_genotype_neuronal_gerror_cv, &
2202  ! Real agent perception components are now substituted by the *fake*
2203  ! values resulting from executing this behaviour (`do_this` method).
2204  ! This is repeated for all the motivations: *hunger*,
2205  ! *passive avoidance,* *fear state* etc.
2206  perception_override_bodymass = perception_override_bodymass, &
2207  perception_override_energy = perception_override_energy &
2208  )
2209  !> Real agent perception components are now substituted by the *fake*
2210  !! values resulting from executing this behaviour (`approach::do_this()`
2211  !! method). This is repeated for all the motivations: *hunger*,
2212  !! *passive avoidance,* *fear state* etc. These optional **override
2213  !! parameters** are substituted by the "fake" values.
2214 
2215  ! @note **Expectancy** assessment for **fear_defence** motivation,
2216  ! using `PERCEPT_COMPONENTS_MOTIV`-bound procedure with intent[in]
2217  ! for `this_agent` now.
2218  call this%expectancy%fear_defence%percept_component%motivation_components &
2219  (this_agent, &
2220  ! Parameters:: Boolean G x P matrices:
2221  param_gp_matrix_light = light_actv_avoid_genotype_neuronal, &
2222  param_gp_matrix_depth = depth_actv_avoid_genotype_neuronal, &
2223  param_gp_matrix_food_dir = foodcount_actv_avoid_genotype_neuronal, &
2224  param_gp_matrix_food_mem = food_mem_actv_avoid_genotype_neuronal, &
2225  param_gp_matrix_conspec = conspcount_actv_avoid_genotype_neuronal, &
2226  param_gp_matrix_pred_dir = pred_direct_actv_avoid_genotype_neuronal, &
2227  param_gp_matrix_predator = pred_meancount_actv_avoid_genotype_neuronal, &
2228  param_gp_matrix_stomach = stom_actv_avoid_genotype_neuronal, &
2229  param_gp_matrix_bodymass = bodymass_actv_avoid_genotype_neuronal, &
2230  param_gp_matrix_energy = energy_actv_avoid_genotype_neuronal, &
2231  param_gp_matrix_age = age_actv_avoid_genotype_neuronal, &
2232  param_gp_matrix_reprfac = reprfac_actv_avoid_genotype_neuronal, &
2233  ! Parameters :: G x P variances:
2234  param_gerror_cv_light = light_actv_avoid_genotype_neuronal_gerror_cv, &
2235  param_gerror_cv_depth = depth_actv_avoid_genotype_neuronal_gerror_cv, &
2236  param_gerror_cv_food_dir = foodcount_actv_avoid_genotype_neuronal_gerror_cv,&
2237  param_gerror_cv_food_mem = food_mem_actv_avoid_genotype_neuronal_gerror_cv, &
2238  param_gerror_cv_conspec = conspcount_actv_avoid_genotype_neuronal_gerror_cv,&
2239  param_gerror_cv_pred_dir = pred_direct_actv_avoid_genotype_neuronal_gerror_cv,&
2240  param_gerror_cv_predator = pred_meancount_actv_avoid_genotype_neuronal_gerror_cv,&
2241  param_gerror_cv_stomach = stom_actv_avoid_genotype_neuronal_gerror_cv, &
2242  param_gerror_cv_bodymass = bodymass_actv_avoid_genotype_neuronal_gerror_cv,&
2243  param_gerror_cv_energy = energy_actv_avoid_genotype_neuronal_gerror_cv,&
2244  param_gerror_cv_age = age_actv_avoid_genotype_neuronal_gerror_cv, &
2245  param_gerror_cv_reprfac = reprfac_actv_avoid_genotype_neuronal_gerror_cv,&
2246  ! @note Real agent perception components are now **substituted**
2247  ! by the **fake** values resulting from executing this
2248  ! behaviour (`do_this` method).
2249  perception_override_bodymass = perception_override_bodymass, &
2250  perception_override_energy = perception_override_energy &
2251  )
2252 
2253  ! @note **Expectancy** assessment for **reproduction** motivation,
2254  ! using `PERCEPT_COMPONENTS_MOTIV`-bound procedure with intent[in]
2255  ! for `this_agent` now.
2256  call this%expectancy%reproduction%percept_component%motivation_components &
2257  (this_agent, &
2258  ! Parameters:: Boolean G x P matrices:
2259  param_gp_matrix_light = light_reproduce_genotype_neuronal, &
2260  param_gp_matrix_depth = depth_reproduce_genotype_neuronal, &
2261  param_gp_matrix_food_dir = foodcount_reproduce_genotype_neuronal, &
2262  param_gp_matrix_food_mem = food_mem_reproduce_genotype_neuronal, &
2263  param_gp_matrix_conspec = conspcount_reproduce_genotype_neuronal, &
2264  param_gp_matrix_pred_dir = pred_direct_reproduce_genotype_neuronal, &
2265  param_gp_matrix_predator = pred_meancount_reproduce_genotype_neuronal, &
2266  param_gp_matrix_stomach = stom_reproduce_genotype_neuronal, &
2267  param_gp_matrix_bodymass = bodymass_reproduce_genotype_neuronal, &
2268  param_gp_matrix_energy = energy_reproduce_genotype_neuronal, &
2269  param_gp_matrix_age = age_reproduce_genotype_neuronal, &
2270  param_gp_matrix_reprfac = reprfac_reproduce_genotype_neuronal, &
2271  ! Parameters :: G x P variances:
2272  param_gerror_cv_light = light_reproduce_genotype_neuronal_gerror_cv, &
2273  param_gerror_cv_depth = depth_reproduce_genotype_neuronal_gerror_cv, &
2274  param_gerror_cv_food_dir = foodcount_reproduce_genotype_neuronal_gerror_cv,&
2275  param_gerror_cv_food_mem = food_mem_reproduce_genotype_neuronal_gerror_cv, &
2276  param_gerror_cv_conspec = conspcount_reproduce_genotype_neuronal_gerror_cv,&
2277  param_gerror_cv_pred_dir = pred_direct_reproduce_genotype_neuronal_gerror_cv,&
2278  param_gerror_cv_predator = pred_meancount_reproduce_genotype_neuronal_gerror_cv,&
2279  param_gerror_cv_stomach = stom_reproduce_genotype_neuronal_gerror_cv, &
2280  param_gerror_cv_bodymass = bodymass_reproduce_genotype_neuronal_gerror_cv,&
2281  param_gerror_cv_energy = energy_reproduce_genotype_neuronal_gerror_cv,&
2282  param_gerror_cv_age = age_reproduce_genotype_neuronal_gerror_cv, &
2283  param_gerror_cv_reprfac = reprfac_reproduce_genotype_neuronal_gerror_cv,&
2284  ! @note Real agent perception components are now **substituted**
2285  ! by the **fake** values resulting from executing this
2286  ! behaviour (`do_this` method).
2287  perception_override_bodymass = perception_override_bodymass, &
2288  perception_override_energy = perception_override_energy &
2289  )
2290 
2291  !> #### Calculate primary and final motivations ####
2292  !> Next, from the perceptual components calculated at the previous
2293  !! step we can obtain the **primary** and **final motivation** values by
2294  !! weighed summing.
2295  if (present(rescale_max_motivation)) then
2296  !> Here we can use global maximum motivation across all behaviours and
2297  !! perceptual components if it is provided, for rescaling.
2298  max_motivation = rescale_max_motivation
2299  else
2300  !> Or can rescale using local maximum value for this behaviour only.
2301  max_motivation = this%expectancy%max_perception()
2302  end if
2303 
2304  !> Transfer attention weights from the actor agent `this_agent` to the
2305  !! `this` behaviour component. So, we will now use the updated modulated
2306  !! attention weights of the agent rather than their default parameter
2307  !! values.
2308  call this%attention_transfer(this_agent)
2309 
2310  !> So the primary motivation values are calculated.
2311  call this%expectancy%motivation_primary_calc(max_motivation)
2312 
2313  !> Primary motivations are logged in the @ref intro_debug_mode "debug mode".
2314  call log_dbg( ltag_info // "Primary motivations: " // &
2315  "hunger: " // &
2316  tostr(this%expectancy%hunger%motivation_prim) // &
2317  ", fear_defence: " // &
2318  tostr(this%expectancy%fear_defence%motivation_prim) // &
2319  ", reproduce: " // &
2320  tostr(this%expectancy%reproduction%motivation_prim), &
2321  procname, modname )
2322 
2323  !> There is **no modulation** at this stage, so the final motivation
2324  !! values are the same as primary motivations.
2325  call this%expectancy%modulation_none()
2326 
2327  !> #### Calculate motivation expectancies ####
2328  !> Finally, calculate the finally **expected arousal level for this
2329  !! behaviour**. As in the GOS, the overall arousal is the maximum value
2330  !! among all motivation components.
2331  this%arousal_expected = this%expectancy%max_final()
2332 
2333  !> Log also the final expectancy value in the @ref intro_debug_mode
2334  !! "debug mode".
2335  call log_dbg( ltag_info // "Expectancy: " // tostr(this%arousal_expected),&
2336  procname, modname )
2337 
2338  !> Now as we know the expected arousal, we can choose the behaviour which
2339  !! would minimise this arousal level.
2340 
2341  end subroutine approach_motivations_expect
2342 
2343  !-----------------------------------------------------------------------------
2344  !> Execute this behaviour component "approach" by `this_agent` agent.
2345  subroutine approach_do_execute( this, this_agent, target_object, is_random, &
2346  target_offset, environment_limits )
2347  class(approach), intent(inout) :: this
2348  !> @param[in] this_agent is the actor agent which eats the food item.
2349  class(appraisal), intent(inout) :: this_agent
2350  !> @param[in] target_object is the spatial target object the actor agent
2351  !! is going to approach.
2352  class(spatial), intent(in) :: target_object
2353  !> @param[in] is_random indicator flag for random correlated walk. If
2354  !! present and is TRUE, the agent approaches to the
2355  !! `target_object` in form of random correlated walk (see
2356  !! the_environment::spatial_moving::corwalk()), otherwise
2357  !! directly.
2358  logical, optional, intent(in) :: is_random
2359  !> @param[in] target_offset is an optional offset for the target, so that
2360  !! the target position of the approaching agent does not
2361  !! coincide with the target object. If absent, a default value
2362  !! set by the commondata::approach_offset_default is used.
2363  !! For the the_behaviour::approach_conspec, the default value
2364  !! is as an average of the agent and target conspecific body
2365  !! lengths.
2366  real(SRP), optional, intent(in) :: target_offset
2367  !> @param environment_limits Limits of the environment area available for
2368  !! the random walk. The moving object cannot get beyond this limit.
2369  class(environment), intent(in), optional :: environment_limits
2370 
2371  ! Temporary local spatial object for keeping the location of the
2372  ! target object.
2373  type(spatial) :: target_object_tmp, target_object_offset
2374 
2375  ! Local copy of optional random flag
2376  logical :: is_random_walk
2377 
2378  ! Local copy of optional target offset
2379  real(SRP) :: target_offset_here
2380 
2381  ! Local copy of the body length of the agent
2382  real(SRP) :: agent_length
2383 
2384  ! Mean shift for random walk
2385  real(SRP) :: rwalk_meanshift_xy
2386 
2387  ! Debugging indicators for correlated random walk.
2388  logical :: is_converged_debug
2389  integer :: iter_debug
2390 
2391  ! PROCNAME is the procedure name for logging and debugging.
2392  character(len=*), parameter :: PROCNAME = "(approach_do_execute)"
2393 
2394  !> ### Implementation details ###
2395  !> #### Checks and preparations ####
2396  !> First, check the optional parameters
2397  !! - random walk flag: `is_random`; if the parameter is not provided,
2398  !! the default value FALSE is set so that the agent does a direct
2399  !! approach towards the target object leaving the target offset
2400  !! distance.
2401  if (present(is_random)) then
2402  is_random_walk = is_random
2403  else
2404  is_random_walk = .false.
2405  end if
2406 
2407  !> - target offset: `target_offset`. Note that setting the default
2408  !! value for the target offset involves calling the `select type`
2409  !! construct. Therefore, the default offset for a simple
2410  !! the_behaviour::approach behaviour is equal to the fixed
2411  !! commondata::approach_offset_default value whereas for the
2412  !! the_behaviour::approach_conspec, it is set as an average of the
2413  !! agent and target conspecific body lengths.
2414  !! .
2415  if (present(target_offset)) then
2416  target_offset_here = target_offset
2417  else
2418  select type (this)
2419  class is (approach)
2420  target_offset_here = approach_offset_default
2421  class is (approach_conspec)
2422  target_offset_here = ( this_agent%get_length() + &
2423  get_prop_size(target_object) ) / 2.0_srp
2424  class default
2425  target_offset_here = approach_offset_default
2426  end select
2427  end if
2428 
2429  !> Second, copy the spatial location of the target `target_object` to
2430  !! a temporary spatial object `target_object_tmp` to avoid multiple
2431  !! calling the the_environment::spatial::position() method.
2432  !! @note This is needed because the `target_object` is **class** and
2433  !! getting location can be only done through the `location` method.
2434  call target_object_tmp%position( target_object%location() )
2435 
2436  !> #### Step 1: do_this ####
2437  !> First, we use the intent-in **do**-procedure
2438  !! the_behaviour::approach::do_this() to perform the behaviour desired.
2439  !! Here it calculates the distance towards the target object also taking
2440  !! account of the offset parameter.
2441  call this%do_this( this_agent = this_agent, &
2442  target_object = target_object_tmp, &
2443  target_offset = target_offset_here )
2444 
2445  !> Also check here if the approach distance exceeds the limit set by the
2446  !! commondata::migrate_dist_max_step parameter. If it does exceed, the
2447  !! agent will move towards the target object, but the distance is reduced
2448  !! according to the limit.
2449  agent_length = this_agent%get_length()
2450  if (this%distance - target_offset_here > &
2451  agent_length * migrate_dist_max_step) then
2452  call log_msg( ltag_warn // "Approach travel distance exceeds big " // &
2453  "threshold in " // procname // " for the agent " // &
2454  this_agent%individ_label() // ". Agent length: " // &
2455  tostr(agent_length) // ", migration distance: " // &
2456  tostr(this%distance) )
2457  this%distance = agent_length * migrate_dist_max_step + target_offset_here
2458  end if
2459 
2460  !> #### Step 2: Change the agent ####
2461  !> ##### Relocate towards the target object #####
2462  !> Relocate to the target object can be either a correlated random walk
2463  !! in the target direction or direct movement to the target.
2464  !! - In the former case, the environmental limits can be either provided
2465  !! by the `environment_limits` parameter or obtained automatically
2466  !! from the global array the_environment::global_habitats_available.
2467  !! - If the approach distance is less then commondata::zero (i.e. the
2468  !! target object is already at a distance smaller than target offset),
2469  !! the correlated random walk step is set to the target offset.
2470  !! .
2471  do_walk_random: if (is_random_walk) then
2472  if (present(environment_limits)) then
2473  if (this%distance > zero) then
2474  rwalk_meanshift_xy = this%distance - target_offset_here
2475  else
2476  rwalk_meanshift_xy = target_offset_here
2477  end if
2478  call this_agent%corwalk( &
2479  target = target_object_tmp, &
2480  meanshift_xy = rwalk_meanshift_xy, &
2481  cv_shift_xy = walk_random_distance_stochastic_cv, &
2482  meanshift_depth = (this%distance - target_offset_here) * &
2483  walk_random_vertical_shift_ratio, &
2484  cv_shift_depth = walk_random_distance_stochastic_cv * &
2485  walk_random_vertical_shift_cv_ratio, &
2486  is_away = .false., &
2487  environment_limits = environment_limits, &
2488  is_converged = is_converged_debug, &
2489  debug_reps = iter_debug )
2490  else
2491  if (this%distance > zero) then
2492  rwalk_meanshift_xy = this%distance - target_offset_here
2493  else
2494  rwalk_meanshift_xy = target_offset_here
2495  end if
2496  call this_agent%corwalk( &
2497  target = target_object_tmp, &
2498  meanshift_xy = rwalk_meanshift_xy, &
2499  cv_shift_xy = walk_random_distance_stochastic_cv, &
2500  meanshift_depth = (this%distance - target_offset_here) * &
2501  walk_random_vertical_shift_ratio, &
2502  cv_shift_depth = walk_random_distance_stochastic_cv * &
2503  walk_random_vertical_shift_cv_ratio, &
2504  is_away = .false., &
2505  environment_limits = global_habitats_available( &
2506  this_agent%find_environment( &
2507  global_habitats_available) ), &
2508  is_converged = is_converged_debug, &
2509  debug_reps = iter_debug )
2510  end if
2511  call log_dbg( ltag_info // "Correlated random walk: converged " // &
2512  tostr(is_converged_debug) // ", iterations: " // &
2513  tostr(iter_debug), procname, modname )
2514  !> - If correlated random walk is not enabled (`is_random` parameter is
2515  !! FALSE), the agent goes *directly* towards the target. It actually
2516  !! relocates to a spatial position with the the target offset. The new
2517  !! position of the agent is defined by the the_environment::offset_dist()
2518  !! function subtracting the value of the offset.
2519  !! - However, if the approach distance is less than commondata::zero,
2520  !! (i.e. the agent is already in proximity of the target object, at a
2521  !! distance smaller than the target offset), the agent "moves" to its
2522  !! *current* position, i.e. no real relocation is done. This situation
2523  !! is logged in the DEBUG mode.
2524  !! .
2525  !! .
2526  else do_walk_random
2527  if (this%distance > zero) then
2528  target_object_offset = offset_dist( this_agent, target_object_tmp, &
2529  target_offset_here)
2530  call this_agent%position( target_object_offset )
2531  call log_dbg(ltag_info // "Agent approached the target, distance to " &
2532  // " the target: " // &
2533  tostr(this_agent%distance(target_object_tmp)) // &
2534  "; distance offset: " // tostr(target_offset_here) // &
2535  ", updated target distance to the target: " // &
2536  tostr(this_agent%distance(target_object_offset)) // &
2537  "; original target: " // tostr([target_object_tmp%xpos(), &
2538  target_object_tmp%ypos(), target_object_tmp%dpos()]) // &
2539  ", new agent position: " // tostr([this_agent%xpos(), &
2540  this_agent%ypos(),this_agent%dpos()]), procname, modname )
2541  else
2542  call this_agent%position( this_agent%location() )
2543  call log_dbg(ltag_info // "Agent has not relocated because it is " // &
2544  "in proximity of the target; distance to target: " // &
2545  tostr(this_agent%distance(target_object)) )
2546  end if
2547 
2548  end if do_walk_random
2549 
2550  !> ##### Process the cost of movement #####
2551  !> - Reset the body mass of the actor agent subtracting the actual cost of
2552  !! moving that is automatically calculated in the call to
2553  !! the_body::condition::cost_swim(). The the_body::condition::set_mass()
2554  !! method is used here to adjust the mass.
2555  call this_agent%set_mass( &
2556  value_set = this_agent%get_mass() - &
2557  this_agent%cost_swim(exponent= &
2558  swimming_cost_exponent_laminar), &
2559  update_history = .true. )
2560 
2561  !> - Additionally, also call the `the_body::condition::set_length()` method
2562  !! to update the body length history stack. However, the value_set
2563  !! parameter here is just the current value. This fake re-setting of the
2564  !! body length is done to keep both mass and length synchronised in their
2565  !! history stack arrays (there is no procedure for only updating history).
2566  call this_agent%set_length( value_set = this_agent%get_length(), &
2567  update_history = .true. )
2568 
2569  !> - After resetting the body mass, update energy reserves of the agent,
2570  !! that depend on both the length and the mass.
2571  !! .
2572  call this_agent%energy_update()
2573 
2574  !> Finally, check if the agent is starved to death. If yes, the agent can
2575  !! die without going any further.
2576  if (this_agent%starved_death()) call this_agent%dies()
2577 
2578  !> #### Step 3: Change the environment ####
2579  !> Approach does not affect the environmental objects.
2580 
2581  end subroutine approach_do_execute
2582 
2583  !-----------------------------------------------------------------------------
2584  !> Initialise the **approach conspecific** behaviour to a zero state.
2585  !! Approach conspecific is a special extension of the generic `APPROACH`
2586  !! behaviour.
2587  elemental subroutine approach_conspecifics_init_zero(this)
2588  class(approach_conspec), intent(inout) :: this
2589 
2590  !> First init components from the base root class
2591  !! `the_behaviour::behaviour_base`.
2592  !> Mandatory label component that should be read-only.
2593  this%label = "APPR_CONSPEC"
2594  !> The execution status is always FALSE, can be reset to TRUE only when
2595  !! the behaviour unit is called to execution.
2596  this%is_active = .false.
2597 
2598  !> And the *expectancy* components.
2599  call this%expectancy%init()
2600  this%arousal_expected = 0.0_srp
2601 
2602  !> Abstract `MOVE` component.
2603  this%distance = missing
2604 
2605  !> Component of `APPROACH` class.
2606  !> Then init components of this specific behaviour component extended class.
2607  this%expected_cost_moving = missing
2608 
2609  !> This class, APPROACH_CONSPEC, initialisations.
2610  this%expected_food_gain = missing
2611  this%expected_predation_risk = missing
2612  this%expected_pred_dir_risk = missing
2613 
2614  end subroutine approach_conspecifics_init_zero
2615 
2616  !-----------------------------------------------------------------------------
2617  !> The "do" procedure component of the behaviour element performs the
2618  !! behaviour without affecting the actor agent (the_agent) and the world
2619  !! (here food_item_eaten) which have intent(in), so it only can change
2620  !! the internal representation of the behaviour (the type to which this
2621  !! procedure is bound to, here `APPROACH_CONSPEC`).
2622  subroutine approach_conspecifics_do_this( this, this_agent, target_object, &
2623  target_offset, &
2624  predict_window_food, &
2625  time_step_model )
2626  class(approach_conspec), intent(inout) :: this
2627  !> @param[in] this_agent is the actor agent which approaches.
2628  class(appraisal), intent(in) :: this_agent
2629  !> @param[in] target_object is the target conspecific the actor agent
2630  !! is going to approach.
2631  class(spatial), intent(in) :: target_object
2632  !> @param[in] target_offset is an optional offset for the target, so that
2633  !! the target position of the approaching agent does not
2634  !! coincide with the target object. If absent, a default value
2635  !! set by the commondata::approach_offset_default is used.
2636  real(SRP), optional, intent(in) :: target_offset
2637  !> @param[in] predict_window_food the size of the prediction window, i.e.
2638  !! how many steps back in memory are used to calculate the
2639  !! predicted food gain. This parameter is limited by the maximum
2640  !! commondata::history_size_perception value of the perception
2641  !! memory history size.
2642  integer, optional, intent(in) :: predict_window_food
2643  !> @param[in] time_step_model optional time step of the model, overrides
2644  !! the value calculated from the spatial data.
2645  integer, optional, intent(in) :: time_step_model
2646 
2647  ! Local copy of the body length of the agent
2648  real(SRP) :: agent_length
2649 
2650  ! Local copy of optional target offset
2651  real(SRP) :: target_offset_here
2652 
2653  ! Local copies of optionals.
2654  integer :: predict_window_food_here, time_step_model_here
2655 
2656  ! PROCNAME is the procedure name for logging and debugging.
2657  character(len=*), parameter :: PROCNAME = "(approach_conspecifics_do_this)"
2658 
2659  ! File name for debug plot.
2660  character(FILENAME_LENGTH) :: debug_plot_file_sufx
2661 
2662  ! WEIGHT_DIRECT is the relative weight given to the immediate
2663  ! perception of predators over the predators counts in the memory stack.
2664  ! Obtained from global parameters
2665  ! (`commondata::predation_risk_weight_immediate`).
2666  real(SRP), parameter :: WEIGHT_DIRECT = predation_risk_weight_immediate
2667 
2668  ! MEM_WIND is the size of the memory window when assessing the
2669  ! predator risk, only this number of the latest elements from the memory
2670  ! stack is taken into account. So we further weight the direct threat
2671  ! over the background risk when making the decision.
2672  ! @note Note that we take into account the whole memory size
2673  ! (commondata::history_size_perception).
2674  integer, parameter :: MEM_WIND = history_size_perception
2675 
2676  !> ### Notable local variables ###
2677  !! - consp_size - the size of the target conspecific,
2678  !! - consp_mass - body mass of the target conspecific
2679  !! - consp_dist - the distance to the target conspecific
2680  real(SRP) :: consp_size, consp_mass, consp_dist
2681 
2682  !> - target_position_agent - the target position of the agent, it does
2683  !! not coincide with the position of the target conspecific and is
2684  !! smaller by the value of the target offset.
2685  type(spatial) :: target_position_agent
2686 
2687  !> - tmp_predator - temporary predator object, a subjective representation
2688  !! of the first nearest predator from the perception object of the actor
2689  !! agent.
2690  type(predator) :: tmp_predator
2691 
2692  !> - risk_pred_expect - an array keeping the expectancy of the predation
2693  !! risk for each predator in the perception object.
2694  real(SRP), allocatable, dimension(:) :: risk_pred_expect
2695 
2696  !> - n_pred_now - current number of predators in the perception object
2697  !! of the actor agent.
2698  integer :: n_pred_now, i
2699 
2700  !> - body_mass_ratio - the ratio of the body mass of the actor agent
2701  !! to the target conspecific @f$ \frac{M}{M_{TC}} @f$.
2702  real(SRP) :: body_mass_ratio
2703 
2704  !> - food_gain_expect_baseline is a baseline expected food gain, not
2705  !! taking account of competition with the target conspecific.
2706  real(SRP) :: food_gain_expect_baseline
2707 
2708  !> - agent_length - agent length by condition::get_length() method.
2709  !! .
2710  agent_length = this_agent%get_length()
2711 
2712  !> #### Checks and preparations ####
2713  !> Check optional parameter for the food perception memory window. If
2714  !! the `predict_window_food` dummy parameter is not provided, its default
2715  !! value is the proportion of the whole perceptual memory window defined
2716  !! by commondata::history_perception_window_food. Thus, only the
2717  !! latest part of the memory is used for the prediction of the future
2718  !! food gain.
2719  if (present(predict_window_food)) then
2720  predict_window_food_here = predict_window_food
2721  else
2722  predict_window_food_here = floor( history_size_perception * &
2723  history_perception_window_food )
2724  end if
2725  !> Check optional time step parameter. If unset, use global
2726  !! `commondata::global_time_step_model_current`.
2727  if (present(time_step_model)) then
2728  time_step_model_here = time_step_model
2729  else
2730  time_step_model_here = global_time_step_model_current
2731  end if
2732 
2733  !> Set the debug plot file name that will be passed to the
2734  !! predator-class-bound function the_environment::predator::risk_fish().
2735  debug_plot_file_sufx = tostr(global_time_step_model_current) // "_" // &
2736  mmdd // "_a_" // trim(this_agent%individ_label()) &
2737  // "_" // &
2738  rand_string(label_length, label_cst,label_cen) // ps
2739 
2740  !> ### Implementation details ###
2741  !> #### Get the properties of the target conspecific ####
2742  !> Get the properties of the conspecific from the perception object
2743  !! or real physical conspecific data. This is done by determining the
2744  !! `target_object` data type with "`select type`" construct (named
2745  !! construct `GET_TARGET`).
2746  !!
2747  !! The distance to the target conspecific is determined from the target
2748  !! object with the_neurobio::conspec_percept_comp::get_dist() for
2749  !! perception object or the_environment::spatial::distance() for real
2750  !! conspecific.
2751  get_target: select type (target_object)
2752  !> - if the `target_object` is a conspecific from the perception object,
2753  !! its body length and mass are obtained from the respective
2754  !! data components of the_neurobio::conspec_percept_comp.
2755  class is (conspec_percept_comp) get_target
2756  consp_size = target_object%get_size()
2757  consp_mass = target_object%get_mass()
2758  consp_dist = target_object%get_dist()
2759  call log_dbg( ltag_info // "Perception of target conspecific in " // &
2760  procname // ", size: " // tostr(consp_size) // &
2761  ", mass: " // tostr(consp_mass) // &
2762  ", distance (from perception): " // tostr(consp_dist) //&
2763  " and (from object): " // &
2764  tostr( this_agent%distance( target_object ) ) // "." )
2765  !> - if the `target_object` is real conspecific (the_neurobio::appraisal
2766  !! class), its body length and mass are obtained from lower order
2767  !! class component the_body::condition::get_length() and
2768  !! the_body::condition::get_mass() methods.
2769  class is (appraisal) get_target
2770  consp_size = target_object%get_length()
2771  consp_mass = target_object%get_mass()
2772  consp_dist = this_agent%distance( target_object )
2773  call log_dbg( ltag_info // "Explicit target conspecific in " // &
2774  procname // ", size: " // tostr(consp_size) // &
2775  ", mass: " // tostr(consp_mass) // &
2776  ", distance: " // tostr(consp_dist) // "." )
2777  !> - in the case construct "default" case, if the `target_object` is
2778  !! neither a perception object nor real conspecific, get the
2779  !! location from the commondata::spatial class position data and other
2780  !! properties of the conspecific from the actor agent itself.
2781  !! Such a situation of **undefined target** type is unexpected and is
2782  !! likely to point to a bug. Therefore, an error is issued into the
2783  !! logger.
2784  !> .
2785  class default get_target
2786  consp_size = agent_length
2787  consp_mass = this_agent%get_mass()
2788  consp_dist = this_agent%distance( target_object )
2789  call log_dbg( ltag_warn // "Target conspecific in " // procname // &
2790  " is undefined, get properties from the agent. " // &
2791  "Length: " // tostr(consp_size) // ", " // &
2792  "mass: " // tostr(consp_mass) // ", " // &
2793  "distance: " // tostr(consp_dist) // ". ", &
2794  procname, modname )
2795  call log_dbg( ltag_warn // "Position of the target object: " // &
2796  tostr([ target_object%xpos(), &
2797  target_object%ypos(), &
2798  target_object%dpos() ]) // " in " // procname,&
2799  procname, modname )
2800  end select get_target
2801 
2802  !> #### Determine the target offset ####
2803  !> Target offset `target_offset` can be provided as an optional dummy
2804  !! parameter to this procedure. However, if it is not provided explicitly,
2805  !! a default value is set as an average of the actor agent body length
2806  !! and the target conspecific body length.
2807  if (present(target_offset)) then
2808  target_offset_here = target_offset
2809  else
2810  target_offset_here = (agent_length + consp_size) / 2.0_srp
2811  end if
2812 
2813  !> #### Proximity check and target distance ####
2814  !> The agent approaches the conspecific but to a nonzero distance equal
2815  !! to the target offset value (`target_offset`). A check is done if the
2816  !! distance between the agent and the conspecific target object is
2817  !! actually smaller than the target offset.
2818  !! - If so, the agent is already in close proximity to the target and
2819  !! there is no need to do an approach movement.
2820  in_proximity: if ( this_agent%distance( target_object ) <= &
2821  target_offset_here ) then
2822  !> - The approach distance is set to zero.
2823  this%distance = 0.0_srp
2824  !> - The target position of the agent (`target_position_agent`) after
2825  !! such a zero approach actually coincides with the current position
2826  !! of the agent: it does not plan to swim.
2827  target_position_agent = this_agent%location()
2828  !> - The expected cost of approach movement is also zero.
2829  !! .
2830  this%expected_cost_moving = 0.0_srp
2831 
2832  !> - If the agent is currently at a distance exceeding the target
2833  !! offset, the approach distance towards the target position of
2834  !! the actor agent is calculated as the true distance towards the
2835  !! target conspecific minus the offset value `target_offset`.
2836  !! (Note that whenever the default target offset is set, i.e. an average
2837  !! of the agent and target body sizes, the approach distance depends
2838  !! on the body sizes of both parties; it is also symmetric, i.e. the
2839  !! same if a large agent approaches a small target conspecific or
2840  !! *vice versa*.)
2841  else in_proximity
2842  this%distance = this_agent%distance( target_object ) - target_offset_here
2843  !> - Check if the distance to the target object exceeds the
2844  !! migration travel maximum value, set as
2845  !! commondata::migrate_dist_max_step body sizes of the agent. This
2846  !! case should not normally occur if the maximum distance is
2847  !! sufficiently large so that the target object is beyond the
2848  !! agent's visual range. So, nothing is done here except logging a
2849  !! warning.
2850  if (this%distance > agent_length * migrate_dist_max_step ) then
2851  call log_msg( ltag_warn // "Target conspecific travel distance " // &
2852  "exceeds big threshold in " // procname // &
2853  " for the agent " // this_agent%individ_label() // &
2854  ". Agent length: " // tostr(agent_length) // &
2855  ", target distance: " // tostr(this%distance) )
2856  end if
2857  !> - Calculate the prospective target position of the agent in
2858  !! proximity of the target conspecific `target_position_agent` with
2859  !! the offset, using the the_environment::offset_dist() procedure.
2860  target_position_agent = offset_dist( this_agent, target_object, &
2861  target_offset_here )
2862  !> - Calculate expected cost of the swimming. The expected cost of
2863  !! swimming in the approach walk step depends on the above approach
2864  !! distance and is calculated using the the_body::condition::cost_swim()
2865  !! method assuming *laminar* flow (laminar flow is due to normal
2866  !! relatively slow swimming pattern).
2867  !! .
2868  !! .
2869  this%expected_cost_moving = &
2870  this_agent%cost_swim(distance=this%distance, &
2871  exponent=swimming_cost_exponent_laminar)
2872  end if in_proximity
2873 
2874  !> #### Calculate expected risk of predation ####
2875  !> The expected risk of predation is assumed to **reduce** due to predator
2876  !! dilution or confusion effects if the agent approaches a conspecific.
2877  !! Furthermore, the risk values depend on the relative positions and
2878  !! distances between the predator and the actor agent and predator and
2879  !! the target conspecific.
2880  !!
2881  !> Calculation of the expected risks of predation depends on the current
2882  !! perception of the agent. The simplest case is when the agent has
2883  !! currently **no predators** in its predator perception object:
2884  no_predators: if ( .not. this_agent%has_pred() ) then
2885 
2886  !> - If there are no predators in the perception object, the expected
2887  !! general risk is calculated using the
2888  !! the_neurobio::predation_risk_backend() method assuming the current
2889  !! perception of predators is null.
2890  this%expected_predation_risk = &
2891  predation_risk_backend( &
2892  pred_count = 0, &
2893  pred_memory_mean = &
2894  this_agent%memory_stack%get_pred_mean(mem_wind), &
2895  weight_direct = weight_direct )
2896  !> - The expected direct risk of predation is zero if there are no
2897  !! predators in the current perception.
2898  !! .
2899  this%expected_pred_dir_risk = 0.0_srp
2900 
2901  !> If there is a **non-zero number of predators** in the current predator
2902  !! perception, calculations of the expected risks are more complex.
2903  else no_predators
2904  !> ##### General risk #####
2905  !> First, get the number of predators in the current perception object
2906  !! using the the_neurobio::percept_predator::get_count().
2907  n_pred_now = this_agent%perceive_predator%get_count()
2908 
2909  !> Accordingly, the **general risk** of predation taking account both the
2910  !! number of predators in the perception object and the average number
2911  !! of predators in the memory stack is calculated using the
2912  !! the_neurobio::predation_risk_backend() method. However, the expected
2913  !! number of predators is reduced by a factor defined by the parameter
2914  !! commondata::approach_conspecfic_dilute_general_risk (the integer
2915  !! expected number of predators is actually obtained by the `floor`
2916  !! intrinsic giving the lower integer value). (Therefore, the reduced
2917  !! expectancy is based on reduction of the expected number of predators
2918  !! while keeping memory part of the expectation fixed).
2919  this%expected_predation_risk = &
2920  predation_risk_backend( &
2921  pred_count = floor( n_pred_now * &
2922  approach_conspecfic_dilute_general_risk ), &
2923  pred_memory_mean = &
2924  this_agent%memory_stack%get_pred_mean(mem_wind),&
2925  weight_direct = weight_direct )
2926 
2927  !> ##### Direct risk #####
2928  !> Expectation of the direct risk of predation depends on the target
2929  !! position of the actor agent @f$ P_T @f$ (with the target offset
2930  !! @f$ \Delta @f$) and relative distances between the actor agent, target
2931  !! conspecific @f$ P_{TC} @f$ and all the predators @f$ P_i @f$ in the
2932  !! current perception object of the actor agent following the predicted
2933  !! agent movement.
2934  !> @image html img_doxygen_approach_consp.svg
2935  !! @image latex img_doxygen_approach_consp.eps "Calculation of the predicted direct risk of predation" width=14cm
2936  !!
2937  !> First, allocate the array `risk_pred_expect` that keeps the values
2938  !! of risk for each of the predators in the perception object.
2939  allocate( risk_pred_expect(n_pred_now) )
2940 
2941  !> Then, cycle over all the predators @f$ P_i @f$ in the current
2942  !! perception object of the actor agent @f$ P_a @f$ and check if the
2943  !! prospective movement towards the target conspecific @f$ P_{TC} @f$
2944  !! would place the agent *further* from the predator (a) than the target
2945  !! conspecific: @f$ D_{AP} > D_{CP} @f$.
2946  !! If yes, direct risk of predation for this
2947  !! predator is equal to the risk of predation @f$ r @f$ unadjusted for
2948  !! the dilution or confusion effects multiplied by the
2949  !! commondata::approach_conspecfic_adjust_pair_behind factor (normally
2950  !! 1/2 as diluted in a half by the target conspecific, @f$ 0.5 r_i @f$).
2951  !! If the movement is likely to place the actor agent *closer* to the
2952  !! predator than the target conspecific @f$ D_{AP} < D_{CP} @f$, the
2953  !! expected risk for the actor agent is calculated as unadjusted value
2954  !! @f$ r_i @f$.
2955  !!
2956  !! Thus, the predator dilution effect is introduced only if the actor
2957  !! agent is moving to the backward position further away from the predator
2958  !! (a) than the target conspecific (the target conspecific then is closer
2959  !! to the predator and suffers higher risk). If the actor agent moves to
2960  !! the forward position with respect to the predator (b), it suffers full
2961  !! unadjusted risk instead. This is the classical "selfish herd" effect.
2962  !!
2963  !! Finally, the **maximum** value of the predation risks across all the
2964  !! predators @f$ max (r_i) @f$ in the perception object of the actor agent
2965  !! constitutes the "final" expectation of the direct risk of predation:
2966  !! the_behaviour::approach_conspec::expected_pred_dir_risk.
2967  pred_percept: do i=1, n_pred_now
2968  !> - At each (*i*-th) step of the loop, create a temporary
2969  !! the_environment::predator type object `tmp_predator` using
2970  !! the_environment::predator::make(). This predator's body size and
2971  !! the spatial position are obtained directly from the *i*-th predator
2972  !! 1/2 the agent's current perception object. But note that the agent
2973  !! is unable to determine the individually specific attack rate of
2974  !! the predator and uses the default value.
2975  call tmp_predator%make( &
2976  body_size = &
2977  this_agent%perceive_predator%predators_seen(i)%get_size(), &
2978  attack_rate = predator_attack_rate_default, &
2979  position = &
2980  this_agent%perceive_predator%predators_seen(i)%location(), &
2981  label="tmp_object" )
2982 
2983  !> - If the distance between the agent and the *i*-th predator in the
2984  !! perception object (the temporary predator object `tmp_predator`)
2985  !! would become **shorter** than the distance between
2986  !! the target conspecific and the predator (i.e. the agent would go
2987  !! closer to the *i*-th predator than the target conspecific
2988  !! @f$ D_{AP} < D_{CP} @f$), the direct risk of predation is
2989  !! calculated as unadjusted risk of predation computed using the
2990  !! the_environment::predator::risk_fish() method, assuming the
2991  !! actor agent is in the target approach position
2992  !! `target_position_agent`.
2993  go_closer: if ( target_position_agent%distance( &
2994  this_agent%perceive_predator%predators_seen(i) ) < &
2995  target_object%distance( &
2996  this_agent%perceive_predator%predators_seen(i) ) ) &
2997  then
2998  risk_pred_expect(i) = &
2999  tmp_predator%risk_fish( prey_spatial=target_position_agent, &
3000  prey_length=this_agent%get_length(), &
3001  prey_distance=this%distance, &
3002  is_freezing=.false., &
3003  time_step_model=time_step_model_here, &
3004  debug_plot_file= &
3005  "plot_debug_exp_predation_risk_" // &
3006  debug_plot_file_sufx )
3007  !> - Otherwise, if the agent is going to relocate to a more remote
3008  !! location from the *i*-th predator (@f$ D_{AP} > D_{CP} @f$), the
3009  !! baseline predation risk the_environment::predator::risk_fish() is
3010  !! diluted by a factor constant that is defined by the parameter
3011  !! commondata::approach_conspecfic_dilute_adjust_pair_behind
3012  !! (normally 1/2, i.e. diluted halfway by the target conspecific that
3013  !! is going to be closer to this predator).
3014  else go_closer
3015  risk_pred_expect(i) = &
3016  approach_conspecfic_dilute_adjust_pair_behind * &
3017  tmp_predator%risk_fish( prey_spatial=target_position_agent, &
3018  prey_length=this_agent%get_length(), &
3019  prey_distance=this%distance, &
3020  is_freezing=.false., &
3021  time_step_model=time_step_model_here, &
3022  debug_plot_file= &
3023  "plot_debug_exp_predation_risk_" // &
3024  debug_plot_file_sufx )
3025  end if go_closer
3026 
3027  end do pred_percept
3028 
3029  !> - Finally, the value of the overall direct predation risk expected if
3030  !! the agent approaches the target conspecific is calculated as the
3031  !! maximum value of the expected risks across all predators in the
3032  !! perception object.
3033  !! .
3034  this%expected_pred_dir_risk = maxval(risk_pred_expect)
3035 
3036  !> - The array of the expected direct risks from each of the predators
3037  !! in perception is logged out in the DEBUG mode.
3038  call log_dbg( ltag_info // "Saved direct predation risks for " // &
3039  tostr(n_pred_now) // " predators in perception; " // &
3040  " the maximum value is: " // &
3041  tostr(this%expected_pred_dir_risk) // &
3042  "; full array: " // tostr(risk_pred_expect), &
3043  procname, modname )
3044 
3045  end if no_predators
3046 
3047  !> #### Calculate the expected food gain ####
3048  !> The expected food gain is assumed to be **reduced** due to possible
3049  !! competition if the agent approaches a conspecific. Furthermore, the
3050  !! competition effect should depend on the relative body masses of the
3051  !! actor agent and the target conspecific.
3052  !!
3053  !> First, a baseline assessment of the food gain @f$ f_0 @f$ is calculated
3054  !! that does not take into account any effects of competition with the
3055  !! target conspecific. It is equal to the average mass of all food items in
3056  !! the current food perception object weighted by the subjective
3057  !! probability of food item capture that is calculated based on the memory
3058  !! the_neurobio::perception::food_probability_capture_subjective().
3059  !! (The mass is zero if there are no food items perceived).
3060  food_gain_expect_baseline = this_agent%perceive_food%get_meanmass() * &
3061  this_agent%food_probability_capture_subjective( &
3062  predict_window_food_here, time_step_model_here )
3063 
3064  !> The expected value of the food gain when the agent is about to approach
3065  !! the target conspecific is calculated as the baseline expected food gain
3066  !! @f$ f_0 @f$ multiplied by a nonparametric weighting function that
3067  !! depends on the ratio of the body mass of the actor agent
3068  !! @f$ M @f$ and the target conspecific @f$ M_{TC} @f$:
3069  !! @f[ f = f_0 \Phi ( \frac{M}{M_{TC}} ) . @f]
3070  !! The function @f$ \Phi @f$ is defined by the grid set by the arrays
3071  !! commondata::approach_food_gain_compet_factor_abscissa and
3072  !! commondata::approach_food_gain_compet_factor_ordinate.
3073  body_mass_ratio = this_agent%get_mass() / consp_mass
3074  !> @image html img_doxygen_approach_consp_food.svg
3075  !! @image latex img_doxygen_approach_consp_food.eps "Food competition factor for expected food gain" width=14cm
3076  !! @note The maximum value of the grid abscissa defines the body mass ratio
3077  !! that guarantees 100% expectancy of winning of competition for food
3078  !! against the target conspecific. For example, the value of 1.5
3079  !! means that an agent is guaranteed to get the whole baseline
3080  !! expected food gain if its body weight is 1.5 of the target
3081  !! conspecific. The grid ordinate corresponding to the abscissa 1.0
3082  !! determines the food gain weighting when the body sizes of the
3083  !! agent and the target conspecifics are equal, e.g. 0.5 points to
3084  !! equal share by equal competitive ability.
3085  this%expected_food_gain = &
3086  food_gain_expect_baseline * &
3087  ddpinterpol( approach_food_gain_compet_factor_abscissa, &
3088  approach_food_gain_compet_factor_ordinate, &
3089  body_mass_ratio )
3090 
3091  !> Interpolation plots can be saved in the @ref intro_debug_mode
3092  !! "debug mode" using this plotting command:
3093  !! `commondata::debug_interpolate_plot_save()`.
3094  !! @warning Involves **huge** number of plots, should normally be
3095  !! disabled.
3096  call debug_interpolate_plot_save( &
3097  grid_xx=approach_food_gain_compet_factor_abscissa, &
3098  grid_yy=approach_food_gain_compet_factor_ordinate, &
3099  ipol_value=body_mass_ratio, algstr="DDPINTERPOL", &
3100  output_file="plot_debug_expect_food_gain_" // &
3101  debug_plot_file_sufx )
3102 
3103  end subroutine approach_conspecifics_do_this
3104 
3105  !-----------------------------------------------------------------------------
3106  !> `the_behaviour::approach_conspec::expectancies_calculate()` (re)calculates
3107  !! motivations from fake expected perceptions following from the procedure
3108  !! the_behaviour::approach_conspec::do_this().
3109  subroutine approach_conspecifics_motivations_expect( this, this_agent, &
3110  target_object, target_offset, time_step_model, rescale_max_motivation)
3111  class(approach_conspec), intent(inout) :: this
3112  !> @param[in] this_agent is the actor agent which approaches a target
3113  !! conspecific.
3114  class(appraisal), intent(in) :: this_agent
3115  !> @param[in] target_object is the spatial target object the actor agent
3116  !! is going to approach.
3117  class(spatial), optional, intent(in) :: target_object
3118  !> @param[in] target_offset is an optional offset for the target, so that
3119  !! the target position of the approaching agent does not
3120  !! coincide with the target object. If absent, a default value
3121  !! set by the commondata::approach_offset_default is used.
3122  real(SRP), optional, intent(in) :: target_offset
3123  !> @param[in] time_step_model optional time step of the model, overrides
3124  !! the value calculated from the spatial data.
3125  integer, optional, intent(in) :: time_step_model
3126  !> @param[in] rescale_max_motivation optional maximum motivation value for
3127  !! rescaling all motivational components for comparison
3128  !! across all motivation and perceptual components and behaviour
3129  !! units.
3130  real(SRP), optional, intent(in) :: rescale_max_motivation
3131 
3132  ! Local variables
3133  real(SRP) :: max_motivation ! Local max. over all motivation components.
3134 
3135  ! Local copy of optional target offset
3136  real(SRP) :: target_offset_here
3137 
3138  ! Local copy of optional model time step
3139  integer :: time_step_model_here
3140 
3141  ! Expected food item that is used in the calculations, its properties are
3142  ! based on the average food items that the agent perceives below.
3143  type(food_item) :: expected_food_item
3144 
3145  real(SRP) :: expected_food_item_distance
3146 
3147  !> The probability of capture of the expected food object.
3148  real(SRP) :: expected_food_item_prob_capture
3149 
3150  !> Expected food gain that is fitting into the stomach of the agent.
3151  real(SRP) :: expected_food_item_gain_fits
3152 
3153  ! Current stomach contents of the agent.
3154  real(SRP) :: agent_stomach
3155 
3156  !> ### Notable local variables ###
3157  !> A full list of @ref percept_overrides_lst "all perception overrides"
3158  !! is available in the description of the
3159  !! the_neurobio::percept_components_motiv::motivation_components()
3160  !! procedure.
3161  !> #### Perception overrides ####
3162  !> - **perception_override_pred_dir** is the expected direct predation risk.
3163  real(SRP) :: perception_override_pred_dir
3164  !> - **perception_override_predator** is the expected general predation
3165  !! risk, that is based on a weighting of the current predation and
3166  !! predation risk from the memory stack.
3167  real(SRP) :: perception_override_predator
3168 
3169  !> - **perception_override_food_dir** is the expected number of food items
3170  !! in perception general predation.
3171  real(SRP) :: perception_override_food_dir
3172 
3173  !> - **perception_override_stomach** is the expected stomach contents as a
3174  !! consequence of approach movement. Note that there is no food
3175  !! consumption during approach.
3176  real(SRP) :: perception_override_stomach
3177  !> - **perception_override_bodymass** is the expected body mass as a
3178  !! consequence of the approaching the target conspecific.
3179  real(SRP) :: perception_override_bodymass
3180  !> - **perception_override_energy** is the expected energy reserves
3181  !! as a consequence of the escape movement. Calculated from the body
3182  !! mass and weight.
3183  !! .
3184  real(SRP) :: perception_override_energy
3185 
3186  ! PROCNAME is the procedure name for logging and debugging
3187  character(len=*), parameter :: PROCNAME = &
3188  "(approach_conspecifics_motivations_expect)"
3189 
3190  !> ### Implementation details ###
3191  !> #### Checks and preparations ####
3192  !> Check optional time step parameter. If not provided, use global
3193  !! parameter value from commondata::global_time_step_model_current.
3194  if (present(time_step_model)) then
3195  time_step_model_here = time_step_model
3196  else
3197  time_step_model_here = global_time_step_model_current
3198  end if
3199 
3200  !> Determine the target offset. Target offset `target_offset` can be
3201  !! provided as an optional dummy parameter to this procedure. However, if
3202  !! it is not provided explicitly, a default value is set as an average of
3203  !! the actor agent body length and the target conspecific body length.
3204  !! The the_neurobio::get_prop_size() method for polymorphic object gets
3205  !! the size of the target conspecific.
3206  if (present(target_offset)) then
3207  target_offset_here = target_offset
3208  else
3209  target_offset_here = ( this_agent%get_length() + &
3210  get_prop_size(target_object) ) / 2.0_srp
3211  end if
3212 
3213  !> #### Call do_this ####
3214  !> As the first step, we use the **do**-procedure
3215  !! approach_conspec::do_this() to perform the behaviour desired
3216  !! without changing either the agent or its environment, obtaining the
3217  !! **subjective** values of the `this` behaviour components that later
3218  !! feed into the motivation **expectancy** functions:
3219  !! - `perception_override_food_dir`
3220  !! - `perception_override_pred_dir`
3221  !! - `perception_override_predator`
3222  !! - `perception_override_stomach`
3223  !! - `perception_override_bodymass`
3224  !! - `perception_override_energy`
3225  !! .
3226  call this%do_this( this_agent = this_agent, &
3227  target_object = target_object, &
3228  target_offset = target_offset_here, &
3229  time_step_model = time_step_model_here )
3230 
3231  !> #### Calculate expected (fake) perceptions ####
3232  !> ##### Fake perception of stomach content #####
3233  !> First, create a fake food item with the spatial position identical to
3234  !! that of the agent. The position is used only to calculate the
3235  !! illumination and therefore visual range. The cost(s) are calculated
3236  !! providing explicit separate distance parameter, so the zero distance
3237  !! from the agent is inconsequential. The size of the
3238  !! food item is obtained from the expected food gain by the reverse
3239  !! calculation function the_environment::mass2size_food().
3240  !! Standard `make` method for the food item class is used.
3241  call expected_food_item%make(location=this_agent%location(), &
3242  size=mass2size_food(this%expected_food_gain),&
3243  iid=unknown )
3244 
3245  !> Second, calculate the **probability of capture** of this expected food
3246  !! item. The probability of capture of the fake food item is calculated
3247  !! using the the_environment::food_item::capture_probability() backend
3248  !! assuming the distance to the food item is equal to the average distance
3249  !! of all food items in the **current perception** object. However, if the
3250  !! agent does not see any food items currently, the distance to the fake
3251  !! food item is assumed to be equal to the visibility range weighted by
3252  !! the (fractional) commondata::walk_random_dist_expect_food_uncertain_fact
3253  !! parameter. Thus, the expected *raw* food gain (in the `do`-function) is
3254  !! based on the past memory whereas the probability of capture is based
3255  !! on the latest perception experience.
3256  if ( this_agent%has_food() ) then
3257  expected_food_item_distance = this_agent%perceive_food%get_meandist()
3258  else
3259  ! TODO: add average food distances to perception memory
3260  expected_food_item_distance = expected_food_item%visibility() * &
3261  dist_expect_food_uncertain_fact
3262  end if
3263 
3264  expected_food_item_prob_capture = &
3265  expected_food_item%capture_probability( &
3266  distance=expected_food_item_distance )
3267 
3268  !> Third, the expected food gain corrected for fitting into the agent's
3269  !! current stomach (and subtracting capture cost) is obtained by
3270  !! the_body::condition::food_fitting(). It is then weighted by the
3271  !! expected capture probability. Note that the probability of capture
3272  !! (weighting factor) is calculated based on the current perception
3273  !! (see above), but the travel cost is based on the actual expected
3274  !! \%distance (see the_behaviour::walk_random::expectancies_calculate()
3275  !! for a similar procedure).
3276  expected_food_item_gain_fits = &
3277  this_agent%food_fitting( this%expected_food_gain, this%distance ) &
3278  * expected_food_item_prob_capture
3279 
3280  !> **Stomach content**: the perception override value for the stomach
3281  !! content is obtained incrementing the current stomach contents by
3282  !! the nonzero expected food gain, adjusting also for the digestion
3283  !! decrement (the_body::stomach_emptify_backend()).
3284  agent_stomach = this_agent%get_stom_content()
3285  perception_override_stomach = &
3286  max( zero, &
3287  agent_stomach - stomach_emptify_backend(agent_stomach) + &
3288  expected_food_item_gain_fits )
3289 
3290  !> **Body mass**: the **body mass** perception override is obtained by
3291  !! incrementing (or decrementing if the expected food gain is negative)
3292  !! the current body mass by the expected food gain and also subtracting
3293  !! the cost of living component.
3294  perception_override_bodymass = &
3295  max( zero, &
3296  this_agent%get_mass() - &
3297  this_agent%living_cost() + &
3298  expected_food_item_gain_fits )
3299 
3300  !> **Energy**: The fake perception values for the energy reserves
3301  !! (`energy_override_perc`) using the `the_body::energy_reserve()`
3302  !! procedure.
3303  perception_override_energy = energy_reserve( perception_override_bodymass,&
3304  this_agent%length() )
3305 
3306  !> **Direct food perception**: override is based on the current count
3307  !! of the food items in the perception object.
3308  !! @note Thus, the prediction of the food gain and stomach contents
3309  !! (see above) are based on a lower value that results from
3310  !! competition with the target conspecific. However, predicted
3311  !! perception of the general food availability is based on the
3312  !! current unmodified "objective" value.
3313  perception_override_food_dir = real( &
3314  this_agent%perceive_food%get_count(), srp)
3315 
3316  !> ##### Fake perception of predation risk #####
3317  !> **Predation risk**: finally, fake perceptions of predation risk are
3318  !! obtained from the values calculated in the `do` procedure:
3319  !! the_behaviour::approach_conspec::expected_pred_dir_risk and
3320  !! the_behaviour::approach_conspec::expected_predation_risk.
3321  perception_override_pred_dir = this%expected_pred_dir_risk
3322  perception_override_predator = this%expected_predation_risk
3323 
3324  !> #### Calculate motivation expectancies ####
3325  !> The next step is to calculate the motivational expectancies using the
3326  !! fake perceptions to override the default (actual agent's) values.
3327  !> At this stage, first, calculate motivation values resulting from the
3328  !! behaviour done (the_behaviour::approach_conspec::do_this()) at the
3329  !! previous steps:
3330  !! - what would be the motivation values *if* the agent does perform
3331  !! the_behaviour::approach_conspec?
3332  !! .
3333  !! Technically, this is done by calling the **neuronal
3334  !! response function**, `percept_components_motiv::motivation_components()`
3335  !! method, for each of the motivational states with `perception_override_`
3336  !! dummy parameters overriding the default values.
3337  !! Here is the list of the fake overriding perceptions for the
3338  !! `the_behaviour::approach_conspec` behaviour:
3339  !! - `perception_override_food_dir`
3340  !! - `perception_override_pred_dir`
3341  !! - `perception_override_predator`
3342  !! - `perception_override_stomach`
3343  !! - `perception_override_bodymass`
3344  !! - `perception_override_energy`
3345  !! .
3346  ! @note **Expectancy** assessment for **hunger** motivation, using
3347  ! `PERCEPT_COMPONENTS_MOTIV`-bound procedure with intent[in] for
3348  ! `this_agent` now.
3349  call this%expectancy%hunger%percept_component%motivation_components &
3350  (this_agent, &
3351  ! Parameters:: Boolean G x P matrices:
3352  param_gp_matrix_light = light_hunger_genotype_neuronal, &
3353  param_gp_matrix_depth = depth_hunger_genotype_neuronal, &
3354  param_gp_matrix_food_dir = foodcount_hunger_genotype_neuronal, &
3355  param_gp_matrix_food_mem = food_mem_hunger_genotype_neuronal, &
3356  param_gp_matrix_conspec = conspcount_hunger_genotype_neuronal, &
3357  param_gp_matrix_pred_dir = pred_direct_hunger_genotype_neuronal, &
3358  param_gp_matrix_predator = pred_meancount_hunger_genotype_neuronal, &
3359  param_gp_matrix_stomach = stom_hunger_genotype_neuronal, &
3360  param_gp_matrix_bodymass = bodymass_hunger_genotype_neuronal, &
3361  param_gp_matrix_energy = energy_hunger_genotype_neuronal, &
3362  param_gp_matrix_age = age_hunger_genotype_neuronal, &
3363  param_gp_matrix_reprfac = reprfac_hunger_genotype_neuronal, &
3364  ! Parameters :: G x P variances:
3365  param_gerror_cv_light = light_hunger_genotype_neuronal_gerror_cv, &
3366  param_gerror_cv_depth = depth_hunger_genotype_neuronal_gerror_cv, &
3367  param_gerror_cv_food_dir = foodcount_hunger_genotype_neuronal_gerror_cv,&
3368  param_gerror_cv_food_mem = food_mem_hunger_genotype_neuronal_gerror_cv, &
3369  param_gerror_cv_conspec = conspcount_hunger_genotype_neuronal_gerror_cv,&
3370  param_gerror_cv_pred_dir = pred_direct_hunger_genotype_neuronal_gerror_cv,&
3371  param_gerror_cv_predator = pred_meancount_hunger_genotype_neuronal_gerror_cv,&
3372  param_gerror_cv_stomach = stom_hunger_genotype_neuronal_gerror_cv, &
3373  param_gerror_cv_bodymass = bodymass_hunger_genotype_neuronal_gerror_cv, &
3374  param_gerror_cv_energy = energy_hunger_genotype_neuronal_gerror_cv, &
3375  param_gerror_cv_age = age_hunger_genotype_neuronal_gerror_cv, &
3376  param_gerror_cv_reprfac = reprfac_hunger_genotype_neuronal_gerror_cv, &
3377  ! Real agent perception components are now substituted by the *fake*
3378  ! values resulting from executing this behaviour (`do_this` method).
3379  ! This is repeated for all the motivations: *hunger*,
3380  ! *passive avoidance,* *fear state* etc.
3381  perception_override_food_dir = perception_override_food_dir, &
3382  perception_override_pred_dir = perception_override_pred_dir, &
3383  perception_override_predator = perception_override_predator, &
3384  perception_override_stomach = perception_override_stomach, &
3385  perception_override_bodymass = perception_override_bodymass, &
3386  perception_override_energy = perception_override_energy &
3387  )
3388  !> Real agent perception components are now substituted by the *fake*
3389  !! values resulting from executing this behaviour (`approach::do_this()`
3390  !! method). This is repeated for all the motivations: *hunger*,
3391  !! *passive avoidance,* *fear state* etc. These optional **override
3392  !! parameters** are substituted by the "fake" values.
3393 
3394  ! @note **Expectancy** assessment for **fear_defence** motivation,
3395  ! using `PERCEPT_COMPONENTS_MOTIV`-bound procedure with intent[in]
3396  ! for `this_agent` now.
3397  call this%expectancy%fear_defence%percept_component%motivation_components &
3398  (this_agent, &
3399  ! Parameters:: Boolean G x P matrices:
3400  param_gp_matrix_light = light_actv_avoid_genotype_neuronal, &
3401  param_gp_matrix_depth = depth_actv_avoid_genotype_neuronal, &
3402  param_gp_matrix_food_dir = foodcount_actv_avoid_genotype_neuronal, &
3403  param_gp_matrix_food_mem = food_mem_actv_avoid_genotype_neuronal, &
3404  param_gp_matrix_conspec = conspcount_actv_avoid_genotype_neuronal, &
3405  param_gp_matrix_pred_dir = pred_direct_actv_avoid_genotype_neuronal, &
3406  param_gp_matrix_predator = pred_meancount_actv_avoid_genotype_neuronal, &
3407  param_gp_matrix_stomach = stom_actv_avoid_genotype_neuronal, &
3408  param_gp_matrix_bodymass = bodymass_actv_avoid_genotype_neuronal, &
3409  param_gp_matrix_energy = energy_actv_avoid_genotype_neuronal, &
3410  param_gp_matrix_age = age_actv_avoid_genotype_neuronal, &
3411  param_gp_matrix_reprfac = reprfac_actv_avoid_genotype_neuronal, &
3412  ! Parameters :: G x P variances:
3413  param_gerror_cv_light = light_actv_avoid_genotype_neuronal_gerror_cv, &
3414  param_gerror_cv_depth = depth_actv_avoid_genotype_neuronal_gerror_cv, &
3415  param_gerror_cv_food_dir = foodcount_actv_avoid_genotype_neuronal_gerror_cv,&
3416  param_gerror_cv_food_mem = food_mem_actv_avoid_genotype_neuronal_gerror_cv, &
3417  param_gerror_cv_conspec = conspcount_actv_avoid_genotype_neuronal_gerror_cv,&
3418  param_gerror_cv_pred_dir = pred_direct_actv_avoid_genotype_neuronal_gerror_cv,&
3419  param_gerror_cv_predator = pred_meancount_actv_avoid_genotype_neuronal_gerror_cv,&
3420  param_gerror_cv_stomach = stom_actv_avoid_genotype_neuronal_gerror_cv, &
3421  param_gerror_cv_bodymass = bodymass_actv_avoid_genotype_neuronal_gerror_cv,&
3422  param_gerror_cv_energy = energy_actv_avoid_genotype_neuronal_gerror_cv,&
3423  param_gerror_cv_age = age_actv_avoid_genotype_neuronal_gerror_cv, &
3424  param_gerror_cv_reprfac = reprfac_actv_avoid_genotype_neuronal_gerror_cv,&
3425  ! @note Real agent perception components are now **substituted**
3426  ! by the **fake** values resulting from executing this
3427  ! behaviour (`do_this` method).
3428  perception_override_food_dir = perception_override_food_dir, &
3429  perception_override_pred_dir = perception_override_pred_dir, &
3430  perception_override_predator = perception_override_predator, &
3431  perception_override_stomach = perception_override_stomach, &
3432  perception_override_bodymass = perception_override_bodymass, &
3433  perception_override_energy = perception_override_energy &
3434  )
3435 
3436  ! @note **Expectancy** assessment for **reproduction** motivation,
3437  ! using `PERCEPT_COMPONENTS_MOTIV`-bound procedure with intent[in]
3438  ! for `this_agent` now.
3439  call this%expectancy%reproduction%percept_component%motivation_components &
3440  (this_agent, &
3441  ! Parameters:: Boolean G x P matrices:
3442  param_gp_matrix_light = light_reproduce_genotype_neuronal, &
3443  param_gp_matrix_depth = depth_reproduce_genotype_neuronal, &
3444  param_gp_matrix_food_dir = foodcount_reproduce_genotype_neuronal, &
3445  param_gp_matrix_food_mem = food_mem_reproduce_genotype_neuronal, &
3446  param_gp_matrix_conspec = conspcount_reproduce_genotype_neuronal, &
3447  param_gp_matrix_pred_dir = pred_direct_reproduce_genotype_neuronal, &
3448  param_gp_matrix_predator = pred_meancount_reproduce_genotype_neuronal, &
3449  param_gp_matrix_stomach = stom_reproduce_genotype_neuronal, &
3450  param_gp_matrix_bodymass = bodymass_reproduce_genotype_neuronal, &
3451  param_gp_matrix_energy = energy_reproduce_genotype_neuronal, &
3452  param_gp_matrix_age = age_reproduce_genotype_neuronal, &
3453  param_gp_matrix_reprfac = reprfac_reproduce_genotype_neuronal, &
3454  ! Parameters :: G x P variances:
3455  param_gerror_cv_light = light_reproduce_genotype_neuronal_gerror_cv, &
3456  param_gerror_cv_depth = depth_reproduce_genotype_neuronal_gerror_cv, &
3457  param_gerror_cv_food_dir = foodcount_reproduce_genotype_neuronal_gerror_cv,&
3458  param_gerror_cv_food_mem = food_mem_reproduce_genotype_neuronal_gerror_cv, &
3459  param_gerror_cv_conspec = conspcount_reproduce_genotype_neuronal_gerror_cv,&
3460  param_gerror_cv_pred_dir = pred_direct_reproduce_genotype_neuronal_gerror_cv,&
3461  param_gerror_cv_predator = pred_meancount_reproduce_genotype_neuronal_gerror_cv,&
3462  param_gerror_cv_stomach = stom_reproduce_genotype_neuronal_gerror_cv, &
3463  param_gerror_cv_bodymass = bodymass_reproduce_genotype_neuronal_gerror_cv,&
3464  param_gerror_cv_energy = energy_reproduce_genotype_neuronal_gerror_cv,&
3465  param_gerror_cv_age = age_reproduce_genotype_neuronal_gerror_cv, &
3466  param_gerror_cv_reprfac = reprfac_reproduce_genotype_neuronal_gerror_cv,&
3467  ! @note Real agent perception components are now **substituted**
3468  ! by the **fake** values resulting from executing this
3469  ! behaviour (`do_this` method).
3470  perception_override_food_dir = perception_override_food_dir, &
3471  perception_override_pred_dir = perception_override_pred_dir, &
3472  perception_override_predator = perception_override_predator, &
3473  perception_override_stomach = perception_override_stomach, &
3474  perception_override_bodymass = perception_override_bodymass, &
3475  perception_override_energy = perception_override_energy &
3476  )
3477 
3478  !> #### Calculate primary and final motivations ####
3479  !> Next, from the perceptual components calculated at the previous
3480  !! step we can obtain the **primary** and **final motivation** values by
3481  !! weighed summing.
3482  if (present(rescale_max_motivation)) then
3483  !> Here we can use global maximum motivation across all behaviours and
3484  !! perceptual components if it is provided, for rescaling.
3485  max_motivation = rescale_max_motivation
3486  else
3487  !> Or can rescale using local maximum value for this behaviour only.
3488  max_motivation = this%expectancy%max_perception()
3489  end if
3490 
3491  !> Transfer attention weights from the actor agent `this_agent` to the
3492  !! `this` behaviour component. So, we will now use the updated modulated
3493  !! attention weights of the agent rather than their default parameter
3494  !! values.
3495  call this%attention_transfer(this_agent)
3496 
3497  !> So the primary motivation values are calculated.
3498  call this%expectancy%motivation_primary_calc(max_motivation)
3499 
3500  !> Primary motivations are logged in the @ref intro_debug_mode "debug mode".
3501  call log_dbg( ltag_info // "Primary motivations: " // &
3502  "hunger: " // &
3503  tostr(this%expectancy%hunger%motivation_prim) // &
3504  ", fear_defence: " // &
3505  tostr(this%expectancy%fear_defence%motivation_prim) // &
3506  ", reproduce: " // &
3507  tostr(this%expectancy%reproduction%motivation_prim), &
3508  procname, modname )
3509 
3510  !> There is **no modulation** at this stage, so the final motivation
3511  !! values are the same as primary motivations.
3512  call this%expectancy%modulation_none()
3513 
3514  !> #### Calculate motivation expectancies ####
3515  !> Finally, calculate the finally **expected arousal level for this
3516  !! behaviour**. As in the GOS, the overall arousal is the maximum value
3517  !! among all motivation components.
3518  this%arousal_expected = this%expectancy%max_final()
3519 
3520  !> Log also the final expectancy value in the @ref intro_debug_mode
3521  !! "debug mode".
3522  call log_dbg( ltag_info // "Expectancy: " // tostr(this%arousal_expected),&
3523  procname, modname )
3524 
3525  !> Now as we know the expected arousal, we can choose the behaviour which
3526  !! would minimise this arousal level.
3527 
3529 
3530  !-----------------------------------------------------------------------------
3531  !> Initialise the **migrate** behaviour component to a zero state.
3532  elemental subroutine migrate_init_zero(this)
3533  class(migrate), intent(inout) :: this
3534 
3535  !> First init components from the base root class
3536  !! `the_behaviour::behaviour_base`.
3537  !> Mandatory label component that should be read-only.
3538  this%label = "MIGRATE"
3539  !> The execution status is always FALSE, can be reset to TRUE only when
3540  !! the behaviour unit is called to execution.
3541  this%is_active = .false.
3542 
3543  !> And the *expectancy* components.
3544  call this%expectancy%init()
3545  this%arousal_expected = 0.0_srp
3546 
3547  !> Abstract `MOVE` component.
3548  this%distance = missing
3549 
3550  !> Then init components of this specific behaviour component extended class.
3551  this%target_point = spatial(x=missing, y=missing, depth=missing)
3552  this%expected_cost_moving = missing
3553  this%expected_food_gain = missing
3554  this%expected_food_dir = missing
3555  this%expected_consp_number = unknown
3556  this%expected_pred_dir_risk = missing
3557  this%expected_predation_risk = missing
3558 
3559  end subroutine migrate_init_zero
3560 
3561  !-----------------------------------------------------------------------------
3562  !> The "do" procedure component of the behaviour element performs the
3563  !! behaviour without affecting the actor agent (the_agent) and the world
3564  !! (here food_item_eaten) which have intent(in), so it only can change
3565  !! the internal representation of the behaviour (the type to which this
3566  !! procedure is bound to, here `MIGRATE`).
3567  subroutine migrate_do_this( this, this_agent, target_env, &
3568  predict_window_food, predict_window_consp, predict_window_pred, &
3569  time_step_model )
3570  class(migrate), intent(inout) :: this
3571  !> @param[in] this_agent is the actor agent which eats the food item.
3572  class(appraisal), intent(in) :: this_agent
3573  !> @param[in] target_env the target environment the actor agent is going
3574  !! to (e)migrate into.
3575  class(environment), intent(in) :: target_env
3576  !> @param[in] predict_window_food optional size of the *food* prediction
3577  !! window, i.e. how many steps back in memory are used to
3578  !! calculate the predicted food gain. This parameter is limited
3579  !! by the maximum commondata::history_size_perception value of
3580  !! the perception memory history size.
3581  integer, optional, intent(in) :: predict_window_food
3582  !> @param[in] predict_window_consp optional size of the *conspecifics*
3583  !! prediction window, i.e. how many steps back in memory are
3584  !! used to calculate the predicted food gain. This parameter
3585  !! is limited by the maximum commondata::history_size_perception
3586  !! value of the perception memory history size.
3587  integer, optional, intent(in) :: predict_window_consp
3588  !> @param[in] predict_window_pred optional size of the *predator*
3589  !! prediction window, i.e. how many steps back in memory are
3590  !! used to calculate the predicted food gain. This parameter
3591  !! is limited by the maximum commondata::history_size_perception
3592  !! value of the perception memory history size.
3593  integer, optional, intent(in) :: predict_window_pred
3594  !> @param[in] time_step_model optional time step of the model, overrides
3595  !! the value calculated from the spatial data.
3596  integer, optional, intent(in) :: time_step_model
3597 
3598  ! Local copies of optionals.
3599  integer :: predict_window_food_here, predict_window_consp_here, &
3600  predict_window_pred_here, time_step_model_here
3601 
3602  ! Local copy of the body length of the agent
3603  real(SRP) :: agent_length
3604 
3605  ! - **WEIGHT_DIRECT** is the relative weight given to the immediate
3606  ! perception of predators over the predators counts in the memory stack.
3607  ! Obtained from global parameters
3608  ! (`commondata::predation_risk_weight_immediate`).
3609  real(SRP), parameter :: WEIGHT_DIRECT = predation_risk_weight_immediate
3610 
3611  !> ### Notable variables ###
3612  !> - **point_target_env** is the target point inside the target
3613  !! environment to which this agent is going to relocate.
3614  type(spatial) :: point_target_env
3615  !> - **distance_target** is the distance to the target environment
3616  real(SRP) :: distance_target
3617 
3618  !> - **mean_n_food_memory_old, mean_n_food_memory_new** are the average
3619  !! numbers of food items in the past memory window, the "older" and
3620  !! "newer" parts that are used to calculate the "older"
3621  !! @f$ \overline{f_1} @f$ and "newer" @f$ \overline{f_2} @f$
3622  !! values of food availability retrieved from the perception memory.
3623  !! Used in calculation of the the_behaviour::hope function.
3624  real(SRP) :: mean_n_food_memory_old, mean_n_food_memory_new
3625 
3626  !> - **mean_size_food_memory_old, mean_size_food_memory_new** are the
3627  !! average sizes of food items in the past memory window, the "older"
3628  !! and "newer" parts that are used to calculate the "older"
3629  !! @f$ \overline{f_1} @f$ and "newer" @f$ \overline{f_2} @f$
3630  !! values of food availability retrieved from the perception memory.
3631  !! Used in calculation of the the_behaviour::hope function.
3632  real(SRP) :: mean_size_food_memory_old, mean_size_food_memory_new
3633 
3634  !> - **food_gain_memory_old, food_gain_memory_new** are the "older"
3635  !! @f$ \overline{f_1} @f$ and "newer" @f$ \overline{f_2} @f$
3636  !! values of food availability retrieved from the perception memory.
3637  !! Used in calculation of the the_behaviour::hope function.
3638  real(SRP) :: food_gain_memory_old, food_gain_memory_new
3639 
3640  !> - **food_gain_memory_baseline** is the baseline value of the food gain
3641  !! retrieved from the memory, that is used to calculate the actual
3642  !! food gain expectancy value calculated from the hope function.
3643  real(SRP) :: food_gain_memory_baseline
3644 
3645  !> - **mean_n_pred_memory_old, mean_n_pred_memory_new** are the average
3646  !! numbers of predators in the past perception memory window.
3647  real(SRP) :: mean_n_pred_memory_old, mean_n_pred_memory_new
3648 
3649  !> - **pred_current** is the current estimate of the general predation
3650  !! risk.
3651  !! .
3652  real(SRP) :: pred_current
3653 
3654  ! PROCNAME is the procedure name for logging and debugging.
3655  character(len=*), parameter :: PROCNAME = "(migrate_do_this)"
3656 
3657  !> ### Implementation details ###
3658  !> #### Checks and preparations ####
3659  !> Check optional parameter for the food perception memory window. If
3660  !! the `predict_window_food` dummy parameter is not provided, its default
3661  !! value is its default value is the whole memory stack
3662  !! commondata::history_size_perception.
3663  if (present(predict_window_food)) then
3664  predict_window_food_here = predict_window_food
3665  else
3666  predict_window_food_here = history_size_perception
3667  end if
3668 
3669  !> Check optional parameter for the conspecifics perception
3670  !! memory window. If the `predict_window_consp` dummy parameter is not
3671  !! provided, its default value is the whole memory stack
3672  !! commondata::history_size_perception.
3673  if (present(predict_window_consp)) then
3674  predict_window_consp_here= predict_window_consp
3675  else
3676  predict_window_consp_here = history_size_perception
3677  end if
3678 
3679  !> Check optional parameter for the general predation risk perception
3680  !! memory window. If the `predict_window_pred` dummy parameter is not
3681  !! provided, its default value is the whole memory stack
3682  !! commondata::history_size_perception.
3683  if (present(predict_window_pred)) then
3684  predict_window_pred_here= predict_window_pred
3685  else
3686  predict_window_pred_here = history_size_perception
3687  end if
3688 
3689  !> Check optional time step parameter. If unset, use global
3690  !! `commondata::global_time_step_model_current`.
3691  if (present(time_step_model)) then
3692  time_step_model_here = time_step_model
3693  else
3694  time_step_model_here = global_time_step_model_current
3695  end if
3696 
3697  ! Agent length is local variable to avoid multiple calls to get_length().
3698  agent_length = this_agent%get_length()
3699 
3700  !> #### Calculate the distance towards the target environment ####
3701  !> The distance towards the target environment (and the target point in
3702  !! this environment) is defined as the minimum distance towards
3703  !! all segments limiting this environment in the 2D X x Y projection
3704  !! @warning This is valid only for the simple box environment
3705  !! implementation. Generally, it equals to the minimum
3706  !! distance across all the polyhedrons limiting the target
3707  !! environment).
3708  !!
3709  !! The target point for the migrating agent within the target
3710  !! environment is then not just the edge of the target environment, but
3711  !! some point penetrating inside to some distance defined by the parameter
3712  !! commondata::migrate_dist_penetrate_offset (in units of the agent's
3713  !! body length). The the_environment::environment::nearest_target()
3714  !! method is used to find the closest point in the target environment and
3715  !! the (smallest) distance towards this environment, these values are
3716  !! adjusted automatically for the offset parameter in the procedure call.
3717  call target_env%nearest_target( outside_object=this_agent, &
3718  offset_into=agent_length * &
3719  migrate_dist_penetrate_offset, &
3720  point_spatial = point_target_env, &
3721  point_dist = distance_target )
3722 
3723  !> The distance value returned from the
3724  !! the_environment::environment::nearest_target() is saved into the
3725  !! this\%distance data component and the target point (of class
3726  !! the_environment::spatial) is saved into the this\%target_point
3727  !! data component.
3728  this%distance = distance_target
3729  this%target_point = point_target_env
3730 
3731  !> Check if the distance to the target environment exceeds the
3732  !! migration travel maximum value, set as commondata::migrate_dist_max_step
3733  !! body sizes of the agent.
3734  if (this%distance > agent_length * migrate_dist_max_step ) then
3735  !> - So far nothing is done in such a case except logging a warning.
3736  !! Note that in the_behaviour::migrate::migrate_do_execute() method,
3737  !! agents that had the distance exceeding this threshold do a random
3738  !! correlated walk towards the target environment, but do not enter
3739  !! it.
3740  !! .
3741  call log_dbg( ltag_warn // "Migration travel distance exceeds big " // &
3742  "threshold in " // procname // " for the agent " // &
3743  this_agent%individ_label() // ". Agent length: " // &
3744  tostr(agent_length) // ", migration distance: " // &
3745  tostr(this%distance), procname, modname )
3746  end if
3747 
3748  !> #### Calculate expected cost of the swimming ####
3749  !> The expected cost of swimming in the random walk depends on the walk
3750  !! distance and is calculated using the the_body::condition::cost_swim()
3751  !! assuming *laminar* flow (laminar flow is due to normal relatively slow
3752  !! swimming pattern).
3753  this%expected_cost_moving = &
3754  this_agent%cost_swim( distance=this%distance, &
3755  exponent=swimming_cost_exponent_laminar )
3756 
3757  !> #### Calculate expected food gain ####
3758  !> The expected food gain resulting from emigrating into a completely
3759  !! different novel habitat cannot be assessed based only on current
3760  !! perception because the agent has virtually no information (i.e. no
3761  !! perception) about this habitat yet. The target habitat is a novel
3762  !! environment about which the agent has absolutely no local knowledge.
3763  !! A mechanism based on the **hope function** (the_behaviour::hope())
3764  !! is used here. Specifically, the hope function calculates the expected
3765  !! food gain in the target novel habitat based on the ratio of the
3766  !! "newer" to "older" food gains in the perceptual memory of the agent.
3767  !!
3768  !> Calculation of the "older" and "newer" average food gain values from
3769  !! the memory involves several steps. First, average *number* of food
3770  !! items and the average *size* of the food items in the above two halves
3771  !! of the memory stack is calculated using the
3772  !! the_neurobio::memory_perceptual::get_food_mean_n_split() and
3773  !! the_neurobio::memory_perceptual::get_food_mean_size_split() procedures.
3774  !! (Note that the `split_val` parameter to this procedure is not
3775  !! provided so the default 1/2 split is used.)
3776  call this_agent%memory_stack%get_food_mean_n_split( &
3777  window = predict_window_food_here, &
3778  older = mean_n_food_memory_old, &
3779  newer = mean_n_food_memory_new )
3780 
3781  call this_agent%memory_stack%get_food_mean_size_split( &
3782  window = predict_window_food_here, &
3783  older = mean_size_food_memory_old, &
3784  newer = mean_size_food_memory_new )
3785 
3786  !> Second, the values of the "old" and "new" *food gain* used to calculate
3787  !! the expectations are obtained by weighting the respective average mass
3788  !! of the food item by the average number of food items if this number is
3789  !! less than 1 or 1 (i.e. unweighted) if their average number is higher.
3790  ! Latex formulas don't render correctly in Doxygen
3791  ! @f[
3792  ! \left\{\begin{matrix}
3793  ! f_{1}=\overline{m_1} \cdot \overline{n_1}, & \overline{n_1}<1; \\
3794  ! f_{1}=\overline{m_1}, & \overline{n_1} \geq 1
3795  ! \end{matrix}\right
3796  ! @f]
3797  ! @f[
3798  ! \left\{\begin{matrix}
3799  ! f_{2}=\overline{m_2} \cdot \overline{n_2}, & \overline{n_2}<1; \\
3800  ! f_{2}=\overline{m_2}, & \overline{n_2} \geq 1
3801  ! \end{matrix}\right.
3802  ! @f]
3803  !> @image html img_doxygen_migrate_formula_1.svg
3804  !! @image latex img_doxygen_migrate_formula_1.eps "" width=14cm
3805  !> where @f$ \overline{m_1} @f$ is the average mass of the food items
3806  !! and @f$ \overline{n_1} @f$ is the average number of food items
3807  !! in the "older" half of the perceptual memory stack and
3808  !! @f$ \overline{m_2} @f$ is the average mass of the food items
3809  !! and @f$ \overline{n_2} @f$ is the average number of food items
3810  !! in the "newer" half of the memory stack.
3811  !!
3812  !! Thus, if the agent had some relatively poor perceptual history of
3813  !! encountering food items, so that the average *number* of food items
3814  !! is fractional < 1 (e.g. average number 0.5, meaning that it has seen a
3815  !! single food item approximately every other time step), the food gain is
3816  !! weighted by this fraction (0.5). If, on the other hand, the agent had
3817  !! more than one food items at each time step previously, the average food
3818  !! item size is unweighted (weight=1.0). This conditional weighting
3819  !! reflects the fact that it is not possible to eat more than
3820  !! one food item at a time in this model version.
3821  !! @note A similar expectancy assessment mechanism is used in the
3822  !! assessment of the food gain expectancy for the
3823  !! the_behaviour::walk_random behaviour component
3824  !! the_behaviour::walk_random_do_this().
3825  food_gain_memory_old = size2mass_food(mean_size_food_memory_old) * &
3826  within( mean_n_food_memory_old, 0.0_srp, 1.0_srp )
3827  food_gain_memory_new = size2mass_food(mean_size_food_memory_new) * &
3828  within( mean_n_food_memory_new, 0.0_srp, 1.0_srp )
3829 
3830  ! Produce diagnostic logger message in the @ref intro_debug_mode DEBUG mode.
3831  call log_dbg( ltag_info // "Mean number of old and new " // &
3832  "food items in memory: " // &
3833  tostr(mean_n_food_memory_old) // &
3834  ":" // tostr(mean_n_food_memory_new), &
3835  procname, modname )
3836  call log_dbg( ltag_info // "Mean size of old and new " // &
3837  "food items in memory: " // &
3838  tostr(mean_size_food_memory_old) &
3839  // ":" // tostr(mean_size_food_memory_new), &
3840  procname, modname )
3841  call log_dbg( ltag_info // "Food gain old and new " // &
3842  "food items in memory: " // tostr(food_gain_memory_old) // &
3843  ":" // tostr(food_gain_memory_new), &
3844  procname, modname )
3845  log_ratio_check: if (is_debug) then
3846  block
3847  real(SRP) :: debug_ratio
3848  ! @warning The logic of the `ìf` condition should be the same as
3849  ! in the the_behaviour::hope() function.
3850  if (food_gain_memory_old < zero) then
3851  debug_ratio = migrate_food_gain_ratio_zero_hope
3852  elseif (food_gain_memory_old < zero .and. &
3853  food_gain_memory_new < zero) then
3854  debug_ratio = 1.0_srp
3855  else
3856  debug_ratio = food_gain_memory_new / food_gain_memory_old
3857  end if
3858  call log_dbg( ltag_info // "Food gain hope ratio (new/old): " // &
3859  tostr(debug_ratio), procname, modname )
3860  end block
3861  end if log_ratio_check
3862 
3863  !> The next step is to calculate the baseline food gain @f$ f_0 @f$,
3864  !! against which the expectancy based on the the_behaviour::hope() function
3865  !! is evaluated. This baseline value is obtained by weighting the average
3866  !! mass of the food items in the whole memory stack @f$ \overline{m} @f$
3867  !! by their average number @f$ \overline{n} @f$ provided this number
3868  !! is *n<1* as above:
3869  ! Latex formula below doesn't render well:
3870  ! @f[
3871  ! \left\{\begin{matrix}
3872  ! f_0=\overline{m} \cdot \overline{n}, & \overline{n}<1; \\
3873  ! f_0=\overline{m}, & \overline{n} \geq 1
3874  ! \end{matrix}\right.
3875  ! @f]
3876  !> @image html img_doxygen_migrate_formula_2.svg
3877  !! @image latex img_doxygen_migrate_formula_2.eps "" width=14cm
3878  !! This baseline value is then weighted by the subjective probability
3879  !! of food item capture that is calculated based on the memory
3880  !! the_neurobio::perception::food_probability_capture_subjective().
3881  food_gain_memory_baseline = &
3882  size2mass_food( &
3883  this_agent%memory_stack%get_food_mean_size( &
3884  predict_window_food_here)) * &
3885  within( &
3886  this_agent%memory_stack%get_food_mean_n(predict_window_food_here),&
3887  0.0_srp, 1.0_srp ) * &
3888  this_agent%food_probability_capture_subjective( &
3889  predict_window_food_here, time_step_model_here )
3890 
3891  !> Finally, the the_behaviour::hope() function is called with the above
3892  !! estimates for the baseline food gain, its "older" and "newer" values.
3893  !! The *zero hope ratio* and the *maximum hope* parameters are obtained from
3894  !! commondata::migrate_food_gain_ratio_zero_hope and
3895  !! commondata::migrate_food_gain_maximum_hope parameter constants.
3896  !! @image html img_doxygen_migrate_hope_food_nonpar.svg "The hope function"
3897  !! @image latex img_doxygen_migrate_hope_food_nonpar.eps "The hope function" width=14cm
3898  this%expected_food_gain = hope( food_gain_memory_baseline, &
3899  food_gain_memory_old, &
3900  food_gain_memory_new, &
3901  migrate_food_gain_ratio_zero_hope, &
3902  migrate_food_gain_maximum_hope )
3903 
3904  ! Produce diagnostic logger message in the @ref intro_debug_mode DEBUG mode.
3905  call log_dbg( ltag_info // "Expected food gain from hope function: " // &
3906  tostr(this%expected_food_gain) // ", with baseline " // &
3907  "value: " // tostr(food_gain_memory_baseline), &
3908  procname, modname )
3909 
3910  !> #### Calculate expected food items perception ####
3911  !> A similar, although simpler, procedure based on the the_behaviour::hope
3912  !! function as above is used to calculate the expected *number* of food
3913  !! items perceived in the target novel habitat.
3914  !!
3915  !! Here, the baseline value @f$ f_0 @f$ is the current number of food
3916  !! items in the food perception object, and the historical ratio
3917  !! @f$ \varrho @f$ is calculated as the mean number of food items in the
3918  !! old to new memory parts:
3919  !! @f[ \varrho = \frac{\overline{n_2}}{\overline{n_1}} . @f]
3920  !! The *zero hope ratio* and the *maximum hope* parameters are also
3921  !! obtained from commondata::migrate_food_gain_ratio_zero_hope and
3922  !! commondata::migrate_food_gain_maximum_hope parameter constants.
3923  this%expected_food_dir = &
3924  hope( real(this_agent%perceive_food%get_count(),srp), &
3925  mean_n_food_memory_old, &
3926  mean_n_food_memory_new, &
3927  migrate_food_gain_ratio_zero_hope, &
3928  migrate_food_gain_maximum_hope )
3929 
3930  ! Produce diagnostic logger message in the @ref intro_debug_mode DEBUG mode.
3931  call log_dbg( ltag_info // "Expected food perception from hope " // &
3932  "function: " // tostr(this%expected_food_dir ), &
3933  procname, modname )
3934 
3935  !> #### Calculate expected predation risks ####
3936  !> **Direct predation** risk is assumed to be zero for migration.
3937  this%expected_pred_dir_risk = 0.0_srp
3938 
3939  !> **General predation** risk expectancy is not possible to determine
3940  !! because there is no local perception of the target novel environment
3941  !! yet. Therefore, its assessment is based on the the_behaviour::hope()
3942  !! function, just as the expected food gain.
3943  !! - First, calculate the older and newer predation averages from the
3944  !! memory stack;
3945  call this_agent%memory_stack%get_pred_mean_split( &
3946  window = predict_window_pred_here, &
3947  older = mean_n_pred_memory_old, &
3948  newer = mean_n_pred_memory_new )
3949 
3950  !> - Second, calculate the *current* general risk of predation, based
3951  !! on the local perception. This is done calling the
3952  !! the_neurobio::predation_risk_backend() function. This current risk
3953  !! serves as a baseline value (@f$ f_0 @f$) for calculation of the
3954  !! general risk in the target novel environment.
3955  pred_current = &
3956  predation_risk_backend( &
3957  pred_count=this_agent%perceive_predator%get_count(), &
3958  pred_memory_mean=this_agent%memory_stack%get_pred_mean( &
3959  predict_window_pred_here),&
3960  weight_direct=weight_direct )
3961 
3962  !> - Third, the expectancy value of general predation risk in the target
3963  !! novel environment is obtained via the the_behaviour::hope() function.
3964  !! If the general predation risk is increasing in the local environment,
3965  !! its expectancy in the novel environment diminishes, if the risk is
3966  !! reducing over time in the local environment, the novel environment
3967  !! expectancy increases. The hope grid values for the general predation
3968  !! hope function are defined by the commondata::migrate_predator_zero_hope
3969  !! and commondata::migrate_predator_maximum_hope parameter constants.
3970  this%expected_predation_risk = hope( pred_current, &
3971  mean_n_pred_memory_old, &
3972  mean_n_pred_memory_new, &
3973  migrate_predator_zero_hope, &
3974  migrate_predator_maximum_hope )
3975 
3976  !> #### Calculate expected conspecifics ####
3977  !> The expected number of conspecifics in the target environment is
3978  !! calculated as an average retrieved from the memory stack with the
3979  !! memory window defined by `predict_window_consp_here`.
3980  this%expected_consp_number = nint( &
3981  this_agent%memory_stack%get_consp_mean_n(predict_window_consp_here) )
3982 
3983  call log_dbg( ltag_info // "Expected N of conspecifics: " // &
3984  tostr(this%expected_consp_number), procname, modname )
3985 
3986  end subroutine migrate_do_this
3987 
3988  !-----------------------------------------------------------------------------
3989  !> `the_behaviour::migrate::expectancies_calculate()` (re)calculates
3990  !! motivations from fake expected perceptions following from the procedure
3991  !! `migrate::do_this()`.
3992  subroutine migrate_motivations_expect(this, this_agent, target_env, &
3993  predict_window_food, predict_window_consp, predict_window_pred, &
3994  time_step_model, rescale_max_motivation)
3995  class(migrate), intent(inout) :: this
3996  !> @param[in] this_agent is the actor agent which is going to migrate.
3997  class(appraisal), intent(in) :: this_agent
3998  !> @param[in] target_env the target environment the actor agent is going
3999  !! to (e)migrate into.
4000  class(environment), intent(in) :: target_env
4001  !> @param[in] predict_window_food optional size of the *food* prediction
4002  !! window, i.e. how many steps back in memory are used to
4003  !! calculate the predicted food gain. This parameter is limited
4004  !! by the maximum commondata::history_size_perception value of
4005  !! the perception memory history size.
4006  integer, optional, intent(in) :: predict_window_food
4007  !> @param[in] predict_window_consp optional size of the *conspecifics*
4008  !! prediction window, i.e. how many steps back in memory are
4009  !! used to calculate the predicted food gain. This parameter
4010  !! is limited by the maximum commondata::history_size_perception
4011  !! value of the perception memory history size.
4012  integer, optional, intent(in) :: predict_window_consp
4013  !> @param[in] predict_window_pred optional size of the *predator*
4014  !! prediction window, i.e. how many steps back in memory are
4015  !! used to calculate the predicted food gain. This parameter
4016  !! is limited by the maximum commondata::history_size_perception
4017  !! value of the perception memory history size.
4018  integer, optional, intent(in) :: predict_window_pred
4019  !> @param[in] time_step_model optional time step of the model, overrides
4020  !! the value calculated from the spatial data.
4021  integer, optional, intent(in) :: time_step_model
4022  !> @param[in] rescale_max_motivation optional maximum motivation value for
4023  !! rescaling all motivational components for comparison
4024  !! across all motivation and perceptual components and behaviour
4025  !! units.
4026  real(SRP), optional, intent(in) :: rescale_max_motivation
4027 
4028  ! PROCNAME is the procedure name for logging and debugging.
4029  character(len=*), parameter :: PROCNAME = "(migrate_motivations_expect)"
4030 
4031  ! Local copies of optionals.
4032  integer :: predict_window_food_here, predict_window_consp_here, &
4033  predict_window_pred_here, time_step_model_here
4034 
4035  ! Local variables
4036  real(SRP) :: max_motivation ! Local max. over all motivation components.
4037 
4038  ! Current stomach contents of the agent.
4039  real(SRP) :: agent_stomach
4040 
4041  ! Expected food item that is used in the calculations, its properties are
4042  ! based on the average food items that the agent perceives below.
4043  type(food_item) :: expected_food_item
4044 
4045  real(SRP) :: expected_food_item_distance
4046 
4047  !> Expected food gain that is fitting into the stomach of the agent.
4048  real(SRP) :: expected_food_item_gain_fits
4049 
4050  !> The probability of capture of the expected food object.
4051  real(SRP) :: expected_food_item_prob_capture
4052 
4053  !> ### Notable local variables ###
4054  !> #### Perception overrides ####
4055  !> - **perception_override_conspec** is the expected number of
4056  !! conspecifics.
4057  real(SRP) :: perception_override_conspec
4058 
4059  !> - **perception_override_pred_dir** is the expected direct
4060  !! predation risk.
4061  real(SRP) :: perception_override_pred_dir
4062  !> - **perception_override_predator** is the expected general predation
4063  !! risk, that is based on a weighting of the current predation and
4064  !! predation risk from the memory stack.
4065  real(SRP) :: perception_override_predator
4066  !> - **perception_override_food_dir** is the expected number of food items
4067  !! in perception.
4068  real(SRP) :: perception_override_food_dir
4069  !> - **perception_override_stomach** is the expected stomach contents
4070  !! as a consequence of random walk.
4071  real(SRP) :: perception_override_stomach
4072  !> - **perception_override_bodymass** is the expected body mass as a
4073  !! consequence of the random walk.
4074  real(SRP) :: perception_override_bodymass
4075  !> - **perception_override_energy** is the expected energy reserves
4076  !! as a consequence of the escape movement. Calculated from the body
4077  !! mass and weight.
4078  !! .
4079  real(SRP) :: perception_override_energy
4080 
4081  !> ### Implementation details ###
4082  !> #### Checks and preparations ####
4083  !> Check optional parameter for the food perception memory window. If
4084  !! the `predict_window_food` dummy parameter is not provided, its default
4085  !! value is its default value is the whole memory stack
4086  !! commondata::history_size_perception.
4087  if (present(predict_window_food)) then
4088  predict_window_food_here = predict_window_food
4089  else
4090  predict_window_food_here = history_size_perception
4091  end if
4092 
4093  !> Check optional parameter for the conspecifics perception
4094  !! memory window. If the `predict_window_consp` dummy parameter is not
4095  !! provided, its default value is the whole memory stack
4096  !! commondata::history_size_perception.
4097  if (present(predict_window_consp)) then
4098  predict_window_consp_here= predict_window_consp
4099  else
4100  predict_window_consp_here = history_size_perception
4101  end if
4102 
4103  !> Check optional parameter for the general predation risk perception
4104  !! memory window. If the `predict_window_pred` dummy parameter is not
4105  !! provided, its default value is the whole memory stack
4106  !! commondata::history_size_perception.
4107  if (present(predict_window_pred)) then
4108  predict_window_pred_here= predict_window_pred
4109  else
4110  predict_window_pred_here = history_size_perception
4111  end if
4112 
4113  !> Check optional time step parameter. If unset, use global
4114  !! commondata::global_time_step_model_current.
4115  if (present(time_step_model)) then
4116  time_step_model_here = time_step_model
4117  else
4118  time_step_model_here = global_time_step_model_current
4119  end if
4120 
4121  !> #### Call do_this ####
4122  !> As the first step, we use the **do**-procedure `migrate::do_this()`
4123  !! => `the_behaviour::walk_random_do_this()` to perform the behaviour desired
4124  !! without changing either the agent or its environment, obtaining the
4125  !! **subjective** values of the `this` behaviour components that later feed
4126  !! into the motivation **expectancy** functions:
4127  !! - `perception_override_food_dir`
4128  !! - `perception_override_conspec`
4129  !! - `perception_override_pred_dir`
4130  !! - `perception_override_predator`
4131  !! - `perception_override_stomach`
4132  !! - `perception_override_bodymass`
4133  !! - `perception_override_energy`
4134  !! .
4135  call this%do_this( this_agent=this_agent, &
4136  target_env=target_env, &
4137  predict_window_food=predict_window_food_here, &
4138  predict_window_consp=predict_window_consp_here, &
4139  predict_window_pred=predict_window_pred_here, &
4140  time_step_model=time_step_model_here )
4141 
4142  !> #### Calculate expected (fake) perceptions ####
4143  !> First, create a fake food item with the spatial position identical to
4144  !! that of the agent. The position is used to calculate the current
4145  !! illumination and therefore visual range. The cost(s) are calculated
4146  !! providing explicit separate distance parameter. The size of the
4147  !! food item is obtained from the expected food gain by the reverse
4148  !! calculation function the_environment::mass2size_food().
4149  !! Standard `make` method for the food item class is used.
4150  call expected_food_item%make(location=this_agent%location(), &
4151  size=mass2size_food(this%expected_food_gain),&
4152  iid=unknown )
4153 
4154  !> Second, calculate the **probability of capture** of this expected food
4155  !! item. The probability of capture of the fake food item is calculated
4156  !! using the the_environment::food_item::capture_probability() backend
4157  !! assuming the distance to the food item is equal to the average distance
4158  !! of all food items in the **current perception** object. However, if the
4159  !! agent does not see any food items currently, the distance to the fake
4160  !! food item is assumed to be equal to the visibility range weighted by
4161  !! the (fractional) commondata::dist_expect_food_uncertain_fact
4162  !! parameter.
4163  ! TODO: add average distance to food items into perception memory and use
4164  ! it here.
4165  if ( this_agent%has_food() ) then
4166  expected_food_item_distance = this_agent%perceive_food%get_meandist()
4167  else
4168  ! TODO: add average food distances to perception memory
4169  expected_food_item_distance = expected_food_item%visibility() * &
4170  dist_expect_food_uncertain_fact
4171  end if
4172 
4173  expected_food_item_prob_capture = &
4174  expected_food_item%capture_probability( &
4175  distance=expected_food_item_distance )
4176 
4177  ! Produce diagnostic logger message in the @ref intro_debug_mode DEBUG mode.
4178  call log_dbg( ltag_info // "Distance to the expected food item: " // &
4179  tostr(expected_food_item_distance) // &
4180  ", capture prpbability of the expected food item: " // &
4181  tostr(expected_food_item_prob_capture) // ".", &
4182  procname, modname )
4183 
4184  !> Third, the expected food gain corrected for fitting into the agent's
4185  !! stomach and capture cost is obtained by
4186  !! the_body::condition::food_fitting(). It is then weighted by the
4187  !! expected capture probability.
4188  expected_food_item_gain_fits = &
4189  this_agent%food_fitting( this%expected_food_gain, &
4190  expected_food_item_distance ) * &
4191  expected_food_item_prob_capture
4192 
4193  ! Produce diagnostic logger message in the @ref intro_debug_mode DEBUG mode.
4194  call log_dbg( ltag_info // "Raw food gain: " // &
4195  tostr(this_agent%food_fitting( this%expected_food_gain, &
4196  expected_food_item_distance )) // &
4197  ", subjective food gain weighted by capture prob.: " // &
4198  tostr(expected_food_item_gain_fits) // ".", &
4199  procname, modname )
4200 
4201  !> **Stomach content**: the perception override value for the stomach
4202  !! content is obtained incrementing the current stomach contents by
4203  !! the nonzero expected food gain, adjusting also for the digestion
4204  !! decrement (the_body::stomach_emptify_backend()).
4205  agent_stomach = this_agent%get_stom_content()
4206  perception_override_stomach = &
4207  max( zero, &
4208  agent_stomach - stomach_emptify_backend(agent_stomach) + &
4209  expected_food_item_gain_fits )
4210 
4211  !> **Body mass**: the **body mass** perception override @f$ \pi_m @f$ is
4212  !! obtained by incrementing (or decrementing if the expected food gain
4213  !! is negative) the current body mass @f$ M @f$ by the expected food gain
4214  !! @f$ \phi @f$ and also subtracting the cost of living @f$ M_c @f$
4215  !! (the_body::condition::living_cost()) and the expected cost of movement
4216  !! into the target novel habitat @f$ \mu @f$:
4217  !! @f[ \pi_m = M + \phi - M_c - \mu @f]
4218  !! Thus, probability of capture and costs of food processing in
4219  !! calculating the stomach content increment depend on the distance to
4220  !! the expected food item and do not take into account the travel cost
4221  !! to the novel environment (it can be quite large, beyond the visibility
4222  !! of the expected food item). However, expectancy of the body mass
4223  !! (the fake perception value) takes into account the cost of migration
4224  !! movement to the novel target habitat.
4225  perception_override_bodymass = &
4226  max( zero, &
4227  this_agent%get_mass() - &
4228  this_agent%living_cost() + &
4229  expected_food_item_gain_fits - &
4230  this%expected_cost_moving )
4231 
4232  !> **Energy**: The fake perception values for the energy reserves
4233  !! (`energy_override_perc`) using the the_body::energy_reserve()
4234  !! procedure.
4235  perception_override_energy = energy_reserve( perception_override_bodymass,&
4236  this_agent%length() )
4237 
4238 
4239  !> **Direct food perception**: The fake perception of the number of food
4240  !! items expected for the perception in the target novel environment
4241  !! is calculated from the this\%expected_food_dir component (obtained in
4242  !! the `do_this` procedure).
4243  perception_override_food_dir = this%expected_food_dir
4244 
4245  !> **Predation risk**: fake perceptions of predation risk are
4246  !! obtained from the values calculated in the `do` procedure:
4247  !! the_behaviour::migrate::expected_pred_dir_risk and
4248  !! the_behaviour::migrate::expected_predation_risk.
4249  perception_override_pred_dir = this%expected_pred_dir_risk
4250  perception_override_predator = this%expected_predation_risk
4251 
4252  !> **Number of conspecifics**: finally, the fake perception of the
4253  !! number of conspecifics is calculated from the values calculated in the
4254  !! `do` procedure: the_behaviour::migrate::expected_consp_number.
4255  perception_override_conspec = this%expected_consp_number
4256 
4257  !> #### Calculate motivation expectancies ####
4258  !> The next step is to calculate the motivational expectancies using the
4259  !! fake perceptions to override the default (actual agent's) values.
4260  !> At this stage, first, calculate motivation values resulting from the
4261  !! behaviour done (`migrate::do_this()` ) at the previous steps: what
4262  !! would be the motivation values *if* the agent does perform
4263  !! MIGRATE? Technically, this is done by calling the **neuronal
4264  !! response function**, `percept_components_motiv::motivation_components()`
4265  !! method, for each of the motivational states with `perception_override_`
4266  !! dummy parameters overriding the default values.
4267  !! Here is the list of the fake overriding perceptions for the
4268  !! MIGRATE behaviour:
4269  !! - `perception_override_food_dir`
4270  !! - `perception_override_conspec`
4271  !! - `perception_override_pred_dir`
4272  !! - `perception_override_predator`
4273  !! - `perception_override_stomach`
4274  !! - `perception_override_bodymass`
4275  !! - `perception_override_energy`
4276  !! .
4277  ! @note **Expectancy** assessment for **hunger** motivation, using
4278  ! `PERCEPT_COMPONENTS_MOTIV`-bound procedure with intent[in] for
4279  ! `this_agent` now.
4280  call this%expectancy%hunger%percept_component%motivation_components &
4281  (this_agent, &
4282  ! Parameters:: Boolean G x P matrices:
4283  param_gp_matrix_light = light_hunger_genotype_neuronal, &
4284  param_gp_matrix_depth = depth_hunger_genotype_neuronal, &
4285  param_gp_matrix_food_dir = foodcount_hunger_genotype_neuronal, &
4286  param_gp_matrix_food_mem = food_mem_hunger_genotype_neuronal, &
4287  param_gp_matrix_conspec = conspcount_hunger_genotype_neuronal, &
4288  param_gp_matrix_pred_dir = pred_direct_hunger_genotype_neuronal, &
4289  param_gp_matrix_predator = pred_meancount_hunger_genotype_neuronal, &
4290  param_gp_matrix_stomach = stom_hunger_genotype_neuronal, &
4291  param_gp_matrix_bodymass = bodymass_hunger_genotype_neuronal, &
4292  param_gp_matrix_energy = energy_hunger_genotype_neuronal, &
4293  param_gp_matrix_age = age_hunger_genotype_neuronal, &
4294  param_gp_matrix_reprfac = reprfac_hunger_genotype_neuronal, &
4295  ! Parameters :: G x P variances:
4296  param_gerror_cv_light = light_hunger_genotype_neuronal_gerror_cv, &
4297  param_gerror_cv_depth = depth_hunger_genotype_neuronal_gerror_cv, &
4298  param_gerror_cv_food_dir = foodcount_hunger_genotype_neuronal_gerror_cv,&
4299  param_gerror_cv_food_mem = food_mem_hunger_genotype_neuronal_gerror_cv, &
4300  param_gerror_cv_conspec = conspcount_hunger_genotype_neuronal_gerror_cv,&
4301  param_gerror_cv_pred_dir = pred_direct_hunger_genotype_neuronal_gerror_cv,&
4302  param_gerror_cv_predator = pred_meancount_hunger_genotype_neuronal_gerror_cv,&
4303  param_gerror_cv_stomach = stom_hunger_genotype_neuronal_gerror_cv, &
4304  param_gerror_cv_bodymass = bodymass_hunger_genotype_neuronal_gerror_cv, &
4305  param_gerror_cv_energy = energy_hunger_genotype_neuronal_gerror_cv, &
4306  param_gerror_cv_age = age_hunger_genotype_neuronal_gerror_cv, &
4307  param_gerror_cv_reprfac = reprfac_hunger_genotype_neuronal_gerror_cv, &
4308  ! Real agent perception components are now substituted by the *fake*
4309  ! values resulting from executing this behaviour (`do_this` method).
4310  ! This is repeated for all the motivations: *hunger*,
4311  ! *passive avoidance,* *fear state* etc.
4312  perception_override_food_dir = perception_override_food_dir, &
4313  perception_override_conspec = perception_override_conspec, &
4314  perception_override_pred_dir = perception_override_pred_dir, &
4315  perception_override_predator = perception_override_predator, &
4316  perception_override_stomach = perception_override_stomach, &
4317  perception_override_bodymass = perception_override_bodymass, &
4318  perception_override_energy = perception_override_energy &
4319  )
4320  !> Real agent perception components are now substituted by the *fake*
4321  !! values resulting from executing this behaviour (`reproduce::do_this()`
4322  !! => `the_behaviour::reproduce_do_this()` method). This is repeated for
4323  !! all the motivations: *hunger*, *passive avoidance,* *active
4324  !! avoidance* etc. These optional **override parameters** are
4325  !! substituted by the "fake" values.
4326 
4327  ! @note **Expectancy** assessment for **fear_defence** motivation,
4328  ! using `PERCEPT_COMPONENTS_MOTIV`-bound procedure with intent[in]
4329  ! for `this_agent` now.
4330  call this%expectancy%fear_defence%percept_component%motivation_components &
4331  (this_agent, &
4332  ! Parameters:: Boolean G x P matrices:
4333  param_gp_matrix_light = light_actv_avoid_genotype_neuronal, &
4334  param_gp_matrix_depth = depth_actv_avoid_genotype_neuronal, &
4335  param_gp_matrix_food_dir = foodcount_actv_avoid_genotype_neuronal, &
4336  param_gp_matrix_food_mem = food_mem_actv_avoid_genotype_neuronal, &
4337  param_gp_matrix_conspec = conspcount_actv_avoid_genotype_neuronal, &
4338  param_gp_matrix_pred_dir = pred_direct_actv_avoid_genotype_neuronal, &
4339  param_gp_matrix_predator = pred_meancount_actv_avoid_genotype_neuronal, &
4340  param_gp_matrix_stomach = stom_actv_avoid_genotype_neuronal, &
4341  param_gp_matrix_bodymass = bodymass_actv_avoid_genotype_neuronal, &
4342  param_gp_matrix_energy = energy_actv_avoid_genotype_neuronal, &
4343  param_gp_matrix_age = age_actv_avoid_genotype_neuronal, &
4344  param_gp_matrix_reprfac = reprfac_actv_avoid_genotype_neuronal, &
4345  ! Parameters :: G x P variances:
4346  param_gerror_cv_light = light_actv_avoid_genotype_neuronal_gerror_cv, &
4347  param_gerror_cv_depth = depth_actv_avoid_genotype_neuronal_gerror_cv, &
4348  param_gerror_cv_food_dir = foodcount_actv_avoid_genotype_neuronal_gerror_cv,&
4349  param_gerror_cv_food_mem = food_mem_actv_avoid_genotype_neuronal_gerror_cv, &
4350  param_gerror_cv_conspec = conspcount_actv_avoid_genotype_neuronal_gerror_cv,&
4351  param_gerror_cv_pred_dir = pred_direct_actv_avoid_genotype_neuronal_gerror_cv,&
4352  param_gerror_cv_predator = pred_meancount_actv_avoid_genotype_neuronal_gerror_cv,&
4353  param_gerror_cv_stomach = stom_actv_avoid_genotype_neuronal_gerror_cv, &
4354  param_gerror_cv_bodymass = bodymass_actv_avoid_genotype_neuronal_gerror_cv,&
4355  param_gerror_cv_energy = energy_actv_avoid_genotype_neuronal_gerror_cv,&
4356  param_gerror_cv_age = age_actv_avoid_genotype_neuronal_gerror_cv, &
4357  param_gerror_cv_reprfac = reprfac_actv_avoid_genotype_neuronal_gerror_cv,&
4358  ! @note Real agent perception components are now **substituted**
4359  ! by the **fake** values resulting from executing this
4360  ! behaviour (`do_this` method).
4361  perception_override_food_dir = perception_override_food_dir, &
4362  perception_override_conspec = perception_override_conspec, &
4363  perception_override_pred_dir = perception_override_pred_dir, &
4364  perception_override_predator = perception_override_predator, &
4365  perception_override_stomach = perception_override_stomach, &
4366  perception_override_bodymass = perception_override_bodymass, &
4367  perception_override_energy = perception_override_energy &
4368  )
4369 
4370  ! @note **Expectancy** assessment for **reproduction** motivation,
4371  ! using `PERCEPT_COMPONENTS_MOTIV`-bound procedure with intent[in]
4372  ! for `this_agent` now.
4373  call this%expectancy%reproduction%percept_component%motivation_components &
4374  (this_agent, &
4375  ! Parameters:: Boolean G x P matrices:
4376  param_gp_matrix_light = light_reproduce_genotype_neuronal, &
4377  param_gp_matrix_depth = depth_reproduce_genotype_neuronal, &
4378  param_gp_matrix_food_dir = foodcount_reproduce_genotype_neuronal, &
4379  param_gp_matrix_food_mem = food_mem_reproduce_genotype_neuronal, &
4380  param_gp_matrix_conspec = conspcount_reproduce_genotype_neuronal, &
4381  param_gp_matrix_pred_dir = pred_direct_reproduce_genotype_neuronal, &
4382  param_gp_matrix_predator = pred_meancount_reproduce_genotype_neuronal, &
4383  param_gp_matrix_stomach = stom_reproduce_genotype_neuronal, &
4384  param_gp_matrix_bodymass = bodymass_reproduce_genotype_neuronal, &
4385  param_gp_matrix_energy = energy_reproduce_genotype_neuronal, &
4386  param_gp_matrix_age = age_reproduce_genotype_neuronal, &
4387  param_gp_matrix_reprfac = reprfac_reproduce_genotype_neuronal, &
4388  ! Parameters :: G x P variances:
4389  param_gerror_cv_light = light_reproduce_genotype_neuronal_gerror_cv, &
4390  param_gerror_cv_depth = depth_reproduce_genotype_neuronal_gerror_cv, &
4391  param_gerror_cv_food_dir = foodcount_reproduce_genotype_neuronal_gerror_cv,&
4392  param_gerror_cv_food_mem = food_mem_reproduce_genotype_neuronal_gerror_cv, &
4393  param_gerror_cv_conspec = conspcount_reproduce_genotype_neuronal_gerror_cv,&
4394  param_gerror_cv_pred_dir = pred_direct_reproduce_genotype_neuronal_gerror_cv,&
4395  param_gerror_cv_predator = pred_meancount_reproduce_genotype_neuronal_gerror_cv,&
4396  param_gerror_cv_stomach = stom_reproduce_genotype_neuronal_gerror_cv, &
4397  param_gerror_cv_bodymass = bodymass_reproduce_genotype_neuronal_gerror_cv,&
4398  param_gerror_cv_energy = energy_reproduce_genotype_neuronal_gerror_cv,&
4399  param_gerror_cv_age = age_reproduce_genotype_neuronal_gerror_cv, &
4400  param_gerror_cv_reprfac = reprfac_reproduce_genotype_neuronal_gerror_cv,&
4401  ! @note Real agent perception components are now **substituted**
4402  ! by the **fake** values resulting from executing this
4403  ! behaviour (`do_this` method).
4404  perception_override_food_dir = perception_override_food_dir, &
4405  perception_override_conspec = perception_override_conspec, &
4406  perception_override_pred_dir = perception_override_pred_dir, &
4407  perception_override_predator = perception_override_predator, &
4408  perception_override_stomach = perception_override_stomach, &
4409  perception_override_bodymass = perception_override_bodymass, &
4410  perception_override_energy = perception_override_energy &
4411  )
4412 
4413  !> #### Calculate primary and final motivations ####
4414  !> Next, from the perceptual components calculated at the previous
4415  !! step we can obtain the **primary** and **final motivation** values by
4416  !! weighed summing.
4417  if (present(rescale_max_motivation)) then
4418  !> Here we can use global maximum motivation across all behaviours and
4419  !! perceptual components if it is provided, for rescaling.
4420  max_motivation = rescale_max_motivation
4421  else
4422  !> Or can rescale using local maximum value for this behaviour only.
4423  max_motivation = this%expectancy%max_perception()
4424  end if
4425 
4426  !> Transfer attention weights from the actor agent `this_agent` to the
4427  !! `this` behaviour component. So, we will now use the updated modulated
4428  !! attention weights of the agent rather than their default parameter
4429  !! values.
4430  call this%attention_transfer(this_agent)
4431 
4432  !> So the primary motivation values are calculated.
4433  call this%expectancy%motivation_primary_calc(max_motivation)
4434 
4435  !> Primary motivations are logged in the @ref intro_debug_mode "debug mode".
4436  call log_dbg( ltag_info // "Primary motivations: " // &
4437  "hunger: " // &
4438  tostr(this%expectancy%hunger%motivation_prim) // &
4439  ", fear_defence: " // &
4440  tostr(this%expectancy%fear_defence%motivation_prim) // &
4441  ", reproduce: " // &
4442  tostr(this%expectancy%reproduction%motivation_prim), &
4443  procname, modname )
4444 
4445  !> There is **no modulation** at this stage, so the final motivation
4446  !! values are the same as primary motivations.
4447  call this%expectancy%modulation_none()
4448 
4449  !> #### Calculate motivation expectancies ####
4450  !> Finally, calculate the finally **expected arousal level for this
4451  !! behaviour**. As in the GOS, the overall arousal is the maximum value
4452  !! among all motivation components.
4453  this%arousal_expected = this%expectancy%max_final()
4454 
4455  !> Log also the final expectancy value in the @ref intro_debug_mode
4456  !! "debug mode".
4457  call log_dbg( ltag_info // "Expectancy: " // tostr(this%arousal_expected),&
4458  procname, modname )
4459 
4460  !> Now as we know the expected arousal, we can choose the behaviour which
4461  !! would minimise this arousal level.
4462 
4463  end subroutine migrate_motivations_expect
4464 
4465  !-----------------------------------------------------------------------------
4466  !> Execute this behaviour component "migrate" by `this_agent` agent.
4467  subroutine migrate_do_execute(this, this_agent, target_env)
4468  class(migrate), intent(inout) :: this
4469  !> @param[in] this_agent is the actor agent which goes down.
4470  class(appraisal), intent(inout) :: this_agent
4471  !> @param[in] target_env the target environment the actor agent is going
4472  !! to (e)migrate into.
4473  class(environment), intent(in) :: target_env
4474 
4475  ! PROCNAME is the procedure name for logging and debugging.
4476  character(len=*), parameter :: PROCNAME = "(migrate_do_execute)"
4477 
4478  ! Local copy of the body length of the agent
4479  real(SRP) :: agent_length
4480 
4481  ! Debugging indicators for correlated random walk.
4482  logical :: is_converged_debug
4483  integer :: iter_debug
4484 
4485  ! 95% confidence interval of Gaussian distribution, sets the upper
4486  ! limit on maximum migration distance.
4487  real(SRP), parameter :: CIDIF = 1.95996_srp
4488 
4489  ! Agent length is local variable to avoid multiple calls to get_length().
4490  agent_length = this_agent%get_length()
4491 
4492  !> ### Implementation details ###
4493  !> #### Step 1: do_this ####
4494  !> First, we use the intent-in **do**-procedure
4495  !! the_behaviour::migrate::do_this() to perform the behaviour desired.
4496  !! However, instead of expectations, get the target point in the novel
4497  !! habitat.(Expectancies for food gain, predator risk etc. are not used
4498  !! at this stage, memory windows are absent from the parameter list.)
4499  call this%do_this( this_agent=this_agent, target_env=target_env )
4500 
4501  !> #### Step 2: Change the agent ####
4502  !> ##### Try to relocate to the target novel habitat #####
4503  !> The agent does a directional walk at this\%distance towards the
4504  !! this\%target_point in the novel target environment. However, it is
4505  !! possible only if the walk distance does not exceed the maximum value
4506  !! defined by the commondata::migrate_dist_max_step body sizes of the
4507  !! agent.
4508  do_walk: if (this%distance > agent_length * migrate_dist_max_step ) then
4509  !> - If this is the case, a warning is logged.
4510  call log_dbg( ltag_warn // "Migration travel distance exceeds big " // &
4511  "threshold in " // procname // " for the agent " // &
4512  this_agent%individ_label() // ". Agent length: " // &
4513  tostr(agent_length) // ", migration distance: " // &
4514  tostr(this%distance), procname, modname )
4515  !> - the agent is executing a Gaussian correlated random walk towards the
4516  !! target point. The average walk length is the above maximum distance
4517  !! minus 95% confidence limit and the CV is the default for random
4518  !! walks (thus, there is almost a guarantee that the actual walk is
4519  !! the maximum commondata::migrate_dist_max_step distance and unlikely
4520  !! to exceed it. This walk is, additionally, limited to the present
4521  !! environment (i.e. no migration is performed by the agent).
4522  !! .
4523  call this_agent%corwalk( &
4524  target = this%target_point, &
4525  meanshift_xy = agent_length * migrate_dist_max_step - &
4526  agent_length * migrate_dist_max_step * cidif * &
4527  (agent_length * migrate_dist_max_step) * &
4528  walk_random_distance_stochastic_cv, &
4529  cv_shift_xy = walk_random_distance_stochastic_cv, &
4530  meanshift_depth = agent_length * &
4531  walk_random_vertical_shift_ratio, &
4532  cv_shift_depth = walk_random_distance_stochastic_cv * &
4533  walk_random_vertical_shift_cv_ratio, &
4534  is_away = .false., &
4535  environment_limits = global_habitats_available( &
4536  this_agent%find_environment( &
4537  global_habitats_available) ),&
4538  is_converged = is_converged_debug, &
4539  debug_reps = iter_debug )
4540  call log_dbg( ltag_info // "Correlated random walk: converged " // &
4541  tostr(is_converged_debug) // ", iterations: " // &
4542  tostr(iter_debug), procname, modname )
4543  !> If the above limit on the length of a single walk is not
4544  !! exceeded, the agent relocates to the target point in the novel
4545  !! target environment. It is now in the target environment.
4546  else do_walk
4547  call log_dbg( ltag_info // "Agent is about to migrate to " // &
4548  tostr([ this%target_point%xpos(), &
4549  this%target_point%ypos(), &
4550  this%target_point%dpos()]), procname, modname )
4551  call this_agent%position( this%target_point%location() )
4552  end if do_walk
4553 
4554  !> In the @ref intro_debug_mode "DEBUG Mode", print diagnostic information
4555  !! to the logger.
4556  call log_dbg( ltag_info // "Migration displacement position:" // &
4557  tostr([ this_agent%xpos(), &
4558  this_agent%ypos(), &
4559  this_agent%dpos()] ) // ", distance (way) " // &
4560  "traversed: " // tostr(this_agent%way()) // &
4561  " (distance expected " // tostr(this%distance) // ")", &
4562  procname, modname )
4563  call log_dbg( ltag_info // "Cost of this movement: " // &
4564  tostr(this_agent%cost_swim(exponent = &
4565  swimming_cost_exponent_laminar)), procname, modname )
4566  call log_dbg( ltag_info // "The agent is now in [" // &
4567  tostr(this_agent%find_environment()) // "] environment: "// &
4568  trim(global_habitats_available( &
4569  this_agent%find_environment())%get_label()), &
4570  procname, modname )
4571 
4572  !> ##### Process the cost of movement #####
4573  !> - Reset the body mass of the actor agent subtracting the actual cost of
4574  !! the migration moving that is automatically calculated in the call to
4575  !! the_body::condition::cost_swim(). The the_body::condition::set_mass()
4576  !! method is used here to adjust the mass.
4577  call this_agent%set_mass( &
4578  value_set = this_agent%get_mass() - &
4579  this_agent%cost_swim(exponent= &
4580  swimming_cost_exponent_laminar), &
4581  update_history = .true. )
4582 
4583  !> - Additionally, also call the `the_body::condition::set_length()` method
4584  !! to update the body length history stack. However, the value_set
4585  !! parameter here is just the current value. This fake re-setting of the
4586  !! body length is done to keep both mass and length synchronised in their
4587  !! history stack arrays (there is no procedure for only updating history).
4588  call this_agent%set_length( value_set = this_agent%get_length(), &
4589  update_history = .true. )
4590 
4591  !> - After resetting the body mass, update energy reserves of the agent,
4592  !! that depend on both the length and the mass.
4593  !! .
4594  call this_agent%energy_update()
4595 
4596  call log_dbg( ltag_info // "Updated mass: " // &
4597  tostr(this_agent%get_mass()) // &
4598  ", body length: " // tostr(this_agent%get_length()) // &
4599  ", energy: " // tostr(this_agent%get_energy()), &
4600  procname, modname )
4601 
4602  !> Finally, check if the agent is starved to death. If yes, the agent can
4603  !! die without going any further.
4604  if (this_agent%starved_death()) call this_agent%dies()
4605 
4606  !> #### Step 3: Change the environment ####
4607  !> Random walk does not affect the environmental objects.
4608 
4609  end subroutine migrate_do_execute
4610 
4611  !-----------------------------------------------------------------------------
4612  !> The hope function for the assessment of expectancy for a completely
4613  !! novel stimulus or environment for which local information is absent.
4614  !!
4615  !> Calculation of the expectancy and therefore fake perceptions is not
4616  !! possible for completely novel environment or stimuli (e.g. for
4617  !! emigrating into a completely different novel habitat) based on the
4618  !! current perception because the agent has absolutely no local information
4619  !! (i.e. no perception of this habitat yet).
4620  !!
4621  !! A mechanism based on the **hope function** should be used in such a case.
4622  !! @image html img_doxygen_hope_function_rule.svg "The hope function mechanism"
4623  !! @image latex img_doxygen_hope_function_rule.eps "The hope function mechanism" width=14cm
4624  !!
4625  !! - A baseline expectancy @f$ f_0 @f$ based on the locally available
4626  !! information (e.g. local expectation of the food gain) is selected.
4627  !! - Then, a trend of the baseline expectancy characteristic (e.g. average
4628  !! food gain) in the past memory stack is determined by
4629  !! - splitting a food memory stack *window* into two halves: older
4630  !! @f$ \mathbf{M_1} @f$ and newer @f$ \mathbf{M_2} @f$,
4631  !! - calculating the average local expectancies for the older
4632  !! @f$ \overline{f_1} @f$ and newer @f$ \overline{f_2} @f$ parts,
4633  !! - calculating the ratio
4634  !! @f[ \varrho = \frac{\overline{f_2}}{\overline{f_1}} . @f]
4635  !! .
4636  !! .
4637  !! Following this, the expectancy (e.g. expected food gain) for the
4638  !! novel stimuli or situation is calculated as:
4639  !! @f[ F_{exp}= f_0 \cdot \Xi(\varrho) , @f] where @f$ f_0 @f$ is the
4640  !! baseline food gain against which the expectancy is evaluated, and
4641  !! @f$ \Xi(\varrho) @f$ is the "hope" function that is obtained as a
4642  !! nonparametric relationship (see the right panel plots above):
4643  !! nonlinear interpolation based on the grid vectors
4644  !! @f$ \mathbf{V} @f$ and @f$ \mathbf{W} @f$:
4645  ! Note: Simplified Latex formula:
4646  ! @f[ \mathbf{V} = \left( 0.0; 1.0; \varrho_0 \right ),
4647  ! \mathbf{W} = \left( \Xi_{max}; 1.0; \to 0.0 \right) , @f]
4648  ! The vectors are now as graphics in svg and eps formats because Latex
4649  ! matrices may not render correctly by Doxygen.
4650  !> @n
4651  !> @image html img_doxygen_hope_function_formula_1.svg
4652  !! @image latex img_doxygen_hope_function_formula_1.eps "" width=14cm
4653  !! @n
4654  !! where @f$ \varrho_0 @f$ is the *zero hope ratio* parameter and
4655  !! @f$ \Xi_{max} @f$ is the *maximum hope* parameter.
4656  pure function hope( baseline, memory_old, memory_new, &
4657  zero_hope, maximum_hope, raw_grid_x, raw_grid_y) &
4658  result(expected_value)
4659  !> @param[in] baseline is the baseline stimulus expectancy @f$ f_0 @f$
4660  !! that is based on the locally available information.
4661  real(srp), intent(in) :: baseline
4662  !> @param[in] memory_old is the older part (half) of the memory stack
4663  !! @f$ \overline{f_1} @f$ for the baseline perception.
4664  real(srp), intent(in) :: memory_old
4665  !> @param[in] memory_new is the newer part (half) of the memory stack
4666  !! @f$ \overline{f_2} @f$ for the baseline perception.
4667  real(srp), intent(in) :: memory_new
4668  !> @param[in] zero_hope is the zero hope ratio @f$ \varrho_0 @f$ parameter
4669  !! of the hope function grid abscissa vector.
4670  real(srp), optional, intent(in) :: zero_hope
4671  !> @param[in] maximum_hope is the maximum hope @f$ \Xi_{max} @f$ parameter
4672  !! of the hope function grid ordinate vector.
4673  real(srp), optional, intent(in) :: maximum_hope
4674  !> @param[in] raw_grid_x a raw interpolation grid array that can be
4675  !! provided (along with raw_grid_y) instead of the normal
4676  !! `zero_hope` and `maximum_hope` parameters.
4677  real(srp), dimension(:), optional, intent(in) :: raw_grid_x
4678  !> @param[in] raw_grid_y a raw interpolation grid array that can be
4679  !! provided (along with raw_grid_x) instead of the normal
4680  !! `zero_hope` and `maximum_hope` parameters.
4681  real(srp), dimension(:), optional, intent(in) :: raw_grid_y
4682 
4683  !> @return The expected value for the wholly novel stimulus or environment.
4684  !> @note Note that the scalar parameters `zero_hope`
4685  !! and `maximum_hope` represent the normal standard
4686  !! way to provide the interpolation grid for the hope
4687  !! function. However, these grids can also be accepted
4688  !! as raw grid arrays (see `raw_grid_x` and `raw_grid_y`
4689  !! parameters below).
4690  !> @note Raw grid arrays have priority if both raw grid arrays
4691  !! and normal scalar parameters `zero_hope` and
4692  !! `maximum_hope` are simultaneously provided.
4693  !> @warning The grid vectors `raw_grid_x` and `raw_grid_y`
4694  !! must have the same length.
4695  real(srp) :: expected_value
4696 
4697  !> ### Notable variables ###
4698  !> - **memory_ratio** is the ratio of the newer to older memory values;
4699  real(srp) :: memory_ratio
4700 
4701  !> - **hope_func_grid_abscissa** and **hope_func_grid_ordinate** are the
4702  !! hope function grid arrays. They define the nonparametric hope function
4703  !! that is obtained by nonlinear interpolation. These arrays can be also
4704  !! provided as raw `raw_grid_x` `raw_grid_y` parameters.
4705  !! .
4706  integer, parameter :: hope_func_grid_dim = 3
4707  real(srp), dimension(HOPE_FUNC_GRID_DIM) :: hope_func_grid_abscissa, &
4708  hope_func_grid_ordinate
4709 
4710  !> ##### Implementation details #####
4711  !> First, calculate the memory-based ratio
4712  !! @f[ \varrho = \frac{\overline{f_2}}{\overline{f_1}} . @f]
4713  !> - The calculation also checks for possible division by zero, if
4714  !! the older memory value @f$ \overline{f_2} = 0.0 @f$; in such
4715  !! a case, the ratio is set to the maximum abscissa grid value
4716  !! resulting in zero hope function.
4717  if (memory_old < zero) then
4718  if (present(raw_grid_x) .and. present(raw_grid_y)) then
4719  memory_ratio = maxval(raw_grid_x)
4720  else if (present(zero_hope) .and. present(maximum_hope)) then
4721  memory_ratio = zero_hope
4722  else
4723  expected_value = missing
4724  return
4725  end if
4726  !> - An additional case of both @f$ \overline{f_1} = 0.0 @f$ and
4727  !! @f$ \overline{f_2} = 0.0 @f$ is also checked, the ratio in such
4728  !! a case is set to 1.0, bringing about a unity hope function value
4729  !! (i.e. baseline expectancy is unchanged).
4730  !! .
4731  elseif (memory_old < zero .and. memory_new < zero) then
4732  memory_ratio = 1.0_srp
4733  else
4734  memory_ratio = memory_new / memory_old
4735  end if
4736 
4737  provide_raw_grid: if (present(raw_grid_x) .and. present(raw_grid_y)) then
4738  expected_value = baseline * ddpinterpol( raw_grid_x, &
4739  raw_grid_y, &
4740  memory_ratio )
4741  ! Grid arrays have priority if both arrays and normal scalar
4742  ! parameters are simultaneously provided, so exit.
4743  return
4744  end if provide_raw_grid
4745 
4746  !> Second, get the hope function grid vectors @f$ \mathbf{V} @f$ and
4747  !! @f$ \mathbf{W} @f$ as:
4748  !! @verbatim
4749  !! V = [ 0.0_SRP, 1.00_SRP, zero_hope ]
4750  !! W = [ maximum_hope, 1.00_SRP, ZERO ]
4751  !! @endverbatim
4752  provide_scalars: if (present(zero_hope) .and. present(maximum_hope)) then
4753  hope_func_grid_abscissa = [ 0.0_srp, 1.00_srp, zero_hope ]
4754  hope_func_grid_ordinate = [ maximum_hope, 1.00_srp, zero ]
4755 
4756  !> Finally, the hope function value is obtained from a nonlinear
4757  !! interpolation based on `DDPINTERPOL` (see HEDTOOLS) with the
4758  !! interpolation grid defined by the @f$ \mathbf{V} @f$ (abscissa)
4759  !! and @f$ \mathbf{W} @f$ (ordinate) vectors.
4760  ! htintrpl.exe [0 1 2] [4 1 0]
4761  expected_value = baseline * ddpinterpol( hope_func_grid_abscissa, &
4762  hope_func_grid_ordinate, &
4763  memory_ratio )
4764  ! Exit, everything below this point is error, wrong parameter pair.
4765  return
4766  end if provide_scalars
4767 
4768  !> If neither a pair of the scalar parameters `zero_hope` and
4769  !! `maximum_hope` nor the raw grid arrays `raw_grid_x` and `raw_grid_y`
4770  !! are provided, return commondata::missing value as an indicator of
4771  !! error.
4772  expected_value = missing
4773 
4774  end function hope
4775 
4776  !-----------------------------------------------------------------------------
4777  !> Calculate the default upward and downward walk step size. This function is
4778  !! called from the_behaviour::go_down_do_this() and
4779  !! the_behaviour::go_down_motivations_expect() if the upwards or downwards
4780  !! walk size is not provided explicitly.
4781  elemental function depth_walk_default (length, walk_factor) &
4782  result(depth_walk_out)
4783  !> @param[in] length The body length of the agent.
4784  real(srp), intent(in) :: length
4785  !> @param[in] walk_factor The multiplocation factor for the walk step.
4786  !! The fdefault value is defined by the parameter
4787  !! commondata::up_down_walk_step_stdlength_factor.
4788  real(srp), intent(in), optional :: walk_factor
4789  !> @return The default up/down walk step size.
4790  real(srp) :: depth_walk_out
4791 
4792  !> ### Details ###
4793  !> If the walk size is not provided, it is set equal to the agent's body
4794  !! length multiplied by the commondata::up_down_walk_step_stdlength_factor
4795  !! factor parameter.
4796  if (present(walk_factor)) then
4797  depth_walk_out = length * walk_factor
4798  else
4799  depth_walk_out = length * up_down_walk_step_stdlength_factor
4800  end if
4801 
4802  end function depth_walk_default
4803 
4804  !-----------------------------------------------------------------------------
4805  !> Initialise the **go down to a deeper spatial layer** behaviour component
4806  !! to a zero state.
4807  elemental subroutine go_down_depth_init_zero(this)
4808  class(go_down_depth), intent(inout) :: this
4809 
4810  !> First init components from the base root class
4811  !! `the_behaviour::behaviour_base`.
4812  !> Mandatory label component that should be read-only.
4813  this%label = "GO_DOWN_DEPTH"
4814  !> The execution status is always FALSE, can be reset to TRUE only when
4815  !! the behaviour unit is called to execution.
4816  this%is_active = .false.
4817 
4818  !> And the *expectancy* components.
4819  call this%expectancy%init()
4820  this%arousal_expected = 0.0_srp
4821 
4822  !> Abstract `MOVE` component.
4823  this%distance = missing
4824 
4825  !> Then init components of this specific behaviour component extended class.
4826  this%decrement_mass_cost = missing
4827  this%expected_food_gain = missing
4828  this%expected_consp_number = unknown
4829  this%expected_predation_risk = missing
4830 
4831  end subroutine go_down_depth_init_zero
4832 
4833  !-----------------------------------------------------------------------------
4834  !> Do go down by `this_agent` (the actor agent). Subjective assessment of the
4835  !! motivational value for this is based on the number of food items,
4836  !! conspecifics and predators at the layers below the `this_agent` actor
4837  !! agent.
4838  subroutine go_down_do_this(this, this_agent, max_depth, depth_walk, &
4839  predict_window_food, time_step_model)
4840  !> @param[inout] this the object itself.
4841  class(go_down_depth), intent(inout) :: this
4842  !> @param[in] this_agent is the actor agent which goes down.
4843  class(appraisal), intent(in) :: this_agent
4844  !> @param[in] max_depth is the maximum limit on the depth.
4845  real(SRP), intent(in) :: max_depth
4846  !> @param[in] depth_walk Optional downward walk size, by how deep
4847  !! the agent goes down.
4848  real(SRP), intent(in), optional :: depth_walk
4849  !> @param[in] predict_window_food the size of the prediction window, i.e.
4850  !! how many steps back in memory are used to calculate the
4851  !! predicted food gain. This parameter is limited by the maximum
4852  !! commondata::history_size_perception value of the perception
4853  !! memory history size.
4854  integer, optional, intent(in) :: predict_window_food
4855  !> @param[in] time_step_model optional time step of the model, overrides
4856  !! the value calculated from the spatial data.
4857  integer, optional, intent(in) :: time_step_model
4858 
4859  ! Local copies of optionals
4860  real(SRP) :: depth_walk_here
4861 
4862  ! Local copies of optionals.
4863  integer :: predict_window_food_here, time_step_model_here
4864 
4865  ! **WEIGHT_DIRECT** is the relative weight given to the immediate
4866  ! perception of predators over the predators counts in the memory stack.
4867  ! Obtained from global parameters
4868  ! (`commondata::predation_risk_weight_immediate`).
4869  real(SRP), parameter :: WEIGHT_DIRECT = predation_risk_weight_immediate
4870 
4871  ! **MEM_WIND** is the size of the memory window when assessing the
4872  ! predator risk, only this number of the latest elements from the memory
4873  ! stack is taken into account. So we further weight the direct threat
4874  ! over the background risk when making the decision.
4875  ! @note Note that we take into account the whole memory size
4876  ! (commondata::history_size_perception).
4877  integer, parameter :: MEM_WIND = history_size_perception
4878 
4879  !> ### Implementation details ###
4880  !> First, check if the size of the downward walk `depth_walk` dummy
4881  !! parameter is provided.
4882  if (present(depth_walk)) then
4883  depth_walk_here = depth_walk
4884  else
4885  !> If it is not provided, it is set equal to the agent's body length
4886  !! multiplied by the commondata::up_down_walk_step_stdlength_factor
4887  !! factor parameter. Calculated by `the_behaviour::depth_walk_default()`.
4888  depth_walk_here = depth_walk_default( this_agent%get_length() )
4889  end if
4890 
4891  !> Check optional parameter for the food perception memory window. If
4892  !! the `predict_window_food` dummy parameter is not provided, its default
4893  !! value is the proportion of the whole perceptual memory window defined
4894  !! by commondata::history_perception_window_food. Thus, only the
4895  !! latest part of the memory is used for the prediction of the future
4896  !! food gain.
4897  if (present(predict_window_food)) then
4898  predict_window_food_here = predict_window_food
4899  else
4900  predict_window_food_here = floor( history_size_perception * &
4901  history_perception_window_food )
4902  end if
4903 
4904  !> Check optional time step parameter. If unset, use global
4905  !! `commondata::global_time_step_model_current`.
4906  if (present(time_step_model)) then
4907  time_step_model_here = time_step_model
4908  else
4909  time_step_model_here = global_time_step_model_current
4910  end if
4911 
4912  !> #### Downward step size ####
4913  !> Here, first, check if the target depth is likely to go beyond the
4914  !! environment depth limits and reduce the downward walk step size
4915  !! accordingly. Namely, if the depth coordinate of the actor agent
4916  !! plus the depth step exceeds the maximum depth, the step is reduced
4917  !! to be within the available environment:
4918  !! @f$ D_{max} - d_{a} - \varepsilon @f$, where @f$ D_{max} @f$ is the
4919  !! maximum depth, @f$ d_{a} @f$ is the agent's current depth and
4920  !! @f$ \varepsilon @f$ is a very small constant defined by the parameter
4921  !! commondata::zero.
4922  if (this_agent%dpos() + depth_walk_here >= max_depth ) &
4923  depth_walk_here = max( 0.0_srp, &
4924  max_depth - this_agent%dpos() - zero )
4925 
4926  !> The down step size component of the class is then equal to the
4927  !! `depth_walk`.
4928  this%distance = depth_walk_here
4929 
4930  !> #### The cost of swimming down ####
4931  !> The expected cost of the swimming down by the buoyancy is much smaller
4932  !! than active propulsion. It is set as a fraction, defined by the
4933  !! parameter commondata::swimming_cost_factor_buoyancy_down, of active
4934  !! laminar propulsion calculated by function
4935  !! the_body::condition_cost_swimming_burst().
4936  this%decrement_mass_cost = swimming_cost_factor_buoyancy_down * &
4937  this_agent%cost_swim( distance=depth_walk_here, &
4938  exponent=swimming_cost_exponent_laminar )
4939 
4940  !> #### Calculate expected perceptions ####
4941  !> Calculate the number of conspecifics at the down of the agent using the
4942  !! function perception::consp_below().
4943  this%expected_consp_number = this_agent%consp_below()
4944 
4945  !> Calculate the expected predation risk at the down of the agent using
4946  !! the `the_neurobio::predation_risk_backend()` function. This is a general
4947  !! predation risk (the_neurobio::percept_components_motiv::predator), not
4948  !! direct risk based on the distance to the nearest predator (see
4949  !! the_neurobio::percept_components_motiv::pred_dir).
4950  this%expected_predation_risk = &
4951  predation_risk_backend( &
4952  this_agent%pred_below(), &
4953  this_agent%memory_stack%get_pred_mean(mem_wind),&
4954  weight_direct )
4955 
4956  !> Calculate the expected food gain as an average mass of the food items
4957  !! down the agent. It is used by calling perception::food_mass_below()
4958  !! function.
4959  !! This expected food gain is then weighted by the subjective probability
4960  !! of food item capture that is calculated based on the memory
4961  !! the_neurobio::perception::food_probability_capture_subjective().
4962  this%expected_food_gain = this_agent%food_mass_below() * &
4963  this_agent%food_probability_capture_subjective( &
4964  predict_window_food_here, time_step_model_here )
4965 
4966  end subroutine go_down_do_this
4967 
4968  !-----------------------------------------------------------------------------
4969  !> `go_down_depth::motivations_expect()` is a subroutine (re)calculating
4970  !! motivations from fake expected perceptions following from the procedure
4971  !! `go_down_depth::do_this()` => `the_behaviour::go_down_do_this()`.
4972  subroutine go_down_motivations_expect(this, this_agent, depth_walk, &
4973  max_depth, environments, &
4974  time_step_model, rescale_max_motivation )
4975  !> @param[inout] this the object itself.
4976  class(go_down_depth), intent(inout) :: this
4977  !> @param[in] this_agent is the actor agent which goes down.
4978  class(appraisal), intent(in) :: this_agent
4979  !> @param[in] depth_walk The downward walk size, by how deep the agent
4980  !! goes down.
4981  real(SRP), intent(in), optional :: depth_walk
4982  !> @param[in] max_depth is the optional maximum limit on the depth.
4983  real(SRP), intent(in), optional :: max_depth
4984  !> @param[in] environments optional array of the all available
4985  !! environments where the this agent can be in, needed for the
4986  !! calculation of the depth limits. If such an array of the
4987  !! environments is provided, `max_depth` has precedence.
4988  class(environment), dimension(:), optional, intent(in) :: environments
4989  !> @param [in] time_step_model optional time step of the model,
4990  !! **overrides** the value calculated from the spatial data.
4991  integer, optional, intent(in) :: time_step_model
4992  !> @param[in] rescale_max_motivation maximum motivation value for
4993  !! rescaling all motivational components for comparison
4994  !! across all motivation and perceptual components and behaviour
4995  !! units.
4996  real(SRP), optional, intent(in) :: rescale_max_motivation
4997 
4998  ! Local copy of optional depth_walk
4999  real(SRP) :: depth_walk_here, max_depth_here
5000 
5001  ! Local copy of optional model time step
5002  integer :: time_step_model_here
5003 
5004  !> Target depth, i.e. the absolute depth of the agent after it moves down.
5005  real(SRP) :: target_depth
5006 
5007  ! Expected food item that is used in the calculations, its properties are
5008  ! based on the average food items that the agent perceives below.
5009  type(food_item) :: expected_food_item
5010 
5011  ! the coordinates of the expected food item.
5012  type(spatial) :: expected_food_item_xyz
5013 
5014  ! The expected distance to the food item at the target downward horizon.
5015  real(SRP) :: expect_distance_food
5016 
5017  ! Expected mass increment from food at the target depth.
5018  real(SRP) :: expect_mass_increment_from_food
5019 
5020  ! Expected stomach increment from food at the target depth.
5021  real(SRP) :: expect_stomach_increment_from_food
5022 
5023  ! The number of food items under the agent, obtained from the current
5024  ! perception object.
5025  integer :: n_food_items_below
5026 
5027  ! Local variable
5028  real(SRP) :: max_motivation ! Local max. over all motivation components.
5029 
5030  !> ### Notable local variables ###
5031  !> #### Perception overrides ####
5032  !> - **expect_food_perc_override** is the fake perception for the food items
5033  !! at the target depth.
5034  integer :: expect_food_perc_override
5035 
5036  !> - **expect_depth_perc_override** is the fake perception of the depth,
5037  !! identical to the target depth.
5038  real(SRP) :: expect_depth_perc_override
5039 
5040  !> - **expect_light_perc_override** is the fake perception of the
5041  !! illumination level at the target depth.
5042  real(SRP) :: expect_light_perc_override
5043 
5044  !> - **expect_mass_perc_override** is the fake perception value for the
5045  !! mass from the expected food.
5046  real(SRP) :: expect_mass_perc_override
5047 
5048  !> - **expect_stomach_perc_override** is the fake perception value for the
5049  !! stomach increment from the expected food.
5050  real(SRP) :: expect_stomach_perc_override
5051 
5052  ! Current stomach contents mass of the actor agent.
5053  real(SRP) :: agent_stomach
5054 
5055  !> - **expect_energy_perc_override** is the fake perception for the energy
5056  !! reserves from the expected food at the target depth.
5057  real(SRP) :: expect_energy_perc_override
5058 
5059  !> - **expected_probability_capture** is the expected probability of capture
5060  !! of the expected food item at the target depth.
5061  real(SRP) :: expected_probability_capture
5062 
5063  !> - **expect_conspecicifc_perc_override** is the fake perception value for
5064  !! the number of conspecifics at the target depth.
5065  integer :: expect_conspecicifc_perc_override
5066 
5067  !> - **expect_predator_perc_override** is fake perception value for the
5068  !! predation risk at the target depth.
5069  !! .
5070  real(SRP) :: expect_predator_perc_override
5071 
5072  ! PROCNAME is the procedure name for logging and debugging
5073  character(len=*), parameter :: PROCNAME = &
5074  "(go_down_motivations_expect)"
5075 
5076  !> ### Implementation details ###
5077  !> #### Sanity checks and preparations ####
5078  !> Initially, check if the size of the downward walk `depth_walk` dummy
5079  !! parameter is provided.
5080  if (present(depth_walk)) then
5081  depth_walk_here = depth_walk
5082  else
5083  !> If it is not provided, it is set equal to the agent's body length
5084  !! multiplied by the commondata::up_down_walk_step_stdlength_factor
5085  !! factor parameter. Calculated by `the_behaviour::depth_walk_default()`.
5086  depth_walk_here = depth_walk_default( this_agent%get_length() )
5087 
5088  end if
5089 
5090  ! @note The `GET_MAXDEPTH` block is used unchanged in several places,
5091  ! however, it cannot be isolated into a single procedure because
5092  ! its code heavily uses optional parameters checks using `present`
5093  ! intrinsic function that should apply to the called procedure.
5094  get_maxdepth: block
5095  !> Check downward step size. Here, first, check if the target depth is
5096  !! likely to go beyond the environment depth limits and reduce the
5097  !! downward walk step size accordingly. Either the explicitly provided
5098  !! maximum depth dummy parameter `max_depth` or an array of possible
5099  !! environment objects where the `this_agent` actor agent can be located
5100  !! is used to get the depth limit.
5101  max_depth_here = missing
5102 
5103  if (present(environments)) then
5104  !> If the array of possible environment objects that can contain the
5105  !! actor agent is provided, the check involves the
5106  !! `the_environment::spatial::find_environment()` function to find the
5107  !! specific environment object the agent is currently in followed by
5108  !! `the_environment::environment::depth_max()` to find the minimum
5109  !! depth in this environment object.
5110  max_depth_here = &
5111  environments(this_agent%find_environment(environments))%depth_max()
5112  else
5113  !> If the array of possible environment objects that can contain the
5114  !! actor agent is not provided, the current environment is obtained
5115  !! from the global array the_environment::global_habitats_available.
5116  !! In this case, the environment that actor agent is within is
5117  !! determined using the the_environment::spatial::find_environment()
5118  !! method, which is in followed by
5119  !! the_environment::environment::depth_max()` to find the minimum
5120  !! depth in this environment object.
5121  max_depth_here = global_habitats_available( &
5122  this_agent%find_environment( &
5123  global_habitats_available) &
5124  )%depth_max()
5125  end if
5126 
5127  !> If `max_depth` is provided, it has precedence over the depth
5128  !! detected explicitly or implicitly from the environment objects.
5129  if (present(max_depth)) max_depth_here = max_depth
5130 
5131  !> In the case the maximum depth cannot be determined,it is set as
5132  !! the depth of the actor agent (with an additional condition that it
5133  !! should exceed zero), so movement down would be **impossible**.
5134  if (max_depth_here .feq. missing) &
5135  max_depth_here = max( 0.0_srp, this_agent%dpos() )
5136  end block get_maxdepth
5137 
5138  !> If the depth coordinate of the actor agent plus the depth step
5139  !! exceeds the maximum depth, the step is reduced to be strictly within
5140  !! the available environment. However, it should also never be below zero.
5141  if (this_agent%dpos() + depth_walk_here >= max_depth_here ) &
5142  depth_walk_here = max( 0.0_srp, &
5143  max_depth_here - this_agent%dpos() - zero )
5144 
5145  !> Check optional time step parameter. If not provided, use global
5146  !! parameter value from commondata::global_time_step_model_current.
5147  if (present(time_step_model)) then
5148  time_step_model_here = time_step_model
5149  else
5150  time_step_model_here = global_time_step_model_current
5151  end if
5152 
5153  !> Assess the number of food items below using the
5154  !! perception::food_items_below() method.
5155  n_food_items_below = this_agent%food_items_below()
5156 
5157  !> Calculate the expected distance to the food item. It is equal to the
5158  !! average distance to the food items perceived below in case there are
5159  !! any such items perceived below. Calculated using the
5160  !! perception::food_dist_below() method.
5161  if ( n_food_items_below > 0 ) then
5162  expect_distance_food = this_agent%food_dist_below()
5163  else
5164  !> However, if there are no food items below (resulting a
5165  !! commondata::missing distance, see perception::food_dist_below()),
5166  !! the expected distance is set the downward walk distance `depth_walk`,
5167  !! that should be sufficiently long to assure the probability of food
5168  !! item capture is very small or zero.
5169  expect_distance_food = depth_walk_here
5170  end if
5171 
5172  !> #### Call do_this ####
5173  !> As the first step, we use the **do**-procedure `go_down_depth::do_this()`
5174  !! => `the_behaviour::go_down_do_this()` to perform the behaviour desired
5175  !! without changing either the agent or its environment, obtaining the
5176  !! **subjective** values of the `this` behaviour components that later feed
5177  !! into the motivation **expectancy** functions:
5178  !! - `perception_override_light`
5179  !! - `perception_override_depth`
5180  !! - `perception_override_food_dir`
5181  !! - `perception_override_predator`
5182  !! - `perception_override_stomach`
5183  !! - `perception_override_bodymass`
5184  !! - `perception_override_energy`
5185  !! .
5186  call this%do_this( this_agent = this_agent, &
5187  max_depth = max_depth_here, &
5188  depth_walk = depth_walk_here, &
5189  time_step_model = time_step_model_here )
5190 
5191  !> The absolute value of the target depth is equal to the agent's current
5192  !! depth **plus** the depth step class data component this\%distance
5193  !! because the agent is intended to deepen down.
5194  target_depth = this_agent%dpos() + this%distance
5195 
5196  !> #### Calculate expected food increments at the target depth ####
5197  !> ##### Create a virtual expected food item #####
5198  !> First, create a subjective representation of the expected food item that
5199  !! is used as a major reference for calculating fake override perceptions.
5200  !! First, calculate the fake coordinates for the expected food item, a
5201  !! spatial object of the class the_environment::spatial. They are equal
5202  !! to those of the actor agent, with the depth coordinate equal to the
5203  !! target depth.
5204  call expected_food_item_xyz%position( &
5205  spatial(this_agent%xpos(), &
5206  this_agent%ypos(), &
5207  target_depth) )
5208 
5209  !> Make an expected food item using the food_item standard method
5210  !! `make` (the_environment::food_item::make()) with the following
5211  !! parameters: the above spatial location, the size equal to the expected
5212  !! food gain from `do_this`, iid is set to commondata::unknown.
5213  !! Note that the size of the food item is reverse-calculated using the
5214  !! the_environment::mass2size_food() function.
5215  call expected_food_item%make( &
5216  location=expected_food_item_xyz, &
5217  size=mass2size_food(this%expected_food_gain),&
5218  iid=unknown )
5219 
5220  !> Calculate the expected probability of capture (normally using the
5221  !! average distance to the food items under the agent
5222  !! perception::food_dist_below(), see above).
5223  !! Note that the illumination level in the calculation backend is set
5224  !! from the food item's current depth, i.e. the target depth of the agent.
5225  !! This means that the subjective illumination level used in the
5226  !! calculation of the capture probability is reduced automatically
5227  !! according to the agent's target depth.
5228  expected_probability_capture = &
5229  expected_food_item%capture_probability( &
5230  distance=expect_distance_food, &
5231  time_step_model=time_step_model_here )
5232 
5233  !> ##### Calculate food increments #####
5234  !> Build the expected food gain perception.
5235  !> The mass increment that this_agent gets from consuming this
5236  !! food item is defined by `the_body::condition::food_fitting`.
5237  !! @note Note that `the_body::condition::food_fitting` already subtracts
5238  !! processing cost automatically. Note that the expected food
5239  !! increment is weighted by the expected probability of capture of
5240  !! the expected food item.
5241  expect_mass_increment_from_food = &
5242  this_agent%food_fitting(expected_food_item, expect_distance_food) &
5243  * expected_probability_capture
5244 
5245  !> Stomach increment from food is equal to the above value of the expected
5246  !! mass increment. However, stomach increment can only be zero or a
5247  !! positive value.
5248  expect_stomach_increment_from_food = &
5249  max(0.0_srp, expect_mass_increment_from_food)
5250 
5251  !> #### Build the fake perceptions ####
5252  !> ##### Body mass and stomach contents #####
5253  !> Finally, the fake perceptions for the body mass and stomach content
5254  !! are calculated as the current body mass minus the cost of moving to
5255  !! the target depth plus the expected food increment.
5256  expect_mass_perc_override = max( zero, &
5257  this_agent%get_mass() - &
5258  this_agent%living_cost() - &
5259  this%decrement_mass_cost + &
5260  expect_mass_increment_from_food )
5261 
5262  !> The expected fake perception value for the stomach content at the
5263  !! target depth is obtained similarly by adding the expected stomach
5264  !! increment to the current stomach content of the agent.
5265  agent_stomach = this_agent%get_stom_content()
5266  expect_stomach_perc_override = &
5267  max( zero, &
5268  agent_stomach - stomach_emptify_backend(agent_stomach) + &
5269  expect_stomach_increment_from_food )
5270 
5271  !> The expected energy reserves perceived are calculated from the fake
5272  !! perceptions of the mass and length using the_body::energy_reserve()
5273  !! function.
5274  expect_energy_perc_override = &
5275  energy_reserve( expect_mass_perc_override, this_agent%length() + &
5276  this_agent%len_incr(expect_mass_increment_from_food) )
5277 
5278  !> ##### Conspecifics #####
5279  !> The fake perception value for the conspecifics at the target depth is
5280  !! calculated directly from the `this` class data component
5281  !! this\%expected_consp_number.
5282  expect_conspecicifc_perc_override = this%expected_consp_number
5283 
5284  !> ##### Predators #####
5285  !> The fake perception value for the predation risk at the target depth is
5286  !! calculated directly from the `this` class data component
5287  expect_predator_perc_override = this%expected_predation_risk
5288 
5289  !> ##### Environmental perceptions #####
5290  !> The number of food items (direct food perception) is equal to the
5291  !! number of food items currently under the agent.
5292  expect_food_perc_override = n_food_items_below
5293 
5294  !> Depth perception is according to the absolute target depth value.
5295  expect_depth_perc_override = target_depth
5296 
5297  !> Light perception is according to the new depth.
5298  expect_light_perc_override = &
5299  light_depth(depth=expect_depth_perc_override, &
5300  surface_light = &
5301  light_surface(tstep=time_step_model_here, &
5302  is_stochastic=daylight_stochastic) )
5303 
5304  !> #### Calculate motivation expectancies ####
5305  !> The next step is to calculate the motivational expectancies using the
5306  !! fake perceptions to override the default (actual agent's) values.
5307  !> At this stage, first, calculate motivation values resulting from the
5308  !! behaviour done (`go_down_depth::do_this()`) at the previous steps: what
5309  !! would be the motivation values *if* the agent does perform
5310  !! GO_DOWN_DEPTH? Technically, this is done by calling the **neuronal
5311  !! response function**, `percept_components_motiv::motivation_components()`
5312  !! method, for each of the motivational states with `perception_override_`
5313  !! dummy parameters overriding the default values.
5314  !! Here is the list of the fake overriding perceptions for the
5315  !! GO_DOWN_DEPTH behaviour:
5316  !! - `perception_override_light`
5317  !! - `perception_override_depth`
5318  !! - `perception_override_food_dir`
5319  !! - `perception_override_predator`
5320  !! - `perception_override_stomach`
5321  !! - `perception_override_bodymass`
5322  !! - `perception_override_energy`
5323  !! .
5324  ! @note **Expectancy** assessment for **hunger** motivation, using
5325  ! `PERCEPT_COMPONENTS_MOTIV`-bound procedure with intent[in] for
5326  ! `this_agent` now.
5327  call this%expectancy%hunger%percept_component%motivation_components &
5328  (this_agent, &
5329  ! Parameters:: Boolean G x P matrices:
5330  param_gp_matrix_light = light_hunger_genotype_neuronal, &
5331  param_gp_matrix_depth = depth_hunger_genotype_neuronal, &
5332  param_gp_matrix_food_dir = foodcount_hunger_genotype_neuronal, &
5333  param_gp_matrix_food_mem = food_mem_hunger_genotype_neuronal, &
5334  param_gp_matrix_conspec = conspcount_hunger_genotype_neuronal, &
5335  param_gp_matrix_pred_dir = pred_direct_hunger_genotype_neuronal, &
5336  param_gp_matrix_predator = pred_meancount_hunger_genotype_neuronal, &
5337  param_gp_matrix_stomach = stom_hunger_genotype_neuronal, &
5338  param_gp_matrix_bodymass = bodymass_hunger_genotype_neuronal, &
5339  param_gp_matrix_energy = energy_hunger_genotype_neuronal, &
5340  param_gp_matrix_age = age_hunger_genotype_neuronal, &
5341  param_gp_matrix_reprfac = reprfac_hunger_genotype_neuronal, &
5342  ! Parameters :: G x P variances:
5343  param_gerror_cv_light = light_hunger_genotype_neuronal_gerror_cv, &
5344  param_gerror_cv_depth = depth_hunger_genotype_neuronal_gerror_cv, &
5345  param_gerror_cv_food_dir = foodcount_hunger_genotype_neuronal_gerror_cv,&
5346  param_gerror_cv_food_mem = food_mem_hunger_genotype_neuronal_gerror_cv, &
5347  param_gerror_cv_conspec = conspcount_hunger_genotype_neuronal_gerror_cv,&
5348  param_gerror_cv_pred_dir = pred_direct_hunger_genotype_neuronal_gerror_cv,&
5349  param_gerror_cv_predator = pred_meancount_hunger_genotype_neuronal_gerror_cv,&
5350  param_gerror_cv_stomach = stom_hunger_genotype_neuronal_gerror_cv, &
5351  param_gerror_cv_bodymass = bodymass_hunger_genotype_neuronal_gerror_cv, &
5352  param_gerror_cv_energy = energy_hunger_genotype_neuronal_gerror_cv, &
5353  param_gerror_cv_age = age_hunger_genotype_neuronal_gerror_cv, &
5354  param_gerror_cv_reprfac = reprfac_hunger_genotype_neuronal_gerror_cv, &
5355  ! Real agent perception components are now substituted by the *fake*
5356  ! values resulting from executing this behaviour (`do_this` method).
5357  ! This is repeated for all the motivations: *hunger*,
5358  ! *passive avoidance,* *fear state* etc.
5359  perception_override_light = expect_light_perc_override, &
5360  perception_override_depth = expect_depth_perc_override, &
5361  perception_override_food_dir = real(expect_food_perc_override, srp), &
5362  perception_override_predator = expect_predator_perc_override, &
5363  perception_override_stomach = expect_stomach_perc_override, &
5364  perception_override_bodymass = expect_mass_perc_override, &
5365  perception_override_energy = expect_energy_perc_override &
5366  )
5367  !> Real agent perception components are now substituted by the *fake*
5368  !! values resulting from executing this behaviour (`reproduce::do_this()`
5369  !! => `the_behaviour::reproduce_do_this()` method). This is repeated for
5370  !! all the motivations: *hunger*, *passive avoidance,* *active
5371  !! avoidance* etc. These optional **override parameters** are
5372  !! substituted by the "fake" values.
5373 
5374  ! @note **Expectancy** assessment for **fear_defence** motivation,
5375  ! using `PERCEPT_COMPONENTS_MOTIV`-bound procedure with intent[in]
5376  ! for `this_agent` now.
5377  call this%expectancy%fear_defence%percept_component%motivation_components &
5378  (this_agent, &
5379  ! Parameters:: Boolean G x P matrices:
5380  param_gp_matrix_light = light_actv_avoid_genotype_neuronal, &
5381  param_gp_matrix_depth = depth_actv_avoid_genotype_neuronal, &
5382  param_gp_matrix_food_dir = foodcount_actv_avoid_genotype_neuronal, &
5383  param_gp_matrix_food_mem = food_mem_actv_avoid_genotype_neuronal, &
5384  param_gp_matrix_conspec = conspcount_actv_avoid_genotype_neuronal, &
5385  param_gp_matrix_pred_dir = pred_direct_actv_avoid_genotype_neuronal, &
5386  param_gp_matrix_predator = pred_meancount_actv_avoid_genotype_neuronal, &
5387  param_gp_matrix_stomach = stom_actv_avoid_genotype_neuronal, &
5388  param_gp_matrix_bodymass = bodymass_actv_avoid_genotype_neuronal, &
5389  param_gp_matrix_energy = energy_actv_avoid_genotype_neuronal, &
5390  param_gp_matrix_age = age_actv_avoid_genotype_neuronal, &
5391  param_gp_matrix_reprfac = reprfac_actv_avoid_genotype_neuronal, &
5392  ! Parameters :: G x P variances:
5393  param_gerror_cv_light = light_actv_avoid_genotype_neuronal_gerror_cv, &
5394  param_gerror_cv_depth = depth_actv_avoid_genotype_neuronal_gerror_cv, &
5395  param_gerror_cv_food_dir = foodcount_actv_avoid_genotype_neuronal_gerror_cv,&
5396  param_gerror_cv_food_mem = food_mem_actv_avoid_genotype_neuronal_gerror_cv, &
5397  param_gerror_cv_conspec = conspcount_actv_avoid_genotype_neuronal_gerror_cv,&
5398  param_gerror_cv_pred_dir = pred_direct_actv_avoid_genotype_neuronal_gerror_cv,&
5399  param_gerror_cv_predator = pred_meancount_actv_avoid_genotype_neuronal_gerror_cv,&
5400  param_gerror_cv_stomach = stom_actv_avoid_genotype_neuronal_gerror_cv, &
5401  param_gerror_cv_bodymass = bodymass_actv_avoid_genotype_neuronal_gerror_cv,&
5402  param_gerror_cv_energy = energy_actv_avoid_genotype_neuronal_gerror_cv,&
5403  param_gerror_cv_age = age_actv_avoid_genotype_neuronal_gerror_cv, &
5404  param_gerror_cv_reprfac = reprfac_actv_avoid_genotype_neuronal_gerror_cv,&
5405  ! @note Real agent perception components are now **substituted**
5406  ! by the **fake** values resulting from executing this
5407  ! behaviour (`do_this` method).
5408  perception_override_light = expect_light_perc_override, &
5409  perception_override_depth = expect_depth_perc_override, &
5410  perception_override_food_dir = real(expect_food_perc_override, srp), &
5411  perception_override_predator = expect_predator_perc_override, &
5412  perception_override_stomach = expect_stomach_perc_override, &
5413  perception_override_bodymass = expect_mass_perc_override, &
5414  perception_override_energy = expect_energy_perc_override &
5415  )
5416 
5417  ! @note **Expectancy** assessment for **reproduction** motivation,
5418  ! using `PERCEPT_COMPONENTS_MOTIV`-bound procedure with intent[in]
5419  ! for `this_agent` now.
5420  call this%expectancy%reproduction%percept_component%motivation_components &
5421  (this_agent, &
5422  ! Parameters:: Boolean G x P matrices:
5423  param_gp_matrix_light = light_reproduce_genotype_neuronal, &
5424  param_gp_matrix_depth = depth_reproduce_genotype_neuronal, &
5425  param_gp_matrix_food_dir = foodcount_reproduce_genotype_neuronal, &
5426  param_gp_matrix_food_mem = food_mem_reproduce_genotype_neuronal, &
5427  param_gp_matrix_conspec = conspcount_reproduce_genotype_neuronal, &
5428  param_gp_matrix_pred_dir = pred_direct_reproduce_genotype_neuronal, &
5429  param_gp_matrix_predator = pred_meancount_reproduce_genotype_neuronal, &
5430  param_gp_matrix_stomach = stom_reproduce_genotype_neuronal, &
5431  param_gp_matrix_bodymass = bodymass_reproduce_genotype_neuronal, &
5432  param_gp_matrix_energy = energy_reproduce_genotype_neuronal, &
5433  param_gp_matrix_age = age_reproduce_genotype_neuronal, &
5434  param_gp_matrix_reprfac = reprfac_reproduce_genotype_neuronal, &
5435  ! Parameters :: G x P variances:
5436  param_gerror_cv_light = light_reproduce_genotype_neuronal_gerror_cv, &
5437  param_gerror_cv_depth = depth_reproduce_genotype_neuronal_gerror_cv, &
5438  param_gerror_cv_food_dir = foodcount_reproduce_genotype_neuronal_gerror_cv,&
5439  param_gerror_cv_food_mem = food_mem_reproduce_genotype_neuronal_gerror_cv, &
5440  param_gerror_cv_conspec = conspcount_reproduce_genotype_neuronal_gerror_cv,&
5441  param_gerror_cv_pred_dir = pred_direct_reproduce_genotype_neuronal_gerror_cv,&
5442  param_gerror_cv_predator = pred_meancount_reproduce_genotype_neuronal_gerror_cv,&
5443  param_gerror_cv_stomach = stom_reproduce_genotype_neuronal_gerror_cv, &
5444  param_gerror_cv_bodymass = bodymass_reproduce_genotype_neuronal_gerror_cv,&
5445  param_gerror_cv_energy = energy_reproduce_genotype_neuronal_gerror_cv,&
5446  param_gerror_cv_age = age_reproduce_genotype_neuronal_gerror_cv, &
5447  param_gerror_cv_reprfac = reprfac_reproduce_genotype_neuronal_gerror_cv,&
5448  ! @note Real agent perception components are now **substituted**
5449  ! by the **fake** values resulting from executing this
5450  ! behaviour (`do_this` method).
5451  perception_override_light = expect_light_perc_override, &
5452  perception_override_depth = expect_depth_perc_override, &
5453  perception_override_food_dir = real(expect_food_perc_override, srp), &
5454  perception_override_predator = expect_predator_perc_override, &
5455  perception_override_stomach = expect_stomach_perc_override, &
5456  perception_override_bodymass = expect_mass_perc_override, &
5457  perception_override_energy = expect_energy_perc_override &
5458  )
5459 
5460  !> Next, from the perceptual components calculated at the previous
5461  !! step we can obtain the **primary** and **final motivation** values by
5462  !! weighed summing.
5463  if (present(rescale_max_motivation)) then
5464  !> Here we can use global maximum motivation across all behaviours and
5465  !! perceptual components if it is provided, for rescaling.
5466  max_motivation = rescale_max_motivation
5467  else
5468  !> Or can rescale using local maximum value for this behaviour only.
5469  max_motivation = this%expectancy%max_perception()
5470  end if
5471 
5472  !> Transfer attention weights from the actor agent `this_agent` to the
5473  !! `this` behaviour component. So, we will now use the updated modulated
5474  !! attention weights of the agent rather than their default parameter
5475  !! values.
5476  call this%attention_transfer(this_agent)
5477 
5478  !> So the primary motivation values are calculated.
5479  call this%expectancy%motivation_primary_calc(max_motivation)
5480 
5481  !> Primary motivations are logged in the @ref intro_debug_mode "debug mode".
5482  call log_dbg( ltag_info // "Primary motivations: " // &
5483  "hunger: " // &
5484  tostr(this%expectancy%hunger%motivation_prim) // &
5485  ", fear_defence: " // &
5486  tostr(this%expectancy%fear_defence%motivation_prim) // &
5487  ", reproduce: " // &
5488  tostr(this%expectancy%reproduction%motivation_prim), &
5489  procname, modname )
5490 
5491  !> There is **no modulation** at this stage, so the final motivation
5492  !! values are the same as primary motivations.
5493  call this%expectancy%modulation_none()
5494 
5495  !> #### Calculate motivation expectancies ####
5496  !> Finally, calculate the finally **expected arousal level for this
5497  !! behaviour**. As in the GOS, the overall arousal is the maximum value
5498  !! among all motivation components.
5499  this%arousal_expected = this%expectancy%max_final()
5500 
5501  !> Log also the final expectancy value in the @ref intro_debug_mode
5502  !! "debug mode".
5503  call log_dbg( ltag_info // "Expectancy: " // tostr(this%arousal_expected),&
5504  procname, modname )
5505 
5506  !> Now as we know the expected arousal, we can choose the behaviour which
5507  !! would minimise this arousal level.
5508 
5509  end subroutine go_down_motivations_expect
5510 
5511  !-----------------------------------------------------------------------------
5512  !> Execute this behaviour component "go down" by `this_agent` agent.
5513  !! @note The "do"-function does not change the state of the this_agent
5514  !! or the the environment (the food item), the "execute" function
5515  !! **does**.
5516  subroutine go_down_do_execute( this, this_agent, &
5517  max_depth, environments, depth_walk )
5518  !> @param[inout] this the object itself.
5519  class(go_down_depth), intent(inout) :: this
5520  !> @param[in] this_agent is the actor agent which goes down.
5521  class(appraisal), intent(inout) :: this_agent
5522  !> @param[in] max_depth is the optional maximum limit on the depth.
5523  real(SRP), optional, intent(in) :: max_depth
5524  !> @param[in] environments optional array of the all available
5525  !! environments where the this agent can be in, needed for the
5526  !! calculation of the depth limits. If such an array of the
5527  !! environments is provided, `max_depth` has precedence.
5528  class(environment), dimension(:), optional, intent(in) :: environments
5529  !> @param[in] depth_walk Optional downward walk size, by how deep
5530  !! the agent goes down.
5531  real(SRP), intent(in), optional :: depth_walk
5532 
5533  ! Local copy of optionals
5534  real(SRP) :: depth_walk_here, max_depth_here
5535 
5536  !> ### Implementation details ###
5537  !> #### Initial checks ####
5538  !> First, check if the size of the downward walk `depth_walk` dummy
5539  !! parameter is provided.
5540  if (present(depth_walk)) then
5541  depth_walk_here = depth_walk
5542  else
5543  !> If it is not provided, it is set equal to the agent's body length
5544  !! multiplied by the commondata::up_down_walk_step_stdlength_factor
5545  !! factor parameter. Calculated by `the_behaviour::depth_walk_default()`.
5546  depth_walk_here = depth_walk_default( this_agent%get_length() )
5547  end if
5548 
5549  ! @note The `GET_MAXDEPTH` block is used unchanged in several places,
5550  ! however, it cannot be isolated into a single procedure because
5551  ! its code heavily uses optional parameters checks using `present`
5552  ! intrinsic function that should apply to the called procedure.
5553  get_maxdepth: block
5554  !> Check downward step size. Here, first, check if the target
5555  !! depth is likely to go beyond the environment depth limits and reduce
5556  !! the downward walk step size accordingly. Either the explicitly provided
5557  !! maximum depth dummy parameter `max_depth` or an array of possible
5558  !! environment objects where the `this_agent` actor agent can be located
5559  !! is used to get the depth limit.
5560  max_depth_here = missing
5561 
5562  if (present(environments)) then
5563  !> If the array of possible environment objects that can contain
5564  !! the max_depth actor agent is provided, the check involves the
5565  !! `the_environment::spatial::find_environment()` function to find the
5566  !! specific environment object the agent is currently in followed by
5567  !! `the_environment::environment::depth_max()` to find the minimum
5568  !! depth in this environment object.
5569  max_depth_here = &
5570  environments(this_agent%find_environment(environments))%depth_max()
5571  else
5572  !> If the array of possible environment objects that can contain the
5573  !! actor agent is not provided, the current environment is obtained
5574  !! from the global array the_environment::global_habitats_available.
5575  !! In this case, the environment that actor agent is within is
5576  !! determined using the the_environment::spatial::find_environment()
5577  !! method, which is in followed by
5578  !! the_environment::environment::depth_max()` to find the minimum
5579  !! depth in this environment object.
5580  max_depth_here = global_habitats_available( &
5581  this_agent%find_environment( &
5582  global_habitats_available) &
5583  )%depth_max()
5584  end if
5585 
5586  !> If `max_depth` is provided, it has precedence over the depth
5587  !! detected explicitly or implicitly from the environment objects.
5588  if (present(max_depth)) max_depth_here = max_depth
5589 
5590  !> In the case neither of the above optional parameters are provided,
5591  !! the maximum depth is set as the depth of the actor agent (with an
5592  !! additional condition that it should exceed zero), so movement
5593  !! down would be **impossible**.
5594  if (max_depth_here .feq. missing) &
5595  max_depth_here = max( 0.0_srp, this_agent%dpos() )
5596  end block get_maxdepth
5597 
5598  !> #### Step 1: do_this ####
5599  !> First, we use the intent-in **do**-procedure `go_down_depth::do_this()`
5600  !! to perform the behaviour desired and get the **expectations of fake
5601  !! perceptions** for GOS. As a result, we now get this\%decrement_mass_cost
5602  !! that defines the cost of buoyancy-based movement downwards.
5603  !! @note At this stage, the state of the actor agent is not changed.
5604  call this%do_this(this_agent = this_agent , &
5605  max_depth = max_depth_here, depth_walk = depth_walk_here )
5606 
5607 
5608  !> #### Step 2: Change the agent ####
5609  !> Change the location of the actor agent, moving it down to the distance
5610  !! this\%distance.
5611  call this_agent%position( spatial( this_agent%xpos(), &
5612  this_agent%ypos(), &
5613  this_agent%dpos() + this%distance) )
5614 
5615  !> Decrement the body mass as a consequence of transfer down. This body
5616  !! mass decrement constitutes the (small) energetic cost of locomotion.
5617  !! Call `the_body::condition::set_mass()` for this.
5618  call this_agent%set_mass( value_set = this_agent%get_mass() - &
5619  this%decrement_mass_cost, &
5620  update_history = .true. )
5621  !> Additionally, also call the `the_body::condition::set_length()` method
5622  !! to update the body length history stack. However, the value_set
5623  !! parameter here is just the current value. This fake re-setting of the
5624  !! body length is done to keep both mass and length synchronised in their
5625  !! history stack arrays (there is no procedure for only updating history).
5626  call this_agent%set_length( value_set = this_agent%get_length(), &
5627  update_history = .true. )
5628 
5629  !> After resetting the body mass, update energy reserves of the agent, that
5630  !! depend on both the length and the mass.
5631  call this_agent%energy_update()
5632 
5633  !> Check if the agent is starved to death. If yes, the agent can
5634  !! die without going any further.
5635  if (this_agent%starved_death()) call this_agent%dies()
5636 
5637  !> #### Step 3: Change the environment ####
5638  !> Moving down by the agent does not affect the environmental objects.
5639 
5640  end subroutine go_down_do_execute
5641 
5642  !-----------------------------------------------------------------------------
5643  !> Initialise the **go up to a shallower spatial layer** behaviour component
5644  !! to a zero state.
5645  elemental subroutine go_up_depth_init_zero(this)
5646  class(go_up_depth), intent(inout) :: this
5647 
5648  !> First init components from the base root class
5649  !! `the_behaviour::behaviour_base`.
5650  !> Mandatory label component that should be read-only.
5651  this%label = "GO_UP_DEPTH"
5652  !> The execution status is always FALSE, can be reset to TRUE only when
5653  !! the behaviour unit is called to execution.
5654  this%is_active = .false.
5655 
5656  !> And the *expectancy* components.
5657  call this%expectancy%init()
5658  this%arousal_expected = 0.0_srp
5659 
5660  !> Abstract `MOVE` component.
5661  this%distance = missing
5662 
5663  !> Then init components of this specific behaviour component extended class.
5664  this%decrement_mass_cost = missing
5665  this%expected_food_gain = missing
5666  this%expected_consp_number = unknown
5667  this%expected_predation_risk = missing
5668 
5669  end subroutine go_up_depth_init_zero
5670 
5671  !-----------------------------------------------------------------------------
5672  !> Do go up by `this_agent` (the actor agent). Subjective assessment of the
5673  !! motivational value for this is based on the number of food items,
5674  !! conspecifics and predators at the layers below the `this_agent` actor
5675  !! agent.
5676  subroutine go_up_do_this(this, this_agent, min_depth, depth_walk, &
5677  predict_window_food, time_step_model)
5678  !> @param[inout] this the object itself.
5679  class(go_up_depth), intent(inout) :: this
5680  !> @param[in] this_agent is the actor agent which goes up.
5681  class(appraisal), intent(in) :: this_agent
5682  !> @param[in] min_depth is the maximum limit on the depth.
5683  real(SRP), intent(in) :: min_depth
5684  !> @param[in] depth_walk Optional downward walk size, by how deep
5685  !! the agent goes down.
5686  real(SRP), intent(in), optional :: depth_walk
5687  !> @param[in] predict_window_food the size of the prediction window, i.e.
5688  !! how many steps back in memory are used to calculate the
5689  !! predicted food gain. This parameter is limited by the maximum
5690  !! commondata::history_size_perception value of the perception
5691  !! memory history size.
5692  integer, optional, intent(in) :: predict_window_food
5693  !> @param[in] time_step_model optional time step of the model, overrides
5694  !! the value calculated from the spatial data.
5695  integer, optional, intent(in) :: time_step_model
5696 
5697  ! Local copies of optionals
5698  real(SRP) :: depth_walk_here
5699 
5700  ! Local copies of optionals.
5701  integer :: predict_window_food_here, time_step_model_here
5702 
5703  ! **WEIGHT_DIRECT** is the relative weight given to the immediate
5704  ! perception of predators over the predators counts in the memory stack.
5705  ! Obtained from global parameters
5706  ! (`commondata::predation_risk_weight_immediate`).
5707  real(SRP), parameter :: WEIGHT_DIRECT = predation_risk_weight_immediate
5708 
5709  ! **MEM_WIND** is the size of the memory window when assessing the
5710  ! predator risk, only this number of the latest elements from the memory
5711  ! stack is taken into account. So we further weight the direct threat
5712  ! over the background risk when making the decision.
5713  ! @note Note that we take into account the whole memory size
5714  ! (commondata::history_size_perception).
5715  integer, parameter :: MEM_WIND = history_size_perception
5716 
5717  !> ### Implementation details ###
5718  !> First, check if the size of the upward walk `depth_walk` dummy
5719  !! parameter is provided.
5720  if (present(depth_walk)) then
5721  depth_walk_here = depth_walk
5722  else
5723  !> If it is not provided, it is set equal to the agent's body length
5724  !! multiplied by the commondata::up_down_walk_step_stdlength_factor
5725  !! factor parameter. Calculated by `the_behaviour::depth_walk_default()`.
5726  depth_walk_here = depth_walk_default( this_agent%get_length() )
5727  end if
5728 
5729  !> Check optional parameter for the food perception memory window. If
5730  !! the `predict_window_food` dummy parameter is not provided, its default
5731  !! value is the proportion of the whole perceptual memory window defined
5732  !! by commondata::history_perception_window_food. Thus, only the
5733  !! latest part of the memory is used for the prediction of the future
5734  !! food gain.
5735  if (present(predict_window_food)) then
5736  predict_window_food_here = predict_window_food
5737  else
5738  predict_window_food_here = floor( history_size_perception * &
5739  history_perception_window_food )
5740  end if
5741 
5742  !> Check optional time step parameter. If unset, use global
5743  !! `commondata::global_time_step_model_current`.
5744  if (present(time_step_model)) then
5745  time_step_model_here = time_step_model
5746  else
5747  time_step_model_here = global_time_step_model_current
5748  end if
5749 
5750  !> #### Upward step size ####
5751  !> Here, first, check if the target depth is likely to go beyond the
5752  !! environment depth limits and reduce the upwnward walk step size
5753  !! accordingly. Namely, if the depth coordinate of the actor agent
5754  !! minus the depth step exceeds the minimum depth, the step is reduced
5755  !! to be within the available environment:
5756  !! @f$ d_{a} - D_{min} - \varepsilon @f$, where @f$ D_{min} @f$ is the
5757  !! maximum depth, @f$ d_{a} @f$ is the agent's current depth and
5758  !! @f$ \varepsilon @f$ is a very small constant defined by the parameter
5759  !! commondata::zero.
5760  if (this_agent%dpos() - depth_walk_here <= min_depth ) &
5761  depth_walk_here = max( 0.0_srp, &
5762  this_agent%dpos() - min_depth - zero )
5763 
5764  !> The upward step size component of the class is then equal to the
5765  !! `depth_walk`.
5766  this%distance = depth_walk_here
5767 
5768  !> #### The cost of swimming up ####
5769  !> The expected cost of the swimming up by the buoyancy is much smaller
5770  !! than active propulsion. It is set as a fraction, defined by the
5771  !! parameter commondata::swimming_cost_factor_buoyancy_down, of active
5772  !! laminar propulsion calculated by function
5773  !! the_body::condition_cost_swimming_burst().
5774  this%decrement_mass_cost = swimming_cost_factor_buoyancy_up * &
5775  this_agent%cost_swim( distance=depth_walk_here, &
5776  exponent=swimming_cost_exponent_laminar )
5777 
5778  !> #### Calculate expected perceptions ####
5779  !> Calculate the number of conspecifics upwards of the agent using the
5780  !! function perception::consp_below().
5781  this%expected_consp_number = this_agent%consp_above()
5782 
5783  !> Calculate the expected predation risk above the agent.
5784  this%expected_predation_risk = &
5785  predation_risk_backend( &
5786  this_agent%pred_above(), &
5787  this_agent%memory_stack%get_pred_mean(mem_wind),&
5788  weight_direct )
5789 
5790  !> Calculate the expected food gain as an average mass of the food items
5791  !! above the agent. It is used by calling perception::food_mass_below()
5792  !! function.
5793  !! This expected food gain is then weighted by the subjective probability
5794  !! of food item capture that is calculated based on the memory
5795  !! the_neurobio::perception::food_probability_capture_subjective().
5796  this%expected_food_gain = this_agent%food_mass_above() * &
5797  this_agent%food_probability_capture_subjective( &
5798  predict_window_food_here, time_step_model_here )
5799 
5800  end subroutine go_up_do_this
5801 
5802  !-----------------------------------------------------------------------------
5803  !> `go_up_depth::motivations_expect()` is a subroutine (re)calculating
5804  !! motivations from fake expected perceptions following from the procedure
5805  !! `go_up_depth::do_this()` => `the_behaviour::go_up_do_this()`.
5806  subroutine go_up_motivations_expect(this, this_agent, depth_walk, &
5807  min_depth, environments, &
5808  time_step_model, rescale_max_motivation)
5809  !> @param[inout] this the object itself.
5810  class(go_up_depth), intent(inout) :: this
5811  !> @param[in] this_agent is the actor agent which goes up.
5812  class(appraisal), intent(in) :: this_agent
5813  !> @param[in] depth_walk The upward walk size, by how deep the agent
5814  !! goes up.
5815  real(SRP), intent(in), optional :: depth_walk
5816  !> @param[in] min_depth is the optional maximum limit on the depth.
5817  real(SRP), intent(in), optional :: min_depth
5818  !> @param[in] environments optional array of the all available
5819  !! environments where the this agent can be in, needed for the
5820  !! calculation of the depth limits. If such an array of the
5821  !! environments is provided, min_depth` has precedence.
5822  class(environment), dimension(:), optional, intent(in) :: environments
5823  !> @param [in] time_step_model optional time step of the model,
5824  !! **overrides** the value calculated from the spatial data.
5825  integer, optional, intent(in) :: time_step_model
5826  !> @param[in] rescale_max_motivation maximum motivation value for
5827  !! rescaling all motivational components for comparison
5828  !! across all motivation and perceptual components and behaviour
5829  !! units.
5830  real(SRP), optional, intent(in) :: rescale_max_motivation
5831 
5832  ! Local copy of optional depth_walk
5833  real(SRP) :: depth_walk_here, min_depth_here
5834 
5835  ! Local copy of optional model time step
5836  integer :: time_step_model_here
5837 
5838  !> Target depth, i.e. the absolute depth of the agent after it moves up.
5839  real(SRP) :: target_depth
5840 
5841  ! Expected food item that is used in the calculations, its properties are
5842  ! based on the average food items that the agent perceives above.
5843  type(food_item) :: expected_food_item
5844 
5845  ! the coordinates of the expected food item.
5846  type(spatial) :: expected_food_item_xyz
5847 
5848  ! The expected distance to the food item at the target upward horizon.
5849  real(SRP) :: expect_distance_food
5850 
5851  ! Expected mass increment from food at the target depth.
5852  real(SRP) :: expect_mass_increment_from_food
5853 
5854  ! Expected stomach increment from food at the target depth.
5855  real(SRP) :: expect_stomach_increment_from_food
5856 
5857  ! The number of food items over the agent, obtained from the current
5858  ! perception object.
5859  integer :: n_food_items_above
5860 
5861  ! Local variable
5862  real(SRP) :: max_motivation ! Local max. over all motivation components.
5863 
5864  !> ### Notable local variables ###
5865  !> #### Perception overrides ####
5866  !> - **expect_food_perc_override** is the fake perception for the food items
5867  !! at the target depth.
5868  integer :: expect_food_perc_override
5869 
5870  !> - **expect_depth_perc_override** is the fake perception of the depth,
5871  !! identical to the target depth.
5872  real(SRP) :: expect_depth_perc_override
5873 
5874  !> - **expect_light_perc_override** is the fake perception of the
5875  !! illumination level at the target depth.
5876  real(SRP) :: expect_light_perc_override
5877 
5878  !> - **expect_mass_perc_override** is the fake perception value for the
5879  !! mass from the expected food.
5880  real(SRP) :: expect_mass_perc_override
5881 
5882  !> - **expect_stomach_perc_override** is the fake perception value for the
5883  !! stomach increment from the expected food.
5884  real(SRP) :: expect_stomach_perc_override
5885 
5886  ! Current stomach contents mass of the actor agent.
5887  real(SRP) :: agent_stomach
5888 
5889  !> - **expect_energy_perc_override** is the fake perception for the energy
5890  !! reserves from the expected food at the target depth.
5891  real(SRP) :: expect_energy_perc_override
5892 
5893  !> - **expected_probability_capture** is the expected probability of capture
5894  !! of the expected food item at the target depth.
5895  real(SRP) :: expected_probability_capture
5896 
5897  !> - **expect_conspecicifc_perc_override** is the fake perception value for
5898  !! the number of conspecifics at the target depth.
5899  integer :: expect_conspecicifc_perc_override
5900 
5901  !> - **expect_predator_perc_override** is fake perception value for the
5902  !! predation risk at the target depth.
5903  !! .
5904  real(SRP) :: expect_predator_perc_override
5905 
5906  ! PROCNAME is the procedure name for logging and debugging
5907  character(len=*), parameter :: PROCNAME = &
5908  "(go_up_motivations_expect)"
5909 
5910  !> ### Implementation details ###
5911  !> #### Sanity checks and preparations ####
5912  !> Initially, check if the size of the upward walk `depth_walk` dummy
5913  !! parameter is provided.
5914  if (present(depth_walk)) then
5915  depth_walk_here = depth_walk
5916  else
5917  !> If it is not provided, it is set equal to the agent's body length
5918  !! multiplied by the commondata::up_down_walk_step_stdlength_factor
5919  !! factor parameter.Calculated by `the_behaviour::depth_walk_default()`.
5920  depth_walk_here = depth_walk_default( this_agent%get_length() )
5921  end if
5922 
5923  ! @note The `GET_MAXDEPTH` block is used unchanged in several places,
5924  ! however, it cannot be isolated into a single procedure because
5925  ! its code heavily uses optional parameters checks using `present`
5926  ! intrinsic function that should apply to the called procedure.
5927  get_maxdepth: block
5928  !> Check upward step size. Here, first, check if the target depth is
5929  !! likely to go beyond the environment depth limits and reduce the upward
5930  !! walk step size accordingly. Either the explicitly provided minimum
5931  !! depth dummy parameter `min_depth` or an array of possible environment
5932  !! objects where the `this_agent` actor agent can be located is used to
5933  !! get the depth limit.
5934  min_depth_here = missing
5935 
5936  if (present(environments)) then
5937  !> If the array of possible environment objects that can contain the
5938  !! actor agent is provided, the check involves the
5939  !! `the_environment::spatial::find_environment()` function to find the
5940  !! specific environment object the agent is currently in followed by
5941  !! `the_environment::environment::depth_min()` to find the minimum
5942  !! depth in this environment object.
5943  min_depth_here = &
5944  environments(this_agent%find_environment(environments))%depth_min()
5945  else
5946  !> If the array of possible environment objects that can contain the
5947  !! actor agent is not provided, the current environment is obtained
5948  !! from the global array the_environment::global_habitats_available.
5949  !! In this case, the environment that actor agent is within is
5950  !! determined using the the_environment::spatial::find_environment()
5951  !! method, which is in followed by
5952  !! the_environment::environment::depth_max()` to find the minimum
5953  !! depth in this environment object.
5954  min_depth_here = global_habitats_available( &
5955  this_agent%find_environment( &
5956  global_habitats_available) &
5957  )%depth_min()
5958  end if
5959 
5960  !> If `min_depth` is provided, it has precedence over the depth
5961  !! detected from environment objects.
5962  if (present(min_depth)) min_depth_here = min_depth
5963 
5964  !> In the case the minimum depth cannot be determined,it is set as
5965  !! the depth of the actor agent (with an additional condition that it
5966  !! should exceed zero), so movement up would be **impossible**.
5967  !! Notably, it is not set to zero, a logical
5968  !! choice, to avoid possible asymmetric effects as the counterpart
5969  !! "move down" procedures use the agent's current depth as a last resort
5970  !! in the analogous case of no depth parameters.
5971  if (min_depth_here .feq. missing) &
5972  min_depth_here = max( 0.0_srp, this_agent%dpos() )
5973  end block get_maxdepth
5974 
5975  !> If the depth coordinate of the actor agent minus the depth step is
5976  !! smaller than the minimum depth, the step is reduced to be strictly within
5977  !! the available environment. However, it should also never be below zero.
5978  if (this_agent%dpos() - depth_walk_here <= min_depth_here ) &
5979  depth_walk_here = max( 0.0_srp, &
5980  this_agent%dpos() - min_depth_here - zero )
5981 
5982  !> Check optional time step parameter. If not provided, use global
5983  !! parameter value from commondata::global_time_step_model_current.
5984  if (present(time_step_model)) then
5985  time_step_model_here = time_step_model
5986  else
5987  time_step_model_here = global_time_step_model_current
5988  end if
5989 
5990  !> Assess the number of food items above using the
5991  !! perception::food_items_above() method.
5992  n_food_items_above = this_agent%food_items_above()
5993 
5994  !> Calculate the expected distance to the food item. It is equal to the
5995  !! average distance to the food items perceived above in case there are
5996  !! any such items perceived above. Calculated using the
5997  !! perception::food_dist_above() method.
5998  if ( n_food_items_above > 0 ) then
5999  expect_distance_food = this_agent%food_dist_above()
6000  else
6001  !> However, if there are no food items above (resulting a
6002  !! commondata::missing distance, see perception::food_dist_below()),
6003  !! the expected distance is set the upward walk distance `depth_walk`,
6004  !! that should be sufficiently long to assure the probability of food
6005  !! item capture is very small or zero.min_depth
6006  expect_distance_food = depth_walk_here
6007  end if
6008 
6009  !> #### Call do_this ####
6010  !> As the first step, we use the **do**-procedure `go_up_depth::do_this()`
6011  !! => `the_behaviour::go_up_do_this()` to perform the behaviour desired
6012  !! without changing either the agent or its environment, obtaining the
6013  !! **subjective** values of the `this` behaviour components that later feed
6014  !! into the motivation **expectancy** functions:
6015  !! - `perception_override_light`
6016  !! - `perception_override_depth`
6017  !! - `perception_override_food_dir`
6018  !! - `perception_override_predator`
6019  !! - `perception_override_stomach`
6020  !! - `perception_override_bodymass`
6021  !! - `perception_override_energy`
6022  !! .
6023  call this%do_this(this_agent = this_agent, &
6024  min_depth = min_depth_here, depth_walk = depth_walk_here )
6025 
6026  !> The absolute value of the target depth is equal to the agent's current
6027  !! depth **minus** the depth step class data component this\%distance
6028  !! because the agent is intended to lift up.
6029  target_depth = this_agent%dpos() - this%distance
6030 
6031  !> #### Calculate expected food increments at the target depth ####
6032  !> ##### Create a virtual expected food item #####
6033  !> First, create a subjective representation of the expected food item that
6034  !! is used as a major reference for calculating fake override perceptions.
6035  !! First, calculate the fake coordinates for the expected food item, a
6036  !! spatial object of the class the_environment::spatial. They are equal
6037  !! to those of the actor agent, with the depth coordinate equal to the
6038  !! target depth.
6039  call expected_food_item_xyz%position( &
6040  spatial(this_agent%xpos(), &
6041  this_agent%ypos(), &
6042  target_depth) )
6043 
6044  !> Make an expected food item using the food_item standard method
6045  !! `make` (the_environment::food_item::make()) with the following
6046  !! parameters: the above spatial location, the size equal to the expected
6047  !! food gain from `do_this`, iid is set to commondata::unknown.
6048  !! Note that the size of the food item is reverse-calculated using the
6049  !! the_environment::mass2size_food() function.
6050  call expected_food_item%make( &
6051  location=expected_food_item_xyz, &
6052  size=mass2size_food(this%expected_food_gain),&
6053  iid=unknown )
6054 
6055  !> Calculate the expected probability of capture (normally using the
6056  !! average distance to the food items above the agent
6057  !! perception::food_dist_above()).
6058  !! Note that the illumination level in the calculation backend is set
6059  !! from the food item's current depth, i.e. the target depth of the agent.
6060  !! This means that the subjective illumination level used in the
6061  !! calculation of the capture probability is increased automatically
6062  !! according to the agent's target depth.
6063  expected_probability_capture = &
6064  expected_food_item%capture_probability( &
6065  distance=expect_distance_food, &
6066  time_step_model=time_step_model_here )
6067 
6068  !> ##### Calculate food increments #####
6069  !> Build the expected food gain perception.
6070  !> The mass increment that this_agent gets from consuming this
6071  !! food item is defined by `the_body::condition::food_fitting`.
6072  !! @note Note that `the_body::condition::food_fitting` already subtracts
6073  !! processing cost automatically. Note that the expected food
6074  !! increment is weighted by the expected probability of capture of
6075  !! the expected food item.
6076  expect_mass_increment_from_food = &
6077  this_agent%food_fitting(expected_food_item, expect_distance_food) &
6078  * expected_probability_capture
6079 
6080  !> Stomach increment from food is equal to the above value of the expected
6081  !! mass increment. However, stomach increment can only be zero or a
6082  !! positive value.
6083  expect_stomach_increment_from_food = &
6084  max(0.0_srp, expect_mass_increment_from_food)
6085 
6086  !> #### Build the fake perceptions ####
6087  !> ##### Body mass and stomach contents #####
6088  !> Finally, the fake perceptions for the body mass and stomach content
6089  !! are calculated as the current body mass minus the cost of moving to
6090  !! the target depth plus the expected food increment.
6091  expect_mass_perc_override = max( zero, &
6092  this_agent%get_mass() - &
6093  this_agent%living_cost() - &
6094  this%decrement_mass_cost + &
6095  expect_mass_increment_from_food )
6096 
6097  !> The expected fake perception value for the stomach content at the
6098  !! target depth is obtained similarly by adding the expected stomach
6099  !! increment to the current stomach content of the agent.
6100  agent_stomach = this_agent%get_stom_content()
6101  expect_stomach_perc_override = &
6102  max( zero, &
6103  agent_stomach - stomach_emptify_backend(agent_stomach) + &
6104  expect_stomach_increment_from_food )
6105 
6106  !> The expected energy reserves perceived are calculated from the fake
6107  !! perceptions of the mass and length using the_body::energy_reserve()
6108  !! function.
6109  expect_energy_perc_override = &
6110  energy_reserve( expect_mass_perc_override, this_agent%length() + &
6111  this_agent%len_incr(expect_mass_increment_from_food) )
6112 
6113  !> ##### Conspecifics #####
6114  !> The fake perception value for the conspecifics at the target depth is
6115  !! calculated directly from the `this` class data component
6116  !! this\%expected_consp_number.
6117  expect_conspecicifc_perc_override = this%expected_consp_number
6118 
6119  !> ##### Predators #####
6120  !> The fake perception value for the predation risk at the target depth is
6121  !! calculated directly from the `this` class data component
6122  expect_predator_perc_override = this%expected_predation_risk
6123 
6124  !> ##### Environmental perceptions #####
6125  !> The number of food items (direct food perception) is equal to the
6126  !! number of food items currently above the agent.
6127  expect_food_perc_override = n_food_items_above
6128 
6129  !> Depth perception is according to the absolute target depth value.
6130  expect_depth_perc_override = target_depth
6131 
6132  !> Light perception is according to the new depth.
6133  expect_light_perc_override = &
6134  light_depth(depth=expect_depth_perc_override, &
6135  surface_light = &
6136  light_surface(tstep=time_step_model_here, &
6137  is_stochastic=daylight_stochastic) )
6138 
6139  !> #### Calculate motivation expectancies ####
6140  !> The next step is to calculate the motivational expectancies using the
6141  !! fake perceptions to override the default (actual agent's) values.
6142  !> At this stage, first, calculate motivation values resulting from the
6143  !! behaviour done (`go_up_depth::do_this()`) at the previous steps: what
6144  !! would be the motivation values *if* the agent does perform
6145  !! GO_UP_DEPTH? Technically, this is done by calling the **neuronal
6146  !! response function**, `percept_components_motiv::motivation_components()`
6147  !! method, for each of the motivational states with `perception_override_`
6148  !! dummy parameters overriding the default values.
6149  !! Here is the list of the fake overriding perceptions for the
6150  !! GO_UP_DEPTH behaviour:
6151  !! - `perception_override_light`
6152  !! - `perception_override_depth`
6153  !! - `perception_override_food_dir`
6154  !! - `perception_override_predator`
6155  !! - `perception_override_stomach`
6156  !! - `perception_override_bodymass`
6157  !! - `perception_override_energy`
6158  !! .
6159  ! @note **Expectancy** assessment for **hunger** motivation, using
6160  ! `PERCEPT_COMPONENTS_MOTIV`-bound procedure with intent[in] for
6161  ! `this_agent` now.
6162  call this%expectancy%hunger%percept_component%motivation_components &
6163  (this_agent, &
6164  ! Parameters:: Boolean G x P matrices:
6165  param_gp_matrix_light = light_hunger_genotype_neuronal, &
6166  param_gp_matrix_depth = depth_hunger_genotype_neuronal, &
6167  param_gp_matrix_food_dir = foodcount_hunger_genotype_neuronal, &
6168  param_gp_matrix_food_mem = food_mem_hunger_genotype_neuronal, &
6169  param_gp_matrix_conspec = conspcount_hunger_genotype_neuronal, &
6170  param_gp_matrix_pred_dir = pred_direct_hunger_genotype_neuronal, &
6171  param_gp_matrix_predator = pred_meancount_hunger_genotype_neuronal, &
6172  param_gp_matrix_stomach = stom_hunger_genotype_neuronal, &
6173  param_gp_matrix_bodymass = bodymass_hunger_genotype_neuronal, &
6174  param_gp_matrix_energy = energy_hunger_genotype_neuronal, &
6175  param_gp_matrix_age = age_hunger_genotype_neuronal, &
6176  param_gp_matrix_reprfac = reprfac_hunger_genotype_neuronal, &
6177  ! Parameters :: G x P variances:
6178  param_gerror_cv_light = light_hunger_genotype_neuronal_gerror_cv, &
6179  param_gerror_cv_depth = depth_hunger_genotype_neuronal_gerror_cv, &
6180  param_gerror_cv_food_dir = foodcount_hunger_genotype_neuronal_gerror_cv,&
6181  param_gerror_cv_food_mem = food_mem_hunger_genotype_neuronal_gerror_cv, &
6182  param_gerror_cv_conspec = conspcount_hunger_genotype_neuronal_gerror_cv,&
6183  param_gerror_cv_pred_dir = pred_direct_hunger_genotype_neuronal_gerror_cv,&
6184  param_gerror_cv_predator = pred_meancount_hunger_genotype_neuronal_gerror_cv,&
6185  param_gerror_cv_stomach = stom_hunger_genotype_neuronal_gerror_cv, &
6186  param_gerror_cv_bodymass = bodymass_hunger_genotype_neuronal_gerror_cv, &
6187  param_gerror_cv_energy = energy_hunger_genotype_neuronal_gerror_cv, &
6188  param_gerror_cv_age = age_hunger_genotype_neuronal_gerror_cv, &
6189  param_gerror_cv_reprfac = reprfac_hunger_genotype_neuronal_gerror_cv, &
6190  ! Real agent perception components are now substituted by the *fake*
6191  ! values resulting from executing this behaviour (`do_this` method).
6192  ! This is repeated for all the motivations: *hunger*,
6193  ! *passive avoidance,* *fear state* etc.
6194  perception_override_light = expect_light_perc_override, &
6195  perception_override_depth = expect_depth_perc_override, &
6196  perception_override_food_dir = real(expect_food_perc_override, srp), &
6197  perception_override_predator = expect_predator_perc_override, &
6198  perception_override_stomach = expect_stomach_perc_override, &
6199  perception_override_bodymass = expect_mass_perc_override, &
6200  perception_override_energy = expect_energy_perc_override &
6201  )
6202  !> Real agent perception components are now substituted by the *fake*
6203  !! values resulting from executing this behaviour (`reproduce::do_this()`
6204  !! => `the_behaviour::reproduce_do_this()` method). This is repeated for
6205  !! all the motivations: *hunger*, *passive avoidance,* *active
6206  !! avoidance* etc. These optional **override parameters** are
6207  !! substituted by the "fake" values.
6208 
6209  ! @note **Expectancy** assessment for **fear_defence** motivation,
6210  ! using `PERCEPT_COMPONENTS_MOTIV`-bound procedure with intent[in]
6211  ! for `this_agent` now.
6212  call this%expectancy%fear_defence%percept_component%motivation_components &
6213  (this_agent, &
6214  ! Parameters:: Boolean G x P matrices:
6215  param_gp_matrix_light = light_actv_avoid_genotype_neuronal, &
6216  param_gp_matrix_depth = depth_actv_avoid_genotype_neuronal, &
6217  param_gp_matrix_food_dir = foodcount_actv_avoid_genotype_neuronal, &
6218  param_gp_matrix_food_mem = food_mem_actv_avoid_genotype_neuronal, &
6219  param_gp_matrix_conspec = conspcount_actv_avoid_genotype_neuronal, &
6220  param_gp_matrix_pred_dir = pred_direct_actv_avoid_genotype_neuronal, &
6221  param_gp_matrix_predator = pred_meancount_actv_avoid_genotype_neuronal, &
6222  param_gp_matrix_stomach = stom_actv_avoid_genotype_neuronal, &
6223  param_gp_matrix_bodymass = bodymass_actv_avoid_genotype_neuronal, &
6224  param_gp_matrix_energy = energy_actv_avoid_genotype_neuronal, &
6225  param_gp_matrix_age = age_actv_avoid_genotype_neuronal, &
6226  param_gp_matrix_reprfac = reprfac_actv_avoid_genotype_neuronal, &
6227  ! Parameters :: G x P variances:
6228  param_gerror_cv_light = light_actv_avoid_genotype_neuronal_gerror_cv, &
6229  param_gerror_cv_depth = depth_actv_avoid_genotype_neuronal_gerror_cv, &
6230  param_gerror_cv_food_dir = foodcount_actv_avoid_genotype_neuronal_gerror_cv,&
6231  param_gerror_cv_food_mem = food_mem_actv_avoid_genotype_neuronal_gerror_cv, &
6232  param_gerror_cv_conspec = conspcount_actv_avoid_genotype_neuronal_gerror_cv,&
6233  param_gerror_cv_pred_dir = pred_direct_actv_avoid_genotype_neuronal_gerror_cv,&
6234  param_gerror_cv_predator = pred_meancount_actv_avoid_genotype_neuronal_gerror_cv,&
6235  param_gerror_cv_stomach = stom_actv_avoid_genotype_neuronal_gerror_cv, &
6236  param_gerror_cv_bodymass = bodymass_actv_avoid_genotype_neuronal_gerror_cv,&
6237  param_gerror_cv_energy = energy_actv_avoid_genotype_neuronal_gerror_cv,&
6238  param_gerror_cv_age = age_actv_avoid_genotype_neuronal_gerror_cv, &
6239  param_gerror_cv_reprfac = reprfac_actv_avoid_genotype_neuronal_gerror_cv,&
6240  ! @note Real agent perception components are now **substituted**
6241  ! by the **fake** values resulting from executing this
6242  ! behaviour (`do_this` method).
6243  perception_override_light = expect_light_perc_override, &
6244  perception_override_depth = expect_depth_perc_override, &
6245  perception_override_food_dir = real(expect_food_perc_override, srp), &
6246  perception_override_predator = expect_predator_perc_override, &
6247  perception_override_stomach = expect_stomach_perc_override, &
6248  perception_override_bodymass = expect_mass_perc_override, &
6249  perception_override_energy = expect_energy_perc_override &
6250  )
6251 
6252  ! @note **Expectancy** assessment for **reproduction** motivation,
6253  ! using `PERCEPT_COMPONENTS_MOTIV`-bound procedure with intent[in]
6254  ! for `this_agent` now.
6255  call this%expectancy%reproduction%percept_component%motivation_components &
6256  (this_agent, &
6257  ! Parameters:: Boolean G x P matrices:
6258  param_gp_matrix_light = light_reproduce_genotype_neuronal, &
6259  param_gp_matrix_depth = depth_reproduce_genotype_neuronal, &
6260  param_gp_matrix_food_dir = foodcount_reproduce_genotype_neuronal, &
6261  param_gp_matrix_food_mem = food_mem_reproduce_genotype_neuronal, &
6262  param_gp_matrix_conspec = conspcount_reproduce_genotype_neuronal, &
6263  param_gp_matrix_pred_dir = pred_direct_reproduce_genotype_neuronal, &
6264  param_gp_matrix_predator = pred_meancount_reproduce_genotype_neuronal, &
6265  param_gp_matrix_stomach = stom_reproduce_genotype_neuronal, &
6266  param_gp_matrix_bodymass = bodymass_reproduce_genotype_neuronal, &
6267  param_gp_matrix_energy = energy_reproduce_genotype_neuronal, &
6268  param_gp_matrix_age = age_reproduce_genotype_neuronal, &
6269  param_gp_matrix_reprfac = reprfac_reproduce_genotype_neuronal, &
6270  ! Parameters :: G x P variances:
6271  param_gerror_cv_light = light_reproduce_genotype_neuronal_gerror_cv, &
6272  param_gerror_cv_depth = depth_reproduce_genotype_neuronal_gerror_cv, &
6273  param_gerror_cv_food_dir = foodcount_reproduce_genotype_neuronal_gerror_cv,&
6274  param_gerror_cv_food_mem = food_mem_reproduce_genotype_neuronal_gerror_cv, &
6275  param_gerror_cv_conspec = conspcount_reproduce_genotype_neuronal_gerror_cv,&
6276  param_gerror_cv_pred_dir = pred_direct_reproduce_genotype_neuronal_gerror_cv,&
6277  param_gerror_cv_predator = pred_meancount_reproduce_genotype_neuronal_gerror_cv,&
6278  param_gerror_cv_stomach = stom_reproduce_genotype_neuronal_gerror_cv, &
6279  param_gerror_cv_bodymass = bodymass_reproduce_genotype_neuronal_gerror_cv,&
6280  param_gerror_cv_energy = energy_reproduce_genotype_neuronal_gerror_cv,&
6281  param_gerror_cv_age = age_reproduce_genotype_neuronal_gerror_cv, &
6282  param_gerror_cv_reprfac = reprfac_reproduce_genotype_neuronal_gerror_cv,&
6283  ! @note Real agent perception components are now **substituted**
6284  ! by the **fake** values resulting from executing this
6285  ! behaviour (`do_this` method).
6286  perception_override_light = expect_light_perc_override, &
6287  perception_override_depth = expect_depth_perc_override, &
6288  perception_override_food_dir = real(expect_food_perc_override, srp), &
6289  perception_override_predator = expect_predator_perc_override, &
6290  perception_override_stomach = expect_stomach_perc_override, &
6291  perception_override_bodymass = expect_mass_perc_override, &
6292  perception_override_energy = expect_energy_perc_override &
6293  )
6294 
6295  !> Next, from the perceptual components calculated at the previous
6296  !! step we can obtain the **primary** and **final motivation** values by
6297  !! weighed summing.
6298  if (present(rescale_max_motivation)) then
6299  !> Here we can use global maximum motivation across all behaviours and
6300  !! perceptual components if it is provided, for rescaling.
6301  max_motivation = rescale_max_motivation
6302  else
6303  !> Or can rescale using local maximum value for this behaviour only.
6304  max_motivation = this%expectancy%max_perception()
6305  end if
6306 
6307  !> Transfer attention weights from the actor agent `this_agent` to the
6308  !! `this` behaviour component. So, we will now use the updated modulated
6309  !! attention weights of the agent rather than their default parameter
6310  !! values.
6311  call this%attention_transfer(this_agent)
6312 
6313  !> So the primary motivation values are calculated.
6314  call this%expectancy%motivation_primary_calc(max_motivation)
6315 
6316  !> Primary motivations are logged in the @ref intro_debug_mode "debug mode".
6317  call log_dbg( ltag_info // "Primary motivations: " // &
6318  "hunger: " // &
6319  tostr(this%expectancy%hunger%motivation_prim) // &
6320  ", fear_defence: " // &
6321  tostr(this%expectancy%fear_defence%motivation_prim) // &
6322  ", reproduce: " // &
6323  tostr(this%expectancy%reproduction%motivation_prim), &
6324  procname, modname )
6325 
6326  !> There is **no modulation** at this stage, so the final motivation
6327  !! values are the same as primary motivations.
6328  call this%expectancy%modulation_none()
6329 
6330  !> #### Calculate motivation expectancies ####
6331  !> Finally, calculate the finally **expected arousal level for this
6332  !! behaviour**. As in the GOS, the overall arousal is the maximum value
6333  !! among all motivation components.
6334  this%arousal_expected = this%expectancy%max_final()
6335 
6336  !> Log also the final expectancy value in the @ref intro_debug_mode
6337  !! "debug mode".
6338  call log_dbg( ltag_info // "Expectancy: " // tostr(this%arousal_expected),&
6339  procname, modname )
6340 
6341  !> Now as we know the expected arousal, we can choose the behaviour which
6342  !! would minimise this arousal level.
6343 
6344  end subroutine go_up_motivations_expect
6345 
6346  !-----------------------------------------------------------------------------
6347  !> Execute this behaviour component "go up" by `this_agent` agent towards.
6348  !! @note The "do"-function does not change the state of the this_agent
6349  !! or the the environment (the food item), the "execute" function
6350  !! **does**.
6351  subroutine go_up_do_execute( this, this_agent, &
6352  min_depth, environments, depth_walk )
6353  !> @param[inout] this the object itself.
6354  class(go_up_depth), intent(inout) :: this
6355  !> @param[in] this_agent is the actor agent which goes up.
6356  class(appraisal), intent(inout) :: this_agent
6357  !> @param[in] min_depth is the optional minimum limit on the depth.
6358  real(SRP), optional, intent(in) :: min_depth
6359  !> @param[in] environments optional array of the all available
6360  !! environments where the this agent can be in, needed for the
6361  !! calculation of the depth limits. If such an array of the
6362  !! environments is provided, `min_depth` has precedence.
6363  class(environment), dimension(:), optional, intent(in) :: environments
6364  !> @param[in] depth_walk Optional upward walk size, by how deep
6365  !! the agent goes up.
6366  real(SRP), intent(in), optional :: depth_walk
6367 
6368  ! Local copies of optionals
6369  real(SRP) :: depth_walk_here, min_depth_here
6370 
6371  !> ### Implementation details ###
6372  !> #### Initial checks ####
6373  !> First, check if the size of the upward walk `depth_walk` dummy
6374  !! parameter is provided.
6375  if (present(depth_walk)) then
6376  depth_walk_here = depth_walk
6377  else
6378  !> If it is not provided, it is set equal to the agent's body length
6379  !! multiplied by the commondata::up_down_walk_step_stdlength_factor
6380  !! factor parameter. Calculated by `the_behaviour::depth_walk_default()`.
6381  depth_walk_here = depth_walk_default( this_agent%get_length() )
6382  end if
6383 
6384  ! @note The `GET_MAXDEPTH` block is used unchanged in several places,
6385  ! however, it cannot be isolated into a single procedure because
6386  ! its code heavily uses optional parameters checks using `present`
6387  ! intrinsic function that should apply to the called procedure.
6388  get_maxdepth: block
6389  !> Check upward step size. Here, first, check if the target depth is
6390  !! likely to go beyond the environment depth limits and reduce the upward
6391  !! walk step size accordingly. Either the explicitly provided minimum
6392  !! depth dummy parameter `min_depth` or an array of possible environment
6393  !! objects where the `this_agent` actor agent can be located is used to
6394  !! get the depth limit.
6395  min_depth_here = missing
6396 
6397  if (present(environments)) then
6398  !> If the array of possible environment objects that can contain the
6399  !! actor agent is provided, the check involves the
6400  !! `the_environment::spatial::find_environment()` function to find the
6401  !! specific environment object the agent is currently in followed by
6402  !! in this `the_environment::environment::depth_min()` to find the
6403  !! minimum depth in this environment object.
6404  min_depth_here = &
6405  environments(this_agent%find_environment(environments))%depth_min()
6406  else
6407  !> If the array of possible environment objects that can contain the
6408  !! actor agent is not provided, the current environment is obtained
6409  !! from the global array the_environment::global_habitats_available.
6410  !! In this case, the environment that actor agent is within is
6411  !! determined using the the_environment::spatial::find_environment()
6412  !! method, which is in followed by
6413  !! the_environment::environment::depth_max()` to find the minimum
6414  !! depth in this environment object.
6415  min_depth_here = global_habitats_available( &
6416  this_agent%find_environment( &
6417  global_habitats_available) &
6418  )%depth_min()
6419  end if
6420 
6421  !> If `min_depth` is provided, it has precedence over the depth
6422  !! detected explicitly or implicitly from the environment objects.
6423  if (present(min_depth)) min_depth_here = min_depth
6424 
6425  !> In the case neither of the above optional parameters are provided,
6426  !! the minimum depth is set as the depth of the actor agent (with an
6427  !! additional condition that it should exceed zero), so movement
6428  !! up would be **impossible**. Notably, it is not set to zero, a logical
6429  !! choice, to avoid possible asymmetric effects as the counterpart
6430  !! "move down" procedures use the agent's current depth as a last resort
6431  !! in the analogous case of no depth parameters.
6432  if (min_depth_here .feq. missing) &
6433  min_depth_here = max( 0.0_srp, this_agent%dpos() )
6434  end block get_maxdepth
6435 
6436  !> #### Step 1: do_this ####
6437  !> First, we use the intent-in **do**-procedure `go_up_depth::do_this()`
6438  !! to perform the behaviour desired and get the **expectations of fake
6439  !! perceptions** for GOS. As a result, we now get this\%decrement_mass_cost
6440  !! that defines the cost of buoyancy-based movement upwards.
6441  !! @note At this stage, the state of the actor agent is not changed.
6442  call this%do_this(this_agent = this_agent , &
6443  min_depth = min_depth_here, depth_walk = depth_walk_here )
6444 
6445 
6446  !> #### Step 2: Change the agent ####
6447  !> Change the location of the actor agent, moving it up to the distance
6448  !! this\%distance.
6449  call this_agent%position( spatial( this_agent%xpos(), &
6450  this_agent%ypos(), &
6451  this_agent%dpos() - this%distance) )
6452 
6453  !> Decrement the body mass as a consequence of transfer upwards. This body
6454  !! mass decrement constitutes the (small) energetic cost of locomotion.
6455  !! Call `the_body::condition::set_mass()` for this.
6456  call this_agent%set_mass( value_set = this_agent%get_mass() - &
6457  this%decrement_mass_cost, &
6458  update_history = .true. )
6459  !> Additionally, also call the `the_body::condition::set_length()` method
6460  !! to update the body length history stack. However, the value_set
6461  !! parameter here is just the current value. This fake re-setting of the
6462  !! body length is done to keep both mass and length synchronised in their
6463  !! history stack arrays (there is no procedure for only updating history).
6464  call this_agent%set_length( value_set = this_agent%get_length(), &
6465  update_history = .true. )
6466 
6467  !> After resetting the body mass, update energy reserves of the agent, that
6468  !! depend on both the length and the mass.
6469  call this_agent%energy_update()
6470 
6471  !> Check if the agent is starved to death. If yes, the agent can
6472  !! die without going any further.
6473  if (this_agent%starved_death()) call this_agent%dies()
6474 
6475  !> #### Step 3: Change the environment ####
6476  !> Moving down by the agent does not affect the environmental objects.
6477 
6478  end subroutine go_up_do_execute
6479 
6480  !-----------------------------------------------------------------------------
6481  !> Initialise the **fake debug behaviour** behaviour component
6482  !! to a zero state.
6483  elemental subroutine debug_base_init_zero(this)
6484  class(debug_base), intent(inout) :: this
6485 
6486  !> First init components from the base root class
6487  !! `the_neurobio::behaviour_base`.
6488  !> Mandatory label component that should be read-only.
6489  this%label = "DEBUG_BASE"
6490  !> The execution status is always FALSE, can be reset to TRUE only when
6491  !! the behaviour unit is called to execution.
6492  !! @note Note that this behaviour unit is never executed.
6493  this%is_active = .false.
6494 
6495  !> And the *expectancy* components.
6496  call this%expectancy%init()
6497  this%arousal_expected = 0.0_srp
6498 
6499  end subroutine debug_base_init_zero
6500 
6501  !-----------------------------------------------------------------------------
6502  !> `the_behaviour::debug_base::motivations_expect()` is a subroutine
6503  !! (re)calculating motivations from fake expected perceptions for the
6504  !! **fake debug behaviour**.
6505  subroutine debug_base_motivations_expect(this, this_agent, time_step_model, &
6506  rescale_max_motivation)
6507  !> @param [inout] this the self object.
6508  class(debug_base), intent(inout) :: this
6509  !> @param[in] this_agent is the actor agent which does reproduce.
6510  class(appraisal), intent(in) :: this_agent
6511  !> @param [in] time_step_model optional time step of the model,
6512  !! **overrides** the value calculated from the spatial data.
6513  integer, optional, intent(in) :: time_step_model
6514  !> @param[in] rescale_max_motivation maximum motivation value for
6515  !! rescaling all motivational components for comparison
6516  !! across all motivation and perceptual components and behaviour
6517  !! units.
6518  real(SRP), optional, intent(in) :: rescale_max_motivation
6519 
6520  ! Local copy of optional model time step
6521  integer :: time_step_model_here
6522 
6523  ! Local variable
6524  real(SRP) :: max_motivation ! Local max. over all motivation components.
6525 
6526  ! PROCNAME is the procedure name for logging and debugging
6527  character(len=*), parameter :: PROCNAME = "(debug_base_motivations_expect)"
6528 
6529  !> ### Implementation notes ###
6530  !> #### Check optional parameters ####
6531  !> Check optional time step parameter. If not provided, use global
6532  !! parameter value from `commondata::global_time_step_model_current`.
6533  if (present(time_step_model)) then
6534  time_step_model_here = time_step_model
6535  else
6536  time_step_model_here = global_time_step_model_current
6537  end if
6538 
6539  !> #### Main processing steps ####
6540  !> This is the **fake debug behaviour**, for which the **do**-procedure
6541  !! is absent.
6542  !!
6543  !> The motivation values resulting from the behaviour are calculated
6544  !! for unchanged perceptions. That is, no fake perceptions are placed
6545  !! into the percept_components_motiv::motivation_components() procedures.
6546  call this%expectancy%hunger%percept_component%motivation_components &
6547  (this_agent, &
6548  ! Parameters:: Boolean G x P matrices:
6549  param_gp_matrix_light = light_hunger_genotype_neuronal, &
6550  param_gp_matrix_depth = depth_hunger_genotype_neuronal, &
6551  param_gp_matrix_food_dir = foodcount_hunger_genotype_neuronal, &
6552  param_gp_matrix_food_mem = food_mem_hunger_genotype_neuronal, &
6553  param_gp_matrix_conspec = conspcount_hunger_genotype_neuronal, &
6554  param_gp_matrix_pred_dir = pred_direct_hunger_genotype_neuronal, &
6555  param_gp_matrix_predator = pred_meancount_hunger_genotype_neuronal, &
6556  param_gp_matrix_stomach = stom_hunger_genotype_neuronal, &
6557  param_gp_matrix_bodymass = bodymass_hunger_genotype_neuronal, &
6558  param_gp_matrix_energy = energy_hunger_genotype_neuronal, &
6559  param_gp_matrix_age = age_hunger_genotype_neuronal, &
6560  param_gp_matrix_reprfac = reprfac_hunger_genotype_neuronal, &
6561  ! Parameters :: G x P variances:
6562  param_gerror_cv_light = light_hunger_genotype_neuronal_gerror_cv, &
6563  param_gerror_cv_depth = depth_hunger_genotype_neuronal_gerror_cv, &
6564  param_gerror_cv_food_dir = foodcount_hunger_genotype_neuronal_gerror_cv,&
6565  param_gerror_cv_food_mem = food_mem_hunger_genotype_neuronal_gerror_cv, &
6566  param_gerror_cv_conspec = conspcount_hunger_genotype_neuronal_gerror_cv,&
6567  param_gerror_cv_pred_dir = pred_direct_hunger_genotype_neuronal_gerror_cv,&
6568  param_gerror_cv_predator = pred_meancount_hunger_genotype_neuronal_gerror_cv,&
6569  param_gerror_cv_stomach = stom_hunger_genotype_neuronal_gerror_cv, &
6570  param_gerror_cv_bodymass = bodymass_hunger_genotype_neuronal_gerror_cv, &
6571  param_gerror_cv_energy = energy_hunger_genotype_neuronal_gerror_cv, &
6572  param_gerror_cv_age = age_hunger_genotype_neuronal_gerror_cv, &
6573  param_gerror_cv_reprfac = reprfac_hunger_genotype_neuronal_gerror_cv &
6574  )
6575 
6576  ! The motivation values resulting from the behaviour are calculated
6577  ! for unchanged perceptions. That is, no fake perceptions are placed
6578  ! into the percept_components_motiv::motivation_components() procedures.
6579  call this%expectancy%fear_defence%percept_component%motivation_components &
6580  (this_agent, &
6581  ! Parameters:: Boolean G x P matrices:
6582  param_gp_matrix_light = light_actv_avoid_genotype_neuronal, &
6583  param_gp_matrix_depth = depth_actv_avoid_genotype_neuronal, &
6584  param_gp_matrix_food_dir = foodcount_actv_avoid_genotype_neuronal, &
6585  param_gp_matrix_food_mem = food_mem_actv_avoid_genotype_neuronal, &
6586  param_gp_matrix_conspec = conspcount_actv_avoid_genotype_neuronal, &
6587  param_gp_matrix_pred_dir = pred_direct_actv_avoid_genotype_neuronal, &
6588  param_gp_matrix_predator = pred_meancount_actv_avoid_genotype_neuronal, &
6589  param_gp_matrix_stomach = stom_actv_avoid_genotype_neuronal, &
6590  param_gp_matrix_bodymass = bodymass_actv_avoid_genotype_neuronal, &
6591  param_gp_matrix_energy = energy_actv_avoid_genotype_neuronal, &
6592  param_gp_matrix_age = age_actv_avoid_genotype_neuronal, &
6593  param_gp_matrix_reprfac = reprfac_actv_avoid_genotype_neuronal, &
6594  ! Parameters :: G x P variances:
6595  param_gerror_cv_light = light_actv_avoid_genotype_neuronal_gerror_cv, &
6596  param_gerror_cv_depth = depth_actv_avoid_genotype_neuronal_gerror_cv, &
6597  param_gerror_cv_food_dir = foodcount_actv_avoid_genotype_neuronal_gerror_cv,&
6598  param_gerror_cv_food_mem = food_mem_actv_avoid_genotype_neuronal_gerror_cv, &
6599  param_gerror_cv_conspec = conspcount_actv_avoid_genotype_neuronal_gerror_cv,&
6600  param_gerror_cv_pred_dir = pred_direct_actv_avoid_genotype_neuronal_gerror_cv,&
6601  param_gerror_cv_predator = pred_meancount_actv_avoid_genotype_neuronal_gerror_cv,&
6602  param_gerror_cv_stomach = stom_actv_avoid_genotype_neuronal_gerror_cv, &
6603  param_gerror_cv_bodymass = bodymass_actv_avoid_genotype_neuronal_gerror_cv,&
6604  param_gerror_cv_energy = energy_actv_avoid_genotype_neuronal_gerror_cv,&
6605  param_gerror_cv_age = age_actv_avoid_genotype_neuronal_gerror_cv, &
6606  param_gerror_cv_reprfac = reprfac_actv_avoid_genotype_neuronal_gerror_cv&
6607  )
6608 
6609  ! The motivation values resulting from the behaviour are calculated
6610  ! for unchanged perceptions. That is, no fake perceptions are placed
6611  ! into the percept_components_motiv::motivation_components() procedures.
6612  call this%expectancy%reproduction%percept_component%motivation_components &
6613  (this_agent, &
6614  ! Parameters:: Boolean G x P matrices:
6615  param_gp_matrix_light = light_reproduce_genotype_neuronal, &
6616  param_gp_matrix_depth = depth_reproduce_genotype_neuronal, &
6617  param_gp_matrix_food_dir = foodcount_reproduce_genotype_neuronal, &
6618  param_gp_matrix_food_mem = food_mem_reproduce_genotype_neuronal, &
6619  param_gp_matrix_conspec = conspcount_reproduce_genotype_neuronal, &
6620  param_gp_matrix_pred_dir = pred_direct_reproduce_genotype_neuronal, &
6621  param_gp_matrix_predator = pred_meancount_reproduce_genotype_neuronal, &
6622  param_gp_matrix_stomach = stom_reproduce_genotype_neuronal, &
6623  param_gp_matrix_bodymass = bodymass_reproduce_genotype_neuronal, &
6624  param_gp_matrix_energy = energy_reproduce_genotype_neuronal, &
6625  param_gp_matrix_age = age_reproduce_genotype_neuronal, &
6626  param_gp_matrix_reprfac = reprfac_reproduce_genotype_neuronal, &
6627  ! Parameters :: G x P variances:
6628  param_gerror_cv_light = light_reproduce_genotype_neuronal_gerror_cv, &
6629  param_gerror_cv_depth = depth_reproduce_genotype_neuronal_gerror_cv, &
6630  param_gerror_cv_food_dir = foodcount_reproduce_genotype_neuronal_gerror_cv,&
6631  param_gerror_cv_food_mem = food_mem_reproduce_genotype_neuronal_gerror_cv, &
6632  param_gerror_cv_conspec = conspcount_reproduce_genotype_neuronal_gerror_cv,&
6633  param_gerror_cv_pred_dir = pred_direct_reproduce_genotype_neuronal_gerror_cv,&
6634  param_gerror_cv_predator = pred_meancount_reproduce_genotype_neuronal_gerror_cv,&
6635  param_gerror_cv_stomach = stom_reproduce_genotype_neuronal_gerror_cv, &
6636  param_gerror_cv_bodymass = bodymass_reproduce_genotype_neuronal_gerror_cv,&
6637  param_gerror_cv_energy = energy_reproduce_genotype_neuronal_gerror_cv,&
6638  param_gerror_cv_age = age_reproduce_genotype_neuronal_gerror_cv, &
6639  param_gerror_cv_reprfac = reprfac_reproduce_genotype_neuronal_gerror_cv &
6640  )
6641 
6642  !> From the perceptual components calculated at the previous
6643  !! step we can obtain the **primary** and **final motivation** values by
6644  !! weighed summing.
6645  if (present(rescale_max_motivation)) then
6646  !> Here we can use global maximum motivation across all behaviours and
6647  !! perceptual components if it is provided, for rescaling.
6648  max_motivation = rescale_max_motivation
6649  else
6650  !> Or can rescale using local maximum value for this behaviour only.
6651  max_motivation = this%expectancy%max_perception()
6652  end if
6653 
6654  !> Transfer attention weights from the actor agent `this_agent` to the
6655  !! `this` behaviour component. So, we will now use the updated modulated
6656  !! attention weights of the agent rather than their default parameter
6657  !! values.
6658  call this%attention_transfer(this_agent)
6659 
6660  !> So the primary motivation values are calculated.
6661  call this%expectancy%motivation_primary_calc(max_motivation)
6662 
6663  !> Primary motivations are logged in the @ref intro_debug_mode "debug mode".
6664  call log_dbg( ltag_info // "Primary motivations: " // &
6665  "hunger: " // &
6666  tostr(this%expectancy%hunger%motivation_prim) // &
6667  ", fear_defence: " // &
6668  tostr(this%expectancy%fear_defence%motivation_prim) // &
6669  ", reproduce: " // &
6670  tostr(this%expectancy%reproduction%motivation_prim), &
6671  procname, modname )
6672 
6673  !> There is **no modulation** at this stage, so the final motivation
6674  !! values are the same as primary motivations.
6675  !! TODO: Should include developmental or other modulation? If yes, need to
6676  !! separate genetic modulation component from
6677  !! `motivation_modulation_genetic` into a procedure bound to
6678  !! `MOTIVATIONS` with `this_agent` as actor.
6679  call this%expectancy%modulation_none()
6680 
6681  !> **Fourth,** Calculate the finally **expected arousal level for this
6682  !! behaviour**. As in the GOS, the overall arousal is the maximum value
6683  !! among all motivation components.
6684  this%arousal_expected = this%expectancy%max_final()
6685 
6686  !> Log also the final expectancy value in the @ref intro_debug_mode
6687  !! "debug mode".
6688  call log_dbg( ltag_info // "Expectancy: " // tostr(this%arousal_expected),&
6689  procname, modname )
6690 
6691  !> Now as we know the expected arousal, we can choose the behaviour which
6692  !! would minimise this arousal level.
6693 
6694  end subroutine debug_base_motivations_expect
6695 
6696  !-----------------------------------------------------------------------------
6697  !> Eat a food item defined by the object `food_item_eaten`.
6698  !! The "do" procedure component of the behaviour element performs the
6699  !! behaviour without affecting the actor agent (the_agent) and the world
6700  !! (here food_item_eaten) which have intent(in), so it only can change
6701  !! the internal representation of the behaviour (the type to which this
6702  !! procedure is bound to, here `the_behaviour::eat_food`). So, here the
6703  !! result of this procedure is assessment of the stomach content increment
6704  !! and body mass increment that would result from eating the **this** food
6705  !! item by the **this_agent**.
6706  !> The **main output** from this **do** procedure is the `this` behavioural
6707  !! unit, namely two of its internal data components:
6708  !! - this\%mass_increment_from_food
6709  !! - this\%stomach_increment_from_food
6710  !! .
6711  !! @note The "do"-function does not change the state of the this_agent
6712  !! or the the environment (the food item), the "execute" function
6713  !! does change them.
6714  !! @note Use subroutine rather than function as the "do"-action can
6715  !! potentially have several results / outputs, affect several
6716  !! components of the behaviour object.
6717  !! @note There are three optional parameters which can be used as "fake"
6718  !! parameters in calculating fake values for subjective expectancy:
6719  !! `distance_food_item`, `capture_prob`, `time_step_model`.
6720  !! If they are not set, true objective values are calculated or used,
6721  !! e.g. time step of the model is taken from
6722  !! `commondata::global_time_step_model_current` and the distance
6723  !! between the agent and the food item `distance_food_item` is
6724  !! calculated from their spatial data.
6725  subroutine eat_food_item_do_this(this, this_agent, food_item_eaten, &
6726  time_step_model, distance_food_item, capture_prob, is_captured)
6727  !> @param[inout] this the object itself.
6728  class(eat_food), intent(inout) :: this
6729  !> @param[in] this_agent is the actor agent which eats the food item.
6730  class(appraisal), intent(in) :: this_agent
6731  !> @param[in] food_item_eaten is the food object that is eaten.
6732  class(food_item), intent(in) :: food_item_eaten
6733 
6734  !> @param[in] time_step_model optional time step of the model, overrides
6735  !! the value calculated from the spatial data.
6736  integer, optional, intent(in) :: time_step_model
6737  !> @param[in] distance_food_item is the optional distance to the food item.
6738  real(SRP), optional, intent(in) :: distance_food_item
6739  !> @param[in] capture_prob is optional probability of capture of this
6740  !! food item, overrides the value calculated from the
6741  !! spatial data.
6742  real(SRP), optional, intent(in) :: capture_prob
6743 
6744  !> @param[out] is_captured optional capture flag, TRUE if the food item is
6745  !! captured by the agent.
6746  logical, optional, intent(out) :: is_captured
6747 
6748  ! PROCNAME is the procedure name for logging and debugging (with MODNAME).
6749  character(len=*), parameter :: PROCNAME="(eat_food_item_do_this)"
6750 
6751  ! Local copy of optional food item capture probability.
6752  real(SRP) :: capture_prob_here, distance_food_item_here
6753 
6754  ! Local copy of the time step parameter.
6755  integer :: time_step_model_here
6756 
6757  !> ### Implementation details ###
6758  !> #### Preliminary checks ####
6759  !> This food item, if found in the perception object, should be available.
6760  !! If not, something wrong has occurred. We cannot process an food item
6761  !! that has been already eaten, so no increments are done and error is
6762  !! reported into the log.
6763  if (food_item_eaten%is_unavailable()) then
6764  call log_dbg( ltag_warn // procname // ", Cannot capture food item " // &
6765  "as it is not available (has been already eaten?). Check code.")
6766  return
6767  end if
6768 
6769  !> Check optional time step parameter.
6770  if (present(time_step_model)) then
6771  time_step_model_here = time_step_model
6772  else
6773  time_step_model_here = global_time_step_model_current
6774  end if
6775 
6776  !> Check distance to the food item. If provided, use the override value,
6777  !! if not, calculate from the the agent and the food item spatial data.
6778  if (present(distance_food_item)) then
6779  distance_food_item_here = distance_food_item
6780  else
6781  distance_food_item_here = this_agent%distance(food_item_eaten)
6782  end if
6783 
6784  !> Check if food item capture probability is supplied.
6785  !! @note If capture probability is supplied as a dummy parameter to
6786  !! this procedure, it will override the intrinsic capture
6787  !! probability that is based on the distance between the predator
6788  !! agent and the food item it is about to eat. This may be for
6789  !! example necessary when a subjective expected motivational
6790  !! expectancy is calculated, it can assume 100% probability and/or
6791  !! weightings of the resulting motivation value(s).
6792  if (present(capture_prob)) then
6793  capture_prob_here = capture_prob
6794  else
6795  !> If the food item capture probability is not supplied, **calculate**
6796  !! it based on the current distance between the predator agent and this
6797  !! food item. (`commondata::food_item_capture_probability` is a baseline
6798  !! value at near-zero distance).
6799  capture_prob_here = &
6800  food_item_eaten%capture_probability( &
6801  distance = distance_food_item_here, &
6802  time_step_model = time_step_model_here )
6803  end if
6804 
6805  !> #### Processing ####
6806  !> The probability that the food item is captured is stochastic and
6807  !! is normally below 100%. However while calculating the behaviour
6808  !! expectancies, the capture probability is set to 1.0 to make
6809  !! the internal subjective processing deterministic.
6810  !! Stochastic capture success is now determined by the
6811  !! `the_environment::food_item::capture_success()` function.
6812  !! @note The distance to the food item `distance_food_item_here` is used
6813  !! here not only to calculate the probability of food item capture
6814  !! (above), but also the fast burst swimming cost of approaching
6815  !! the food item that is about to be eaten.
6816  captured: if (food_item_eaten%capture_success(capture_prob_here)) then
6817  !> ##### Food item is captured #####
6818  !> The food item **is captured**, set the optional logical flag first.
6819  if (present(is_captured)) is_captured = .true.
6820  !> The mass increment that this_agent gets from consuming this
6821  !! food item is defined by `the_body::condition::food_fitting`.
6822  !! @note Note that `the_body::condition::food_fitting` already subtracts
6823  !! processing cost.
6824  this%mass_increment_from_food = this%mass_increment_from_food + &
6825  this_agent%food_fitting(food_item_eaten, distance_food_item_here)
6826  this%stomach_increment_from_food = this%mass_increment_from_food
6827  else captured
6828  !> ##### Food item is not captured #####
6829  !> The food item is **not** captured, set the optional logical flag first.
6830  if (present(is_captured)) is_captured = .false.
6831  !> If the food item is **not captured**, the agent has only to
6832  !! pay the energetic **processing cost** without food gain.
6833  !! The cost (mass decrement) is defined by
6834  !! `the_body::condition::food_process_cost()`. The stomach contents
6835  !! mass does not change in this case.
6836  this%mass_increment_from_food = this%mass_increment_from_food - &
6837  this_agent%food_process_cost(food_item_eaten, distance_food_item_here)
6838  this%stomach_increment_from_food = 0.0_srp
6839  end if captured
6840 
6841  end subroutine eat_food_item_do_this
6842 
6843  !-----------------------------------------------------------------------------
6844  !> `eat_food::motivations_expect()` is a subroutine (re)calculating
6845  !! motivations from fake expected perceptions following from the procedure
6846  !! `eat_food::do_this()` => `the_behaviour::eat_food_item_do_this()`.
6847  subroutine eat_food_item_motivations_expect(this,this_agent,food_item_eaten,&
6848  time_step_model, distance_food_item, capture_prob, &
6849  rescale_max_motivation )
6850 
6851  !> @param [inout] this the self object.
6852  class(eat_food), intent(inout) :: this
6853  !> @param[in] this_agent is the actor agent which does eat.
6854  class(appraisal), intent(in) :: this_agent
6855  !> @param[in] food_item_eaten is the food item object that is eaten.
6856  class(food_item), intent(in) :: food_item_eaten
6857 
6858  !> @param [in] time_step_model optional time step of the model,
6859  !! **overrides** the value calculated from the spatial data.
6860  integer, optional, intent(in) :: time_step_model
6861  !> @param[in] distance_food_item optional distance to the food item,
6862  !! **overrides** the value calculated from the spatial data.
6863  real(SRP), optional, intent(in) :: distance_food_item
6864  !> @param[in] capture_prob is optional probability of capture of this
6865  !! food item, **overrides** the value calculated from the
6866  !! spatial data.
6867  real(SRP), optional, intent(in) :: capture_prob
6868 
6869  !> @param[in] rescale_max_motivation maximum motivation value for
6870  !! rescaling all motivational components for comparison
6871  !! across all motivation and perceptual components and behaviour
6872  !! units.
6873  real(SRP), optional, intent(in) :: rescale_max_motivation
6874 
6875  ! Local copy of optionals, capture probability, override distance.
6876  real(SRP) :: capture_prob_here, distance_food_item_here
6877 
6878  ! Local copy of optional model time step
6879  integer :: time_step_model_here
6880 
6881  ! Local variables
6882  real(SRP) :: max_motivation ! Local max. over all motivation components.
6883 
6884  !> ### Notable local parameters ###
6885  !> #### food_capture_prob ####
6886  !> `FOOD_CAPTURE_PROB` is the expected (subjective) food item capture
6887  !! probability parameter. We assume that the agent assumes 100% probability
6888  !! of capture of the food item.
6889  !! @note The probability is here > 1.0 to make sure the procedure
6890  !! is never stochastic (subjective prob=1) and the food item
6891  !! is always caught (the stochastic function it is based on
6892  !! random_value[0..1] < P ).
6893  real(SRP), parameter :: FOOD_CAPTURE_PROB = 1.1_srp
6894 
6895  !> #### Stomach contents ####
6896  !> `stomach_increment_from_food_perc` is expected increment of the stomach
6897  !! contents that is used in the fake perception value in the neuronal
6898  !! response function.
6899  real(SRP) :: stomach_increment_from_food_perc
6900 
6901  !> `stomach_overrride_perc` is the fake perception value for the
6902  !! stomach contents that goes into the neuronal response function.
6903  real(SRP) :: stomach_overrride_perc
6904 
6905  !> #### Body mass ####
6906  !> `mass_increment_from_food_perc` is the expected increment of the agent's
6907  !! body mass that is used in the fake perception value in the neuronal
6908  !! response function.
6909  real(SRP) :: mass_increment_from_food_perc
6910 
6911  !> `bodymass_override_perc` is the fake perception value for the body mass
6912  !! that goes into the neuronal response function.
6913  real(SRP) :: bodymass_override_perc
6914 
6915  !> #### energy_override_perc ####
6916  !> `energy_override_perc` is the fake perception value that goes into
6917  !! the neuronal response function.
6918  real(SRP) :: energy_override_perc
6919 
6920  !> #### capture_prob_intrinsic ####
6921  !> `capture_prob_intrinsic` is the intrinsic probability of capture of the
6922  !! this food item. It is calculated using the
6923  !! `food_item::capture_probability()` method.
6924  real(SRP) :: capture_prob_intrinsic
6925 
6926  ! Local value of the current agent stomach contents.
6927  real(SRP) :: agent_stomach
6928 
6929  ! PROCNAME is the procedure name for logging and debugging
6930  character(len=*), parameter :: PROCNAME = &
6931  "(eat_food_item_motivations_expect)"
6932 
6933  !> ### Implementation details ###
6934  !> #### Preliminary steps and checks ####
6935  !> Check optional time step parameter. If not provided, use global
6936  !! parameter value from `commondata::global_time_step_model_current`.
6937  if (present(time_step_model)) then
6938  time_step_model_here = time_step_model
6939  else
6940  time_step_model_here = global_time_step_model_current
6941  end if
6942 
6943  !> Check distance to the food item. If provided, use the override value,
6944  !! if not, calculate from the the agent and the food item spatial data.
6945  if (present(distance_food_item)) then
6946  distance_food_item_here = distance_food_item
6947  else
6948  distance_food_item_here = this_agent%distance(food_item_eaten)
6949  end if
6950 
6951  !> Check if food item capture probability is supplied.
6952  !! If capture probability is supplied as a dummy parameter to
6953  !! this procedure, it will override the intrinsic capture
6954  !! probability that is based on the distance between the predator
6955  !! agent and the food item it is about to eat. This may be for
6956  !! example necessary when a subjective expected motivational
6957  !! expectancy is calculated, it can assume 100% probability and/or
6958  !! weightings of the resulting motivation value(s).
6959  if (present(capture_prob)) then
6960  capture_prob_here = capture_prob
6961  else
6962  !> If the food item capture probability is not supplied, expectancy is
6963  !! based on a 100% capture probability.
6964  !! @warning Unlike the `eat_food::do_this()` procedure where the capture
6965  !! probability is calculated from the true objective values,
6966  !! the subjective expectancies are based by default on **100%
6967  !! expected probability** of this food item capture.
6968  capture_prob_here = food_capture_prob
6969  end if
6970 
6971  !> The intrinsic (objective) probability of capture of this food item
6972  !! `capture_prob_intrinsic` is calculated using the
6973  !! `food_item::capture_probability()` method.
6974  capture_prob_intrinsic = &
6975  food_item_eaten%capture_probability(distance=distance_food_item_here, &
6976  time_step_model=time_step_model_here)
6977 
6978  ! Produce diagnostic logger message in the @ref intro_debug_mode DEBUG mode.
6979  call log_dbg( ltag_info // "Distance to the food item: " // &
6980  tostr(distance_food_item_here) // &
6981  ", intrinsic capture probability: " // &
6982  tostr(capture_prob_intrinsic) // ".", procname, modname )
6983 
6984  !> #### Main processing steps ####
6985  !> **First,** we use the **do**-procedure `eat_food::do_this()` =>
6986  !! `the_behaviour::eat_food_item_do_this()` to perform the behaviour desired
6987  !! without changing either the agent or its environment and here find
6988  !! **representation** values that later feed into the motivation
6989  !! **expectancy** functions.
6990  !! @note Note that the optional capture success flag is not used here
6991  !! as what is important for expectancy calculation is the agent's
6992  !! weight and stomach increments only.
6993  !! @note The dummy parameter `time_step_model` is not used here for
6994  !! calculating the capture probability because a fixed fake value
6995  !! of the later `FOOD_CAPTURE_PROB` is used.
6996  call this%do_this( this_agent = this_agent, &
6997  food_item_eaten = food_item_eaten, &
6998  distance_food_item = distance_food_item_here, &
6999  capture_prob = capture_prob_here )
7000 
7001  !> We then weight the subjective increments of the body mass and
7002  !! stomach content that are expected from eating this food item by the
7003  !! **intrinsic objective capture probability** `capture_prob_intrinsic`
7004  !! calculated for the current time step on the basis of the distance
7005  !! between the agent and the food item.
7006  stomach_increment_from_food_perc = this%stomach_increment_from_food * &
7007  capture_prob_intrinsic
7008 
7009  mass_increment_from_food_perc = this%mass_increment_from_food * &
7010  capture_prob_intrinsic
7011 
7012  ! Produce diagnostic logger message in the @ref intro_debug_mode DEBUG mode.
7013  call log_dbg( ltag_info // "Raw stomach increment: " // &
7014  tostr(this%stomach_increment_from_food) // &
7015  ", raw mass increment: " // &
7016  tostr(this%mass_increment_from_food) // ".", &
7017  procname, modname )
7018  call log_dbg( ltag_info // "Subjective stomach increment (weighted " // &
7019  "by intrinsic probability): " // &
7020  tostr(stomach_increment_from_food_perc) // &
7021  ", subjective mass increment (weighted by intrinsic " // &
7022  "probability): " // tostr(mass_increment_from_food_perc), &
7023  procname, modname )
7024 
7025  !> After this, it is possible to calculate the fake perceptions for the
7026  !! stomach contents (`stomach_overrride_perc`), body mass
7027  !! (`bodymass_override_perc`) and the energy reserves
7028  !! (`energy_override_perc`). These values are ready to be passed
7029  !! to the neuronal response function.
7030  agent_stomach = this_agent%get_stom_content()
7031  stomach_overrride_perc = &
7032  max( zero, &
7033  agent_stomach - &
7034  stomach_emptify_backend(agent_stomach) + &
7035  stomach_increment_from_food_perc )
7036 
7037  bodymass_override_perc = &
7038  max( zero, &
7039  this_agent%mass() - &
7040  this_agent%living_cost() + &
7041  mass_increment_from_food_perc )
7042 
7043  energy_override_perc = &
7044  energy_reserve( bodymass_override_perc, this_agent%length() + &
7045  this_agent%len_incr(mass_increment_from_food_perc)&
7046  )
7047 
7048  !> **Second,** we calculate motivation values resulting from the behaviour
7049  !! done (`eat_food::do_this()`) at the previous step: what would be the
7050  !! motivation values *if* the agent eats this food item? This is
7051  !! done by calling the **neuronal response function**,
7052  !! `percept_components_motiv::motivation_components()`
7053  !! method, for each of the motivational states with `perception_override_`
7054  !! dummy parameters overriding the default values:
7055  !! - `perception_override_stomach`;
7056  !! - `perception_override_bodymass`;
7057  !! - `perception_override_energy`.
7058  !! .
7059  ! @note **Expectancy** assessment for **hunger** motivation, using
7060  ! `PERCEPT_COMPONENTS_MOTIV`-bound procedure with intent[in] for
7061  ! `this_agent` now.
7062  call this%expectancy%hunger%percept_component%motivation_components &
7063  (this_agent, &
7064  ! Parameters:: Boolean G x P matrices:
7065  param_gp_matrix_light = light_hunger_genotype_neuronal, &
7066  param_gp_matrix_depth = depth_hunger_genotype_neuronal, &
7067  param_gp_matrix_food_dir = foodcount_hunger_genotype_neuronal, &
7068  param_gp_matrix_food_mem = food_mem_hunger_genotype_neuronal, &
7069  param_gp_matrix_conspec = conspcount_hunger_genotype_neuronal, &
7070  param_gp_matrix_pred_dir = pred_direct_hunger_genotype_neuronal, &
7071  param_gp_matrix_predator = pred_meancount_hunger_genotype_neuronal, &
7072  param_gp_matrix_stomach = stom_hunger_genotype_neuronal, &
7073  param_gp_matrix_bodymass = bodymass_hunger_genotype_neuronal, &
7074  param_gp_matrix_energy = energy_hunger_genotype_neuronal, &
7075  param_gp_matrix_age = age_hunger_genotype_neuronal, &
7076  param_gp_matrix_reprfac = reprfac_hunger_genotype_neuronal, &
7077  ! Parameters :: G x P variances:
7078  param_gerror_cv_light = light_hunger_genotype_neuronal_gerror_cv, &
7079  param_gerror_cv_depth = depth_hunger_genotype_neuronal_gerror_cv, &
7080  param_gerror_cv_food_dir = foodcount_hunger_genotype_neuronal_gerror_cv,&
7081  param_gerror_cv_food_mem = food_mem_hunger_genotype_neuronal_gerror_cv, &
7082  param_gerror_cv_conspec = conspcount_hunger_genotype_neuronal_gerror_cv,&
7083  param_gerror_cv_pred_dir = pred_direct_hunger_genotype_neuronal_gerror_cv,&
7084  param_gerror_cv_predator = pred_meancount_hunger_genotype_neuronal_gerror_cv,&
7085  param_gerror_cv_stomach = stom_hunger_genotype_neuronal_gerror_cv, &
7086  param_gerror_cv_bodymass = bodymass_hunger_genotype_neuronal_gerror_cv, &
7087  param_gerror_cv_energy = energy_hunger_genotype_neuronal_gerror_cv, &
7088  param_gerror_cv_age = age_hunger_genotype_neuronal_gerror_cv, &
7089  param_gerror_cv_reprfac = reprfac_hunger_genotype_neuronal_gerror_cv, &
7090  ! Real agent perception components are now substituted by
7091  ! the *fake* values resulting from executing this
7092  ! behaviour (`do_this` method). This is repeated for all the motivatios:
7093  ! *hunger*, *passive avoidance,* *fear state* etc.
7094  perception_override_stomach = stomach_overrride_perc, &
7095  perception_override_bodymass = bodymass_override_perc, &
7096  perception_override_energy = energy_override_perc &
7097  )
7098  !> Real agent perception components are now substituted by
7099  !! the *fake* values resulting from executing this
7100  !! behaviour (`eat_food::do_this()` =>
7101  !! `the_behaviour::eat_food_item_do_this()` method). This is repeated
7102  !! for all the motivatios: *hunger*, *passive avoidance,* *active
7103  !! avoidance* etc. These optional **override parameters** are
7104  !! substituted by the "fake" values:
7105  !! - `perception_override_stomach`;
7106  !! - `perception_override_bodymass`;
7107  !! - `perception_override_energy`.
7108  !! .
7109 
7110  ! @note **Expectancy** assessment for **fear_defence** motivation,
7111  ! using `PERCEPT_COMPONENTS_MOTIV`-bound procedure with intent[in]
7112  ! for `this_agent` now.
7113  call this%expectancy%fear_defence%percept_component%motivation_components &
7114  (this_agent, &
7115  ! Parameters:: Boolean G x P matrices:
7116  param_gp_matrix_light = light_actv_avoid_genotype_neuronal, &
7117  param_gp_matrix_depth = depth_actv_avoid_genotype_neuronal, &
7118  param_gp_matrix_food_dir = foodcount_actv_avoid_genotype_neuronal, &
7119  param_gp_matrix_food_mem = food_mem_actv_avoid_genotype_neuronal, &
7120  param_gp_matrix_conspec = conspcount_actv_avoid_genotype_neuronal, &
7121  param_gp_matrix_pred_dir = pred_direct_actv_avoid_genotype_neuronal, &
7122  param_gp_matrix_predator = pred_meancount_actv_avoid_genotype_neuronal, &
7123  param_gp_matrix_stomach = stom_actv_avoid_genotype_neuronal, &
7124  param_gp_matrix_bodymass = bodymass_actv_avoid_genotype_neuronal, &
7125  param_gp_matrix_energy = energy_actv_avoid_genotype_neuronal, &
7126  param_gp_matrix_age = age_actv_avoid_genotype_neuronal, &
7127  param_gp_matrix_reprfac = reprfac_actv_avoid_genotype_neuronal, &
7128  ! Parameters :: G x P variances:
7129  param_gerror_cv_light = light_actv_avoid_genotype_neuronal_gerror_cv, &
7130  param_gerror_cv_depth = depth_actv_avoid_genotype_neuronal_gerror_cv, &
7131  param_gerror_cv_food_dir = foodcount_actv_avoid_genotype_neuronal_gerror_cv,&
7132  param_gerror_cv_food_mem = food_mem_actv_avoid_genotype_neuronal_gerror_cv, &
7133  param_gerror_cv_conspec = conspcount_actv_avoid_genotype_neuronal_gerror_cv,&
7134  param_gerror_cv_pred_dir = pred_direct_actv_avoid_genotype_neuronal_gerror_cv,&
7135  param_gerror_cv_predator = pred_meancount_actv_avoid_genotype_neuronal_gerror_cv,&
7136  param_gerror_cv_stomach = stom_actv_avoid_genotype_neuronal_gerror_cv, &
7137  param_gerror_cv_bodymass = bodymass_actv_avoid_genotype_neuronal_gerror_cv,&
7138  param_gerror_cv_energy = energy_actv_avoid_genotype_neuronal_gerror_cv,&
7139  param_gerror_cv_age = age_actv_avoid_genotype_neuronal_gerror_cv, &
7140  param_gerror_cv_reprfac = reprfac_actv_avoid_genotype_neuronal_gerror_cv,&
7141  ! @note Real agent perception components are now **substituted**
7142  ! by the **fake** values resulting from executing this
7143  ! behaviour (`do_this` method).
7144  perception_override_stomach = stomach_overrride_perc, &
7145  perception_override_bodymass = bodymass_override_perc, &
7146  perception_override_energy = energy_override_perc &
7147  )
7148 
7149  ! @note **Expectancy** assessment for **reproduction** motivation, using
7150  ! `PERCEPT_COMPONENTS_MOTIV`-bound procedure with intent[in] for
7151  ! `this_agent` now.
7152  call this%expectancy%reproduction%percept_component%motivation_components &
7153  (this_agent, &
7154  ! Parameters:: Boolean G x P matrices:
7155  param_gp_matrix_light = light_reproduce_genotype_neuronal, &
7156  param_gp_matrix_depth = depth_reproduce_genotype_neuronal, &
7157  param_gp_matrix_food_dir = foodcount_reproduce_genotype_neuronal, &
7158  param_gp_matrix_food_mem = food_mem_reproduce_genotype_neuronal, &
7159  param_gp_matrix_conspec = conspcount_reproduce_genotype_neuronal, &
7160  param_gp_matrix_pred_dir = pred_direct_reproduce_genotype_neuronal, &
7161  param_gp_matrix_predator = pred_meancount_reproduce_genotype_neuronal, &
7162  param_gp_matrix_stomach = stom_reproduce_genotype_neuronal, &
7163  param_gp_matrix_bodymass = bodymass_reproduce_genotype_neuronal, &
7164  param_gp_matrix_energy = energy_reproduce_genotype_neuronal, &
7165  param_gp_matrix_age = age_reproduce_genotype_neuronal, &
7166  param_gp_matrix_reprfac = reprfac_reproduce_genotype_neuronal, &
7167  ! Parameters :: G x P variances:
7168  param_gerror_cv_light = light_reproduce_genotype_neuronal_gerror_cv, &
7169  param_gerror_cv_depth = depth_reproduce_genotype_neuronal_gerror_cv, &
7170  param_gerror_cv_food_dir = foodcount_reproduce_genotype_neuronal_gerror_cv,&
7171  param_gerror_cv_food_mem = food_mem_reproduce_genotype_neuronal_gerror_cv, &
7172  param_gerror_cv_conspec = conspcount_reproduce_genotype_neuronal_gerror_cv,&
7173  param_gerror_cv_pred_dir = pred_direct_reproduce_genotype_neuronal_gerror_cv,&
7174  param_gerror_cv_predator = pred_meancount_reproduce_genotype_neuronal_gerror_cv,&
7175  param_gerror_cv_stomach = stom_reproduce_genotype_neuronal_gerror_cv, &
7176  param_gerror_cv_bodymass = bodymass_reproduce_genotype_neuronal_gerror_cv,&
7177  param_gerror_cv_energy = energy_reproduce_genotype_neuronal_gerror_cv,&
7178  param_gerror_cv_age = age_reproduce_genotype_neuronal_gerror_cv, &
7179  param_gerror_cv_reprfac = reprfac_reproduce_genotype_neuronal_gerror_cv,&
7180  ! @note Real agent perception components are now **substituted**
7181  ! by the **fake** values resulting from executing this
7182  ! behaviour (`do_this` method).
7183  perception_override_stomach = stomach_overrride_perc, &
7184  perception_override_bodymass = bodymass_override_perc, &
7185  perception_override_energy = energy_override_perc &
7186  )
7187 
7188  !> **Third,** From the perceptual components calculated at the previous
7189  !! step we can obtain the **primary** and **final motivation** values by
7190  !! weighed summing.
7191  if (present(rescale_max_motivation)) then
7192  !> Here we can use global maximum motivation across all behaviours and
7193  !! perceptual components if it is provided, for rescaling.
7194  max_motivation = rescale_max_motivation
7195  else
7196  !> Or can rescale using local maximum value for this behaviour only.
7197  max_motivation = this%expectancy%max_perception()
7198  end if
7199 
7200  !> Transfer attention weights from the actor agent `this_agent` to the
7201  !! `this` behaviour component. So, we will now use the updated modulated
7202  !! attention weights of the agent rather than their default parameter
7203  !! values.
7204  call this%attention_transfer(this_agent)
7205 
7206  !> So the primary motivation values are calculated.
7207  call this%expectancy%motivation_primary_calc(max_motivation)
7208 
7209  !> Primary motivations are logged in the @ref intro_debug_mode "debug mode".
7210  call log_dbg( ltag_info // "Primary motivations: " // &
7211  "hunger: " // &
7212  tostr(this%expectancy%hunger%motivation_prim) // &
7213  ", fear_defence: " // &
7214  tostr(this%expectancy%fear_defence%motivation_prim) // &
7215  ", reproduce: " // &
7216  tostr(this%expectancy%reproduction%motivation_prim), &
7217  procname, modname )
7218 
7219  !> There is **no modulation** at this stage, so the final motivation
7220  !! values are the same as primary motivations.
7221  !! TODO: Should include developmental or other modulation? If yes, need to
7222  !! separate genetic modulation component from
7223  !! `motivation_modulation_genetic` into a procedure bound to
7224  !! `MOTIVATIONS` with `this_agent` as actor.
7225  call this%expectancy%modulation_none()
7226 
7227  !> **Fourth,** Calculate the finally **expected arousal level for this
7228  !! behaviour**. As in the GOS, the overall arousal is the maximum value
7229  !! among all motivation components.
7230  this%arousal_expected = this%expectancy%max_final()
7231 
7232  !> Log also the final expectancy value in the @ref intro_debug_mode
7233  !! "debug mode".
7234  call log_dbg( ltag_info // "Expectancy: " // tostr(this%arousal_expected),&
7235  procname, modname )
7236 
7237  !> Now as we know the expected arousal, we can choose the behaviour which
7238  !! would minimise this arousal level.
7239 
7240  end subroutine eat_food_item_motivations_expect
7241 
7242  !-----------------------------------------------------------------------------
7243  !> Execute this behaviour component "eat food item" by `this_agent` agent
7244  !! towards the `food_item_eaten`.
7245  !! @note The "do"-function does not change the state of the this_agent
7246  !! or the the environment (the food item), the "execute" function
7247  !! **does** change them.
7248  subroutine eat_food_item_do_execute(this, this_agent, food_item_eaten, &
7249  food_resource_real, eat_is_success)
7250  !> @param [inout] this the self object.
7251  class(eat_food), intent(inout) :: this
7252  !> @param[inout] this_agent is the actor agent which eats the food item.
7253  class(appraisal), intent(inout) :: this_agent
7254  !> @param[inout] food_item_eaten is the food item object that is eaten.
7255  class(food_item), intent(inout) :: food_item_eaten
7256  !> @param[inout] food_resource_real The food resource we are eating the
7257  !! food item in.
7258  !! @note We need to provide the food resource that the agent has perceived
7259  !! the food items (using the `see_food` method) because the
7260  !! food perception object contains **copies** of food items from the
7261  !! physical resource. So we have to change the availability status of
7262  !! the real physical resource items, not just items in the perception
7263  !! object of the agent.
7264  class(food_resource), intent(inout) :: food_resource_real
7265  !> @param[out] eat_is_success logical indicator showing if the food item
7266  !! has actually been eaten (TRUE) or failed (FALSE).
7267  logical, optional, intent(out) :: eat_is_success
7268 
7269  ! PROCNAME is the procedure name for logging and debugging (with MODNAME).
7270  character(len=*), parameter :: PROCNAME = "(eat_food_item_do_execute)"
7271 
7272  ! Local logical flag setting stochastic food item capture success.
7273  logical :: is_captured
7274 
7275  ! Real id number of the food item iid
7276  integer :: food_item_real_iid
7277 
7278  !> ### Implementation details ###
7279  !> First, check if this food item is **not eaten** and this agent is
7280  !! **not dead**. It should normally the case. If not, may point to a bug.
7281  ! TODO: probably it is better to remove the logging code out here and only
7282  ! execute it once at start of behaviour procedure. Then can use pure
7283  ! elemental procedure.
7284  error_nofood_check: if (food_item_eaten%is_unavailable()) then
7285  call log_dbg( ltag_warn // procname // ", Cannot capture food " // &
7286  "item as it is not available (has been already eaten?). Check code.")
7287  return
7288  end if error_nofood_check
7289  error_dead_check: if (this_agent%is_dead()) then
7290  call log_dbg( ltag_warn // procname // "Agent is dead, cannot " // &
7291  "enter this subroutine. Check code.")
7292  return
7293  end if error_dead_check
7294 
7295  !> Now process the food item by `this_agent`.
7296  !> #### Step 1: do_this ####
7297  !> First, we use the intent-in do-procedure `eat_food::do_this()` =>
7298  !! `the_behaviour::eat_food_item_do_this()` to perform the behaviour
7299  !! desired and get the **expectations of fake perceptions** for GOS.
7300  !! As a result, we get `mass_increment_from_food` and
7301  !! `stomach_increment_from_food`.
7302  !! @note At this stage, the state of the food item is not changed.
7303  !! Only the state of `this` behaviour changes, and it will
7304  !! be later passed to modify the agent.
7305  !! @note `capture_prob` is not set here, so it is set to the true
7306  !! objective value that depends on the distance between the
7307  !! predator agent and the food item, see `capture_probability`
7308  !! function bound to the `FOOD_ITEM` class.
7309  call this%do_this( this_agent = this_agent, &
7310  food_item_eaten = food_item_eaten, &
7311  is_captured = is_captured)
7312 
7313  !> Also, here set the optional output argument `eat_is_success` from the
7314  !! stochastic result (success/failed) of the foor item capture.
7315  if (present(eat_is_success)) eat_is_success = is_captured
7316 
7317  !> Also log the fake perceptions along with the agent's sex if running in
7318  !! the DEBUG mode.
7319  call log_dbg( "INFO: Body mass increment from food item: " // &
7320  tostr(this%mass_increment_from_food) // &
7321  " with raw stomach content increment: " // &
7322  tostr(this%stomach_increment_from_food) // &
7323  "; food item processed has size: " // &
7324  tostr(food_item_eaten%get_size()) // &
7325  " and mass: " // tostr(food_item_eaten%get_mass()), &
7326  procname, modname )
7327 
7328  !> #### Step 2: Change the agent ####
7329  !> Second, **change the agent's state** as a consequence of eating.
7330  !! (1) Grow the **body length** of the agent based on the mass increment
7331  !! from food.
7332  !! @warning Note that we increment the body length first, before
7333  !! incrementing/growing the body **mass**. This is because the
7334  !! body length increment uses the ratio of the food gain mass
7335  !! to the agent's body mass. So incrementing the body mass itself
7336  !! with the food gain should be done after the length is
7337  !! processed, otherwise a wrong (mass+gain) value is used.
7338  call this_agent%len_grow(this%mass_increment_from_food)
7339 
7340  !> (2). Grow the **body mass** of the agent.
7341  !! @note Note that `mass_increment_from_food` already has
7342  !! the processing cost subtracted. Specifically, the
7343  !! mass increment can be negative if the agent did not
7344  !! catch the food item.
7345  !! @note Note that even if `is_captured` is False, we do call
7346  !! the mass and stomach increment procedures as in such a
7347  !! case there is a mass cost that is still subtracted
7348  !! (increment negative), and stomach increment is zero.
7349  call this_agent%mass_grow(this%mass_increment_from_food)
7350 
7351  !> (3). And increment the **stomach contents** of the agent using
7352  !! `condition::stomach_increment()`.
7353  call this_agent%stomach_increment(this%stomach_increment_from_food)
7354 
7355  !> (4). Update the energy reserves using the new currently updated mass
7356  !! and length by calling `condition::energy_update()`.
7357  call this_agent%energy_update()
7358 
7359  !> (5). Check if the agent is starved to death. If yes, the agent can
7360  !! die without going any further.
7361  ! TODO: decide should it be also checked here, after each behaviour
7362  ! that can have cost or only after executing the behaviour...
7363  ! the latter should avoid the overhead of multiple checking but
7364  ! gets unrealistic as a starved to death zombie agent could
7365  ! execute behaviours.
7366  if (this_agent%starved_death()) then
7367  call this_agent%dies()
7368  call log_dbg( ltag_info // "The agent dies of starvation.", &
7369  procname, modname )
7370  return
7371  end if
7372 
7373  !> #### Step 3: Change the environment ####
7374  !> Third, **change the state of the environment**. Disable the food
7375  !! item if it is eaten and not available any more. If the capture
7376  !! success if False, the item is not affected.
7377  captured: if (is_captured) then
7378  !> Set the eaten status to the food item in the perception object.
7379  call food_item_eaten%disappear()
7380  !> We also have to set the food item in the real food resource the
7381  !! same eaten/absent status because the perception object may operate
7382  !! on a **copy of the real food objects**.
7383  !! So we here first get the ID number of the food item.
7384  ! ERROR: Sometimes an out of bound id is produced for unknown reason:
7385  ! @verbatim
7386  ! Fortran runtime error: Index '88986' of dimension 1 of array
7387  ! 'food_resource_real' above upper bound of 60000
7388  ! @endverbatim
7389  food_item_real_iid = food_item_eaten%get_iid()
7390  !> Second, set the food item in the food resource with the same iid
7391  !! the absent/eaten status.
7392  out_bound: if ( food_item_real_iid>food_resource_real%abundance() ) then
7393  call log_msg( ltag_error // "ID of the food item " // &
7394  tostr(food_item_real_iid) // &
7395  " is outside of the valid range " // &
7396  tostr(food_resource_real%abundance()) // &
7397  ", array size is " // &
7398  tostr( size(food_resource_real%food) ) // " in " // &
7399  procname // ". Cannot call (disappear) on this item!" )
7400  else out_bound
7401  call log_dbg( ltag_info // "The food item " // &
7402  tostr(food_item_real_iid) // &
7403  " from the resource " // &
7404  trim( food_resource_real%get_label() ) // &
7405  " (array size " // &
7406  tostr( size(food_resource_real%food) ) // &
7407  " = " // &
7408  tostr(food_resource_real%abundance()) // &
7409  " ) is marked eaten: (disappear) method called", &
7410  procname, modname )
7411  call food_resource_real%food(food_item_real_iid)%disappear()
7412 
7413  !> Log the food item eaten in the @ref intro_debug_mode "debug mode".
7414  !! @warning This would result in huge amount of log writing that
7415  !! significantly slows down execution!
7416  call log_dbg(ltag_info // "Food item capture SUCCESS.", &
7417  procname, modname)
7418  call log_dbg(ltag_info // &
7419  "Food item " // tostr(food_item_eaten%get_iid()) // &
7420  " in the physical resource " // &
7421  trim(food_resource_real%food_label) // " (real iid=" // &
7422  tostr(food_resource_real%food(food_item_real_iid)%get_iid()) // &
7423  ") is now eaten and unavailable; size: " // &
7424  tostr(food_item_eaten%get_size()) // &
7425  ", mass: " // tostr(food_item_eaten%get_mass()) // &
7426  " (physical resource size: " // &
7427  tostr(food_resource_real%food(food_item_real_iid)%get_size()) //&
7428  ", mass: " // &
7429  tostr(food_resource_real%food(food_item_real_iid)%get_mass()) //&
7430  ")", procname, modname)
7431  call log_dbg(ltag_info // "Check food item final status is " // &
7432  tostr(food_item_eaten%is_available()) // &
7433  ", in the physical resource: " // &
7434  tostr(food_resource_real%food(food_item_real_iid)% &
7435  is_available()),&
7436  procname, modname)
7437  food_item_real_iid = 0
7438  end if out_bound
7439  else captured
7440  call log_dbg( ltag_info // "Food item capture FAILED for item " // &
7441  tostr(food_item_eaten%get_iid()), procname, modname )
7442  end if captured
7443 
7444  end subroutine eat_food_item_do_execute
7445 
7446  !- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
7447 
7448  !-----------------------------------------------------------------------------
7449  !> Initialise reproduce behaviour object.
7450  elemental subroutine reproduce_init_zero(this)
7451  class(reproduce), intent(inout) :: this
7452 
7453  ! Local parameter for zero = 0.0
7454  real(srp), parameter :: null_srp = 0.0_srp
7455 
7456  !> First init components from the base root class
7457  !! `the_behaviour::behaviour_base`:
7458  !! Mandatory label component that should be read-only.
7459  this%label = "REPRODUCE"
7460  !> The execution status is always FALSE, can be reset to TRUE only when
7461  !! the behaviour unit is called to execution.
7462  this%is_active = .false.
7463 
7464  !> And the *expectancy* type components.
7465  call this%expectancy%init()
7466  !> And init the expected arousal data component.
7467  this%arousal_expected = null_srp
7468 
7469  !> Second, init components of this specific behaviour (`REPRODUCE`)
7470  !! component extended class.
7471  !! @note Note that we initialise increments to 0.0, not MISSING as
7472  !! increments will be later added. And several items can be added
7473  !! consecutively.
7474  this%reprfact_decrement_testosterone = null_srp
7475  this%reprfact_decrement_estrogen = null_srp
7476  this%decrement_mass = null_srp
7477 
7478  end subroutine reproduce_init_zero
7479 
7480  !-----------------------------------------------------------------------------
7481  !> Calculate the maximum number of possible reproductions for this agent.
7482  !! It is assumed that a male can potentially fertilise several females
7483  !! that are within its perception object (in proximity) during a single
7484  !! reproduction event. For females, this number if always one.
7485  function maximum_n_reproductions(this) result (max_num)
7486  class(appraisal), intent(in) :: this
7487  !> @returns The maximum number of reproductions (successful fertilisations)
7488  !! within the same reproduction event.
7489  integer :: max_num
7490 
7491  ! Local variables: number of conspecifics in the perception object.
7492  integer :: n_conspecifics_perception
7493  integer :: n_males_high_t_perception, n_females_perception
7494 
7495  ! Local counter
7496  integer :: i
7497 
7498  n_conspecifics_perception = this%perceive_consp%get_count()
7499  !> Initialise the number of same- and opposite-sex conspecifics
7500  !! (integer counters) to zero.
7501  n_males_high_t_perception = 0
7502  n_females_perception = 0
7503 
7504  !> ### Implementation details ###
7505  !> **First,** determine if there are any conspecifics in the perception, if
7506  !! there are no, reproduction is impossible. Return straight away with zero
7507  !! result in such a case.
7508  check_is_alone: if ( .NOT. this%has_consp() ) then
7509  max_num = 0
7510  return
7511  end if check_is_alone
7512 
7513  !> **Second,** check if this agent is **female**. If yes, only one
7514  !! fertilisation is possible, so return `max_num=1`.
7515  if (this%is_female()) then
7516  max_num = 1
7517  !> Exit from the procedure afterwards.
7518  return
7519  end if
7520 
7521  !> From now on, it is assumed the agent is male.
7522  !> **Third,** determine how many conspecific male agents in the perception
7523  !! object have testosterone level **higher** than this actor agent. These
7524  !! conspecific male agents can take part in the fertilisation. However, all
7525  !! male conspecifics with testosterone **lower** than in this agent are
7526  !! out-competed by this agent and the other high-testosterone males and
7527  !! would not be involved in reproduction.
7528  do concurrent(i=1:n_conspecifics_perception)
7529  if ( this%perceive_consp%conspecifics_seen(i)%is_male() ) then
7530  if ( this%testosterone_get() < 1. ) & !this%perceive_consp%conspecifics_seen(i)%testosterone )
7531  n_males_high_t_perception = n_males_high_t_perception + 1
7532  else
7533  n_females_perception = n_females_perception + 1
7534  end if
7535  end do
7536 
7537  !> **Finally,** calculate the expected number of fertilised females, i.e.
7538  !! the number of reproductions for this agent assuming only this agent and
7539  !! all other male agents with the testosterone levels exceeding that in
7540  !! this agent can reproduce.
7541  max_num = floor( real(n_females_perception, srp) / &
7542  (1.0_srp + real(n_males_high_t_perception, srp)) )
7543  ! TODO: calculate on the basis of average testosterone in perception
7544  ! where only those > average can fertilise. Could result in zero
7545  ! for the this agent.
7546 
7547  end function maximum_n_reproductions
7548 
7549  !-----------------------------------------------------------------------------
7550  !> Do reproduce by `this_agent` (the actor agent) given the specific
7551  !! probability of successful reproduction. The probability of reproduction
7552  !! depends on the number of agents of the same and of the opposite sex
7553  !! within the visual range of the this agent weighted by the difference in
7554  !! the body mass between the actor agent and the average body mass of the
7555  !! other same-sex agents.
7556  !> The **main output** from this **do** procedure is the `this` behavioural
7557  !! unit object, namely its two components:
7558  !! - this\%reprfact_decrement_testosterone
7559  !! - this\%reprfact_decrement_estrogen
7560  !! .
7561  subroutine reproduce_do_this(this, this_agent, p_reproduction, is_reproduce)
7562  !> @param[inout] this the object itself.
7563  class(reproduce), intent(inout) :: this
7564  !> @param[in] this_agent is the actor agent which does/does not reproduce.
7565  class(appraisal), intent(in) :: this_agent
7566  !> @param[in] p_reproduction optional probability of reproduction,
7567  !! overrides the value calculated from `this_agent` data.
7568  real(SRP), optional, intent(in) :: p_reproduction
7569  !> @param[out] is_reproduce optional reproduction success flag, TRUE if
7570  !! the reproduction is successfully done by the agent.
7571  logical, optional, intent(out) :: is_reproduce
7572 
7573  ! Local copies of optionals
7574  real(SRP) :: p_reproduction_here
7575 
7576  !> ### Implementation details ###
7577  !> Determine if the agent's hormonal system is ready for reproduction, that
7578  !! its current level of sex steroids @f$ \sigma_{i} @f$ exceeds the
7579  !! baseline (initially determined by the genome) @f$ \sigma_{0} @f$ by a
7580  !! factor @f$ \nu @f$ determined by the parameter
7581  !! commondata::sex_steroids_reproduction_threshold:
7582  !! @f[ \sigma_{i} > \nu \sigma_{0} . @f]
7583  !! This check is done by the the_body::is_ready_reproduce() function.
7584  !! - If the level of sex steroids is insufficient, reproduction is
7585  !! impossible and the values of gonadal steroid decrements get are
7586  !! zero. The reproduction indicator `is_reproduce` if present, is
7587  !! also set to FALSE and no further processing is then performed.
7588  !! .
7589  check_mature: if ( .not. this_agent%is_ready_reproduce() ) then
7590  this%reprfact_decrement_testosterone = 0.0_srp
7591  this%reprfact_decrement_estrogen = 0.0_srp
7592  if (present(is_reproduce)) is_reproduce = .false.
7593  return
7594  end if check_mature
7595 
7596  !> Determine if there are any conspecifics in the perception, if there
7597  !! are no, reproduction is impossible. Return straight away with zero
7598  !! values of gonadal steroid decrements, as in the case of unsuccessful
7599  !! reproduction. The reproduction indicator `is_reproduce` if present,
7600  !! is also set to FALSE.
7601  check_is_alone: if ( .NOT. this_agent%has_consp() ) then
7602  this%reprfact_decrement_testosterone = 0.0_srp
7603  this%reprfact_decrement_estrogen = 0.0_srp
7604  if (present(is_reproduce)) is_reproduce = .false.
7605  return
7606  end if check_is_alone
7607 
7608  !> Check optional probability of reproduction dummy parameter. If it is
7609  !! absent, use the value calculated from the `this_agent` agent's
7610  !! perception data calling `probability_reproduction()` method. This is
7611  !! the **upper limit** on the reproduction probability provided the actor
7612  !! agent has sufficient motivation and resources.
7613  if (present(p_reproduction)) then
7614  p_reproduction_here = p_reproduction
7615  else
7616  p_reproduction_here = this_agent%probability_reproduction()
7617  end if
7618 
7619  !> Then we call stochastic logical function `reproduction_success()`
7620  !! to determine the **actual outcome of reproduction**.
7621  if ( this_agent%reproduction_success() ) then
7622  !> If reproduction is **successful**, the reproductive factor gonadal
7623  !! steroid (hormonal) components
7624  !! reproduce::reprfact_decrement_testosterone` and
7625  !! reproduce::reprfact_decrement_estrogen data component are determined
7626  !! in sex specific manner:
7627  !! - in males testosterone is decreased,
7628  !! - in females, estrogen is decreased.
7629  !! .
7630  !! An additional condition is that the level of the gonadal hormones
7631  !! should not fall below the baseline level.
7632  !! Additionally, the cost of reproduction, body mass decrement
7633  !! `reproduce::decrement_mass`, is calculated and set using the
7634  !! `reproduction::reproduction_cost()` method.
7635  ! @note TODO: The other steroid (i.e. estrogen in males) can also
7636  ! be changed, or not?
7637  if ( this_agent%is_male() ) then
7638  this%reprfact_decrement_testosterone = &
7639  this_agent%testosterone_get()*decrement_factor_fixed()
7640  if ( this_agent%testosterone_get() - &
7641  this%reprfact_decrement_testosterone < &
7642  this_agent%testosterone_base_get() ) &
7643  this%reprfact_decrement_testosterone = &
7644  this_agent%testosterone_get() - &
7645  this_agent%testosterone_base_get()
7646  this%decrement_mass = this_agent%reproduction_cost()
7647  else
7648  this%reprfact_decrement_estrogen = &
7649  this_agent%estrogen_get() * decrement_factor_fixed()
7650  if ( this_agent%estrogen_get() - &
7651  this%reprfact_decrement_estrogen < &
7652  this_agent%estrogen_base_get() ) &
7653  this%reprfact_decrement_estrogen = &
7654  this_agent%estrogen_get() - &
7655  this_agent%estrogen_base_get()
7656  this%decrement_mass = this_agent%reproduction_cost()
7657  end if
7658  !> Also, if `is_reproduce` optional parameter is provided, set it to TRUE.
7659  if (present(is_reproduce)) is_reproduce = .true.
7660  else
7661  !> If reproduction is **not successful**, reproduction factor decrements
7662  !! equal to zero are returned. The body mass decrement is equivalent to
7663  !! the reproduction cost of unsuccessful reproduction
7664  !! (`reproduction::reproduction_cost_unsuccess()`).
7665  this%reprfact_decrement_testosterone = 0.0_srp
7666  this%reprfact_decrement_estrogen = 0.0_srp
7667  this%decrement_mass = this_agent%reproduction_cost_unsuccess()
7668  !> Additionally, set `is_reproduce` to FALSE if it is provided.
7669  if (present(is_reproduce)) is_reproduce = .false.
7670  end if
7671 
7672  contains
7673  !- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
7674  !> Calculate the decrement factor for the gonadal steroids based
7675  !! reproductive factor.
7676  !! @note This is based on fixed parameter value, trivial. A more complex
7677  !! pattern can also be implemented.
7678  function decrement_factor_fixed() result (decrement)
7679  real(srp) :: decrement
7680  !> `REPRFAC_DECREMENT_FACTOR_REPRODUCTION` is a fixed decrement factor
7681  !! for the gonadal steroid hormone based reproductive factor (reprfact).
7682  real(srp), parameter :: reprfac_decrement_factor_reproduction = 0.3_srp
7683  decrement = reprfac_decrement_factor_reproduction
7684  end function decrement_factor_fixed
7685 
7686  end subroutine reproduce_do_this
7687 
7688  !-----------------------------------------------------------------------------
7689  !> `reproduce::motivations_expect()` is a subroutine (re)calculating
7690  !! motivations from fake expected perceptions following from
7691  !! `reproduce::do_this()` => `the_behaviour::reproduce_do_this()` procedure.
7692  subroutine reproduce_motivations_expect(this, this_agent, time_step_model, &
7693  reprod_prob, non_stochastic, rescale_max_motivation)
7694  !> @param [inout] this the self object.
7695  class(reproduce), intent(inout) :: this
7696  !> @param[in] this_agent is the actor agent which does reproduce.
7697  class(appraisal), intent(in) :: this_agent
7698  !> @param [in] time_step_model optional time step of the model,
7699  !! **overrides** the value calculated from the spatial data.
7700  integer, optional, intent(in) :: time_step_model
7701  !> @param[in] reprod_prob is optional probability of reproduction for the
7702  !! this actor agent, **overrides** the value calculated from the
7703  !! agent data using the probability_reproduction() function.
7704  real(SRP), optional, intent(in) :: reprod_prob
7705  !> @param[in] non_stochastic is a logical flag that sets 100% probability
7706  !! of reproduction. This parameter has precedence over the
7707  !! `reprod_prob`.
7708  logical, optional, intent(in) :: non_stochastic
7709  !> @param[in] rescale_max_motivation maximum motivation value for
7710  !! rescaling all motivational components for comparison
7711  !! across all motivation and perceptual components and behaviour
7712  !! units.
7713  real(SRP), optional, intent(in) :: rescale_max_motivation
7714 
7715  ! Local copy of optional model time step
7716  integer :: time_step_model_here
7717 
7718  ! Local copy of optionals, capture probability, override distance.
7719  real(SRP) :: reprod_prob_here
7720 
7721  ! Local variable
7722  real(SRP) :: max_motivation ! Local max. over all motivation components.
7723 
7724  !> ### Notable local parameters ###
7725  !> #### probability_reproduction_base_def ####
7726  !> `PROBABILITY_REPRODUCTION_BASE_DEF` is the expected (subjective)
7727  !! probability of reproduction; set as a parameter.
7728  !! @details We assume that the agent assumes 100% probability of
7729  !! reproduction.
7730  !! @note The probability is here > 1.0 to make sure the procedure
7731  !! is never stochastic (subjective prob=1) and reproduction
7732  !! always performed (it is based on random_value[0..1] < P ).
7733  ! TODO: we may also make the agent expectation
7734  ! of the probability the default fixed parameter
7735  ! value from `COMMONDATA` or genetically-selected value or
7736  ! calculated depending on the agent's current state.
7737  real(SRP), parameter :: PROBABILITY_REPRODUCTION_BASE_DEF = 1.1_srp
7738 
7739  !> #### reproduction_prob_intrinsic ####
7740  !> `reproduction_prob_intrinsic` is the probability of reproduction that
7741  !! is intrinsic for the agent at the given conditions, calculated using the
7742  !! probability_reproduction() function.
7743  real(SRP) :: reproduction_prob_intrinsic
7744 
7745  !> #### reprfactor_percept ####
7746  !> `reprfactor_percept` is the value of the reproductive factor that
7747  !! goes as a fake perception value into the neuronal response function.
7748  !! This reproductive factor is determined in a sex specific way:
7749  !! - `reprfact_decrement_testosterone` in males;
7750  !! - `reprfact_decrement_estrogen` in females.
7751  !! .
7752  real(SRP) :: reprfactor_percept
7753 
7754  !> #### body_mass_percept ####
7755  !> `body_mass_percept` is the "subjective" value of the energetic
7756  !! cost of reproduction that goes as a fake perception value into the
7757  !! neuronal response function. It is calculated via the
7758  !! `reproduction::reproduction_cost()` method.
7759  real(SRP) :: body_mass_percept
7760 
7761  !> #### energy_override_perc ####
7762  !> `energy_override_perc` is the fake perception value for the energy
7763  !! reserves that goes into the neuronal response function.
7764  real(SRP) :: energy_override_perc
7765 
7766  ! PROCNAME is the procedure name for logging and debugging
7767  character(len=*), parameter :: PROCNAME = "(reproduce_motivations_expect)"
7768 
7769  !> ### Implementation details ###
7770  !! First, calculate the intrinsic probability of reproduction for this
7771  !! actor agent using the probability_reproduction() method.
7772  reproduction_prob_intrinsic = this_agent%probability_reproduction()
7773 
7774  !> #### Check optional parameters ####
7775  !> Check optional time step parameter. If not provided, use global
7776  !! parameter value from `commondata::global_time_step_model_current`.
7777  if (present(time_step_model)) then
7778  time_step_model_here = time_step_model
7779  else
7780  time_step_model_here = global_time_step_model_current
7781  end if
7782 
7783  !> Check if the probability of reproduction is supplied.
7784  !! If the probability of reproduction is supplied as a dummy
7785  !! parameter to this procedure, it will override the intrinsic
7786  !! probability of reproduction for this actor agent that is
7787  !! calculated using the probability_reproduction() method.
7788  !! This may be for example necessary when a subjective motivational
7789  !! expectancy is calculated, it can assume 100% probability and/or
7790  !! weightings of the resulting motivation value(s).
7791  if (present(reprod_prob)) then
7792  reprod_prob_here = reprod_prob
7793  else
7794  !> If the probability of reproduction is not supplied, expectancy is
7795  !! based on the intrinsic probability_reproduction() value.
7796  reprod_prob_here = reproduction_prob_intrinsic
7797  end if
7798 
7799  !> If the `non_stochastic` dummy parameter is set to TRUE, the probability
7800  !! of reproduction is obtained from the `PROBABILITY_REPRODUCTION_BASE_DEF`
7801  !! local parameter that is 1.1. In such a case, it guarantees that the
7802  !! agent will always reproduce.
7803  !! @note Unlike the `reproduce::do_this()` procedure where the reproduction
7804  !! probability is calculated from the true objective values, the
7805  !! subjective expectancies are based by default on **100% expected
7806  !! probability** of this agent reproduction.
7807  if (present(non_stochastic)) then
7808  if(non_stochastic) reprod_prob_here = probability_reproduction_base_def
7809  end if
7810 
7811  call log_dbg( ltag_info // "Probability of peprodiuction: " // &
7812  tostr(reprod_prob_here) // ", P intrinsic: " // &
7813  tostr(reproduction_prob_intrinsic), procname, modname )
7814 
7815  !> #### Main processing steps ####
7816  !> **First,** we use the **do**-procedure `reproduce::do_this()` =>
7817  !! `the_behaviour::reproduce_do_this()` to perform the behaviour desired
7818  !! without changing either the agent or its environment, obtaining the
7819  !! **subjective** values of the `this` behaviour components that later feed
7820  !! into the motivation **expectancy** functions:
7821  !! - `reprfact_decrement_testosterone`
7822  !! - `reprfact_decrement_estrogen`
7823  !! .
7824  call this%do_this( this_agent = this_agent, &
7825  p_reproduction = reprod_prob_here )
7826 
7827  call log_dbg( ltag_info // "Repfactor decrements: " // &
7828  tostr(this%reprfact_decrement_testosterone) // "," // &
7829  tostr(this%reprfact_decrement_estrogen) // &
7830  ", mass decrement: " // tostr(this%decrement_mass), &
7831  procname, modname )
7832 
7833  !> We then weight the expected subjective decrements of the reproductive
7834  !! factor components of he_neurobio::reproduce class, testosterone or
7835  !! estrogen, that are intrinsically expected for the actor agent by the
7836  !! **objective probability of reproduction** `reproduction_prob_intrinsic`
7837  !! (calculated for the current time step using the **intrinsic**
7838  !! the_neurobio::probability_reproduction() method).
7839  !> The reproductive factor `reprfactor_percept` that goes into the neuronal
7840  !! response function as a fake perception is based on gonadal steroid
7841  !! (hormonal) components: `reprfact_decrement_testosterone` and
7842  !! `reprfact_decrement_estrogen` in a sex specific manner:
7843  !! - in males testosterone is weighted by `reproduction_prob_intrinsic`,
7844  !! - in females, estrogen is weighted by `reproduction_prob_intrinsic`.
7845  !! .
7846  ! TODO: The other steroid (i.e. estrogen in males) can also
7847  ! be changed, or not?
7848  if ( this_agent%is_male() ) then
7849  reprfactor_percept = this_agent%testosterone_get() &
7850  - this%reprfact_decrement_testosterone * &
7851  reproduction_prob_intrinsic
7852  else
7853  reprfactor_percept = this_agent%estrogen_get() &
7854  - this%reprfact_decrement_estrogen * &
7855  reproduction_prob_intrinsic
7856  end if
7857 
7858  call log_dbg( ltag_info // "Reproductive factor fake perception:" // &
7859  tostr(reprfactor_percept), procname, modname )
7860 
7861  !> The same is done for the subjective assessment of the body mass cost
7862  !! of reproduction (`body_mass_percept`): it is weighted by the
7863  !! intrinsic probability of reproduction (`reproduction_prob_intrinsic`).
7864  body_mass_percept = &
7865  max( zero, &
7866  this_agent%get_mass() - this_agent%living_cost() - &
7867  this%decrement_mass * reproduction_prob_intrinsic )
7868 
7869  !> At this point, therefore, the fake perception values for the
7870  !! reproductive factor (`reprfactor_percept`) and body mass
7871  !! (`body_mass_percept`) are known. Finally, calculate also the fake
7872  !! perception for the energy reserves (`energy_override_perc`) using the
7873  !! `the_body::energy_reserve()` procedure.
7874  energy_override_perc = energy_reserve( body_mass_percept, &
7875  this_agent%length() )
7876 
7877  !> **Second,** we calculate motivation values resulting from the behaviour
7878  !! done (`reproduce::do_this()` => `the_behaviour::reproduce_do_this()`) at
7879  !! the previous step: what would be the motivation values *if* the
7880  !! agent doe perform reproduction? Technically, this is done by
7881  !! calling the **neuronal response function**,
7882  !! `percept_components_motiv::motivation_components()`
7883  !! method, for each of the motivational states with `perception_override_`
7884  !! dummy parameters overriding the default values:
7885  !! `perception_override_reprfac` and also `perception_override_energy`.
7886  ! @note **Expectancy** assessment for **hunger** motivation, using
7887  ! `PERCEPT_COMPONENTS_MOTIV`-bound procedure with intent[in] for
7888  ! `this_agent` now.
7889  call this%expectancy%hunger%percept_component%motivation_components &
7890  (this_agent, &
7891  ! Parameters:: Boolean G x P matrices:
7892  param_gp_matrix_light = light_hunger_genotype_neuronal, &
7893  param_gp_matrix_depth = depth_hunger_genotype_neuronal, &
7894  param_gp_matrix_food_dir = foodcount_hunger_genotype_neuronal, &
7895  param_gp_matrix_food_mem = food_mem_hunger_genotype_neuronal, &
7896  param_gp_matrix_conspec = conspcount_hunger_genotype_neuronal, &
7897  param_gp_matrix_pred_dir = pred_direct_hunger_genotype_neuronal, &
7898  param_gp_matrix_predator = pred_meancount_hunger_genotype_neuronal, &
7899  param_gp_matrix_stomach = stom_hunger_genotype_neuronal, &
7900  param_gp_matrix_bodymass = bodymass_hunger_genotype_neuronal, &
7901  param_gp_matrix_energy = energy_hunger_genotype_neuronal, &
7902  param_gp_matrix_age = age_hunger_genotype_neuronal, &
7903  param_gp_matrix_reprfac = reprfac_hunger_genotype_neuronal, &
7904  ! Parameters :: G x P variances:
7905  param_gerror_cv_light = light_hunger_genotype_neuronal_gerror_cv, &
7906  param_gerror_cv_depth = depth_hunger_genotype_neuronal_gerror_cv, &
7907  param_gerror_cv_food_dir = foodcount_hunger_genotype_neuronal_gerror_cv,&
7908  param_gerror_cv_food_mem = food_mem_hunger_genotype_neuronal_gerror_cv, &
7909  param_gerror_cv_conspec = conspcount_hunger_genotype_neuronal_gerror_cv,&
7910  param_gerror_cv_pred_dir = pred_direct_hunger_genotype_neuronal_gerror_cv,&
7911  param_gerror_cv_predator = pred_meancount_hunger_genotype_neuronal_gerror_cv,&
7912  param_gerror_cv_stomach = stom_hunger_genotype_neuronal_gerror_cv, &
7913  param_gerror_cv_bodymass = bodymass_hunger_genotype_neuronal_gerror_cv, &
7914  param_gerror_cv_energy = energy_hunger_genotype_neuronal_gerror_cv, &
7915  param_gerror_cv_age = age_hunger_genotype_neuronal_gerror_cv, &
7916  param_gerror_cv_reprfac = reprfac_hunger_genotype_neuronal_gerror_cv, &
7917  ! Real agent perception components are now substituted by the *fake*
7918  ! values resulting from executing this behaviour (`do_this` method).
7919  ! This is repeated for all the motivations: *hunger*,
7920  ! *passive avoidance,* *fear state* etc.
7921  perception_override_reprfac = reprfactor_percept, &
7922  perception_override_bodymass = body_mass_percept, &
7923  perception_override_energy = energy_override_perc &
7924  )
7925  !> Real agent perception components are now substituted by the *fake*
7926  !! values resulting from executing this behaviour (`reproduce::do_this()`
7927  !! => `the_behaviour::reproduce_do_this()` method). This is repeated for
7928  !! all the motivations: *hunger*, *passive avoidance,* *active
7929  !! avoidance* etc. These optional **override parameters** are
7930  !! substituted by the "fake" values:
7931  !! - `perception_override_reprfac`;
7932  !! - `perception_override_bodymass`.
7933  !! .
7934 
7935  ! @note **Expectancy** assessment for **fear_defence** motivation,
7936  ! using `PERCEPT_COMPONENTS_MOTIV`-bound procedure with intent[in]
7937  ! for `this_agent` now.
7938  call this%expectancy%fear_defence%percept_component%motivation_components &
7939  (this_agent, &
7940  ! Parameters:: Boolean G x P matrices:
7941  param_gp_matrix_light = light_actv_avoid_genotype_neuronal, &
7942  param_gp_matrix_depth = depth_actv_avoid_genotype_neuronal, &
7943  param_gp_matrix_food_dir = foodcount_actv_avoid_genotype_neuronal, &
7944  param_gp_matrix_food_mem = food_mem_actv_avoid_genotype_neuronal, &
7945  param_gp_matrix_conspec = conspcount_actv_avoid_genotype_neuronal, &
7946  param_gp_matrix_pred_dir = pred_direct_actv_avoid_genotype_neuronal, &
7947  param_gp_matrix_predator = pred_meancount_actv_avoid_genotype_neuronal, &
7948  param_gp_matrix_stomach = stom_actv_avoid_genotype_neuronal, &
7949  param_gp_matrix_bodymass = bodymass_actv_avoid_genotype_neuronal, &
7950  param_gp_matrix_energy = energy_actv_avoid_genotype_neuronal, &
7951  param_gp_matrix_age = age_actv_avoid_genotype_neuronal, &
7952  param_gp_matrix_reprfac = reprfac_actv_avoid_genotype_neuronal, &
7953  ! Parameters :: G x P variances:
7954  param_gerror_cv_light = light_actv_avoid_genotype_neuronal_gerror_cv, &
7955  param_gerror_cv_depth = depth_actv_avoid_genotype_neuronal_gerror_cv, &
7956  param_gerror_cv_food_dir = foodcount_actv_avoid_genotype_neuronal_gerror_cv,&
7957  param_gerror_cv_food_mem = food_mem_actv_avoid_genotype_neuronal_gerror_cv, &
7958  param_gerror_cv_conspec = conspcount_actv_avoid_genotype_neuronal_gerror_cv,&
7959  param_gerror_cv_pred_dir = pred_direct_actv_avoid_genotype_neuronal_gerror_cv,&
7960  param_gerror_cv_predator = pred_meancount_actv_avoid_genotype_neuronal_gerror_cv,&
7961  param_gerror_cv_stomach = stom_actv_avoid_genotype_neuronal_gerror_cv, &
7962  param_gerror_cv_bodymass = bodymass_actv_avoid_genotype_neuronal_gerror_cv,&
7963  param_gerror_cv_energy = energy_actv_avoid_genotype_neuronal_gerror_cv,&
7964  param_gerror_cv_age = age_actv_avoid_genotype_neuronal_gerror_cv, &
7965  param_gerror_cv_reprfac = reprfac_actv_avoid_genotype_neuronal_gerror_cv,&
7966  ! @note Real agent perception components are now **substituted**
7967  ! by the **fake** values resulting from executing this
7968  ! behaviour (`do_this` method).
7969  perception_override_reprfac = reprfactor_percept, &
7970  perception_override_bodymass = body_mass_percept, &
7971  perception_override_energy = energy_override_perc &
7972  )
7973 
7974  ! @note **Expectancy** assessment for **reproduction** motivation,
7975  ! using `PERCEPT_COMPONENTS_MOTIV`-bound procedure with intent[in]
7976  ! for `this_agent` now.
7977  call this%expectancy%reproduction%percept_component%motivation_components &
7978  (this_agent, &
7979  ! Parameters:: Boolean G x P matrices:
7980  param_gp_matrix_light = light_reproduce_genotype_neuronal, &
7981  param_gp_matrix_depth = depth_reproduce_genotype_neuronal, &
7982  param_gp_matrix_food_dir = foodcount_reproduce_genotype_neuronal, &
7983  param_gp_matrix_food_mem = food_mem_reproduce_genotype_neuronal, &
7984  param_gp_matrix_conspec = conspcount_reproduce_genotype_neuronal, &
7985  param_gp_matrix_pred_dir = pred_direct_reproduce_genotype_neuronal, &
7986  param_gp_matrix_predator = pred_meancount_reproduce_genotype_neuronal, &
7987  param_gp_matrix_stomach = stom_reproduce_genotype_neuronal, &
7988  param_gp_matrix_bodymass = bodymass_reproduce_genotype_neuronal, &
7989  param_gp_matrix_energy = energy_reproduce_genotype_neuronal, &
7990  param_gp_matrix_age = age_reproduce_genotype_neuronal, &
7991  param_gp_matrix_reprfac = reprfac_reproduce_genotype_neuronal, &
7992  ! Parameters :: G x P variances:
7993  param_gerror_cv_light = light_reproduce_genotype_neuronal_gerror_cv, &
7994  param_gerror_cv_depth = depth_reproduce_genotype_neuronal_gerror_cv, &
7995  param_gerror_cv_food_dir = foodcount_reproduce_genotype_neuronal_gerror_cv,&
7996  param_gerror_cv_food_mem = food_mem_reproduce_genotype_neuronal_gerror_cv, &
7997  param_gerror_cv_conspec = conspcount_reproduce_genotype_neuronal_gerror_cv,&
7998  param_gerror_cv_pred_dir = pred_direct_reproduce_genotype_neuronal_gerror_cv,&
7999  param_gerror_cv_predator = pred_meancount_reproduce_genotype_neuronal_gerror_cv,&
8000  param_gerror_cv_stomach = stom_reproduce_genotype_neuronal_gerror_cv, &
8001  param_gerror_cv_bodymass = bodymass_reproduce_genotype_neuronal_gerror_cv,&
8002  param_gerror_cv_energy = energy_reproduce_genotype_neuronal_gerror_cv,&
8003  param_gerror_cv_age = age_reproduce_genotype_neuronal_gerror_cv, &
8004  param_gerror_cv_reprfac = reprfac_reproduce_genotype_neuronal_gerror_cv,&
8005  ! @note Real agent perception components are now **substituted**
8006  ! by the **fake** values resulting from executing this
8007  ! behaviour (`do_this` method).
8008  perception_override_reprfac = reprfactor_percept, &
8009  perception_override_bodymass = body_mass_percept, &
8010  perception_override_energy = energy_override_perc &
8011  )
8012 
8013  !> **Third,** From the perceptual components calculated at the previous
8014  !! step we can obtain the **primary** and **final motivation** values by
8015  !! weighed summing.
8016  if (present(rescale_max_motivation)) then
8017  !> Here we can use global maximum motivation across all behaviours and
8018  !! perceptual components if it is provided, for rescaling.
8019  max_motivation = rescale_max_motivation
8020  else
8021  !> Or can rescale using local maximum value for this behaviour only.
8022  max_motivation = this%expectancy%max_perception()
8023  end if
8024 
8025  !> Transfer attention weights from the actor agent `this_agent` to the
8026  !! `this` behaviour component. So, we will now use the updated modulated
8027  !! attention weights of the agent rather than their default parameter
8028  !! values.
8029  call this%attention_transfer(this_agent)
8030 
8031  !> So the primary motivation values are calculated.
8032  call this%expectancy%motivation_primary_calc(max_motivation)
8033 
8034  !> Primary motivations are logged in the @ref intro_debug_mode "debug mode".
8035  call log_dbg( ltag_info // "Primary motivations: " // &
8036  "hunger: " // &
8037  tostr(this%expectancy%hunger%motivation_prim) // &
8038  ", fear_defence: " // &
8039  tostr(this%expectancy%fear_defence%motivation_prim) // &
8040  ", reproduce: " // &
8041  tostr(this%expectancy%reproduction%motivation_prim), &
8042  procname, modname )
8043 
8044  !> There is **no modulation** at this stage, so the final motivation
8045  !! values are the same as primary motivations.
8046  !! TODO: Should include developmental or other modulation? If yes, need to
8047  !! separate genetic modulation component from
8048  !! `motivation_modulation_genetic` into a procedure bound to
8049  !! `MOTIVATIONS` with `this_agent` as actor.
8050  call this%expectancy%modulation_none()
8051 
8052  !> **Fourth,** Calculate the finally **expected arousal level for this
8053  !! behaviour**. As in the GOS, the overall arousal is the maximum value
8054  !! among all motivation components.
8055  this%arousal_expected = this%expectancy%max_final()
8056 
8057  !> Log also the final expectancy value in the @ref intro_debug_mode
8058  !! "debug mode".
8059  call log_dbg( ltag_info // "Expectancy: " // tostr(this%arousal_expected),&
8060  procname, modname )
8061 
8062  !> Now as we know the expected arousal, we can choose the behaviour which
8063  !! would minimise this arousal level.
8064 
8065  end subroutine reproduce_motivations_expect
8066 
8067  !-----------------------------------------------------------------------------
8068  !> Execute this behaviour component "reproduce" by the `this_agent` agent.
8069  subroutine reproduce_do_execute(this, this_agent)
8070  class(reproduce), intent(inout) :: this
8071  !> @param[inout] this_agent is the actor agent which reproduces.
8072  class(appraisal), intent(inout) :: this_agent
8073 
8074  ! PROCNAME is the procedure name for logging and debugging (with MODNAME).
8075  character(len=*), parameter :: PROCNAME = "(reproduce_do_execute)"
8076 
8077  ! Local logical flag setting actual stochastic reproduction success.
8078  logical :: is_reproduce
8079 
8080  !> #### Notable local variables ####
8081  !> *body_mass_after* is the updated body mass of the agent excluding the
8082  !! cost of reproduction.
8083  real(SRP) :: body_mass_after
8084 
8085  !> ### Implementation details ###
8086  !> #### Basic checks ####
8087  !> First, check if there are **any conspecifics** in the perception object
8088  !! of the agent and this agent is **not dead**. It should normally the
8089  !! case. If not, may point to a bug.
8090  if (.not. this_agent%has_consp()) then
8091  call log_dbg( ltag_warn // procname // " Cannot reproduce as " // &
8092  "there are no conspecifics in perception. Check code.")
8093  return
8094  end if
8095  if (this_agent%is_dead()) then
8096  call log_dbg( ltag_warn // procname // " Agent is dead, cannot " // &
8097  "enter this subroutine. Check code.")
8098  return
8099  end if
8100 
8101  !> #### Check the agent condition ####
8102  !> Calculate the updated body mass of the agent after reproduction
8103  !! `body_mass_after`. It is obtained by subtracting the cost of
8104  !! reproduction from the current body mass of the agent. The cost of
8105  !! reproduction is calculated using the function
8106  !! `reproduction::reproduction_cost()`
8107  !! (=> `the_body::reproduction_cost_energy()`). Therefore it does not
8108  !! necessarily coincide with the subjective cost of reproduction that is
8109  !! kept in the `the_behaviour::reproduce` class.
8110  body_mass_after = this_agent%get_mass() - this_agent%reproduction_cost()
8111 
8112  !> Additionally, check if the energy reserves of the agent and the body
8113  !! mass are enough for reproduction. That is, if the agent survives
8114  !! following the reproduction and does not get starved to death. The check
8115  !! is done using the `the_body::is_starved()` function in the named if
8116  !! block `CHECK_STARVED_AFTER`.
8117  check_starved_after: if ( is_starved( body_mass_after, &
8118  this_agent%stomach_content_mass, &
8119  this_agent%body_mass_birth, &
8120  this_agent%body_mass_maximum, &
8121  this_agent%energy_current, &
8122  this_agent%energy_maximum) ) then
8123  !> - If the condition of the agent is insufficient for reproduction, it
8124  !! is assumed that the agent **has attempted** reproduction but was not
8125  !! successful. Then, the `::reproduction_unsuccessful_cost_subtract()`
8126  !! procedure is called to subtract some small cost if unsuccessful
8127  !! reproduction.
8129  !> - Following this, exit and **return** back from this procedure.
8130  !! .
8131  return
8132  end if check_starved_after
8133 
8134  !> #### Step 1: do_this ####
8135  !> First, we use the intent-in do-procedure `reproduce::do_this()` =>
8136  !! `the_behaviour::reproduce_do_this()` to perform the behaviour
8137  !! desired and get the **expectations of fake perceptions** for GOS:
8138  !! - this\%reprfact_decrement_testosterone
8139  !! - this\%reprfact_decrement_estrogen.
8140  !! .
8141  !! At this stage, the state of the agent is not changed. Only the state of
8142  !! `this` behaviour changes, and it will be later passed to modify the
8143  !! agent. The `do_this` procedure also returns the stochastic status
8144  !! of the reproduction event `is_reproduce` is TRUE if the reproduction
8145  !! event was successful.
8146  call this%do_this( this_agent = this_agent, &
8147  p_reproduction=this_agent%probability_reproduction(), &
8148  is_reproduce = is_reproduce)
8149 
8150  !> Also log the fake perceptions along with the agent's sex if running in
8151  !! the DEBUG mode.
8152  call log_dbg( ltag_info // "Reproduction attempted, success is: " // &
8153  tostr(is_reproduce) // &
8154  " for agent " // this_agent%individ_label() )
8155  call log_dbg( ltag_info // "Agent sex is: " // this_agent%label_sex() // &
8156  "(is male: " // tostr(this_agent%is_male()) // "); " // &
8157  "testosterone decrement: " // &
8158  tostr(this%reprfact_decrement_testosterone) // &
8159  "; estrogen decrement: " // &
8160  tostr(this%reprfact_decrement_estrogen), procname, modname )
8161 
8162  !> #### Step 2: Change the agent ####
8163  !> ##### Check reproduction success #####
8164  !> Second, **change the agent's state** as a consequence of reproduction.
8165  !> Check if reproduction event was stochastically successful. If the
8166  !! reproduction event was not successful (`is_reproduce` is FALSE), the
8167  !! `::reproduction_unsuccessful_cost_subtract()` procedure is called to
8168  !! subtract some small cost of unsuccessful reproduction.
8169  if ( .not. is_reproduce ) then
8171  !> Following this, exit and **return** back from this procedure.
8172  return
8173  end if
8174 
8175  !> ##### Process reproducing agent #####
8176  !> From now on it is assumed that the reproduction event was stochastically
8177  !! **successful**.
8178  !> (A) Update the number of successful reproductions and the number of
8179  !! offspring that result from this reproduction, for this agent, by the
8180  !! default number (=1) calling `reproduction::reproductions_increment()`.
8181  call this_agent%reproductions_increment(add_repr=1)
8182 
8183  !> (B) Decrease the sex steroids level following the reproduction. This
8184  !! is different in males and females: testosterone is decreased in males
8185  !! and estrogen, in females. An additional condition is that the
8186  !! level of gonadal steroids could not fall to less than the baseline.
8187  if ( this_agent%is_male() ) then
8188  call this_agent%testosterone_set( &
8189  value_set = max( this_agent%testosterone_base_get(), &
8190  this_agent%testosterone_get() - &
8191  this%reprfact_decrement_testosterone ), &
8192  update_history=.true. )
8193  else
8194  call this_agent%estrogen_set( &
8195  value_set = max( this_agent%estrogen_base_get(), &
8196  this_agent%estrogen_get() - &
8197  this%reprfact_decrement_estrogen ), &
8198  update_history=.true. )
8199  end if
8200 
8201  !> (C) Decrement the body mass as a consequence of reproduction. This
8202  !! body mass decrement constitutes the energetic cost of reproduction.
8203  !! The updated body mass (after subtraction of the cost) has already been
8204  !! calculated as `body_mass_after`.
8205  call this_agent%set_mass( value_set = body_mass_after, &
8206  update_history = .true. )
8207  !> Additionally, also call the `the_body::condition::set_length()` method
8208  !! to update the body length history stack. However, the value_set
8209  !! parameter here is just the current value. This fake re-setting of the
8210  !! body length is done to keep both mass and length synchronised in their
8211  !! history stack arrays (there is no procedure for only updating history).
8212  call this_agent%set_length( value_set = this_agent%get_length(), &
8213  update_history = .true. )
8214 
8215  !> After resetting the body mass, update energy reserves of the agent, that
8216  !! depend on both the length and the mass.
8217  call this_agent%energy_update()
8218 
8219  !> (D). Check if the agent is starved to death. If yes, the agent can
8220  !! die without going any further.
8221  if (this_agent%starved_death()) call this_agent%dies()
8222 
8223  !> #### Step 3: Change the environment ####
8224  !> Reproduction of the agent does not affect the environmental objects.
8225  !! TODO: add method to do actual reproduction crossover mate choice and
8226  !! produce eggs
8227 
8228  contains
8229  !- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
8230  !> Process the costs of unsuccessful reproduction. Reproduction can
8231  !! be unsuccessful for various reasons: insufficient reserves
8232  !! (reproduction results in starvation death) or stochastic no success.
8234 
8235  !> Unsuccessful reproduction attempt results in a cost,
8236  !! in terms of the body mass, that is a fraction of the normal cost
8237  !! of reproduction: the fraction is defined by the parameter
8238  !! `commondata::reproduction_cost_unsuccess` in `COMMONDATA`.
8239  !! The cost of unsuccessful reproduction is calculated by the
8240  !! function `reproduction::reproduction_cost_unsuccess()`.
8241  !> The body mass of the agent is then reduced to take this fraction of
8242  !! the full cost of reproduction. This updated value is saved into
8243  !! the body mass history stack (`update_history` parameter is `TRUE`).
8244  call this_agent%set_mass( value_set = this_agent%get_mass() - &
8245  this_agent%reproduction_cost_unsuccess(), &
8246  update_history = .true. )
8247  !> Body length is also saved to history to make the mass and length
8248  !! history stack arrays synchronised.
8249  call this_agent%set_length( value_set = this_agent%get_length(), &
8250  update_history = .true. )
8251  !> The energy reserve of the agent, depending on both the length
8252  !! and the mass, is updated.
8253  call this_agent%energy_update()
8254 
8256 
8257  end subroutine reproduce_do_execute
8258 
8259  !- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
8260 
8261  !-----------------------------------------------------------------------------
8262  !> The "do" procedure component of the behaviour element performs the
8263  !! behaviour without affecting the actor agent (the_agent) and the world
8264  !! (here food_item_eaten) which have intent(in), so it only can change
8265  !! the internal representation of the behaviour (the type to which this
8266  !! procedure is bound to, here `WALK_RANDOM`).
8267  subroutine walk_random_do_this(this, this_agent, distance, distance_cv, &
8268  predict_window_pred, predict_window_food, time_step_model)
8269  class(walk_random), intent(inout) :: this
8270  !> @param[in] this_agent is the actor agent which eats the food item.
8271  class(appraisal), intent(in) :: this_agent
8272  !> @param[in] distance is an optional walk distance. If stochastic Gaussian
8273  !! walk is set, this value defines the average distance.
8274  !! @note Even though the walk distance is internally defined in
8275  !! terms of the agent's body length, this parameter
8276  !! defines the **absolute distance** in cm.
8277  real(SRP), optional, intent(in) :: distance
8278  !> @param[in] distance_cv is an optional coefficient of variation for the
8279  !! random walk distance. If absent, non-stochastic walk step
8280  !! size is used.
8281  real(SRP), optional, intent(in) :: distance_cv
8282  !> @param[in] predict_window_pred the size of the prediction window, i.e.
8283  !! how many steps back in memory are used to calculate the
8284  !! predicted general predation risk. This parameter is limited
8285  !! by the maximum
8286  !! commondata::history_size_perception value of the perception
8287  !! memory history size.
8288  integer, optional, intent(in) :: predict_window_pred
8289  !> @param[in] predict_window_food the size of the prediction window, i.e.
8290  !! how many steps back in memory are used to calculate the
8291  !! predicted food gain. This parameter is limited by the maximum
8292  !! commondata::history_size_perception value of the perception
8293  !! memory history size.
8294  integer, optional, intent(in) :: predict_window_food
8295  !> @param[in] time_step_model optional time step of the model, overrides
8296  !! the value calculated from the spatial data.
8297  integer, optional, intent(in) :: time_step_model
8298 
8299  ! Local copies of optionals.
8300  integer :: time_step_model_here, predict_window_food_here, &
8301  predict_window_pred_here
8302 
8303  ! mean_n_food_memory_old, mean_n_food_memory_new** are the average
8304  ! numbers of food items in the past memory window, the "older" and
8305  ! "newer" parts that are used to calculate the "older"
8306  ! and "newer" values of food availability retrieved from the
8307  ! perception memory. Used in calculation of the the_behaviour::hope
8308  ! function.
8309  real(SRP) :: mean_n_food_memory_old, mean_n_food_memory_new
8310 
8311  ! **mean_size_food_memory_old, mean_size_food_memory_new** are the
8312  ! average sizes of food items in the past memory window, the "older"
8313  ! and "newer" parts that are used to calculate the "older"
8314  ! @f$ \overline{f_1} @f$ and "newer" @f$ \overline{f_2} @f$
8315  ! values of food availability retrieved from the perception memory.
8316  ! Used in calculation of the the_behaviour::hope function.
8317  real(SRP) :: mean_size_food_memory_old, mean_size_food_memory_new
8318 
8319  ! **food_gain_memory_old, food_gain_memory_new** are the "older"
8320  ! @f$ \overline{f_1} @f$ and "newer" @f$ \overline{f_2} @f$
8321  ! values of food gain retrieved from the perception memory.
8322  ! Used in calculation of the the_behaviour::hope function.
8323  real(SRP) :: food_gain_memory_old, food_gain_memory_new
8324 
8325  ! **food_gain_memory_baseline** is the baseline value of the food gain
8326  ! retrieved from the memory, that is used to calculate the actual
8327  ! food gain expectancy value calculated from the hope function.
8328  real(SRP) :: food_gain_memory_baseline
8329 
8330  ! Baseline distance for random walk.
8331  real(SRP) :: distance_baseline
8332 
8333  ! **WEIGHT_DIRECT** is the relative weight given to the immediate
8334  ! perception of predators over the predators counts in the memory stack.
8335  ! Obtained from global parameters
8336  ! (`commondata::predation_risk_weight_immediate`).
8337  real(SRP), parameter :: WEIGHT_DIRECT = predation_risk_weight_immediate
8338 
8339  ! **mean_n_pred_memory_old, mean_n_pred_memory_new** are the average
8340  ! numbers of predators in the past perception memory window.
8341  real(SRP) :: mean_n_pred_memory_old, mean_n_pred_memory_new
8342 
8343  ! **pred_dir_current** and **pred_current** are the current estimates
8344  ! of the direct and general predation risk.
8345  real(SRP) :: pred_dir_current, pred_current
8346 
8347  !> ### Implementation details ###
8348  !> #### Checks and preparations ####
8349  !> Check optional time step parameter. If unset, use global
8350  !! `commondata::global_time_step_model_current`.
8351  if (present(time_step_model)) then
8352  time_step_model_here = time_step_model
8353  else
8354  time_step_model_here = global_time_step_model_current
8355  end if
8356 
8357  !> Check optional parameter for the general predation risk perception
8358  !! memory window. If the `predict_window_pred` dummy parameter is not
8359  !! provided, its default value is the proportion of the whole perceptual
8360  !! memory window defined by commondata::history_perception_window_pred.
8361  !! Thus, only the latest part of the memory is used for the prediction
8362  !! of the future predation risk.
8363  if (present(predict_window_pred)) then
8364  predict_window_pred_here= predict_window_pred
8365  else
8366  predict_window_pred_here = floor( history_size_perception * &
8367  history_perception_window_pred )
8368  end if
8369 
8370  !> Check optional parameter for the food perception memory window. If
8371  !! the `predict_window_food` dummy parameter is not provided, its default
8372  !! value is the proportion of the whole perceptual memory window defined
8373  !! by commondata::history_perception_window_food. Thus, only the
8374  !! latest part of the memory is used for the prediction of the future
8375  !! food gain.
8376  if (present(predict_window_food)) then
8377  predict_window_food_here = predict_window_food
8378  else
8379  predict_window_food_here = floor( history_size_perception * &
8380  history_perception_window_food )
8381  end if
8382 
8383  !> #### Calculate the distance of swimming ####
8384  !> The normal locomotion distance is fixed to the fraction of the agent
8385  !! current body length set by the parameter
8386  !! commondata::walk_random_distance_default_factor. This is a baseline
8387  !! value that can serve as the mean in case of stochastic walks
8388  !! (the_environment::spatial_moving::rwalk()) or as the actual value in
8389  !! case of deterministic walks.
8390  !!
8391  !! The walk distance @f$ D_{rw} = L \varrho @f$ where @f$ L @f$ is the
8392  !! agent's body length and @f$ \varrho @f$ is the parameter factor
8393  !! commondata::walk_random_distance_default_factor.
8394  !!
8395  !! However, if the walk distance is provided as an optional parameter
8396  !! `distance` to this procedure, this provided value is used as the
8397  !! baseline distance instead. This allows to easily implement several
8398  !! types of walks, e.g. "long" (migration-like) and short (local).
8399  if (present(distance)) then
8400  distance_baseline = distance
8401  else
8402  distance_baseline = this_agent%get_length() * &
8403  walk_random_distance_default_factor
8404  end if
8405 
8406  !> This baseline distance value @f$ D_{rw} @f$ is saved into the `this`
8407  !! behaviour data component \%distance.
8408  this%distance = distance_baseline
8409 
8410  !> - If the `distance_cv` optional dummy parameter is set to a
8411  !! non-zero value (> commondata::tolerance_high_def_srp), the the walk
8412  !! distance is *stochastic* with the mean equal to the above baseline
8413  !! value and the coefficient of variation set by the \%distance_cv
8414  !! data component of the `this` walk object, that is in turn equal to
8415  !! the `distance_cv` parameter.
8416  if (present(distance_cv)) then
8417  if ( distance_cv > tolerance_high_def_srp ) then
8418  this%distance_cv = distance_cv
8419  !> The \%distance is then reset to a Gaussian value, creating an
8420  !! error/uncertainty in the expectancy.
8421  this%distance = rnorm( distance_baseline, &
8422  cv2variance(distance_cv, distance_baseline) )
8423  else
8424  this%distance_cv = 0.0_srp
8425  end if
8426  !> - If `distance_cv` parameter is absent or is explicitly set to zero, the
8427  !! walk distance is deterministic with the value equal to the baseline.
8428  !! Also, the \%distance_c data component is 0.0 for non-stochastic
8429  !! distances.
8430  !! .
8431  !! This allows to implement uncertainty in the walk distance depending on
8432  !! different factors, such as the arousal or hormone level.
8433  else
8434  this%distance_cv = 0.0_srp
8435  end if
8436 
8437  !> #### Calculate expected cost of the swimming ####
8438  !> The expected cost of swimming in the random walk depends on the walk
8439  !! distance and is calculated using the the_body::condition::cost_swim()
8440  !! assuming *laminar* flow (laminar flow is due to normal relatively slow
8441  !! swimming pattern).
8442  this%expected_cost_moving = &
8443  this_agent%cost_swim( distance=this%distance, &
8444  exponent=swimming_cost_exponent_laminar )
8445 
8446  !> #### Calculate expected food item perception ####
8447  !> *Food item* perception expected after a random walk is calculated
8448  !! using the the_behaviour::hope() function mechanism.
8449  !!
8450  !! First, average number of food items in the "older" and "newer" parts of
8451  !! the memory is calculated using the
8452  !! the_neurobio::memory_perceptual::get_food_mean_n_split() procedure.
8453  !! (Note that the `split_val` parameter to this procedure is not
8454  !! provided so the default 1/2 split is used.)
8455  call this_agent%memory_stack%get_food_mean_n_split( &
8456  window = predict_window_food_here, &
8457  older = mean_n_food_memory_old, &
8458  newer = mean_n_food_memory_new )
8459 
8460  !> Second, the expected number of food items following the walk
8461  !! (\%expected_food_dir) is calculated based on the the_behaviour::hope()
8462  !! function mechanism. Here, the baseline value @f$ f_0 @f$ is
8463  !! the current number of food items in the food perception object of the
8464  !! actor agent, and the historical ratio @f$ \varrho @f$ is calculated
8465  !! as the mean number of food items in the "older" to "newer" memory
8466  !! parts: @f[ \varrho = \frac{\overline{n_2}}{\overline{n_1}} . @f]
8467  !! The grid arrays for the hope function are defined by the
8468  !! obtained from commondata::walk_random_food_hope_abscissa and
8469  !! commondata::walk_random_food_hope_ordinate parameter arrays.
8470  this%expected_food_dir = &
8471  hope( baseline = real( &
8472  this_agent%perceive_food%get_count(),srp ), &
8473  memory_old = mean_n_food_memory_old, &
8474  memory_new = mean_n_food_memory_new, &
8475  raw_grid_x = walk_random_food_hope_abscissa, &
8476  raw_grid_y = walk_random_food_hope_ordinate )
8477 
8478  !> #### Calculate expected food gain ####
8479  !> The expected food gain is calculated differently depending on the
8480  !! mean distance of the random walk.
8481  !! - If the agent currently has any food items in perception, the short
8482  !! walk is defined as a walk with the distance not exceeding
8483  !! commondata::walk_random_food_gain_hope units of the average
8484  !! to the food items in perception.
8485  !! - If there is no food in the perception object, a walk is "short" if
8486  !! it does not exceed commondata::walk_random_food_gain_hope_agentl
8487  !! units of the agent body length.
8488  !! .
8489  !> ##### Short walks #####
8490  !> For relatively short walks, the expected food gain is based on the
8491  !! currently available value.
8492  select_dist_food: if ( ( this_agent%has_food() .and. &
8493  this%distance < walk_random_food_gain_hope * &
8494  this_agent%perceive_food%get_meandist() ) &
8495  .or. &
8496  ( .not. this_agent%has_food() .and. &
8497  this%distance < walk_random_food_gain_hope_agentl * &
8498  this_agent%get_length() ) ) then
8499  !> The expected food gain is equal to the average mass of the food item
8500  !! in the latest `predict_window_food_here` steps of the memory stack,
8501  !! weighted by the average number of food items in the same width latest
8502  !! memory if this number is less than 1 or 1 (i.e. unweighted) if their
8503  !! number is higher.
8504  ! @f[
8505  ! \left\{\begin{matrix}
8506  ! F_{exp}=\overline{f(m)} \cdot \overline{n(m)}, & \overline{n(m)}<1; \\
8507  ! F_{exp}=\overline{f(m)}, & \overline{n(m)} \geq 1
8508  ! \end{matrix}\right.
8509  ! @f]
8510  !> @image html img_doxygen_walk_rand_formula_1.svg
8511  !> @image latex img_doxygen_walk_rand_formula_1.eps "" width=14cm
8512  !! where @f$ \overline{f(m)} @f$ is the average mass of the food items
8513  !! and @f$ \overline{n(m)} @f$ is the average number of food items
8514  !! in the @f$ m @f$ latest steps of the perceptual memory stack.
8515  !!
8516  !! The averages are calculated with
8517  !! the_neurobio::memory_perceptual::get_food_mean_size() and
8518  !! the_neurobio::memory_perceptual::get_food_mean_n(). The average mass of
8519  !! the food items is calculated from their average size using the
8520  !! the_environment::size2mass_food() function.
8521  !!
8522  !! Thus, if the agent had previously some relatively poor perceptual
8523  !! history of encountering food items, so that the average number of food
8524  !! items is fractional < 1 (e.g. average number 0.5, meaning that it has
8525  !! seen a single food item approximately every other time step), the
8526  !! expected food is weighted by this fraction (0.5). If, on the other
8527  !! hand, the agent had several food items at each time step previously,
8528  !! the average food item size is unweighted (weight=1.0). This conditional
8529  !! weighting reflects the fact that it is not possible to eat more than
8530  !! one food item at a time in this model version.
8531  !!
8532  !! This expected food gain is then weighted by the subjective probability
8533  !! of food item capture that is calculated based on the memory
8534  !! the_neurobio::perception::food_probability_capture_subjective().
8535  this%expected_food_gain = &
8536  size2mass_food( &
8537  this_agent%memory_stack%get_food_mean_size( &
8538  predict_window_food_here)) * &
8539  within( &
8540  this_agent%memory_stack%get_food_mean_n( &
8541  predict_window_food_here),&
8542  0.0_srp, 1.0_srp ) * &
8543  this_agent%food_probability_capture_subjective( &
8544  predict_window_food_here, time_step_model_here )
8545 
8546  !> ##### Long walks #####
8547  !> For relatively long walks, the expected food gain is based on the
8548  !! the_behaviour::hope() function.
8549  else select_dist_food
8550 
8551  !> First, average size of food items in the "older" and "newer" parts of
8552  !! the memory is calculated using the
8553  !! the_neurobio::memory_perceptual::get_food_mean_size_split() procedure.
8554  !! (Note that the `split_val` parameter to this procedure is not
8555  !! provided so the default 1/2 split is used.)
8556  call this_agent%memory_stack%get_food_mean_size_split( &
8557  window = predict_window_food_here, &
8558  older = mean_size_food_memory_old, &
8559  newer = mean_size_food_memory_new )
8560 
8561  !> Second, the values of the "old" and "new" *food gain* used to calculate
8562  !! the expectations are obtained by weighting the respective average mass
8563  !! of the food item by the average number of food items if this number is
8564  !! less than 1 or 1 (i.e. unweighted) if their average number is higher.
8565  !> @image html img_doxygen_migrate_formula_1.svg
8566  !! @image latex img_doxygen_migrate_formula_1.eps "" width=14cm
8567  !> where @f$ \overline{m_1} @f$ is the average mass of the food items
8568  !! and @f$ \overline{n_1} @f$ is the average number of food items
8569  !! in the "older" half of the perceptual memory stack and
8570  !! @f$ \overline{m_2} @f$ is the average mass of the food items
8571  !! and @f$ \overline{n_2} @f$ is the average number of food items
8572  !! in the "newer" half of the memory stack.
8573  !!
8574  !! Thus, if the agent had some relatively poor perceptual history of
8575  !! encountering food items, so that the average *number* of food items
8576  !! is fractional < 1 (e.g. average number 0.5, meaning that it has seen a
8577  !! single food item approximately every other time step), the food gain is
8578  !! weighted by this fraction (0.5). If, on the other hand, the agent had
8579  !! more than one food items at each time step previously, the average food
8580  !! item size is unweighted (weight=1.0). This conditional weighting
8581  !! reflects the fact that it is not possible to eat more than
8582  !! one food item at a time in this model version.
8583  !! @note A similar expectancy assessment mechanism is used in the
8584  !! assessment of the food gain expectancy for the
8585  !! the_behaviour::migrate behaviour component
8586  !! the_behaviour::migrate_do_this().
8587  food_gain_memory_old = size2mass_food(mean_size_food_memory_old) * &
8588  within( mean_n_food_memory_old, 0.0_srp, 1.0_srp )
8589  food_gain_memory_new = size2mass_food(mean_size_food_memory_new) * &
8590  within( mean_n_food_memory_new, 0.0_srp, 1.0_srp )
8591 
8592  !> The next step is to calculate the baseline food gain @f$ f_0 @f$,
8593  !! against which the expectancy based on the the_behaviour::hope() function
8594  !! is evaluated. This baseline value is obtained by weighting the average
8595  !! mass of the food items in the whole memory stack @f$ \overline{m} @f$
8596  !! by their average number @f$ \overline{n} @f$ provided this number
8597  !! is *n<1* as above:
8598  !> @image html img_doxygen_migrate_formula_2.svg
8599  !! @image latex img_doxygen_migrate_formula_2.eps "" width=14cm
8600  !!
8601  !! This baseline food gain is then weighted by the subjective probability
8602  !! of food item capture that is calculated based on values from the the
8603  !! memory the_neurobio::perception::food_probability_capture_subjective().
8604  food_gain_memory_baseline = &
8605  size2mass_food( &
8606  this_agent%memory_stack%get_food_mean_size( &
8607  predict_window_food_here)) * &
8608  within( &
8609  this_agent%memory_stack%get_food_mean_n( &
8610  predict_window_food_here), &
8611  0.0_srp, 1.0_srp ) * &
8612  this_agent%food_probability_capture_subjective( &
8613  predict_window_food_here, time_step_model_here )
8614 
8615  !> Finally, the the_behaviour::hope() function is called with the above
8616  !! estimates for the baseline food gain, its "older" and "newer" values.
8617  !! The *zero hope ratio* and the *maximum hope* parameters are obtained
8618  !! from commondata::migrate_food_gain_ratio_zero_hope and
8619  !! commondata::migrate_food_gain_maximum_hope parameter constants.
8620  this%expected_food_gain = &
8621  hope( baseline = food_gain_memory_baseline, &
8622  memory_old = food_gain_memory_old, &
8623  memory_new = food_gain_memory_new, &
8624  raw_grid_x = walk_random_food_hope_abscissa, &
8625  raw_grid_y = walk_random_food_hope_ordinate )
8626 
8627  end if select_dist_food
8628 
8629  !> #### Calculate expected predation risk ####
8630  !> The expected risk of predation (as the food gain above) is calculated
8631  !! differently for relatively short and long walks. The walk is considered
8632  !! *short* if the distance does not exceed
8633  !! commondata::walk_random_pred_risk_hope_agentl units of the agent
8634  !! body lengths and *long* otherwise.
8635  !!
8636  !> First, the current level of the direct risk of predation is calculated
8637  !! using the_neurobio::perception::risk_pred() based on the perception of
8638  !! the `this_agent` agent assuming the agent is not freezing (because it
8639  !! is going to move a random walk).
8640  pred_dir_current = this_agent%risk_pred( is_freezing=.false. )
8641  !!
8642  !> Second, calculate the current value of the general predation risk using
8643  !! the the_neurobio::predation_risk_backend() procedure. The size of this
8644  !! limited memory window is set by the `predict_window_pred` dummy
8645  !! parameter.
8646  !! @note In contrast to the above limited prediction memory window,
8647  !! calculation of the predation risk in the "objective" procedure
8648  !! the_neurobio::perception_predation_risk_objective() uses
8649  !! the same backend but the *whole* memory window
8650  !! (commondata::history_size_perception).
8651  pred_current = &
8652  predation_risk_backend( &
8653  pred_count = this_agent%perceive_predator%get_count(), &
8654  pred_memory_mean = this_agent%memory_stack%get_pred_mean( &
8655  predict_window_pred_here), &
8656  weight_direct = weight_direct )
8657 
8658  !> ##### Short walk #####
8659  !! In short walks, the expected values are just equal to the above current
8660  !! direct extimates.
8661  select_dist_pred: if ( this%distance < walk_random_pred_risk_hope_agentl &
8662  * this_agent%get_length() ) then
8663 
8664  !> - **Direct** risk of predation is equal to the current value as
8665  !! calculated above using the_neurobio::perception::risk_pred().
8666  this%expected_pred_dir_risk = pred_dir_current
8667 
8668  !> - **General** risk, the expected *general* risk of predation in
8669  !! random walk is equal to the current value of direct predation risk
8670  !! as above.
8671  !! .
8672  this%expected_predation_risk = pred_current
8673 
8674  !> ##### Long walk #####
8675  !! On the other hand, for long walks, the expected values of the risks
8676  !! are based on the the_behaviour::hope() function mechanism.
8677  else select_dist_pred
8678 
8679  !> - First, calculate the older and newer predation averages from the
8680  !! memory stack using the
8681  !! the_neurobio::memory_perceptual::get_pred_mean_split() method.
8682  !! These averages serve as the base point for calculating the
8683  !! new to old ratio in the the_behaviour::hope() function.
8684  call this_agent%memory_stack%get_pred_mean_split( &
8685  window = predict_window_pred_here, &
8686  older = mean_n_pred_memory_old, &
8687  newer = mean_n_pred_memory_new )
8688 
8689  !> - The **direct risk** of predation is based on the_behaviour::hope()
8690  !! function. If the number of predators in the latest memory
8691  !! (predation risk) is increasing in the local environment, its
8692  !! expectancy in the unknown environment at a long distance
8693  !! diminishes, if the risk is reducing over time in the agent's
8694  !! perception, the expectancy increases. The hope grid values for
8695  !! the general predation hope function are defined by the
8696  !! commondata::migrate_predator_zero_hope and
8697  !! commondata::migrate_predator_maximum_hope parameter constants.
8698  !! @note Note that the hope function constants used here are the same
8699  !! as for the_behaviour::migrate.
8700  this%expected_pred_dir_risk = hope( pred_dir_current, &
8701  mean_n_pred_memory_old, &
8702  mean_n_pred_memory_new, &
8703  migrate_predator_zero_hope, &
8704  migrate_predator_maximum_hope )
8705 
8706  !> - The expectancy value of **general predation risk** after long walk
8707  !! is obtained via the the_behaviour::hope() function. If the number of
8708  !! predators (risk) is increasing in the latest perception memory,
8709  !! its expectancy after long walk diminishes, if the perceived risk is
8710  !! reducing over time, the expectancy increases. The hope grid values
8711  !! for the general predation hope function are defined by the
8712  !! commondata::migrate_predator_zero_hope and
8713  !! commondata::migrate_predator_maximum_hope parameter constants.
8714  !! @note Note that the hope function constants used here are the same
8715  !! as for the_behaviour::migrate.
8716  !! .
8717  this%expected_predation_risk = hope( pred_current, &
8718  mean_n_pred_memory_old, &
8719  mean_n_pred_memory_new, &
8720  migrate_predator_zero_hope, &
8721  migrate_predator_maximum_hope )
8722 
8723  end if select_dist_pred
8724 
8725  end subroutine walk_random_do_this
8726 
8727  !-----------------------------------------------------------------------------
8728  !> `the_behaviour::walk_random::expectancies_calculate()` (re)calculates
8729  !! motivations from fake expected perceptions following from the procedure
8730  !! `walk_random::do_this()` => `the_behaviour::walk_random_do_this()`.
8731  subroutine walk_random_motivations_expect(this, this_agent, &
8732  distance, distance_cv, &
8733  predict_window_pred, predict_window_food, &
8734  time_step_model, rescale_max_motivation)
8735  class(walk_random), intent(inout) :: this
8736  !> @param[in] this_agent is the actor agent which does random walk.
8737  class(appraisal), intent(in) :: this_agent
8738  !> @param[in] distance is an optional walk distance. If stochastic Gaussian
8739  !! walk is set, this value defines the average distance.
8740  real(SRP), optional, intent(in) :: distance
8741  !> @param[in] distance_cv is an optional coefficient of variation for the
8742  !! random walk distance. If absent, non-stochastic walk step
8743  !! size is used.
8744  real(SRP), optional, intent(in) :: distance_cv
8745  !> @param[in] predict_window_pred the size of the prediction window, i.e.
8746  !! how many steps back in memory are used to calculate the
8747  !! predicted general predation risk. This parameter is limited
8748  !! by the maximum
8749  !! commondata::history_size_perception value of the perception
8750  !! memory history size.
8751  integer, optional, intent(in) :: predict_window_pred
8752  !> @param[in] predict_window_food the size of the prediction window, i.e.
8753  !! how many steps back in memory are used to calculate the
8754  !! predicted food gain. This parameter is limited by the maximum
8755  !! commondata::history_size_perception value of the perception
8756  !! memory history size.
8757  integer, optional, intent(in) :: predict_window_food
8758  !> @param [in] time_step_model optional time step of the model,
8759  !! **overrides** the value calculated from the spatial data.
8760  integer, optional, intent(in) :: time_step_model
8761  !> @param[in] rescale_max_motivation optional maximum motivation value for
8762  !! rescaling all motivational components for comparison
8763  !! across all motivation and perceptual components and behaviour
8764  !! units.
8765  real(SRP), optional, intent(in) :: rescale_max_motivation
8766 
8767  ! Local copies of optionals
8768  real(SRP) :: dist_loc
8769 
8770  ! Local copy of optional model time step
8771  integer :: time_step_model_here, predict_window_food_here, &
8772  predict_window_pred_here
8773 
8774  ! Local variables
8775  real(SRP) :: max_motivation ! Local max. over all motivation components.
8776 
8777  ! Expected food item that is used in the calculations, its properties are
8778  ! based on the average food items that the agent perceives below.
8779  type(food_item) :: expected_food_item
8780 
8781  real(SRP) :: expected_food_item_distance
8782 
8783  !> The probability of capture of the expected food object.
8784  real(SRP) :: expected_food_item_prob_capture
8785 
8786  !> Expected food gain that is fitting into the stomach of the agent.
8787  real(SRP) :: expected_food_item_gain_fits
8788 
8789  ! Current stomach contents of the agent.
8790  real(SRP) :: agent_stomach
8791 
8792  !> ### Notable local variables ###
8793  !> #### Perception overrides ####
8794  !> - **perception_override_food_dir** is the expected number of food items
8795  !! in perception.
8796  real(SRP) :: perception_override_food_dir
8797  !> - **perception_override_pred_dir** is the expected direct
8798  !! predation risk.
8799  real(SRP) :: perception_override_pred_dir
8800  !> - **perception_override_predator** is the expected general predation
8801  !! risk, that is based on a weighting of the current predation and
8802  !! predation risk from the memory stack.
8803  real(SRP) :: perception_override_predator
8804  !> - **perception_override_stomach** is the expected stomach contents
8805  !! as a consequence of random walk.
8806  real(SRP) :: perception_override_stomach
8807  !> - **perception_override_bodymass** is the expected body mass as a
8808  !! consequence of the random walk.
8809  real(SRP) :: perception_override_bodymass
8810  !> - **perception_override_energy** is the expected energy reserves
8811  !! as a consequence of the escape movement. Calculated from the body
8812  !! mass and weight.
8813  !! .
8814  real(SRP) :: perception_override_energy
8815 
8816  ! PROCNAME is the procedure name for logging and debugging
8817  character(len=*), parameter :: PROCNAME = &
8818  "(walk_random_motivations_expect)"
8819 
8820  !> ### Implementation details ###
8821  !> #### Checks and preparations ####
8822  !> Check optional distance of walk. If it is absent, defined as
8823  !! commondata::walk_random_distance_default_factor times of the agent
8824  !! body length.
8825  if (present(distance)) then
8826  dist_loc = distance
8827  else
8828  dist_loc = this_agent%get_length() * walk_random_distance_default_factor
8829  end if
8830 
8831  !> Check optional time step parameter. If not provided, use global
8832  !! parameter value from commondata::global_time_step_model_current.
8833  if (present(time_step_model)) then
8834  time_step_model_here = time_step_model
8835  else
8836  time_step_model_here = global_time_step_model_current
8837  end if
8838 
8839  !> Check optional parameter for the general predation risk perception
8840  !! memory window. If the `predict_window_pred` dummy parameter is not
8841  !! provided, its default value is the proportion of the whole perceptual
8842  !! memory window defined by commondata::history_perception_window_pred.
8843  !! Thus, only the latest part of the memory is used for the prediction
8844  !! of the future predation risk.
8845  if (present(predict_window_pred)) then
8846  predict_window_pred_here= predict_window_pred
8847  else
8848  predict_window_pred_here = floor( history_size_perception * &
8849  history_perception_window_pred )
8850  end if
8851 
8852  !> Check optional parameter for the food perception memory window. If
8853  !! the `predict_window_food` dummy parameter is not provided, its default
8854  !! value is the proportion of the whole perceptual memory window defined
8855  !! by commondata::history_perception_window_food. Thus, only the
8856  !! latest part of the memory is used for the prediction of the future
8857  !! food gain.
8858  if (present(predict_window_food)) then
8859  predict_window_food_here = predict_window_food
8860  else
8861  predict_window_food_here = floor( history_size_perception * &
8862  history_perception_window_food )
8863  end if
8864 
8865  !> #### Call do_this ####
8866  !> As the first step, we use the **do**-procedure walk_random::do_this()
8867  !! => the_behaviour::walk_random_do_this() to perform the behaviour desired
8868  !! without changing either the agent or its environment, obtaining the
8869  !! **subjective** values of the `this` behaviour components that later feed
8870  !! into the motivation **expectancy** functions:
8871  !! - `perception_override_food_dir`
8872  !! - `perception_override_pred_dir`
8873  !! - `perception_override_predator`
8874  !! - `perception_override_stomach`
8875  !! - `perception_override_bodymass`
8876  !! - `perception_override_energy`
8877  !! .
8878  if (present(distance_cv)) then
8879  ! Stochastic walk expectancy.
8880  call this%do_this( this_agent=this_agent, &
8881  distance=dist_loc, &
8882  distance_cv=distance_cv, &
8883  predict_window_pred=predict_window_pred_here, &
8884  predict_window_food=predict_window_food_here, &
8885  time_step_model=time_step_model_here )
8886  else
8887  ! Normal deterministic walk expectancy.
8888  call this%do_this( this_agent=this_agent, &
8889  distance=dist_loc, &
8890  predict_window_pred=predict_window_pred_here, &
8891  predict_window_food=predict_window_food_here, &
8892  time_step_model=time_step_model_here )
8893  end if
8894 
8895  !> #### Calculate expected (fake) perceptions ####
8896  !> ##### Fake perception for the food items #####
8897  !> The expected perception of the number of food items that the agent
8898  !! is going to see following the walk is calculated in the `do_this`
8899  !! procedure. Here it is obtained from the \%expected_food_dir data
8900  !! component of the class.
8901  perception_override_food_dir = this%expected_food_dir
8902 
8903  !> ##### Fake perception of stomach content #####
8904  !> First, create a fake food item with the spatial position identical to
8905  !! that of the agent. The position is used only to calculate the
8906  !! illumination and therefore visual range. The cost(s) are calculated
8907  !! providing explicit separate distance parameter, so the zero distance
8908  !! from the agent is inconsequential. The size of the
8909  !! food item is obtained from the expected food gain by the reverse
8910  !! calculation function the_environment::mass2size_food().
8911  !! Standard `make` method for the food item class is used.
8912  call expected_food_item%make(location=this_agent%location(), &
8913  size=mass2size_food(this%expected_food_gain),&
8914  iid=unknown )
8915 
8916  !> Second, calculate the **probability of capture** of this expected food
8917  !! item. The probability of capture of the fake food item is calculated
8918  !! using the the_environment::food_item::capture_probability() backend
8919  !! assuming the distance to the food item is equal to the average distance
8920  !! of all food items in the **current perception** object. However, if the
8921  !! agent does not see any food items currently, the distance to the fake
8922  !! food item is assumed to be equal to the visibility range weighted by
8923  !! the (fractional) commondata::walk_random_dist_expect_food_uncertain_fact
8924  !! parameter. Thus, the expected *raw* food gain (in the `do`-function) is
8925  !! based on the past memory whereas the probability of capture is based
8926  !! on the latest perception experience.
8927  if ( this_agent%has_food() ) then
8928  expected_food_item_distance = this_agent%perceive_food%get_meandist()
8929  else
8930  ! TODO: add average food distances to perception memory
8931  expected_food_item_distance = expected_food_item%visibility() * &
8932  dist_expect_food_uncertain_fact
8933  end if
8934 
8935  expected_food_item_prob_capture = &
8936  expected_food_item%capture_probability( &
8937  distance=expected_food_item_distance )
8938 
8939  !> Third, the expected food gain corrected for fitting into the agent's
8940  !! current stomach and capture cost is obtained by
8941  !! the_body::condition::food_fitting(). It is then weighted by the
8942  !! expected capture probability. Note that the probability of capture
8943  !! (weighting factor) is calculated based on the current perception
8944  !! (see above), but the travel cost is based on the actual expected
8945  !! \%distance.
8946  expected_food_item_gain_fits = &
8947  this_agent%food_fitting( this%expected_food_gain, this%distance ) &
8948  * expected_food_item_prob_capture
8949 
8950  !> **Stomach content**: the perception override value for the stomach
8951  !! content is obtained incrementing the current stomach contents by
8952  !! the nonzero expected food gain, adjusting also for the digestion
8953  !! decrement (the_body::stomach_emptify_backend()).
8954  agent_stomach = this_agent%get_stom_content()
8955  perception_override_stomach = &
8956  max( zero, &
8957  agent_stomach - stomach_emptify_backend(agent_stomach) + &
8958  expected_food_item_gain_fits )
8959 
8960  !> **Body mass**: the **body mass** perception override is obtained by
8961  !! incrementing (or decrementing if the expected food gain is negative)
8962  !! the current body mass by the expected food gain and also subtracting
8963  !! the cost of living component.
8964  perception_override_bodymass = &
8965  max( zero, &
8966  this_agent%get_mass() - &
8967  this_agent%living_cost() + &
8968  expected_food_item_gain_fits )
8969 
8970  !> **Energy**: The fake perception values for the energy reserves
8971  !! (`energy_override_perc`) using the `the_body::energy_reserve()`
8972  !! procedure.
8973  perception_override_energy = energy_reserve( perception_override_bodymass,&
8974  this_agent%length() )
8975 
8976  !> **Predation risk**: finally, fake perceptions of predation risk are
8977  !! obtained from the values calculated in the `do` procedure:
8978  !! the_behaviour::walk_random::expected_pred_dir_risk and
8979  !! the_behaviour::walk_random::expected_predation_risk.
8980  perception_override_pred_dir = this%expected_pred_dir_risk
8981  perception_override_predator = this%expected_predation_risk
8982 
8983  !> #### Calculate motivation expectancies ####
8984  !> The next step is to calculate the motivational expectancies using the
8985  !! fake perceptions to override the default (actual agent's) values.
8986  !> At this stage, first, calculate motivation values resulting from the
8987  !! behaviour done (`walk_random::do_this()` ) at the previous steps: what
8988  !! would be the motivation values *if* the agent does perform
8989  !! WALK_RANDOM? Technically, this is done by calling the **neuronal
8990  !! response function**, `percept_components_motiv::motivation_components()`
8991  !! method, for each of the motivational states with `perception_override_`
8992  !! dummy parameters overriding the default values.
8993  !! Here is the list of the fake overriding perceptions for the
8994  !! WALK_RANDOM behaviour:
8995  !! - `perception_override_food_dir`
8996  !! - `perception_override_pred_dir`
8997  !! - `perception_override_predator`
8998  !! - `perception_override_stomach`
8999  !! - `perception_override_bodymass`
9000  !! - `perception_override_energy`
9001  !! .
9002  ! @note **Expectancy** assessment for **hunger** motivation, using
9003  ! `PERCEPT_COMPONENTS_MOTIV`-bound procedure with intent[in] for
9004  ! `this_agent` now.
9005  call this%expectancy%hunger%percept_component%motivation_components &
9006  (this_agent, &
9007  ! Parameters:: Boolean G x P matrices:
9008  param_gp_matrix_light = light_hunger_genotype_neuronal, &
9009  param_gp_matrix_depth = depth_hunger_genotype_neuronal, &
9010  param_gp_matrix_food_dir = foodcount_hunger_genotype_neuronal, &
9011  param_gp_matrix_food_mem = food_mem_hunger_genotype_neuronal, &
9012  param_gp_matrix_conspec = conspcount_hunger_genotype_neuronal, &
9013  param_gp_matrix_pred_dir = pred_direct_hunger_genotype_neuronal, &
9014  param_gp_matrix_predator = pred_meancount_hunger_genotype_neuronal, &
9015  param_gp_matrix_stomach = stom_hunger_genotype_neuronal, &
9016  param_gp_matrix_bodymass = bodymass_hunger_genotype_neuronal, &
9017  param_gp_matrix_energy = energy_hunger_genotype_neuronal, &
9018  param_gp_matrix_age = age_hunger_genotype_neuronal, &
9019  param_gp_matrix_reprfac = reprfac_hunger_genotype_neuronal, &
9020  ! Parameters :: G x P variances:
9021  param_gerror_cv_light = light_hunger_genotype_neuronal_gerror_cv, &
9022  param_gerror_cv_depth = depth_hunger_genotype_neuronal_gerror_cv, &
9023  param_gerror_cv_food_dir = foodcount_hunger_genotype_neuronal_gerror_cv,&
9024  param_gerror_cv_food_mem = food_mem_hunger_genotype_neuronal_gerror_cv, &
9025  param_gerror_cv_conspec = conspcount_hunger_genotype_neuronal_gerror_cv,&
9026  param_gerror_cv_pred_dir = pred_direct_hunger_genotype_neuronal_gerror_cv,&
9027  param_gerror_cv_predator = pred_meancount_hunger_genotype_neuronal_gerror_cv,&
9028  param_gerror_cv_stomach = stom_hunger_genotype_neuronal_gerror_cv, &
9029  param_gerror_cv_bodymass = bodymass_hunger_genotype_neuronal_gerror_cv, &
9030  param_gerror_cv_energy = energy_hunger_genotype_neuronal_gerror_cv, &
9031  param_gerror_cv_age = age_hunger_genotype_neuronal_gerror_cv, &
9032  param_gerror_cv_reprfac = reprfac_hunger_genotype_neuronal_gerror_cv, &
9033  ! Real agent perception components are now substituted by the *fake*
9034  ! values resulting from executing this behaviour (`do_this` method).
9035  ! This is repeated for all the motivations: *hunger*,
9036  ! *passive avoidance,* *fear state* etc.
9037  perception_override_food_dir = perception_override_food_dir, &
9038  perception_override_pred_dir = perception_override_pred_dir, &
9039  perception_override_predator = perception_override_predator, &
9040  perception_override_stomach = perception_override_stomach, &
9041  perception_override_bodymass = perception_override_bodymass, &
9042  perception_override_energy = perception_override_energy &
9043  )
9044  !> Real agent perception components are now substituted by the *fake*
9045  !! values resulting from executing this behaviour (`reproduce::do_this()`
9046  !! => `the_behaviour::reproduce_do_this()` method). This is repeated for
9047  !! all the motivations: *hunger*, *passive avoidance,* *active
9048  !! avoidance* etc. These optional **override parameters** are
9049  !! substituted by the "fake" values.
9050 
9051  ! @note **Expectancy** assessment for **fear_defence** motivation,
9052  ! using `PERCEPT_COMPONENTS_MOTIV`-bound procedure with intent[in]
9053  ! for `this_agent` now.
9054  call this%expectancy%fear_defence%percept_component%motivation_components &
9055  (this_agent, &
9056  ! Parameters:: Boolean G x P matrices:
9057  param_gp_matrix_light = light_actv_avoid_genotype_neuronal, &
9058  param_gp_matrix_depth = depth_actv_avoid_genotype_neuronal, &
9059  param_gp_matrix_food_dir = foodcount_actv_avoid_genotype_neuronal, &
9060  param_gp_matrix_food_mem = food_mem_actv_avoid_genotype_neuronal, &
9061  param_gp_matrix_conspec = conspcount_actv_avoid_genotype_neuronal, &
9062  param_gp_matrix_pred_dir = pred_direct_actv_avoid_genotype_neuronal, &
9063  param_gp_matrix_predator = pred_meancount_actv_avoid_genotype_neuronal, &
9064  param_gp_matrix_stomach = stom_actv_avoid_genotype_neuronal, &
9065  param_gp_matrix_bodymass = bodymass_actv_avoid_genotype_neuronal, &
9066  param_gp_matrix_energy = energy_actv_avoid_genotype_neuronal, &
9067  param_gp_matrix_age = age_actv_avoid_genotype_neuronal, &
9068  param_gp_matrix_reprfac = reprfac_actv_avoid_genotype_neuronal, &
9069  ! Parameters :: G x P variances:
9070  param_gerror_cv_light = light_actv_avoid_genotype_neuronal_gerror_cv, &
9071  param_gerror_cv_depth = depth_actv_avoid_genotype_neuronal_gerror_cv, &
9072  param_gerror_cv_food_dir = foodcount_actv_avoid_genotype_neuronal_gerror_cv,&
9073  param_gerror_cv_food_mem = food_mem_actv_avoid_genotype_neuronal_gerror_cv, &
9074  param_gerror_cv_conspec = conspcount_actv_avoid_genotype_neuronal_gerror_cv,&
9075  param_gerror_cv_pred_dir = pred_direct_actv_avoid_genotype_neuronal_gerror_cv,&
9076  param_gerror_cv_predator = pred_meancount_actv_avoid_genotype_neuronal_gerror_cv,&
9077  param_gerror_cv_stomach = stom_actv_avoid_genotype_neuronal_gerror_cv, &
9078  param_gerror_cv_bodymass = bodymass_actv_avoid_genotype_neuronal_gerror_cv,&
9079  param_gerror_cv_energy = energy_actv_avoid_genotype_neuronal_gerror_cv,&
9080  param_gerror_cv_age = age_actv_avoid_genotype_neuronal_gerror_cv, &
9081  param_gerror_cv_reprfac = reprfac_actv_avoid_genotype_neuronal_gerror_cv,&
9082  ! @note Real agent perception components are now **substituted**
9083  ! by the **fake** values resulting from executing this
9084  ! behaviour (`do_this` method).
9085  perception_override_food_dir = perception_override_food_dir, &
9086  perception_override_pred_dir = perception_override_pred_dir, &
9087  perception_override_predator = perception_override_predator, &
9088  perception_override_stomach = perception_override_stomach, &
9089  perception_override_bodymass = perception_override_bodymass, &
9090  perception_override_energy = perception_override_energy &
9091  )
9092 
9093  ! @note **Expectancy** assessment for **reproduction** motivation,
9094  ! using `PERCEPT_COMPONENTS_MOTIV`-bound procedure with intent[in]
9095  ! for `this_agent` now.
9096  call this%expectancy%reproduction%percept_component%motivation_components &
9097  (this_agent, &
9098  ! Parameters:: Boolean G x P matrices:
9099  param_gp_matrix_light = light_reproduce_genotype_neuronal, &
9100  param_gp_matrix_depth = depth_reproduce_genotype_neuronal, &
9101  param_gp_matrix_food_dir = foodcount_reproduce_genotype_neuronal, &
9102  param_gp_matrix_food_mem = food_mem_reproduce_genotype_neuronal, &
9103  param_gp_matrix_conspec = conspcount_reproduce_genotype_neuronal, &
9104  param_gp_matrix_pred_dir = pred_direct_reproduce_genotype_neuronal, &
9105  param_gp_matrix_predator = pred_meancount_reproduce_genotype_neuronal, &
9106  param_gp_matrix_stomach = stom_reproduce_genotype_neuronal, &
9107  param_gp_matrix_bodymass = bodymass_reproduce_genotype_neuronal, &
9108  param_gp_matrix_energy = energy_reproduce_genotype_neuronal, &
9109  param_gp_matrix_age = age_reproduce_genotype_neuronal, &
9110  param_gp_matrix_reprfac = reprfac_reproduce_genotype_neuronal, &
9111  ! Parameters :: G x P variances:
9112  param_gerror_cv_light = light_reproduce_genotype_neuronal_gerror_cv, &
9113  param_gerror_cv_depth = depth_reproduce_genotype_neuronal_gerror_cv, &
9114  param_gerror_cv_food_dir = foodcount_reproduce_genotype_neuronal_gerror_cv,&
9115  param_gerror_cv_food_mem = food_mem_reproduce_genotype_neuronal_gerror_cv, &
9116  param_gerror_cv_conspec = conspcount_reproduce_genotype_neuronal_gerror_cv,&
9117  param_gerror_cv_pred_dir = pred_direct_reproduce_genotype_neuronal_gerror_cv,&
9118  param_gerror_cv_predator = pred_meancount_reproduce_genotype_neuronal_gerror_cv,&
9119  param_gerror_cv_stomach = stom_reproduce_genotype_neuronal_gerror_cv, &
9120  param_gerror_cv_bodymass = bodymass_reproduce_genotype_neuronal_gerror_cv,&
9121  param_gerror_cv_energy = energy_reproduce_genotype_neuronal_gerror_cv,&
9122  param_gerror_cv_age = age_reproduce_genotype_neuronal_gerror_cv, &
9123  param_gerror_cv_reprfac = reprfac_reproduce_genotype_neuronal_gerror_cv,&
9124  ! @note Real agent perception components are now **substituted**
9125  ! by the **fake** values resulting from executing this
9126  ! behaviour (`do_this` method).
9127  perception_override_food_dir = perception_override_food_dir, &
9128  perception_override_pred_dir = perception_override_pred_dir, &
9129  perception_override_predator = perception_override_predator, &
9130  perception_override_stomach = perception_override_stomach, &
9131  perception_override_bodymass = perception_override_bodymass, &
9132  perception_override_energy = perception_override_energy &
9133  )
9134 
9135  !> #### Calculate primary and final motivations ####
9136  !> Next, from the perceptual components calculated at the previous
9137  !! step we can obtain the **primary** and **final motivation** values by
9138  !! weighed summing.
9139  if (present(rescale_max_motivation)) then
9140  !> Here we can use global maximum motivation across all behaviours and
9141  !! perceptual components if it is provided, for rescaling.
9142  max_motivation = rescale_max_motivation
9143  else
9144  !> Or can rescale using local maximum value for this behaviour only.
9145  max_motivation = this%expectancy%max_perception()
9146  end if
9147 
9148  !> Transfer attention weights from the actor agent `this_agent` to the
9149  !! `this` behaviour component. So, we will now use the updated modulated
9150  !! attention weights of the agent rather than their default parameter
9151  !! values.
9152  call this%attention_transfer(this_agent)
9153 
9154  !> So the primary motivation values are calculated.
9155  call this%expectancy%motivation_primary_calc(max_motivation)
9156 
9157  !> Primary motivations are logged in the @ref intro_debug_mode "debug mode".
9158  call log_dbg( ltag_info // "Primary motivations: " // &
9159  "hunger: " // &
9160  tostr(this%expectancy%hunger%motivation_prim) // &
9161  ", fear_defence: " // &
9162  tostr(this%expectancy%fear_defence%motivation_prim) // &
9163  ", reproduce: " // &
9164  tostr(this%expectancy%reproduction%motivation_prim), &
9165  procname, modname )
9166 
9167  !> There is **no modulation** at this stage, so the final motivation
9168  !! values are the same as primary motivations.
9169  call this%expectancy%modulation_none()
9170 
9171  !> #### Calculate motivation expectancies ####
9172  !> Finally, calculate the finally **expected arousal level for this
9173  !! behaviour**. As in the GOS, the overall arousal is the maximum value
9174  !! among all motivation components.
9175  this%arousal_expected = this%expectancy%max_final()
9176 
9177  !> Log also the final expectancy value in the @ref intro_debug_mode
9178  !! "debug mode".
9179  call log_dbg( ltag_info // "Expectancy: " // tostr(this%arousal_expected),&
9180  procname, modname )
9181 
9182  !> Now as we know the expected arousal, we can choose the behaviour which
9183  !! would minimise this arousal level.
9184 
9185  end subroutine walk_random_motivations_expect
9186 
9187  !-----------------------------------------------------------------------------
9188  !> Execute this behaviour component "random walk" by `this_agent` agent.
9189  subroutine walk_random_do_execute(this, this_agent, step_dist, step_cv, &
9190  environment_limits)
9191  class(walk_random), intent(inout) :: this
9192  !> @param[in] this_agent is the actor agent which goes down.
9193  class(appraisal), intent(inout) :: this_agent
9194  !> @param[in] step_dist optional fixed distance of the walk. In case the
9195  !! coefficient of variation (next optional parameter) is
9196  !! provided, the walk distance is stochastic with the later
9197  !! coefficient of variation.
9198  real(SRP), optional, intent(in) :: step_dist
9199  !> @param[in] step_cv Optional coefficient of variation for the walk step,
9200  !! if not provided, the step CV set by the parameter
9201  !! commondata::walk_random_distance_stochastic_cv.
9202  real(SRP), optional, intent(in) :: step_cv
9203  !> @param environment_limits Limits of the environment area available for
9204  !! the random walk. The moving object cannot get beyond this limit.
9205  !! If this parameter is not provided, the environmental limits are
9206  !! obtained automatically from the global array
9207  !! the_environment::global_habitats_available.
9208  class(environment), intent(in), optional :: environment_limits
9209 
9210  ! Local copies of optionals
9211  real(SRP) :: step_cv_here
9212 
9213  !> ### Implementation details ###
9214  !> #### Checks and preparations ####
9215  !> Check if the optional coefficient of variation for the step size. If the
9216  !! parameter is not provided, the CV is set from the parameter
9217  !! commondata::walk_random_distance_stochastic_cv.
9218  !! @warning To set deterministic walk, the coefficient of variation should
9219  !! be explicitly set to 0.0. This is different from the expectancy
9220  !! procedures , which assume deterministic default walk (CV=0.0).
9221  if (present(step_cv)) then
9222  step_cv_here = step_cv
9223  else
9224  step_cv_here = walk_random_distance_stochastic_cv
9225  end if
9226 
9227  !> #### Step 1: do_this ####
9228  !> First, we use the intent-in **do**-procedure
9229  !! the_behaviour::walk_random::do_this() to perform the behaviour desired.
9230  !! However, Expectancies for food gain and predator risk that are not used
9231  !! at this stage.
9232  if (present(step_dist)) then
9233  call this%do_this( this_agent=this_agent, distance=step_dist, &
9234  distance_cv=step_cv_here )
9235  else
9236  call this%do_this( this_agent=this_agent, distance_cv=step_cv_here )
9237  end if
9238 
9239  !> #### Step 2: Change the agent ####
9240  !> ##### Perform walk #####
9241  !> The agent does the random walk with the step size this\%distance.
9242  !! Therefore, it is now possible to change the state of the agent.
9243  !!
9244  !! Random walk is done in the "2.5D" mode, i.e. with separate parameters
9245  !! for the horizontal distance (and CV) and vertical depth distance (and
9246  !! its CV). This is done to avoid potentially a too large vertical
9247  !! displacement of the agent (vertical migration involves separate
9248  !! behaviours). Thus, the vertical shift distance should normally be
9249  !! smaller than the horizontal shift. The difference between the main
9250  !! horizontal and smaller vertical shifts is defined by the parameter
9251  !! commondata::walk_random_vertical_shift_ratio. Note that the coefficient
9252  !! of variation for the vertical walk component is set separately
9253  !! using the ratio commondata::walk_random_vertical_shift_cv_ratio.
9254  !!
9255  !! The agent performs the random walk using the main
9256  !! the_environment::spatial_moving::rwalk() procedure. If the limiting
9257  !! environment is known (`environment_limits` optional parameter), the
9258  !! `rwalk` call also includes it. If environmental limits are not provided
9259  !! as a dummy parameter, they are obtained automatically from the global
9260  !! array the_environment::global_habitats_available.
9261  if (present(environment_limits)) then
9262  call this_agent%rwalk( &
9263  this%distance, this%distance_cv, &
9264  this%distance * walk_random_vertical_shift_ratio, &
9265  this%distance_cv*walk_random_vertical_shift_cv_ratio, &
9266  environment_limits )
9267  else
9268  call this_agent%rwalk( &
9269  this%distance, this%distance_cv, &
9270  this%distance * walk_random_vertical_shift_ratio, &
9271  this%distance_cv*walk_random_vertical_shift_cv_ratio, &
9272  global_habitats_available( &
9273  this_agent%find_environment( &
9274  global_habitats_available) ) )
9275  end if
9276 
9277  !> ##### Process the cost of movement #####
9278  !> - Reset the body mass of the actor agent subtracting the actual cost of
9279  !! moving that is automatically calculated in the call to
9280  !! the_body::condition::cost_swim(). The the_body::condition::set_mass()
9281  !! method is used here to adjust the mass.
9282  call this_agent%set_mass( &
9283  value_set = this_agent%get_mass() - &
9284  this_agent%cost_swim(exponent= &
9285  swimming_cost_exponent_laminar), &
9286  update_history = .true. )
9287 
9288  !> - Additionally, also call the `the_body::condition::set_length()` method
9289  !! to update the body length history stack. However, the value_set
9290  !! parameter here is just the current value. This fake re-setting of the
9291  !! body length is done to keep both mass and length synchronised in their
9292  !! history stack arrays (there is no procedure for only updating history).
9293  call this_agent%set_length( value_set = this_agent%get_length(), &
9294  update_history = .true. )
9295 
9296  !> - After resetting the body mass, update energy reserves of the agent,
9297  !! that depend on both the length and the mass.
9298  !! .
9299  call this_agent%energy_update()
9300 
9301  !> Finally, check if the agent is starved to death. If yes, the agent can
9302  !! die without going any further.
9303  if (this_agent%starved_death()) call this_agent%dies()
9304 
9305  !> #### Step 3: Change the environment ####
9306  !> Random walk does not affect the environmental objects.
9307 
9308  end subroutine walk_random_do_execute
9309 
9310  !- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
9311 
9312  !-----------------------------------------------------------------------------
9313  !> Initialise the behaviour components of the agent, the
9314  !! the_behaviour::behaviour class.
9315  elemental subroutine behaviour_whole_agent_init(this)
9316  class(behaviour), intent(inout) :: this
9317 
9318  !> ### Implementation notes ###
9319  !> Initialise the label for the currently executed behaviour to an easily
9320  !! discernible value (e.g. by `gre`).
9321  this%behaviour_label = "init_unknown"
9322 
9323  !> Initialise the execution status of each of the behaviour units that
9324  !! compose this class to FALSE (these behavioural units are not executing).
9325  call this%deactivate()
9326 
9327  !> Cleanup the history stack of behaviour labels
9328  !! the_behaviour::behaviour::history_behave.
9329  call this%cleanup_behav_history()
9330 
9331  !> Initialise @ref anchor behav_debug_indicators "debugging indicators"
9332  !! for the_behaviour::behaviour class.
9333  this%n_eats_all_indicator = 0
9334  this%n_eaten_indicator = 0
9335  this%mass_eaten_indicator = 0.0_srp
9336 
9337  end subroutine behaviour_whole_agent_init
9338 
9339  !-----------------------------------------------------------------------------
9340  !> Deactivate all behaviour units that compose the behaviour repertoire of
9341  !! the agent.
9342  elemental subroutine behaviour_whole_agent_deactivate(this)
9343  class(behaviour), intent(inout) :: this
9344 
9345  this%eat%is_active = .false.
9346  this%reproduce%is_active = .false.
9347  this%walk_random%is_active = .false.
9348  this%freeze%is_active = .false.
9349  this%escape_dart%is_active = .false.
9350  this%approach_spatial%is_active = .false.
9351  this%approach_conspec%is_active = .false.
9352  this%migrate%is_active = .false.
9353  this%depth_down%is_active = .false.
9354  this%depth_up%is_active = .false.
9355  this%debug_base%is_active = .false.
9356 
9357  end subroutine behaviour_whole_agent_deactivate
9358 
9359  !-----------------------------------------------------------------------------
9360  !> Obtain the label of the currently executing behaviour for the `this` agent.
9361  elemental function behaviour_get_behaviour_label_executing(this) &
9362  result(label_is)
9363  class(behaviour), intent(in) :: this
9364  character(len=LABEL_LENGTH) :: label_is
9365 
9366  label_is = this%behaviour_label
9367 
9369 
9370  !-----------------------------------------------------------------------------
9371  !> Select the optimal conspecific among (possibly) several ones that are
9372  !! available in the **perception object** of the agent.
9373  function behaviour_select_conspecific(this, rescale_max_motivation) &
9374  result(number_in_seen)
9375  class(behaviour), intent(inout) :: this !> @param[in] self object.
9376  !> @param[in] rescale_max_motivation maximum motivation value for
9377  !! rescaling all motivational components for comparison
9378  !! across all motivation and perceptual components and behaviour
9379  !! units.
9380  real(srp), optional, intent(in) :: rescale_max_motivation
9381  !> @return The function returns the index of the food item that is chosen
9382  !! for eating (if there are any food items within the perception
9383  !! object of the agent) or 0 otherwise.
9384  integer :: number_in_seen
9385 
9386  ! Local variables.
9387  !> ### Notable local variables ###
9388  !> - **n_seen_percepis** is the total number of food items found in the
9389  !! perception object.
9390  integer :: iconsp, n_seen_percep
9391  real(srp) :: rescale_max_motivation_here
9392 
9393  ! PROCNAME is the procedure name for logging and debugging (with MODNAME).
9394  character(len=*), parameter :: procname = "(behaviour_select_conspecific)"
9395 
9396  !> - **expected_gos_consp** is an *array* of motivational GOS expectancies
9397  !! from each of the food items within the perception object.
9398  real(srp), dimension(this%perceive_consp%conspecifics_seen_count) :: &
9399  expected_gos_consp
9400 
9401  !> ### Implementation details ###
9402  !> #### Preparation steps ####
9403  !> First, check if the agent has any conspecific(s) within its perception
9404  !! objects using `perception::has_consp()` method. Return zero straight
9405  !! away if no conspecifics are seen. Therefore, from now on it is assumed
9406  !! that the agent has at least one conspecific in its perception object.
9407  if (.not. this%has_consp()) then
9408  number_in_seen = 0
9409  return
9410  end if
9411 
9412  !> The local variable `n_seen_percep` is the total number of conspecifics
9413  !! found in the perception object.
9414  ! @note Can also be obtained using class function `...%get_count()`.
9415  n_seen_percep = this%perceive_consp%conspecifics_seen_count
9416 
9417  !> If there is only one conspecific, get its number (1) and exit. There
9418  !! is no choice if only a single conspecific is here.
9419  if (n_seen_percep==1) then
9420  number_in_seen = 1
9421  return
9422  end if
9423 
9424  !> Check if the maximum motivation value for rescale is provided as
9425  !! a parameter.
9426  if (present(rescale_max_motivation)) then
9427  !> If provided, use global maximum motivation across all behaviours and
9428  !! perceptual components for rescaling.
9429  rescale_max_motivation_here = rescale_max_motivation
9430  else
9431  !> If not provided, rescale using local maximum motivation value for
9432  !! this agent.
9433  rescale_max_motivation_here = this%motivations%max_final()
9434  end if
9435 
9436  !> #### Calculate GOS expectancies ####
9437  !> Calculate GOS expectancies from approaching each of the conspecifics
9438  !! in the perception object. This is implemented in the `CONSP_EXPECT`
9439  !! loop.
9440  !> ##### CONSP_EXPECT loop #####
9441  consp_expect: do iconsp = 1, n_seen_percep
9442 
9443  !> - First, initialise the behavioural state. Specifically, the
9444  !! `approach_conspec::init()` method initialises the attention weights.
9445  call this%approach_conspec%init()
9446 
9447  !> - Second, calculate the motivation GOS expectancies that would result
9448  !! if the agent approaches to each of the conspecifics that are
9449  !! in its perception object. The method
9450  !! approach_conspec::expectancies_calculate()` does the job.
9451  !! @note Note that the target offset parameter is absent, which means
9452  !! that the default value, average body size of the agent and its
9453  !! target, is used. TODO: or set explicitly?
9454  call this%approach_conspec%expectancies_calculate( &
9455  this_agent = this, &
9456  target_object = this%perceive_consp%conspecifics_seen(iconsp),&
9457  rescale_max_motivation = rescale_max_motivation_here )
9458 
9459  !> - Now we can get an array of motivational GOS expectancies from
9460  !! approaching each of the conspecifics within the perception object:
9461  !! `expected_gos_consp`.
9462  expected_gos_consp(iconsp) = this%approach_conspec%arousal_expected ! %gos_expected()
9463 
9464  end do consp_expect
9465 
9466  !> #### Select minimum arousal items ####
9467  !> Once we calculated GOS motivational expectancies for all the food items,
9468  !! we can determine which of the food items results in the **minimum**
9469  !! arousal.
9470  number_in_seen = minloc(expected_gos_consp, 1)
9471 
9472  call log_dbg(ltag_info // "arousal expectancies for all conspecifics" // &
9473  "in the perception object: " // tostr(expected_gos_consp), &
9474  procname,modname)
9475 
9476  call log_dbg(ltag_info // "minimum arousal # " // tostr(number_in_seen) //&
9477  " = " // tostr(expected_gos_consp(number_in_seen)), &
9478  procname, modname)
9479 
9480  end function behaviour_select_conspecific
9481 
9482  !-----------------------------------------------------------------------------
9483  !> Select the nearest conspecific among (possibly) several ones that are
9484  !! available in the perception object. Note that conspecifics are sorted
9485  !! by distance within the perception object. Thus, this procedure just
9486  !! selects the first conspecific.
9487  function behaviour_select_conspecific_nearest(this) result(number_in_seen)
9488  class(behaviour), intent(in) :: this !> @param[in] self object.
9489  !> @return The function returns the index of the first conspecific
9490  !! if there are any within the perception object of the agent,
9491  !! 0 otherwise.
9492  integer :: number_in_seen
9493 
9494  if(this%has_consp()) then
9495  number_in_seen = 1
9496  else
9497  number_in_seen = 0
9498  end if
9499 
9501 
9502  !-----------------------------------------------------------------------------
9503  !> Select the optimal food item among (possibly) several ones that are
9504  !! available in the **perception object** of the agent.
9505  !! @details Choosing the optimal food item to catch may be a non-trivial task
9506  !! and different decision rules could be implemented for this.
9507  function behaviour_select_food_item(this, rescale_max_motivation) &
9508  result(number_in_seen)
9509  class(behaviour), intent(inout) :: this !> @param[in] self object.
9510  !> @param[in] rescale_max_motivation maximum motivation value for
9511  !! rescaling all motivational components for comparison
9512  !! across all motivation and perceptual components and behaviour
9513  !! units.
9514  real(srp), optional, intent(in) :: rescale_max_motivation
9515  !> @return The function returns the index of the food item that is chosen
9516  !! for eating (if there are any food items within the perception
9517  !! object of the agent) or 0 otherwise.
9518  integer :: number_in_seen
9519 
9520  ! Local variables.
9521  !> ### Notable local variables ###
9522  !> - **n_seen_percepis** is the total number of food items found in the
9523  !! perception object.
9524  integer :: fitem, n_seen_percep
9525  real(srp) :: rescale_max_motivation_here
9526 
9527  !> - **expected_gos_fitem** is an *array* of motivational GOS expectancies
9528  !! from each of the food items within the perception object.
9529  real(srp), dimension(this%perceive_food%food_seen_count) :: &
9530  expected_gos_fitem
9531 
9532  ! PROCNAME is the procedure name for logging and debugging (with MODNAME).
9533  character(len=*), parameter :: procname = "(behaviour_select_food_item)"
9534 
9535  !> ### Implementation details ###
9536  !> #### Preparation steps ####
9537  !> First, check if the agent has any food item(s) within its perception
9538  !! objects using `perception::has_food()` method. Return zero straight away
9539  !! if no food seen. Therefore, from now on it is assumed that the agent
9540  !! has at least one food item in its perception object.
9541  if (.not. this%has_food()) then
9542  number_in_seen = 0
9543  return
9544  end if
9545 
9546  !> The local variable `n_seen_percep` is the total number of food items
9547  !! found in the perception object.
9548  ! @note Can also be obtained using class function `...%get_count()`.
9549  n_seen_percep = this%perceive_food%food_seen_count
9550 
9551  !> If there is only one food item, get its number (1) and exit.
9552  ! @warning The condition can be disabled if we check the
9553  ! possible case when eating the food actually reduces
9554  ! fitness (GOS arousal increases), in such case
9555  ! do **not** eat the food item. But for just selecting
9556  ! which of the available items to eat, this case is
9557  ! degenerate.
9558  if (n_seen_percep==1) then
9559  number_in_seen = 1
9560  return
9561  end if
9562 
9563  !> Check if the maximum motivation value for rescale is provided as
9564  !! a parameter.
9565  if (present(rescale_max_motivation)) then
9566  !> If provided, use global maximum motivation across all behaviours and
9567  !! perceptual components for rescaling.
9568  rescale_max_motivation_here = rescale_max_motivation
9569  else
9570  !> If not provided, rescale using local maximum motivation value for
9571  !! this agent.
9572  rescale_max_motivation_here = this%motivations%max_final()
9573  end if
9574 
9575  !> #### Calculate GOS expectancies ####
9576  !> Calculate GOS expectancies from each of the food items in the perception
9577  !! object. This is implemented in the `ITEMS_EXPECT` loop.
9578  !> ##### ITEMS_EXPECT loop #####
9579  items_expect: do fitem = 1, n_seen_percep
9580 
9581  !> - First, initialise the behavioural state. Specifically, the
9582  !! `eat_food::init()` method initialises the attention weights.
9583  call this%eat%init()
9584 
9585  !> - Second, calculate the motivation GOS expectancies from each of the
9586  !! food item in the perception object of the **this** agent. The
9587  !! `eat_food::expectancies_calculate()` does the job.
9588  call this%eat%expectancies_calculate( &
9589  this_agent = this, &
9590  food_item_eaten = this%perceive_food%foods_seen(fitem), &
9591  rescale_max_motivation = rescale_max_motivation_here )
9592 
9593  !> - Now we can get an array of motivational GOS expectancies from
9594  !! each of the food items within the perception object:
9595  !! `expected_gos_fitem`.
9596  expected_gos_fitem(fitem) = this%eat%arousal_expected ! %gos_expected()
9597 
9598  ! - And finally **weight** the final GOS expectancy value for this food
9599  ! item by a subjective assessment of the capture probability of this
9600  ! food item (weighting is reverse). The subjective capture probability
9601  ! is calculated by the sub-function `::subjective_capture_prob()`.
9602  ! .
9603  !expected_gos_fitem(fitem) = expected_gos_fitem(fitem) * &
9604  ! (1.0_SRP - subjective_capture_prob(fitem))
9605 
9606  end do items_expect
9607 
9608  !> #### Select minimum arousal items ####
9609  !> Once we calculated GOS motivational expectancies for all the food items,
9610  !! we can determine which of the food items results in the **minimum**
9611  !! arousal.
9612  ! @details The final value of the GOS expectancy is the the minimum
9613  ! @f[ min( \gamma_{i} \cdot (1-\rho_{i} \varepsilon ) ) , @f]
9614  ! where @f$ \gamma_{i} @f$ is the expected GOS arousal value
9615  ! for the i-th food item and @f$ \rho_{i} @f$ is subjective
9616  ! probability of the capture for this item, while
9617  ! @f$ \varepsilon @f$ is a Gaussian subjective probability
9618  ! assessment error.
9619  number_in_seen = minloc(expected_gos_fitem, 1)
9620 
9621  call log_dbg(ltag_info // "Arousal expectancies for all food items " // &
9622  "in the perception object: " // tostr(expected_gos_fitem), &
9623  procname,modname)
9624 
9625  call log_dbg(ltag_info // "Minimum arousal # " // &
9626  tostr(number_in_seen) // " = " // &
9627  tostr(expected_gos_fitem(number_in_seen)) //" item mass=" &
9628  // tostr(this%perceive_food%foods_seen(number_in_seen)%get_mass()), &
9629  procname, modname)
9630 
9631  contains !. . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . .
9632  !> Calculate subjective probability of food item capture, as objective
9633  !! capture probability and random assessment error.
9634  !! @note Note that this function is contained (ower order) in
9635  !! the_behaviour::behaviour_select_food_item().
9636  function subjective_capture_prob(fitem) result (capture_prob_subjective)
9637  real(srp) :: capture_prob_subjective
9638  integer :: fitem
9639  !! For this we first calculate the probability of capture for this
9640  !! specific food item.
9641  capture_prob_subjective = &
9642  this%perceive_food%foods_seen(fitem)%capture_probability( &
9643  distance=this%perceive_food%foods_distances(fitem) )
9644  call log_dbg( ltag_info // &
9645  "Subjective capture probability, true value: " // &
9646  tostr(capture_prob_subjective), procname, modname )
9647  !> Then we add a random Gaussian error to the above objective value.
9648  !! Now we have obtained the stochastic subjective value of the capture
9649  !! probability for this food item including a Gaussian error. There is
9650  !! also a strong limitation for the subjective probability to be within
9651  !! the range [0.0, 1.0].
9652  !! See the_neurobio::food_perception_probability_capture_memory_object()
9653  !! for a similar Gaussian error in subjective probability.
9654  capture_prob_subjective = within( rnorm( capture_prob_subjective, &
9655  cv2variance( &
9656  food_item_capture_probability_subjective_errorr_cv, &
9657  capture_prob_subjective) ), 0.0_srp, 1.0_srp )
9658 
9659  call log_dbg( ltag_info // &
9660  "Subjective capture probability, final value " // &
9661  "with Gaussian error: " // tostr(capture_prob_subjective),&
9662  procname, modname )
9663 
9664  end function subjective_capture_prob
9665 
9666  end function behaviour_select_food_item
9667 
9668  !-----------------------------------------------------------------------------
9669  !> Select the nearest food item among (possibly) several ones that are
9670  !! available in the perception object. This is a specific and **most
9671  !! simplistic** version of the `behaviour_select_food_item` function: select
9672  !! the nearest food item available in the agent's perception object. Because
9673  !! the food items are sorted within the perception object just select the
9674  !! first item.
9675  function behaviour_select_food_item_nearest(this) result(number_in_seen)
9676  class(behaviour), intent(in) :: this !> @param[in] self object.
9677  !> @return The function returns the index of the first food item if there
9678  !! are any food items within the perception object of the agent or
9679  !! 0 otherwise.
9680  integer :: number_in_seen
9681 
9682  if(this%has_food()) then
9683  number_in_seen = 1
9684  else
9685  number_in_seen = 0
9686  end if
9687 
9689 
9690  !-----------------------------------------------------------------------------
9691  !> Eat a specific food item that are found in the perception object.
9692  subroutine behaviour_do_eat_food_item(this, &
9693  number_in_seen, food_resource_real)
9694  class(behaviour), intent(inout) :: this !> @param[in] self object.
9695  !> @param[in] The index of the first food item (if there are any food items)
9696  !! within the perception object of the agent. If not set,
9697  !! default is the first (nearest) food item in the perception
9698  !! object.
9699  integer, optional, intent(in) :: number_in_seen
9700 
9701  !> @param[inout] food_resource_real The food resource the agent is eating
9702  !! the food item in. Note that it could be a joined food
9703  !! resource composed with the_environment::join() procedure
9704  !! for assembling several habitats into the
9705  !! the_environment::global_habitats_available array or
9706  !! resources collapsed using the
9707  !! the_environment::food_resource::join() method.
9708  class(food_resource), intent(inout) :: food_resource_real
9709 
9710  ! Local copies of optionals.
9711  integer :: number_in_seen_here
9712 
9713  ! Local indicator of the eat success
9714  logical :: eat_food_item_is_success
9715 
9716  !> ### Implementation details ###
9717  !> First, check if the agent has any food items in its perception object
9718  !! using the perception::has_food() method. Return straight away if no
9719  !! food perceived.
9720  if (.not. this%has_food()) return
9721 
9722  if (present(number_in_seen)) then
9723  !> If there are no food items in the perception object or nothing is
9724  !! chosen, exit without any further processing. Normally this should
9725  !! not occur as the `perception::has_food()` check method guarantees
9726  !! that there are some food items in the perception object.
9727  if ( number_in_seen == 0 ) return
9728  !> If this check is passed set the id of the food perception object.
9729  number_in_seen_here = number_in_seen
9730  else
9731  number_in_seen_here = 1
9732  end if
9733 
9734  !> Finally, init the behaviour object `eat` before "execute". Calls the
9735  !! eat_food::init() method.
9736  call this%eat%init()
9737 
9738  !> Set the currently executed behaviour label. It is from the
9739  !! the_behaviour::behaviour_base::label data component of the base class.
9740  this%behaviour_label = this%eat%label
9741 
9742  !> Set the execution status for all behaviours to FALSE and then for this
9743  !! specific behaviour to TRUE. Only one behaviour unit can be executed at
9744  !! a time.
9745  call this%deactivate()
9746  this%eat%is_active = .true.
9747 
9748  !> Do eat the food item chosen using the `execute` method of the
9749  !! `EAT_FOOD` class: eat_food::execute().
9750  call this%eat%execute( this_agent = this, &
9751  food_item_eaten = &
9752  this%perceive_food%foods_seen( &
9753  number_in_seen_here), &
9754  food_resource_real = food_resource_real, &
9755  eat_is_success = eat_food_item_is_success )
9756 
9757  !> Update (add to stack) the agent's history of behaviours
9758  !! the_behaviour::behaviour::history_behave: string labels of the
9759  !! behaviours are are saved.
9760  call add_to_history( this%history_behave, this%eat%label )
9761 
9762  !> Update (increment) the agent's debugging indicators from
9763  !! @ref behav_debug_indicators "indicators":
9764  !! - individual count of the_behaviour::eat_food occasions;
9765  this%n_eats_all_indicator = this%n_eats_all_indicator +1
9766  !> - individual count of successful food items \%n_eaten_indicator.
9767  !! .
9768  if (eat_food_item_is_success) then
9769  this%n_eaten_indicator = this%n_eaten_indicator + 1
9770  this%mass_eaten_indicator = this%mass_eaten_indicator + &
9771  this%perceive_food%foods_seen(number_in_seen_here)%get_mass()
9772  end if
9773 
9774  !> Shift the position of the agent to the position of the food item eaten.
9775  !! That is, the agent itself moves to the spatial position that has been
9776  !! occupied by the food item that has just been consumed.
9777  call this%position( &
9778  this%perceive_food%foods_seen(number_in_seen_here)%location() )
9779 
9780  end subroutine behaviour_do_eat_food_item
9781 
9782  !-----------------------------------------------------------------------------
9783  !> Reproduce based on the `this` agent's current state.
9784  subroutine behaviour_do_reproduce(this)
9785  class(behaviour), intent(inout) :: this !> @param[in] self object.
9786 
9787  !> ### Implementation details ###
9788  !! First, check if there are any conspecifics in the perception object.
9789  !! Return straight away if no conspecifics seen. No cost of reproduction
9790  !! is subtracted in such a case.
9791  if (.not. this%has_consp()) return
9792 
9793  !> Then, Init the behaviour (`reproduce::init()` =>
9794  !! `the_behaviour::reproduce_init_zero`) before "execute".
9795  call this%reproduce%init()
9796 
9797  !> Set the currently executed behaviour label. It is from the
9798  !! the_behaviour::behaviour_base::label data component of the base class.
9799  this%behaviour_label = this%reproduce%label
9800 
9801  !> Set the execution status for all behaviours to FALSE and then for this
9802  !! specific behaviour to TRUE. Only one behaviour unit can be executed at
9803  !! a time.
9804  call this%deactivate()
9805  this%reproduce%is_active = .true.
9806 
9807  !> Finally, do the reproduction using the `reproduce::execute()` =>
9808  !! `the_behaviour::reproduce_do_execute()` method from the
9809  !! `the_behaviour::reproduce` class.
9810  call this%reproduce%execute( this )
9811 
9812  !> Update (add to stack) the agent's history of behaviours
9813  !! the_behaviour::behaviour::history_behave: string labels of the
9814  !! behaviours are are saved.
9815  call add_to_history( this%history_behave, this%reproduce%label )
9816 
9817  !> Finally, update the positional history stack
9818  !! the_environment::spatial_moving::history: the current spatial
9819  !! position of the agent is re-saved in the history stack using
9820  !! the_environment::spatial_moving::repeat_position().
9821  !! @note Re-saving the current position is necessary to keep the
9822  !! full positional history even for the behaviours that do not
9823  !! involve spatial displacement (movement).
9824  call this%repeat_position()
9825 
9826  end subroutine behaviour_do_reproduce
9827 
9828  !-----------------------------------------------------------------------------
9829  !> Perform a random Gaussian walk to a specific average distance with
9830  !! certain variance (set by the CV).
9831  subroutine behaviour_do_walk(this, distance, distance_cv)
9832  class(behaviour), intent(inout) :: this
9833  !> @param[in] distance is an optional walk distance. If stochastic Gaussian
9834  !! walk is set, this value defines the average distance.
9835  !! @note Even though the walk distance is internally defined in
9836  !! terms of the agent's body length, this parameter
9837  !! defines the **absolute distance** in cm.
9838  real(SRP), optional, intent(in) :: distance
9839  !> @param[in] distance_cv is an optional coefficient of variation for the
9840  !! random walk distance. If absent, non-stochastic walk step
9841  !! size is used.
9842  real(SRP), optional, intent(in) :: distance_cv
9843 
9844  ! Local copies of optionals.
9845  real(SRP) :: distance_loc, distance_cv_loc
9846 
9847  !> ### Implementation notes ###
9848  !> - First, check if the walk distance is provided as a dummy parameter,
9849  !! and if not, the default value is set by the
9850  !! commondata::walk_random_distance_default_factor times of the agent
9851  !! body length.
9852  if (present(distance)) then
9853  distance_loc = distance
9854  else
9855  distance_loc = this%get_length() * walk_random_distance_default_factor
9856  end if
9857 
9858  !> - Then check if the Coefficient of Variation of the distance parameter
9859  !! is also provided. If no, the default If the `distance_cv` optional
9860  !! dummy parameter is set to the value defined by the
9861  !! commondata::walk_random_distance_stochastic_cv parameter.
9862  distance_cv_loc = walk_random_distance_stochastic_cv
9863  if (present(distance_cv)) then
9864  if ( distance_cv > tolerance_high_def_srp ) then
9865  distance_cv_loc = distance_cv
9866  else
9867  distance_cv_loc = 0.0_srp
9868  end if
9869  end if
9870 
9871  !> - Initialise the behavioural component for this behaviour,
9872  !! the_behaviour::walk_random::init().
9873  call this%walk_random%init()
9874 
9875  !> Set the currently executed behaviour label. It is from the
9876  !! the_behaviour::behaviour_base::label data component of the base class.
9877  this%behaviour_label = this%walk_random%label
9878 
9879  !> Set the execution status for all behaviours to FALSE and then for this
9880  !! specific behaviour to TRUE. Only one behaviour unit can be executed at
9881  !! a time.
9882  call this%deactivate()
9883  this%walk_random%is_active = .true.
9884 
9885  !> - Finally, call the `execute` method for this behaviour:
9886  !! the_behaviour::walk_random::execute().
9887  !! .
9888  call this%walk_random%execute( this, step_dist=distance_loc, &
9889  step_cv=distance_cv )
9890 
9891  !> Update (add to stack) the agent's history of behaviours
9892  !! the_behaviour::behaviour::history_behave: string labels of the
9893  !! behaviours are are saved.
9894  call add_to_history( this%history_behave, this%walk_random%label )
9895 
9896  end subroutine behaviour_do_walk
9897 
9898  !-----------------------------------------------------------------------------
9899  !> Perform (execute) the the_behaviour::freeze behaviour.
9900  subroutine behaviour_do_freeze(this)
9901  class(behaviour), intent(inout) :: this
9902 
9903  !> ### Implementation notes ###
9904  !> This behaviour has no parameters (e.g. target) and is rather trivial
9905  !! to execute:
9906  !! - initialise the behaviour using the the_behaviour::freeze::init()
9907  !! method.
9908  call this%freeze%init()
9909 
9910  !> Set the currently executed behaviour label. It is from the
9911  !! the_behaviour::behaviour_base::label data component of the base class.
9912  this%behaviour_label = this%freeze%label
9913 
9914  !> Set the execution status for all behaviours to FALSE and then for this
9915  !! specific behaviour to TRUE. Only one behaviour unit can be executed at
9916  !! a time.
9917  call this%deactivate()
9918  this%freeze%is_active = .true.
9919 
9920  !> - execute the behaviour with the_behaviour::freeze::execute() method.
9921  !! .
9922  call this%freeze%execute( this )
9923 
9924  !> Update (add to stack) the agent's history of behaviours
9925  !! the_behaviour::behaviour::history_behave: string labels of the
9926  !! behaviours are are saved.
9927  call add_to_history( this%history_behave, this%freeze%label )
9928 
9929  !> Finally, update the positional history stack
9930  !! the_environment::spatial_moving::history: the current spatial
9931  !! position of the agent is re-saved in the history stack using
9932  !! the_environment::spatial_moving::repeat_position() method.
9933  !! @note Re-saving the current position is necessary to keep the
9934  !! full positional history even for the behaviours that do not
9935  !! involve spatial displacement (movement).
9936  call this%repeat_position()
9937 
9938  end subroutine behaviour_do_freeze
9939 
9940  !-----------------------------------------------------------------------------
9941  !> Perform (execute) the the_behaviour::escape_dart behaviour.
9942  subroutine behaviour_do_escape_dart(this, predator_object)
9943  class(behaviour), intent(inout) :: this
9944  !> @param[in] predator_object optional predator object, if present, it is
9945  !! assumed the actor agent tries to actively escape from this
9946  !! specific predator.
9947  class(spatial), optional, intent(in) :: predator_object
9948 
9949  !> ### Implementation notes ###
9950  !! - Initialise the behaviour using the the_behaviour::escape_dart::init()
9951  !! method.
9952  call this%escape_dart%init()
9953 
9954  !> Set the currently executed behaviour label. It is from the
9955  !! the_behaviour::behaviour_base::label data component of the base class.
9956  this%behaviour_label = this%escape_dart%label
9957 
9958  !> Set the execution status for all behaviours to FALSE and then for this
9959  !! specific behaviour to TRUE. Only one behaviour unit can be executed at
9960  !! a time.
9961  call this%deactivate()
9962  this%escape_dart%is_active = .true.
9963 
9964  !> - Execute the behaviour with the_behaviour::escape_dart::execute()
9965  !! method. Note that if the target predator object is not provided, a
9966  !! default predator with the size commondata::predator_body_size is
9967  !! assumed. See the_behaviour::escape_dart_do_this() for details.
9968  !! .
9969  if (present(predator_object)) then
9970  call this%escape_dart%execute( this, predator_object )
9971  else
9972  call this%escape_dart%execute( this )
9973  end if
9974 
9975  !> Update (add to stack) the agent's history of behaviours
9976  !! the_behaviour::behaviour::history_behave: string labels of the
9977  !! behaviours are are saved.
9978  call add_to_history( this%history_behave, this%escape_dart%label )
9979 
9980  end subroutine behaviour_do_escape_dart
9981 
9982  !-----------------------------------------------------------------------------
9983  !> Approach a specific the_environment::spatial class target, i.e. execute
9984  !! the the_behaviour::approach behaviour. The target is either a
9985  !! conspecific from the perception (the_neurobio::conspec_percept_comp class)
9986  !! or any arbitrary the_environment::spatial class object.
9987  subroutine behaviour_do_approach(this, target_object, is_random, target_offset)
9988  class(behaviour), intent(inout) :: this
9989  !> @param[in] target_object is the spatial target object the actor agent
9990  !! is going to approach.
9991  class(spatial), intent(in) :: target_object
9992  !> @param[in] is_random indicator flag for random correlated walk. If
9993  !! present and is TRUE, the agent approaches to the
9994  !! `target_object` in form of random correlated walk (see
9995  !! the_environment::spatial_moving::corwalk()), otherwise
9996  !! directly.
9997  logical, optional, intent(in) :: is_random
9998  !> @param[in] target_offset is an optional offset for the target, so that
9999  !! the target position of the approaching agent does not
10000  !! coincide with the target object. If absent, a default value
10001  !! set by the commondata::approach_offset_default is used.
10002  !! For the the_behaviour::approach_conspec, the default value
10003  !! is as an average of the agent and target conspecific body
10004  !! lengths.
10005  real(SRP), optional, intent(in) :: target_offset
10006 
10007  ! Local copies of optionals
10008  logical :: is_random_walk
10009  real(SRP) :: target_offset_here
10010 
10011  !> ### Implementation details ###
10012  !> - Check the optional parameter flag: `is_random`: if the parameter is
10013  !! set to TRUE, a random Gaussian walk towards the target object is done,
10014  !! otherwise a direct direct approach towards the target object leaving
10015  !! the target offset distance is performed.
10016  !! .
10017  if (present(is_random)) then
10018  is_random_walk = is_random
10019  else
10020  is_random_walk = .false.
10021  end if
10022 
10023  !> Check the type of the target object. Different targets are processed
10024  !! differently for approach.
10025  conspec_other: select type (target_object)
10026 
10027  !> - If it is of the class the_neurobio::conspec_percept_comp (i.e.
10028  !! conspecific perception object):
10029  !! - the default target offset is set to the average body sizes of
10030  !! the agent and its target conspecific;
10031  !! - The the_behaviour::approach_conspec behaviour class is initialised
10032  !! with the the_behaviour::approach_conspec::init() method;
10033  !! - Finally, approach to the conspecific is executed with the
10034  !! the_behaviour::approach_conspec::execute() method.
10035  !! .
10036  class is (conspec_percept_comp) conspec_other
10037 
10038  if (present(target_offset)) then
10039  target_offset_here = target_offset
10040  else
10041  target_offset_here = ( this%get_length() + &
10042  get_prop_size(target_object) ) / 2.0_srp
10043  end if
10044  call this%approach_conspec%init()
10045  this%behaviour_label = this%approach_conspec%label
10046  call this%deactivate()
10047  this%approach_conspec%is_active = .true.
10048  call this%approach_conspec%execute(this, target_object, &
10049  is_random_walk, target_offset_here)
10050 
10051  !> Update (add to stack) the agent's history of behaviours
10052  !! the_behaviour::behaviour::history_behave: string labels of the
10053  !! behaviours are are saved.
10054  call add_to_history( this%history_behave, this%approach_conspec%label )
10055 
10056  !> - If, on the other hand, the target object is of the any other
10057  !! class (i.e. it is an arbitrary object):
10058  !! - The default target offset is set by the the parameter constant
10059  !! commondata::approach_offset_default;
10060  !! - The the_behaviour::approach_spatial behaviour class is initialised
10061  !! with the the_behaviour::approach_spatial::init() method;
10062  !! - Finally, approach to the conspecific is executed with the
10063  !! the_behaviour::approach_spatial::execute() method.
10064  !! .
10065  class default conspec_other
10066 
10067  if (present(target_offset)) then
10068  target_offset_here = target_offset
10069  else
10070  target_offset_here = approach_offset_default
10071  end if
10072  call this%approach_spatial%init()
10073  this%behaviour_label = this%approach_spatial%label
10074  call this%deactivate()
10075  this%approach_spatial%is_active = .true.
10076  call this%approach_spatial%execute(this, target_object, &
10077  is_random_walk, target_offset_here)
10078 
10079  !> Update (add to stack) the agent's history of behaviours
10080  !! the_behaviour::behaviour::history_behave: string labels of the
10081  !! behaviours are are saved.
10082  call add_to_history( this%history_behave, this%approach_spatial %label )
10083 
10084  end select conspec_other
10085 
10086  end subroutine behaviour_do_approach
10087 
10088  !-----------------------------------------------------------------------------
10089  !> Perform (execute) the the_behaviour::migrate (migration) behaviour.
10090  subroutine behaviour_do_migrate(this, target_env)
10091  class(behaviour), intent(inout) :: this
10092  !> @param[in] target_env the target environment the actor agent is going
10093  !! to (e)migrate into.
10094  class(environment), intent(in) :: target_env
10095 
10096  !> ### Implementation notes ###
10097  !> - Initialise the the_behaviour::migrate behaviour component
10098  !! using the the_behaviour::migrate::init() method.
10099  call this%migrate%init()
10100 
10101  !> Set the currently executed behaviour label. It is from the
10102  !! the_behaviour::behaviour_base::label data component of the base class.
10103  this%behaviour_label = this%migrate%label
10104 
10105  !> Set the execution status for all behaviours to FALSE and then for this
10106  !! specific behaviour to TRUE. Only one behaviour unit can be executed at
10107  !! a time.
10108  call this%deactivate()
10109  this%migrate%is_active = .true.
10110 
10111  !> - The "migrate" behaviour is executed by the
10112  !! the_behaviour::migrate::execute() method.
10113  !! .
10114  call this%migrate%execute( this, target_env )
10115 
10116  !> Update (add to stack) the agent's history of behaviours
10117  !! the_behaviour::behaviour::history_behave: string labels of the
10118  !! behaviours are are saved.
10119  call add_to_history( this%history_behave, this%migrate%label )
10120 
10121  end subroutine behaviour_do_migrate
10122 
10123  !-----------------------------------------------------------------------------
10124  !> Perform a simplistic random migration. If the agent is within a specific
10125  !! distance to the target environment, it emigrates there with a specific
10126  !! fixed probability.
10127  function behaviour_try_migrate_random( this, target_env, max_dist, prob ) &
10128  result(is_migrated)
10129  class(behaviour), intent(inout) :: this
10130  !> @param[in] target_env the target environment the actor agent is going
10131  !! to (e)migrate into.
10132  class(environment), intent(in) :: target_env
10133  !> @param[in] max_dist Optional maximum distance, in units of the agent's
10134  !! body size, towards the target environment when the agent
10135  !! can (probabilistically) emigrate into it.
10136  real(srp), optional, intent(in) :: max_dist
10137  !> @param[in] prob Probability of migration
10138  real(srp), optional, intent(in) :: prob
10139  !> @returns Logical flag that shows if the agent has actually emigrated
10140  !! (TRUE) or not (FALSE).
10141  logical :: is_migrated
10142 
10143  ! Local copies of optionals.
10144  real(srp) :: max_dist_loc, prob_loc
10145 
10146  !> ### Notable variables ###
10147  !> - **point_target_env** is the target point inside the target
10148  !! environment to which this agent is going to relocate.
10149  type(spatial) :: point_target_env
10150  !> - **distance_target** is the distance to the target environment.
10151  real(srp) :: distance_target
10152  !> - **MAX_DIST_DEFAULT** is the default maximum distance towards the
10153  !! target environment (units of the agent's body size) when the agent
10154  !! can emigrate into it. This default distance is set by the parameter
10155  !! commondata::migrate_random_max_dist_target. However, note that the
10156  !! migration is probabilistic and occurs with the probability `prob`.
10157  !! .
10158  real(srp), parameter :: max_dist_default = migrate_random_max_dist_target
10159 
10160  ! PROCNAME is the procedure name for logging and debugging
10161  character(len=*), parameter :: procname = "(behaviour_do_migrate_random)"
10162 
10163  !> ### Implementation notes ###
10164  !> The function returns FALSE whenever the agent has not actually migrated
10165  !! into the target environment.
10166  is_migrated = .false.
10167 
10168  !> #### Optional parameters ####
10169  !! Optional parameters `max_dist` and `prob` are checked and the default
10170  !! values are set in case any of them is absent.
10171  !! - `max_dist` = `MAX_DIST_DEFAULT`
10172  !! (commondata::migrate_random_max_dist_target)
10173  !! - `prob` = 0.5.
10174  !! .
10175  if (present(max_dist)) then
10176  max_dist_loc = max_dist
10177  else
10178  max_dist_loc = max_dist_default
10179  end if
10180  if (present(prob)) then
10181  prob_loc = prob
10182  else
10183  prob_loc = 0.5_srp
10184  end if
10185 
10186  !> #### Calculate the distance towards the target environment ####
10187  !> First, determine the nearest target point within the target environment
10188  !! and calculate the distance to the target point.
10189  !!
10190  !> The distance towards the target environment (and the target point in
10191  !! this environment) is defined as the minimum distance towards
10192  !! all segments limiting this environment in the 2D X x Y projection
10193  !! @warning This is valid only for the simple box environment
10194  !! implementation. Generally, it equals to the minimum
10195  !! distance across all the polyhedrons limiting the target
10196  !! environment).
10197  !!
10198  !! The target point for the migrating agent within the target
10199  !! environment is then not just the edge of the target environment, but
10200  !! some point penetrating inside to some distance defined by the parameter
10201  !! commondata::migrate_dist_penetrate_offset (in units of the agent's
10202  !! body length). The the_environment::environment::nearest_target()
10203  !! method is used to find the closest point in the target environment and
10204  !! the (smallest) distance towards this environment, these values are
10205  !! adjusted automatically for the offset parameter in the procedure call.
10206  call target_env%nearest_target( outside_object=this, &
10207  offset_into=this%get_length() * &
10208  migrate_dist_penetrate_offset, &
10209  point_spatial = point_target_env, &
10210  point_dist = distance_target )
10211 
10212  !> #### Move to the target environment with probability "prob" ####
10213  !> If the distance towards the target environment does not exceed
10214  !! `max_dist` body lengths of the agent, the agent can move into
10215  !! this target environment, exactly to the target point `point_target_env`
10216  !! with the probability `prob`.
10217  if ( distance_target < max_dist_loc * this%get_length() ) then
10218  if ( rand() < prob_loc ) then
10219  call log_dbg( ltag_info // "Agent is about to migrate to " // &
10220  tostr([ point_target_env%xpos(), &
10221  point_target_env%ypos(), &
10222  point_target_env%dpos()]), procname, modname )
10223  call this%position( point_target_env%location() )
10224  !> - If the agent has emigrated into the target environment, the
10225  !! output logical flag `is_migrated` is set to TRUE. (Otherwise, it is
10226  !! always FALSE.)
10227  is_migrated = .true.
10228  else
10229  return
10230  end if
10231  else
10232  return
10233  end if
10234 
10235  !> ##### Process the cost of movement #####
10236  !> This only concerns the cases when the agent had migrated into the
10237  !! target environment `target_env`.
10238  !> - Reset the body mass of the agent subtracting the actual cost of
10239  !! the migration moving that is automatically calculated in the call to
10240  !! the_body::condition::cost_swim(). The the_body::condition::set_mass()
10241  !! method is used here to adjust the mass.
10242  call this%set_mass( value_set = this%get_mass() - &
10243  this%cost_swim(exponent= &
10244  swimming_cost_exponent_laminar), &
10245  update_history = .true. )
10246 
10247  !> - Additionally, also call the `the_body::condition::set_length()` method
10248  !! to update the body length history stack. However, the value_set
10249  !! parameter here is just the current value. This fake re-setting of the
10250  !! body length is done to keep both mass and length synchronised in their
10251  !! history stack arrays (there is no procedure for only updating history).
10252  call this%set_length(value_set = this%get_length(),update_history = .true.)
10253 
10254  !> - After resetting the body mass, update energy reserves of the agent,
10255  !! that depend on both the length and the mass.
10256  !! .
10257  call this%energy_update()
10258 
10259  !> Finally, check if the agent is starved to death. If yes, the agent can
10260  !! die without going any further.
10261  if (this%starved_death()) call this%dies()
10262 
10263  end function behaviour_try_migrate_random
10264 
10265  !-----------------------------------------------------------------------------
10266  !> Perform (execute) the the_behaviour::go_down_depth (go down) behaviour.
10267  subroutine behaviour_do_go_down(this, depth_walk)
10268  class(behaviour), intent(inout) :: this
10269  !> @param[in] depth_walk Optional downward walk size, by how deep
10270  !! the agent goes down.
10271  real(SRP), intent(in), optional :: depth_walk
10272 
10273  !> ### Implementation notes ###
10274  !> - Initialise the the_behaviour::go_down_depth behaviour component
10275  !! using the the_behaviour::go_down_depth::init() method.
10276  call this%depth_down%init()
10277 
10278  !> Set the currently executed behaviour label. It is from the
10279  !! the_behaviour::behaviour_base::label data component of the base class.
10280  this%behaviour_label = this%depth_down%label
10281 
10282  !> Set the execution status for all behaviours to FALSE and then for this
10283  !! specific behaviour to TRUE. Only one behaviour unit can be executed at
10284  !! a time.
10285  call this%deactivate()
10286  this%depth_down%is_active = .true.
10287 
10288  !> - The "go down" behaviour is executed by calling the
10289  !! the_behaviour::go_down_depth::execute() method. Note that
10290  !! the walk length can be provided by dummy parameter `depth_walk`,
10291  !! otherwise the default step is used that is equal to the
10292  !! commondata::up_down_walk_step_stdlength_factor times of
10293  !! the agent body length.
10294  !! .
10295  if (present(depth_walk)) then
10296  call this%depth_down%execute( this, depth_walk = depth_walk )
10297  else
10298  call this%depth_down%execute( this )
10299  end if
10300 
10301  !> Update (add to stack) the agent's history of behaviours
10302  !! the_behaviour::behaviour::history_behave: string labels of the
10303  !! behaviours are are saved.
10304  call add_to_history( this%history_behave, this%depth_down%label )
10305 
10306  end subroutine behaviour_do_go_down
10307 
10308  !-----------------------------------------------------------------------------
10309  !> Perform (execute) the the_behaviour::go_up_depth (go up) behaviour.
10310  subroutine behaviour_do_go_up(this, depth_walk)
10311  class(behaviour), intent(inout) :: this
10312  !> @param[in] depth_walk Optional downward walk size, by how deep
10313  !! the agent goes up.
10314  real(SRP), intent(in), optional :: depth_walk
10315 
10316  !> ### Implementation notes ###
10317  !> - Initialise the the_behaviour::go_up_depth behaviour component
10318  !! using the the_behaviour::go_up_depth::init() method.
10319  call this%depth_up%init()
10320 
10321  !> Set the currently executed behaviour label. It is from the
10322  !! the_behaviour::behaviour_base::label data component of the base class.
10323  this%behaviour_label = this%depth_up%label
10324 
10325  !> Set the execution status for all behaviours to FALSE and then for this
10326  !! specific behaviour to TRUE. Only one behaviour unit can be executed at
10327  !! a time.
10328  call this%deactivate()
10329  this%depth_up%is_active = .true.
10330 
10331  !> - The "go up" behaviour is executed by calling the
10332  !! the_behaviour::go_up_depth::execute() method. Note that
10333  !! the walk length can be provided by dummy parameter `depth_walk`,
10334  !! otherwise the default step is used that is equal to the
10335  !! commondata::up_down_walk_step_stdlength_factor times of
10336  !! the agent body length.
10337  !! .
10338  if (present(depth_walk)) then
10339  call this%depth_up%execute( this, depth_walk = depth_walk )
10340  else
10341  call this%depth_up%execute( this )
10342  end if
10343 
10344  !> Update (add to stack) the agent's history of behaviours
10345  !! the_behaviour::behaviour::history_behave: string labels of the
10346  !! behaviours are are saved.
10347  call add_to_history( this%history_behave, this%depth_up%label )
10348 
10349 
10350  end subroutine behaviour_do_go_up
10351 
10352  !-----------------------------------------------------------------------------
10353  !> Cleanup the behaviour history stack for the agent. All values are empty.
10354  elemental subroutine behaviour_cleanup_history(this)
10355  class(behaviour), intent(inout) :: this
10356 
10357  this%history_behave = ""
10358 
10359  end subroutine behaviour_cleanup_history
10360 
10361  !-----------------------------------------------------------------------------
10362  !> Select and **execute** the optimal behaviour, i.e. the behaviour which
10363  !! minimizes the expected GOS arousal.
10364  !! @note Note that the "select" method should be called **after** the
10365  !! the_neurobio::perception, the_neurobio::appraisal and the Global
10366  !! Organismic State (the_neurobio::gos_global) objects were obtained.
10367  subroutine behaviour_select_optimal( this, rescale_max_motivation, &
10368  food_resource_real )
10369  class(behaviour), intent(inout) :: this
10370  !> @param[inout] food_resource_real The food resource the agent is eating
10371  !! the food item in. Note that it could be a joined food
10372  !! resource composed with the_environment::join() procedure
10373  !! for assembling several habitats into the
10374  !! the_environment::global_habitats_available array or
10375  !! resources collapsed using the
10376  !! the_environment::food_resource::join() method.
10377  class(food_resource), optional, intent(inout) :: food_resource_real
10378  !> @param[in] rescale_max_motivation maximum motivation value for
10379  !! rescaling all motivational components for comparison
10380  !! across all motivation and perceptual components and behaviour
10381  !! units.
10382  real(SRP), optional, intent(in) :: rescale_max_motivation
10383 
10384  ! PROCNAME is the procedure name for logging and debugging
10385  character(len=*), parameter :: PROCNAME = "(behaviour_select_optimal)"
10386 
10387  ! Local copies of optionals
10388  real(SRP) :: rescale_max_motivation_here
10389 
10390  !> ### Notable local variables ###
10391  !> - **expected_gos_debug_base** is the GOS expectancy for the fake debug
10392  !! behaviour unit the_behaviour::debug_base: it does not depend on any
10393  !! fake perceptions and represents a baseline estimate. This behaviour
10394  !! unit also does not participate in the procedure that selects the
10395  !! minimum arousal.
10396  real(SRP) :: expected_gos_debug_base
10397  !> - **expected_gos_eat** is the GOS expectancy value predicted from
10398  !! eating the optimal food item.
10399  real(SRP) :: expected_gos_eat
10400  !> - **food_item_selected** is the optimal food item selected from all
10401  !! those that are currently within the perception object of the agent.
10402  integer :: food_item_selected
10403 
10404  !> - **expected_gos_reproduce** is the GOS expectancy value predicted
10405  !! from reproduction.
10406  real(SRP) :: expected_gos_reproduce
10407 
10408  !> - **expected_gos_walk** is the GOS expectancy value predicted
10409  !! from the Gaussian random walk of the optimal step size.
10410  real(SRP) :: expected_gos_walk
10411  !> - **walk_distance_selected** - the static step (from values in the
10412  !! commondata::behav_walk_step_stdlen_static array).
10413  real(SRP) :: walk_distance_selected
10414 
10415  !> - **expected_gos_freeze** is the GOS expectancy value predicted
10416  !! from freezing.
10417  real(SRP) :: expected_gos_freeze
10418 
10419  !> - **expected_gos_escape** is the GOS expectancy value predicted
10420  !! from escape movement.
10421  real(SRP) :: expected_gos_escape
10422  !> - **predator_selected_n** - the predator object within the perception,
10423  !! that is associated with the lowest GOS arousal of escape, i.e. the
10424  !! most subjectively dangerous predator for the agent. Thus is actually
10425  !! the *number* of the predator within the perception object.
10426  integer :: predator_selected_n
10427 
10428  !> - **expected_gos_approach_conspec** is the GOS expectancy value
10429  !! predicted from the approach to conspecific behaviour.
10430  real(SRP) :: expected_gos_approach_conspec
10431  !> - **conspec_selected_n** - the conspecific object within the perception,
10432  !! that is associated with the lowest GOS arousal of approach, i.e. the
10433  !! most subjectively attractive conspecific for the agent. Thus is
10434  !! actually the *number* of the conspecific within the perception object.
10435  integer :: conspec_selected_n
10436 
10437  !> - **expected_gos_migrate** is the GOS expectancy value predicted from
10438  !! migration behaviour into the optimal habitat, i.e. the habitat within
10439  !! the array of available habitats commondata::global_habitats_available
10440  !! that minimises the linked GOS arousal.
10441  real(SRP) :: expected_gos_migrate
10442  !> - **habitat_selected_n** - the number of the habitat object within the
10443  !! commondata::global_habitats_available array, that is associated with
10444  !! the lowest GOS arousal of the migration behaviour, i.e. the most
10445  !! subjectively attractive habitat for the agent.
10446  integer :: habitat_selected_n
10447 
10448  !> - **expected_gos_depth_down** is the GOS expectancy value predicted
10449  !! from the downward vertical migration with the optimal step size.
10450  real(SRP) :: expected_gos_depth_down
10451  !> - **go_down_distance_selected** - the static step size for the downwards
10452  !! vertical migration (from values in the
10453  !! commondata::behav_go_up_down_step_stdlen_static array).
10454  real(SRP) :: go_down_distance_selected
10455 
10456  !> - **expected_gos_depth_up** is the GOS expectancy value predicted
10457  !! from the upward vertical migration with the optimal step size.
10458  real(SRP) :: expected_gos_depth_up
10459  !> - **go_up_distance_selected** - the static step size for the upwards
10460  !! vertical migration (from values in the
10461  !! commondata::behav_go_up_down_step_stdlen_static array).
10462  real(SRP) :: go_up_distance_selected
10463 
10464  !> - **expected_gos_all** is the array that contains GOS arousal values
10465  !! for all of the behaviours that count when calculating the minimum.
10466  !! .
10467  !> @warning Automatic allocation of the `expected_gos_all` array might not
10468  !! work on all compilers and platforms. If manually allocated,
10469  !! check the exact number of behaviour units.
10470  real(SRP), allocatable, dimension(:) :: expected_gos_all
10471 
10472  ! A very big positive number that is used for GOS arousal values that
10473  ! should never be able to win in the arousal minimisation procedure. This
10474  ! parameter is also used for initialisations.
10475  real(SRP), parameter :: BIG_NEVER_WINS = -1.0_srp * missing
10476 
10477  ! Local number of food resource within the global array
10478  ! the_environment::global_habitats_available.
10479  integer :: fres_num
10480 
10481  !> ### Implementation details ###
10482  !> #### Checks and preparations ####
10483  !> Determine optional parameter `rescale_max_motivation`. If it is absent
10484  !! from the parameter list, the value is calculated from the current
10485  !! perception using the the_neurobio::motivation::max_perception() method.
10486  if (present(rescale_max_motivation)) then
10487  rescale_max_motivation_here = rescale_max_motivation
10488  else
10489  rescale_max_motivation_here = this%motivations%max_perception()
10490  end if
10491 
10492  !> #### Calculate the motivational expectancies ####
10493  !> First, the expectancies of the GOS arousal from each of the available
10494  !! behaviour units are calculated.
10495  !> - **Debug base fake behaviour** (the_behaviour::debug_base) calling
10496  !! ::debug_base_select(). This behaviour does not enter in the
10497  !! competition of behaviour units for arousal minimisation and is useful
10498  !! only in the @ref intro_debug_mode "debug mode".
10499  if (is_debug) call debug_base_select(expected_gos_debug_base)
10500 
10501  !> - **Eat food** (the_behaviour::eat_food) calling ::eat_food_select().
10502  call eat_food_select(expected_gos_eat, food_item_selected)
10503 
10504  !> - **Reproduce** (the_behaviour::reproduce) calling ::reproduce_select().
10505  call reproduce_select(expected_gos_reproduce)
10506 
10507  !> - **Random walks** (the_behaviour::walk_random) calling
10508  !! ::walk_random_select().
10509  call walk_random_select(expected_gos_walk, walk_distance_selected)
10510  log_step: block
10511  real(SRP) :: walk_dist_fi
10512  if ( is_near_zero(this%memory_stack%get_food_mean_dist()) ) then
10513  walk_dist_fi = missing
10514  else
10515  walk_dist_fi = walk_distance_selected / &
10516  this%memory_stack%get_food_mean_dist()
10517  end if
10518  call log_dbg( ltag_info // "Optimal walk step: " // &
10519  tostr(walk_distance_selected) // ", SL units: " // &
10520  tostr(walk_distance_selected/this%get_length()) // &
10521  ", units of average distance food items: " // &
10522  tostr(walk_dist_fi), procname, modname )
10523  end block log_step
10524 
10525  !> - **Freezing** (the_behaviour::freeze) calling ::freeze_select().
10526  call freeze_select(expected_gos_freeze)
10527 
10528  !> - **Escape** (the_behaviour::escape_dart) calling ::escape_dart_select().
10529  call escape_dart_select(expected_gos_escape, predator_selected_n)
10530 
10531  !> - **Approach to a spatial object** (the_behaviour::apprach): Approach
10532  !! to an arbitrary spatial object is not used in this version, this
10533  !! behaviour is never executed.
10534 
10535  !> - **Approach conspecifics** (the the_behaviour::approach_conspec)
10536  !! calling ::approach_consp_select().
10537  call approach_consp_select(expected_gos_approach_conspec,conspec_selected_n)
10538 
10539  !> - **Migrate** (the_behaviour::migrate) calling ::migrate_select().
10540  call migrate_select(expected_gos_migrate, habitat_selected_n)
10541 
10542  !> - **Go down** (the_behaviour::go_down_depth) calling ::go_down_select().
10543  call go_down_select(expected_gos_depth_down, go_down_distance_selected)
10544  call log_dbg( ltag_info // "Optimal walk step down: " // &
10545  tostr(go_down_distance_selected) // ", sl units: " // &
10546  tostr(go_down_distance_selected/this%get_length()), &
10547  procname, modname )
10548 
10549  !> - **Go up** (the the_behaviour::go_up_depth) calling ::go_up_select().
10550  !! .
10551  call go_up_select(expected_gos_depth_up, go_up_distance_selected)
10552  call log_dbg( ltag_info // "Optimal walk step up: " // &
10553  tostr(go_up_distance_selected) // ", sl units: " // &
10554  tostr(go_up_distance_selected/this%get_length()), &
10555  procname, modname )
10556 
10557  !> #### Execute behaviours that minimise GOS arousal ####
10558  !> After the GOS arousal values for all behaviour units are calculated,
10559  !! the agent can determine the minimum value and what is the associated
10560  !! behaviour unit that minimises the GOS arousal.
10561  !!
10562  !! First, an array containing all GOS arousal values for all of the above
10563  !! behaviour units is constructed `expected_gos_all`.
10564  !! @note Note that there is no `allocate` command here as all fairly modern
10565  !! Fortran compilers support automatic allocation of arrays on
10566  !! intrinsic assignment. This feature should work by default in
10567  !! GNU gfortran v.4.6 and Intel ifort v.17.0.1. Automatic allocation
10568  !! allows to avoid a possible bug when the number of array elements
10569  !! in the `allocate` statement is not updated when the `expected_gos_`
10570  !! components of the array are added or removed.
10571  expected_gos_all = [ expected_gos_eat, &
10572  expected_gos_reproduce, &
10573  expected_gos_walk, &
10574  expected_gos_freeze, &
10575  expected_gos_escape, &
10576  expected_gos_approach_conspec, &
10577  expected_gos_migrate, &
10578  expected_gos_depth_down, &
10579  expected_gos_depth_up ]
10580 
10581  !> Automatic array allocation is checked. If the ` expected_gos_all array
10582  !! turns out not allocated, a critical error is signalled in the logger.
10583  if (.not. allocated(expected_gos_all) ) then
10584  call log_msg( ltag_crit // "Automatic array allocation is not " // &
10585  "enabled or supported by the compiler. Check " // &
10586  procname // " code and insert explicit" // &
10587  "'allocate(expected_gos_all(N))' or use compiler " // &
10588  "switch to enable F2003 features." )
10589  call system_halt(is_error=.true., message=error_no_autoalloc )
10590  end if
10591 
10592  !> In the @ref intro_debug_mode "DEBUG mode", the array of the GOS
10593  !! arousal levels is logged.
10594  if (is_debug) call log_delimiter(log_level_chapter)
10595  call log_dbg( ltag_info // " +++ GOS arousal array: " // &
10596  tostr(expected_gos_all) // &
10597  ", agent label: " // this%individ_label() // &
10598  ", minimum # " // tostr(minloc(expected_gos_all)) // &
10599  " is value: " // tostr(minval(expected_gos_all)) )
10600  if (is_debug) call log_delimiter(log_level_chapter)
10601 
10602  !> Second, each of the behaviours is checked for being the minimum value.
10603  !! If true, this behaviour is executed using the `do_` method of the
10604  !! the_behaviour::behaviour class.
10605  !!
10606  !! Additionally, for each behaviour unit, an additional check is performed
10607  !! to make sure the conditions for the behaviour are satisfied. If the
10608  !! conditions are not satisfied, a default Gausssian random walk
10609  !! the_behaviour::behaviour::do_walk() is done.
10610  !!
10611  !! The correctness conditions for each of the behaviour units are:
10612  !> - the_behaviour::eat_food: the agent must have food items in perception,
10613  !! the_neurobio::perception::has_food() is TRUE.
10614  if ( is_minval( expected_gos_eat, expected_gos_all ) ) then
10615  if (this%has_food()) then
10616  if (present(food_resource_real)) then
10617  call this%do_eat_food_item( food_item_selected, food_resource_real )
10618  else
10619  fres_num = this%find_environment(global_habitats_available)
10620  call this%do_eat_food_item( food_item_selected, &
10621  global_habitats_available(fres_num)%food )
10622  end if
10623  else
10624  call this%do_walk()
10625  end if
10626  return
10627  end if
10628 
10629  !> - the_behaviour::reproduce: the agent must be mature
10630  !! (the_body::reproduction::is_ready_reproduce() is TRUE) *and* have
10631  !! conspecifics in perception (the_neurobio::perception::has_consp()
10632  !! is TRUE).
10633  if ( is_minval( expected_gos_reproduce, expected_gos_all ) ) then
10634  if (this%is_ready_reproduce() .and. this%has_consp()) then
10635  call this%do_reproduce()
10636  else
10637  call this%do_walk()
10638  end if
10639  return
10640  end if
10641 
10642  !> - the_behaviour::walk_random: the optimal distance selected
10643  !! `walk_distance_selected` must be nonzero, i.e. exceed the tolerance
10644  !! value commondata::tolerance_high_def_srp.
10645  if ( is_minval( expected_gos_walk, expected_gos_all ) ) then
10646  if (walk_distance_selected > tolerance_high_def_srp ) then
10647  call this%do_walk( walk_distance_selected )
10648  else
10649  call this%do_walk()
10650  end if
10651  return
10652  end if
10653 
10654  !> - the_behaviour::freeze: this behaviour does not require any specific
10655  !! conditions and can be executed anyway.
10656  if ( is_minval( expected_gos_freeze, expected_gos_all ) ) then
10657  call this%do_freeze()
10658  return
10659  end if
10660 
10661  !> - the_behaviour::escape_dart: the agent must have predators in its
10662  !! perception, i.e. the_neurobio::perception::has_pred() should return
10663  !! TRUE. If no predators are present, a non-targeted
10664  !! the_behaviour::escape_dart instance is esecuted.
10665  if ( is_minval( expected_gos_escape, expected_gos_all ) ) then
10666  if (this%has_pred()) then
10667  call this%do_escape( predator_object = &
10668  this%perceive_predator%predators_seen(predator_selected_n) )
10669  else
10670  call this%do_escape( )
10671  end if
10672  return
10673  end if
10674 
10675  !> - the_behaviour::approach_conspec: the agent must have conspecifics in
10676  !! perception, the_neurobio::perception::has_consp() is TRUE.
10677  if ( is_minval( expected_gos_approach_conspec, expected_gos_all ) ) then
10678  if (this%has_consp()) then
10679  call this%do_approach( &
10680  target_object = &
10681  this%perceive_consp%conspecifics_seen(conspec_selected_n),&
10682  is_random = .false. )
10683  else
10684  call this%do_walk()
10685  end if
10686  return
10687  end if
10688 
10689  !> - the_behaviour::migrate: the agent must have a valid target habitat for
10690  !! migration; the optimal habitat index `habitat_selected_n` must
10691  !! correspond to a valid habitat in the global array
10692  !! the_environment::global_habitats_available.
10693  if ( is_minval( expected_gos_migrate, expected_gos_all ) ) then
10694  if ( habitat_selected_n > 0 .and. &
10695  habitat_selected_n <= size(global_habitats_available) ) then
10696  call this%do_migrate( &
10697  target_env = global_habitats_available(habitat_selected_n) )
10698  else
10699  call this%do_walk()
10700  end if
10701  return
10702  end if
10703 
10704  !> - the_behaviour::go_down_depth: the optimal vertical migration distance
10705  !! selected `go_down_distance_selected` must be nonzero, i.e. exceed the
10706  !! tolerance value commondata::tolerance_high_def_srp.
10707  if ( is_minval( expected_gos_depth_down, expected_gos_all ) ) then
10708  if ( go_down_distance_selected > tolerance_high_def_srp ) then
10709  call this%do_go_down( depth_walk = go_down_distance_selected )
10710  else
10711  call this%do_walk()
10712  end if
10713  return
10714  end if
10715 
10716  !> - the_behaviour::go_up_depth: the optimal vertical migration distance
10717  !! selected `go_up_distance_selected` must be nonzero, i.e. exceed the
10718  !! tolerance value commondata::tolerance_high_def_srp.
10719  !! .
10720  if ( is_minval( expected_gos_depth_up, expected_gos_all ) ) then
10721  if ( go_up_distance_selected > tolerance_high_def_srp ) then
10722  call this%do_go_up( depth_walk = go_up_distance_selected )
10723  else
10724  call this%do_walk()
10725  end if
10726  return
10727  end if
10728 
10729  !> The control is passed back out of this procedure on execution of the
10730  !! optimal behaviour. However, if no behaviour was selected up to this
10731  !! point, the agent just does a default Gaussian walk. However, this
10732  !! situation is very suspicious and can point to a bug. Therefore, such
10733  !! situation is logged with the ERROR tag.
10734  call log_msg( ltag_error // "Cannot select optimal behaviour unit in " // &
10735  procname // ". Default random Gaussian walk is executed." )
10736 
10737  call this%do_walk()
10738 
10739  contains
10740  !- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
10741  !> Calculate the expected GOS arousal that would be predicted from execution
10742  !! of the the_behaviour::eat_food behaviour unit. The subjectively optimal
10743  !! food item (that minimises GOS arousal) is also obtained in this procedure.
10744  !! @note This procedure is part of the_behaviour::behaviour_select_optimal()
10745  !! procedure and called within.
10746  subroutine eat_food_select(expected_gos, selected)
10747  !> @param[out] expected_gos is the GOS expectancy value predicted from
10748  !! eating the optimal food item.
10749  real(SRP), intent(out) :: expected_gos
10750  !> @param[out] selected optimal food item that would result in
10751  !! the minimum resulting GOS arousal.
10752  integer, intent(out) :: selected
10753 
10754  !> ### Implementation details ###
10755  !> First, the the_behaviour::eat_food behaviour class is initialised by
10756  !! calling the the_behaviour::eat_food::init() method.
10757  call this%eat%init()
10758 
10759  !> Then, perception components of the food objects are processed.
10760  !! If the agent has any food items in perception, then
10761  if ( this%has_food() ) then
10762  !> - determine the best, optimal food item out of all the items
10763  !! currently in perception object of the agent: this is the food item
10764  !! that would result in the *minimum expected arousal*
10765  !! the_behaviour::behaviour::food_item_select();
10766  selected = this%food_item_select( &
10767  rescale_max_motivation = rescale_max_motivation_here )
10768  !> - calculate the overall motivational expectancy that eating this
10769  !! optimal food item would provide. This value is now the *arousal
10770  !! expectancy* from eating behaviour (the_behaviour::eat_food) by call
10771  !! to the the_behaviour::eat_food::expectancies_calculate() method.
10772  !! .
10773  call this%eat%expectancies_calculate( this_agent = this, &
10774  food_item_eaten = this%perceive_food%foods_seen( &
10775  selected), &
10776  rescale_max_motivation = rescale_max_motivation_here )
10777  expected_gos = this%eat%arousal_expected ! %gos_expected()
10778  !> On the other hand, if the agent has no food items in its perception
10779  !! object, the motivational expectancy is set to a large value that is
10780  !! guaranteed to not win, so that this behaviour cannot be executed.
10781  else
10782  expected_gos = big_never_wins
10783  selected = 0
10784  end if
10785 
10786  debug_log: block
10787  call log_dbg( ltag_info // "Selected optimal food item number: " // &
10788  tostr(selected) // ", out of total " // &
10789  tostr(this%perceive_food%food_seen_count) // &
10790  " items in perception." , procname, modname )
10791  end block debug_log
10792 
10793  end subroutine eat_food_select
10794 
10795  !- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
10796  !> Calculate the expected GOS arousal that would be predicted from execution
10797  !! of the the_behaviour::reproduce behaviour unit.
10798  !! @note This procedure is part of the_behaviour::behaviour_select_optimal()
10799  !! procedure and called within.
10800  subroutine reproduce_select(expected_gos)
10801  !> @param[out] expected_gos is the GOS expectancy value
10802  !! predicted from reproduction.
10803  real(SRP), intent(out) :: expected_gos
10804 
10805  !> ### Implementation notes ###
10806  !> Calculation is rather straightforward here. It involves calling the
10807  !! the the_behaviour::reproduce::expectancies_calculate() method.
10808  if ( this%has_consp() .and. this%is_ready_reproduce() ) then
10809  call this%reproduce%expectancies_calculate( this_agent = this, &
10810  rescale_max_motivation = rescale_max_motivation_here )
10811  expected_gos = this%reproduce%arousal_expected ! %gos_expected()
10812  else
10813  expected_gos = big_never_wins
10814  end if
10815 
10816  end subroutine reproduce_select
10817 
10818  !- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
10819  !> Calculate the expected GOS arousal that would be predicted from execution
10820  !! of the the_behaviour::walk_random behaviour unit. The best (subjectively
10821  !! optimal) walk step from the commondata::behav_walk_step_stdlen_static
10822  !! parameter array values (that minimises GOS arousal) is also obtained in
10823  !! this procedure.
10824  !! @note This procedure is part of the_behaviour::behaviour_select_optimal()
10825  !! procedure and called within.
10826  subroutine walk_random_select(expected_gos, selected)
10827  !> @param[out] expected_gos is the GOS expectancy value predicted
10828  !! from the Gaussian random walk of the optimal step size.
10829  real(SRP), intent(out) :: expected_gos
10830  !> @param[out] selected the static step (from values in the
10831  !! commondata::behav_walk_step_stdlen_static array).
10832  real(SRP), intent(out) :: selected
10833 
10834  ! Local counter.
10835  integer :: walk_step
10836  ! Local temporary value of the walk.
10837  real(SRP) :: walk_current
10838 
10839  !> ### Implementation notes ###
10840  !> There are several random walks with different step sizes that are
10841  !! defined by the commondata::behav_walk_step_stdlen_static parameter array
10842  !! (i.e. a *repertoire* of walks). Therefore, selection of the arousal
10843  !! expectancy that would follow from the_behaviour::walk_random behaviour
10844  !! as a whole requires finding the *optimal walk step* among all those
10845  !! defined in the repertoire (commondata::behav_walk_step_stdlen_static).
10846  !! Such an optimal walk step size is the step size that would result in
10847  !! the lowest expected arousal. This is done by looping over the values of
10848  !! the walk step size repertoire, commondata::behav_walk_step_stdlen_static.
10849  ! @note `expected_gos`, the value being minimized, starts with a
10850  ! large number.
10851  expected_gos = big_never_wins
10852  selected = missing
10853  do walk_step=1, size(behav_walk_step_stdlen_static)
10854  walk_current = behav_walk_step_stdlen_static(walk_step)*this%get_length()
10855  call this%walk_random%init()
10856  call this%walk_random%expectancies_calculate( this_agent = this, &
10857  distance = walk_current, &
10858  rescale_max_motivation = rescale_max_motivation_here )
10859  if (this%walk_random%arousal_expected < expected_gos ) then
10860  expected_gos = this%walk_random%arousal_expected
10861  selected = walk_current
10862  end if
10863  end do
10864 
10865  end subroutine walk_random_select
10866 
10867  !- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
10868  !> Calculate the expected GOS arousal that would be predicted from execution
10869  !! of the the_behaviour::freeze behaviour unit.
10870  !! @note This procedure is part of the_behaviour::behaviour_select_optimal()
10871  !! procedure and called within.
10872  subroutine freeze_select(expected_gos)
10873  !> @param[out] expected_gos the GOS expectancy value predicted
10874  !! from freezing.
10875  real(SRP), intent(out) :: expected_gos
10876 
10877  !> ### Implementation notes ###
10878  !> First, initialise this behaviour unit object by calling the
10879  !! the_behaviour::freeze::init() method.
10880  call this%freeze%init()
10881 
10882  !> The following calculations are rather straightforward here. The
10883  !! arousal expectancy that would follow from freezing the_behaviour::freeze
10884  !! is done by calling the the_behaviour::freeze::expectancies_calculate()
10885  !! method.
10886  call this%freeze%expectancies_calculate( this_agent = this, &
10887  rescale_max_motivation = rescale_max_motivation_here )
10888  expected_gos = this%freeze%arousal_expected ! %gos_expected()
10889 
10890  end subroutine freeze_select
10891 
10892  !- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
10893  !> Calculate the expected GOS arousal that would be predicted from execution
10894  !! of the the_behaviour::escape_dart behaviour unit. The predator object that
10895  !! minimises the expected arousal (i.e. subjectively the most dangerous)
10896  !! is also obtained in this procedure.
10897  !! @note This procedure is part of the_behaviour::behaviour_select_optimal()
10898  !! procedure and called within.
10899  subroutine escape_dart_select (expected_gos, selected)
10900  !> @param[out] expected_gos is the GOS expectancy value predicted
10901  !! from escape movement.
10902  real(SRP), intent(out) :: expected_gos
10903  !> @param[out] selected the predator object within the
10904  !! perception, that is associated with the lowest GOS arousal
10905  !! of escape, i.e. the most subjectively dangerous predator
10906  !! for the agent. Thus is actually the *number* of the predator
10907  !! within the perception object.
10908  integer, intent(out) :: selected
10909 
10910  ! Local counter
10911  integer :: escape_step
10912 
10913  !> ### Implementation details ###
10914  !> There can be several different escape behaviour instances if the agent
10915  !! perceives several predators simultaneously: escape in response to each
10916  !! of these predators. Additionally, if the agent has no predator in the
10917  !! perception, escape behaviour is still possible to execute, but in such
10918  !! a case it is an undirected escape.
10919  !!
10920  !! Thus, first, a check is done if the agent has any predator in perception.
10921  if ( this%has_pred() ) then
10922  !> - If yes, a loop is constructed overall predators within perception,
10923  !! the expected arousal is calculated for escape in response to each of
10924  !! these predators by calling
10925  !! the_behaviour::escape_dart::expectancies_calculate(). Finally,
10926  !! the predator number `selected` that minimises the expected arousal
10927  !! is taken as the "selected" predator and its linked (the minimum)
10928  !! arousal now represents the arousal expectancy for the escape
10929  !! behaviour.
10930  ! @note `expected_gos`, the value being minimized, starts
10931  ! with a large number.
10932  expected_gos = big_never_wins
10933  selected = unknown
10934  do escape_step=1, this%perceive_predator%get_count()
10935  call this%escape_dart%init()
10936  call this%escape_dart%expectancies_calculate( this_agent = this, &
10937  predator_object = &
10938  this%perceive_predator%predators_seen(escape_step), &
10939  rescale_max_motivation = rescale_max_motivation_here )
10940  if ( this%escape_dart%arousal_expected < expected_gos ) then
10941  expected_gos = this%escape_dart%arousal_expected
10942  selected = escape_step
10943  end if
10944  end do
10945  else
10946  !> - If there are no predators in the operception of the agent, an
10947  !! undirected escape is assumed. In such a case, the
10948  !! the_behaviour::escape_dart::expectancies_calculate() method is
10949  !! called omitting the optional predator object parameter.
10950  !! Also, the number of the predator in the perception
10951  !! (`selected`) is set to 0.
10952  !! .
10953  call this%escape_dart%expectancies_calculate( this_agent = this, &
10954  rescale_max_motivation = rescale_max_motivation_here )
10955  expected_gos = this%escape_dart%arousal_expected
10956  selected = 0
10957  end if
10958 
10959  end subroutine escape_dart_select
10960 
10961  !- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
10962  !> Calculate the expected GOS arousal that would be predicted from execution
10963  !! of the the_behaviour::approach_conspec behaviour unit. The conspecific that
10964  !! minimises the expected arousal (i.e. subjectively the most attractive)
10965  !! is also obtained in this procedure.
10966  !! @note This procedure is part of the_behaviour::behaviour_select_optimal()
10967  !! procedure and called within.
10968  subroutine approach_consp_select(expected_gos, selected)
10969  !> @param[out] expected_gos is the GOS expectancy value
10970  !! predicted from the approach to conspecific behaviour.
10971  real(SRP), intent(out) :: expected_gos
10972  !> @param[out] selected the conspecific object within the
10973  !! perception, that is associated with the lowest GOS arousal
10974  !! of approach, i.e. the most subjectively attractive
10975  !! conspecific for the agent. Thus is actually the *number*
10976  !! of the conspecific within the perception object.
10977  integer, intent(out) :: selected
10978 
10979  !> ### Implementation details ###
10980  !> First, the the_behaviour::approach_conspec behaviour class is
10981  !! initialised by calling the the_behaviour::approach_conspec::init()
10982  !! method.
10983  call this%approach_conspec%init()
10984  !> There can potentially be several different approach behaviour instances
10985  !! if the agent perceives several conspecifics simultaneously: separate
10986  !! instances of the approach behaviour are evaluated towards each of these
10987  !! conspecifics. However, if the agent has no conspecifics in its
10988  !! perception, approach has no mandatory target and is impossible. Thus,
10989  !! first, a check is done if the agent has any conspecifics in perception
10990  !! using the the_neurobio::perception::has_consp() method.
10991  if ( this%has_consp() ) then
10992  !> - If yes, determine the best, optimal conspecific to approach among
10993  !! all that currently are in the perception object of the agent: this
10994  !! is the conspecific that would result in the *minimum expected
10995  !! arousal* the_behaviour::behaviour::consp_select();
10996  selected = this%consp_select( rescale_max_motivation = &
10997  rescale_max_motivation_here)
10998  !> - calculate the overall motivational expectancy that approaching
10999  !! this most attractive conspecific would provide by calling
11000  !! the the_behaviour::approach_conspec::expectancies_calculate() method.
11001  !! This value is now the *arousal expectancy* from the "approach
11002  !! conspecifics" behaviour (the_behaviour::approach_conspec)
11003  !! .
11004  call this%approach_conspec%expectancies_calculate( this_agent = this, &
11005  target_object = &
11006  this%perceive_consp%conspecifics_seen(selected), &
11007  rescale_max_motivation = rescale_max_motivation_here )
11008 
11009  expected_gos = this%approach_conspec%arousal_expected
11010  else
11011  !> - On the other hand, if the agent has **no conspecifics** in its
11012  !! perception object, the motivational expectancy is set to a large
11013  !! positive value that is guaranteed to not win, so that this
11014  !! behaviour cannot be executed.
11015  !! .
11016  expected_gos = big_never_wins
11017  selected = 0
11018  end if
11019 
11020  end subroutine approach_consp_select
11021 
11022  !- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
11023  !> Calculate the expected GOS arousal that would be predicted from execution
11024  !! of the the_behaviour::migrate behaviour unit. The habitat object that
11025  !! minimises the expected arousal (i.e. subjectively the most attractive)
11026  !! is also obtained in this procedure.
11027  !! @note This procedure is part of the_behaviour::behaviour_select_optimal()
11028  !! procedure and called within.
11029  subroutine migrate_select(expected_gos, selected)
11030  !> @param[out] expected_gos is the GOS expectancy value predicted
11031  !! from migration behaviour into the optimal habitat, i.e.
11032  !! the habitat within the array of available habitats
11033  !! commondata::global_habitats_available that minimises the
11034  !! linked GOS arousal.
11035  real(SRP), intent(out) :: expected_gos
11036  !> @param[out] selected the number of the habitat object within
11037  !! the commondata::global_habitats_available array, that is
11038  !! associated with the lowest GOS arousal of the migration
11039  !! behaviour, i.e. the most subjectively attractive habitat
11040  !! for the agent.
11041  integer, intent(out) :: selected
11042 
11043  ! Local counter.
11044  integer :: habitat_step
11045 
11046  !> ### Implementation details ###
11047  !> The migration behaviour depends on the target habitat that is different
11048  !! than the current habitat the agent is currently in. Therefore, there
11049  !! can potentially be several instances of the migration behaviour with
11050  !! different specific migration habitat targets. Then, a loop is
11051  !! constructed over all these targets (they are by default obtained from
11052  !! the the_environment::global_habitats_available global array) and the
11053  !! expected arousal is calculated for each one using
11054  !! the_behaviour::migrate::expectancies_calculate(). Finally, the habitat
11055  !! that minimises the expected arousal is taken as the "selected"habitat
11056  !! and its linked (the minimum) arousal now represents the arousal
11057  !! expectancy for the migration behaviour.
11058  expected_gos = big_never_wins
11059  selected = unknown
11060  do habitat_step=1, size(global_habitats_available)
11061  if ( habitat_step /= this%find_environment() ) then
11062  call this%migrate%init()
11063  call this%migrate%expectancies_calculate( this_agent = this, &
11064  target_env = global_habitats_available(habitat_step), &
11065  rescale_max_motivation = rescale_max_motivation_here )
11066  if ( this%migrate%arousal_expected < expected_gos ) then
11067  expected_gos = this%migrate%arousal_expected
11068  selected = habitat_step
11069  end if
11070  end if
11071  end do
11072 
11073  debug_log: block
11074  call log_dbg( ltag_info // "Current agent's environment number: " // &
11075  tostr(this%find_environment()), procname, modname )
11076  call log_dbg( ltag_info // "Selected optimal environment number: " // &
11077  tostr(selected) // ", distance to traverse: " // &
11078  tostr(this%migrate%distance) // ", expected cost of " // &
11079  "moving: " // tostr(this%migrate%expected_cost_moving), &
11080  procname, modname )
11081  end block debug_log
11082 
11083  end subroutine migrate_select
11084 
11085  !- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
11086  !> Calculate the expected GOS arousal that would be predicted from execution
11087  !! of the the_behaviour::go_down_depth behaviour unit. The vertical migration
11088  !! walk step, from the commondata::behav_go_up_down_step_stdlen_static
11089  !! parameter array, that minimises the expected arousal (i.e. subjectively
11090  !! optimal) is also obtained in this procedure.
11091  !! @note This procedure is part of the_behaviour::behaviour_select_optimal()
11092  !! procedure and called within.
11093  subroutine go_down_select(expected_gos, selected)
11094  !> @param[out] expected_gos is the GOS expectancy value
11095  !! predicted from the downward vertical migration with the
11096  !! optimal step size.
11097  real(SRP), intent(out) :: expected_gos
11098  !> @param[out] selected the static step size for the
11099  !! downwards vertical migration (from values in the
11100  !! commondata::behav_go_up_down_step_stdlen_static array).
11101  real(SRP), intent(out) :: selected
11102 
11103  ! Local counter
11104  integer :: depth_step
11105  ! Local value of the walk.
11106  real(SRP) :: walk_current
11107 
11108  !> ### Implementation details ###
11109  !> There are several Go down step sizes that are defined by the
11110  !! commondata::behav_go_up_down_step_stdlen_static parameter array
11111  !! (i.e. a *repertoire* of the vertical migration walks). Therefore,
11112  !! selection of the arousal expectancy that would follow from
11113  !! the_behaviour::go_down_depth behaviour as a whole requires finding the
11114  !! *optimal walk step* among all those defined in the repertoire
11115  !! (commondata::behav_go_up_down_step_stdlen_static). Such an optimal walk
11116  !! step size is the step size that would result in the lowest expected
11117  !! arousal (as computed by
11118  !! the_behaviour::go_down_depth::expectancies_calculate()).
11119  !! - This is done by looping over the available values of the depth
11120  !! step size repertoire, commondata::behav_go_up_down_step_stdlen_static.
11121  !! .
11122  ! @note `expected_gos`, the value being minimized, starts
11123  ! with a large number.
11124  expected_gos = big_never_wins
11125  selected = missing
11126  do depth_step=1, size(behav_go_up_down_step_stdlen_static)
11127  walk_current = behav_go_up_down_step_stdlen_static(depth_step) * &
11128  this%get_length()
11129  call this%depth_down%init()
11130  call this%depth_down%expectancies_calculate( this_agent = this, &
11131  depth_walk = walk_current, &
11132  environments = global_habitats_available, &
11133  rescale_max_motivation = rescale_max_motivation_here )
11134  if (this%depth_down%arousal_expected < expected_gos ) then
11135  expected_gos = this%depth_down%arousal_expected
11136  selected = walk_current
11137  end if
11138  end do
11139 
11140  end subroutine go_down_select
11141 
11142  !- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
11143  !> Calculate the expected GOS arousal that would be predicted from execution
11144  !! of the the_behaviour::go_up_depth behaviour unit. The vertical migration
11145  !! walk step, from the commondata::behav_go_up_down_step_stdlen_static
11146  !! parameter array, that minimises the expected arousal (i.e. subjectively
11147  !! optimal) is also obtained in this procedure.
11148  !! @note This procedure is part of the_behaviour::behaviour_select_optimal()
11149  !! procedure and called within.
11150  subroutine go_up_select(expected_gos, selected)
11151  !> @param[out] expected_gos is the GOS expectancy value predicted
11152  !! from the upward vertical migration with the optimal step
11153  !! size.
11154  real(SRP), intent(out) :: expected_gos
11155  !> @param[out] selected the static step size for the upwards
11156  !! vertical migration (from values in the
11157  !! commondata::behav_go_up_down_step_stdlen_static array).
11158  real(SRP), intent(out) :: selected
11159 
11160  ! Local counter
11161  integer :: depth_step
11162  ! Local value of the walk.
11163  real(SRP) :: walk_current
11164 
11165  !> ###Implementation details ###
11166  !> There are several Go up step sizes that are defined by the
11167  !! commondata::behav_go_up_down_step_stdlen_static parameter array
11168  !! (i.e. a *repertoire* of the vertical migration walks). Therefore,
11169  !! selection of the arousal expectancy that would follow from
11170  !! the_behaviour::go_up_depth behaviour as a whole requires finding the
11171  !! *optimal walk step* among all those defined in the repertoire
11172  !! (commondata::behav_go_up_down_step_stdlen_static). Such an optimal walk
11173  !! step size is the step size that would result in the lowest expected
11174  !! arousal (as computed by
11175  !! the_behaviour::go_up_depth::expectancies_calculate()).
11176  !! - This is done by looping over the available values of the depth
11177  !! step size repertoire, commondata::behav_go_up_down_step_stdlen_static.
11178  !! .
11179  ! @note `expected_gos`, the value being minimized, starts
11180  ! with a large number.
11181  expected_gos = big_never_wins
11182  selected = missing
11183  do depth_step=1, size(behav_go_up_down_step_stdlen_static)
11184  walk_current = behav_go_up_down_step_stdlen_static(depth_step) * &
11185  this%get_length()
11186  call this%depth_up%init()
11187  call this%depth_up%expectancies_calculate( this_agent = this, &
11188  depth_walk = walk_current, &
11189  environments = global_habitats_available, &
11190  rescale_max_motivation = rescale_max_motivation_here )
11191  if (this%depth_up%arousal_expected < expected_gos ) then
11192  expected_gos = this%depth_up%arousal_expected
11193  selected = walk_current
11194  end if
11195  end do
11196 
11197  end subroutine go_up_select
11198 
11199  !- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
11200  !> Calculate the expected GOS arousal that would be predicted from execution
11201  !! of the the_behaviour::debug_base behaviour unit.
11202  !! @note This procedure is part of the_behaviour::behaviour_select_optimal()
11203  !! procedure and called within.
11204  subroutine debug_base_select(expected_gos)
11205  !> @param[out] expected_gos the GOS expectancy value predicted
11206  !! from freezing.
11207  real(SRP), intent(out) :: expected_gos
11208 
11209  !> ### Implementation notes ###
11210  !> First, initialise this behaviour unit object by calling the
11211  !! the_behaviour::debug_base::init() method.
11212  call this%debug_base%init()
11213 
11214  !> The following calculations are rather straightforward here. The
11215  !! arousal expectancy that would follow from the_behaviour::debug_base
11216  !! is done by calling the_behaviour::debug_base::expectancies_calculate().
11217  call this%debug_base%expectancies_calculate( this_agent = this, &
11218  rescale_max_motivation = rescale_max_motivation_here )
11219  expected_gos = this%debug_base%arousal_expected ! %gos_expected()
11220 
11221  call log_dbg( ltag_info // "Expected GOS arousal: " // &
11222  tostr(expected_gos), procname, modname )
11223 
11224  end subroutine debug_base_select
11225 
11226  end subroutine behaviour_select_optimal
11227 
11228  !-----------------------------------------------------------------------------
11229  !> Select and **execute** behaviour based on the current global organismic
11230  !! state. This procedure is significantly different from
11231  !! the_behaviour::behaviour_select_optimal() in that the behaviour that is
11232  !! executed is not based on optimisation of the expected GOS. Rather, the
11233  !! current GOS fully determines which behaviour unit is executed. Such a
11234  !! rigid link necessarily limits the range of behaviours that could be
11235  !! executed.
11236  subroutine behaviour_select_fixed_from_gos( this, rescale_max_motivation, &
11237  food_resource_real )
11238  class(behaviour), intent(inout) :: this
11239  !> @param[inout] food_resource_real The food resource the agent is eating
11240  !! the food item in. Note that it could be a joined food
11241  !! resource composed with the_environment::join() procedure
11242  !! for assembling several habitats into the
11243  !! the_environment::global_habitats_available array or
11244  !! resources collapsed using the
11245  !! the_environment::food_resource::join() method.
11246  class(food_resource), optional, intent(inout) :: food_resource_real
11247  !> @param[in] rescale_max_motivation maximum motivation value for
11248  !! rescaling all motivational components for comparison
11249  !! across all motivation and perceptual components and behaviour
11250  !! units.
11251  real(SRP), optional, intent(in) :: rescale_max_motivation
11252 
11253  ! PROCNAME is the procedure name for logging and debugging
11254  character(len=*), parameter :: &
11255  PROCNAME = "(behaviour_select_fixed_from_gos)"
11256 
11257  ! Local copies of optionals
11258  real(SRP) :: rescale_max_motivation_here
11259 
11260  !> ### Notable local variables ###
11261  !> - **food_item_selected** is the optimal food item selected from all
11262  !! the items that are currently within the perception object of the
11263  !! agent. In this version of `do_behave`, the nearest food item is
11264  !! selected.
11265  integer :: food_item_selected
11266  !> - **predator_selected_n** - the predator object within the perception,
11267  !! that is considered the most subjectively dangerous for the agent.
11268  !! (This is actually the *number* of the predator within the perception
11269  !! object.) Note that in this version of `do_behave`, the nearest
11270  !! predator is selected.
11271  integer :: predator_selected_n
11272  ! Local number of food resource within the global array
11273  ! the_environment::global_habitats_available.
11274  integer :: fres_num
11275 
11276  !> ### Implementation details ###
11277  !> #### Checks and preparations ####
11278  !> Determine optional parameter `rescale_max_motivation`. If it is absent
11279  !! from the parameter list, the value is calculated from the current
11280  !! perception using the the_neurobio::motivation::max_perception() method.
11281  if (present(rescale_max_motivation)) then
11282  rescale_max_motivation_here = rescale_max_motivation
11283  else
11284  rescale_max_motivation_here = this%motivations%max_perception()
11285  end if
11286 
11287  !> #### Try to perform random migration ####
11288  !! Random migration is implemented in the `TRY_MIGRATE` block.
11289  !! @warning This code does not work well in case the agent is within the
11290  !! maximum random migration distance from more than one target
11291  !! environment at once. It cycles in fixed order 1,2... over
11292  !! the commondata::global_habitats_available. Ideally, should
11293  !! select at random. Hopefully, such cases are very rare. TODO.
11294  try_migrate: block
11295  logical :: is_migrated
11296  integer :: current_in, i
11297  is_migrated = .false.
11298  !> - First, find what is the current agent's environment within the
11299  !! commondata::global_habitats_available array, calling
11300  !! the_environment::spatial::find_environment() method.
11301  current_in = this%find_environment()
11302  !> - Second, loop over all the habitats available in the
11303  !! commondata::global_habitats_available array. If the `i`th habitat
11304  !! does not coincide with the current agent's habitat (i.e. the agent
11305  !! cannot emigrate to the currently occupied habitat), the agent
11306  !! tries to perform random migration
11307  !! the_behaviour::behaviour::migrate_random().
11308  do i = 1, size(global_habitats_available)
11309  if ( current_in /= i ) then
11310  is_migrated = this%migrate_random( global_habitats_available(i) )
11311  end if
11312  !> Note that the loop is terminated (`exit`) if migration into
11313  !! the i-th habitat was successful. The agent can perform only a
11314  !! single behaviour (migration across habitats) per a single time
11315  !! step.
11316  !! .
11317  if ( is_migrated ) exit
11318  end do
11319  !> If the migration was successful, no further behaviour is executed,
11320  !! it is assumed that the agent has executed the_behaviour::migrate
11321  !! behaviour unit.
11322  if ( is_migrated ) return
11323  end block try_migrate
11324 
11325  !> #### Execute behaviours depending on the current GOS arousal ####
11326  !! Fixed behaviour selection is implemented in the `SELECT_BEHAV`construct.
11327  !! Each of the GOS is rigidly associated with a specific behaviour pattern.
11328  !> - the_neurobio::state_hunger is the GOS:
11329  select_behav: if ( this%motivations%hunger%is_dominant() ) then
11330  !> - at least one food item is present within the perception object,
11331  !! calls the the_behaviour::eat_food() method for the nearest
11332  !! food item.
11333  if (this%has_food()) then
11334  food_item_selected = 1 ! first is nearest food item
11335  if (present(food_resource_real)) then
11336  call this%do_eat_food_item(food_item_selected, food_resource_real)
11337  else
11338  fres_num = this%find_environment(global_habitats_available)
11339  call this%do_eat_food_item(food_item_selected, &
11340  global_habitats_available(fres_num)%food)
11341  end if
11342  !> - there are no food items in the perception object, calls default
11343  !! random walk the_behaviour::walk_random.
11344  !! .
11345  else
11346  call this%do_walk()
11347  end if
11348  !> - the_neurobio::state_fear_defence is the GOS:
11349  else if ( this%motivations%fear_defence%is_dominant() ) then select_behav
11350  !> - there is at least one predator in perception: calls
11351  !! the_behaviour::escape_dart
11352  if (this%has_pred()) then
11353  predator_selected_n = 1 ! first is the nearest predator
11354  call this%do_escape( predator_object = &
11355  this%perceive_predator%predators_seen(predator_selected_n) )
11356  !> - no predators are present in the perception object: call
11357  !! the_behaviour::freeze.
11358  !! .
11359  else
11360  call this%do_freeze( )
11361  end if
11362 
11363  !> - the_neurobio::state_reproduce is the GOS:
11364  else if ( this%motivations%reproduction%is_dominant() ) then select_behav
11365  !> - if the agent is ready to reproduce and there are conspecifics in
11366  !! proximity, call the_behaviour::reproduce
11367  if (this%is_ready_reproduce() .and. this%has_consp()) then
11368  call this%do_reproduce()
11369  !> - if the above condition is not satisfied, do default
11370  !! the_behaviour::walk_random.
11371  !! .
11372  else
11373  call this%do_walk()
11374  end if
11375  end if select_behav
11376 
11377  end subroutine behaviour_select_fixed_from_gos
11378 
11379  !-----------------------------------------------------------------------------
11380  !> Initialise neuro-biological architecture.
11381  elemental subroutine neurobio_init_components(this)
11382  class(architecture_neuro), intent(inout) :: this
11383 
11384  !> Initialise neurobiological components of the agent.
11385  call this%init_perception()
11386  call this%init_appraisal()
11387  call this%init_gos()
11388  call this%init_behaviour()
11389 
11390  end subroutine neurobio_init_components
11391 
11392 end module
Abstract interface for the deferred init function that has to be overriden by each object that extend...
Definition: m_behav.f90:76
Abstract interface for the deferred init function that has to be overriden by each object that extend...
Definition: m_behav.f90:101
subroutine migrate_select(expected_gos, selected)
Calculate the expected GOS arousal that would be predicted from execution of the the_behaviour::migra...
Definition: m_behav.f90:11030
subroutine reproduce_select(expected_gos)
Calculate the expected GOS arousal that would be predicted from execution of the the_behaviour::repro...
Definition: m_behav.f90:10801
subroutine go_down_select(expected_gos, selected)
Calculate the expected GOS arousal that would be predicted from execution of the the_behaviour::go_do...
Definition: m_behav.f90:11094
real(srp) function subjective_capture_prob(fitem)
Calculate subjective probability of food item capture, as objective capture probability and random as...
Definition: m_behav.f90:9637
real(srp) function decrement_factor_fixed()
Calculate the decrement factor for the gonadal steroids based reproductive factor.
Definition: m_behav.f90:7679
subroutine escape_dart_select(expected_gos, selected)
Calculate the expected GOS arousal that would be predicted from execution of the the_behaviour::escap...
Definition: m_behav.f90:10900
subroutine go_up_select(expected_gos, selected)
Calculate the expected GOS arousal that would be predicted from execution of the the_behaviour::go_up...
Definition: m_behav.f90:11151
subroutine reproduction_unsuccessful_cost_subtract()
Process the costs of unsuccessful reproduction. Reproduction can be unsuccessful for various reasons:...
Definition: m_behav.f90:8234
subroutine debug_base_select(expected_gos)
Calculate the expected GOS arousal that would be predicted from execution of the the_behaviour::debug...
Definition: m_behav.f90:11205
subroutine approach_consp_select(expected_gos, selected)
Calculate the expected GOS arousal that would be predicted from execution of the the_behaviour::appro...
Definition: m_behav.f90:10969
subroutine eat_food_select(expected_gos, selected)
Calculate the expected GOS arousal that would be predicted from execution of the the_behaviour::eat_f...
Definition: m_behav.f90:10747
subroutine freeze_select(expected_gos)
Calculate the expected GOS arousal that would be predicted from execution of the the_behaviour::freez...
Definition: m_behav.f90:10873
subroutine walk_random_select(expected_gos, selected)
Calculate the expected GOS arousal that would be predicted from execution of the the_behaviour::walk_...
Definition: m_behav.f90:10827
COMMONDATA – definitions of global constants and procedures.
Definition: m_common.f90:1497
integer, parameter, public srp
Definition of the standard real type precision (SRP).
Definition: m_common.f90:1551
Definition of high level behavioural architecture.
Definition: m_behav.f90:17
elemental subroutine behaviour_cleanup_history(this)
Cleanup the behaviour history stack for the agent. All values are empty.
Definition: m_behav.f90:10355
elemental subroutine, private behaviour_whole_agent_init(this)
Initialise the behaviour components of the agent, the the_behaviour::behaviour class.
Definition: m_behav.f90:9316
subroutine go_up_do_execute(this, this_agent, min_depth, environments, depth_walk)
Execute this behaviour component "go up" by this_agent agent towards.
Definition: m_behav.f90:6353
subroutine reproduce_do_this(this, this_agent, p_reproduction, is_reproduce)
Do reproduce by this_agent (the actor agent) given the specific probability of successful reproductio...
Definition: m_behav.f90:7562
pure subroutine behaviour_root_attention_weights_transfer(this, this_agent)
Transfer attention weights from the actor agent to the behaviour's GOS expectancy object....
Definition: m_behav.f90:670
subroutine migrate_do_this(this, this_agent, target_env, predict_window_food, predict_window_consp, predict_window_pred, time_step_model)
The "do" procedure component of the behaviour element performs the behaviour without affecting the ac...
Definition: m_behav.f90:3570
subroutine reproduce_do_execute(this, this_agent)
Execute this behaviour component "reproduce" by the this_agent agent.
Definition: m_behav.f90:8070
integer function maximum_n_reproductions(this)
Calculate the maximum number of possible reproductions for this agent. It is assumed that a male can ...
Definition: m_behav.f90:7486
subroutine eat_food_item_motivations_expect(this, this_agent, food_item_eaten, time_step_model, distance_food_item, capture_prob, rescale_max_motivation)
eat_food::motivations_expect() is a subroutine (re)calculating motivations from fake expected percept...
Definition: m_behav.f90:6850
elemental subroutine go_up_depth_init_zero(this)
Initialise the go up to a shallower spatial layer behaviour component to a zero state.
Definition: m_behav.f90:5646
subroutine behaviour_do_go_up(this, depth_walk)
Perform (execute) the the_behaviour::go_up_depth (go up) behaviour.
Definition: m_behav.f90:10311
integer function behaviour_select_conspecific(this, rescale_max_motivation)
Select the optimal conspecific among (possibly) several ones that are available in the perception obj...
Definition: m_behav.f90:9375
elemental subroutine go_down_depth_init_zero(this)
Initialise the go down to a deeper spatial layer behaviour component to a zero state.
Definition: m_behav.f90:4808
integer function behaviour_select_conspecific_nearest(this)
Select the nearest conspecific among (possibly) several ones that are available in the perception obj...
Definition: m_behav.f90:9488
elemental subroutine reproduce_init_zero(this)
Initialise reproduce behaviour object.
Definition: m_behav.f90:7451
subroutine behaviour_do_migrate(this, target_env)
Perform (execute) the the_behaviour::migrate (migration) behaviour.
Definition: m_behav.f90:10091
character(len= *), parameter, private modname
Definition: m_behav.f90:26
elemental logical function behaviour_root_get_is_executed(this)
Get the execution status of the behaviour unit. If TRUE, the unit is currently active and is being ex...
Definition: m_behav.f90:759
subroutine eat_food_item_do_execute(this, this_agent, food_item_eaten, food_resource_real, eat_is_success)
Execute this behaviour component "eat food item" by this_agent agent towards the food_item_eaten.
Definition: m_behav.f90:7250
elemental subroutine approach_spatial_object_init_zero(this)
Initialise the approach behaviour component to a zero state. Approach is a generic type but not abstr...
Definition: m_behav.f90:1937
elemental subroutine, private neurobio_init_components(this)
Initialise neuro-biological architecture.
Definition: m_behav.f90:11382
elemental character(len=label_length) function behaviour_get_behaviour_label_executing(this)
Obtain the label of the currently executing behaviour for the this agent.
Definition: m_behav.f90:9363
subroutine behaviour_do_reproduce(this)
Reproduce based on the this agent's current state.
Definition: m_behav.f90:9785
integer function behaviour_select_food_item(this, rescale_max_motivation)
Select the optimal food item among (possibly) several ones that are available in the perception objec...
Definition: m_behav.f90:9509
subroutine go_down_motivations_expect(this, this_agent, depth_walk, max_depth, environments, time_step_model, rescale_max_motivation)
go_down_depth::motivations_expect() is a subroutine (re)calculating motivations from fake expected pe...
Definition: m_behav.f90:4975
subroutine walk_random_do_execute(this, this_agent, step_dist, step_cv, environment_limits)
Execute this behaviour component "random walk" by this_agent agent.
Definition: m_behav.f90:9191
subroutine go_down_do_execute(this, this_agent, max_depth, environments, depth_walk)
Execute this behaviour component "go down" by this_agent agent.
Definition: m_behav.f90:5518
subroutine behaviour_do_eat_food_item(this, number_in_seen, food_resource_real)
Eat a specific food item that are found in the perception object.
Definition: m_behav.f90:9694
subroutine behaviour_do_escape_dart(this, predator_object)
Perform (execute) the the_behaviour::escape_dart behaviour.
Definition: m_behav.f90:9943
subroutine walk_random_motivations_expect(this, this_agent, distance, distance_cv, predict_window_pred, predict_window_food, time_step_model, rescale_max_motivation)
the_behaviour::walk_random::expectancies_calculate() (re)calculates motivations from fake expected pe...
Definition: m_behav.f90:8735
elemental real(srp) function behaviour_root_gos_expectation(this)
Accessor get-function for the final expected GOS arousal from this behaviour. All calculations for ar...
Definition: m_behav.f90:746
subroutine freeze_do_this(this, this_agent)
Do freeze by this_agent (the actor agent). Subjective assessment of the motivational value for this i...
Definition: m_behav.f90:863
subroutine freeze_do_execute(this, this_agent)
Execute this behaviour component "freeze" by this_agent agent.
Definition: m_behav.f90:1222
subroutine go_up_motivations_expect(this, this_agent, depth_walk, min_depth, environments, time_step_model, rescale_max_motivation)
go_up_depth::motivations_expect() is a subroutine (re)calculating motivations from fake expected perc...
Definition: m_behav.f90:5809
subroutine escape_dart_motivations_expect(this, this_agent, predator_object, time_step_model, rescale_max_motivation)
escape_dart::motivations_expect() is a subroutine (re)calculating motivations from fake expected perc...
Definition: m_behav.f90:1486
subroutine approach_do_this(this, this_agent, target_object, target_offset, predict_window_food, time_step_model)
The "do" procedure component of the behaviour element performs the behaviour without affecting the ac...
Definition: m_behav.f90:1967
subroutine behaviour_do_go_down(this, depth_walk)
Perform (execute) the the_behaviour::go_down_depth (go down) behaviour.
Definition: m_behav.f90:10268
subroutine debug_base_motivations_expect(this, this_agent, time_step_model, rescale_max_motivation)
the_behaviour::debug_base::motivations_expect() is a subroutine (re)calculating motivations from fake...
Definition: m_behav.f90:6507
subroutine approach_conspecifics_do_this(this, this_agent, target_object, target_offset, predict_window_food, time_step_model)
The "do" procedure component of the behaviour element performs the behaviour without affecting the ac...
Definition: m_behav.f90:2626
elemental subroutine approach_conspecifics_init_zero(this)
Initialise the approach conspecific behaviour to a zero state. Approach conspecific is a special exte...
Definition: m_behav.f90:2588
elemental subroutine migrate_init_zero(this)
Initialise the migrate behaviour component to a zero state.
Definition: m_behav.f90:3533
elemental subroutine freeze_init_zero(this)
Initialise the freeze behaviour component to a zero state. Freeze is a special type of move to a zero...
Definition: m_behav.f90:834
subroutine freeze_motivations_expect(this, this_agent, time_step_model, rescale_max_motivation)
the_behaviour::freeze::motivations_expect() (re)calculates motivations from fake expected perceptions...
Definition: m_behav.f90:920
subroutine escape_dart_do_this(this, this_agent, predator_object, dist_is_stochastic, time_step_model)
Do active escape dart by this_agent (the actor agent). Subjective assessment of the motivational valu...
Definition: m_behav.f90:1298
subroutine migrate_motivations_expect(this, this_agent, target_env, predict_window_food, predict_window_consp, predict_window_pred, time_step_model, rescale_max_motivation)
the_behaviour::migrate::expectancies_calculate() (re)calculates motivations from fake expected percep...
Definition: m_behav.f90:3995
subroutine go_up_do_this(this, this_agent, min_depth, depth_walk, predict_window_food, time_step_model)
Do go up by this_agent (the actor agent). Subjective assessment of the motivational value for this is...
Definition: m_behav.f90:5678
subroutine behaviour_do_freeze(this)
Perform (execute) the the_behaviour::freeze behaviour.
Definition: m_behav.f90:9901
subroutine behaviour_select_optimal(this, rescale_max_motivation, food_resource_real)
Select and execute the optimal behaviour, i.e. the behaviour which minimizes the expected GOS arousal...
Definition: m_behav.f90:10369
subroutine behaviour_select_fixed_from_gos(this, rescale_max_motivation, food_resource_real)
Select and execute behaviour based on the current global organismic state. This procedure is signific...
Definition: m_behav.f90:11238
pure real(srp) function hope(baseline, memory_old, memory_new, zero_hope, maximum_hope, raw_grid_x, raw_grid_y)
The hope function for the assessment of expectancy for a completely novel stimulus or environment for...
Definition: m_behav.f90:4659
subroutine migrate_do_execute(this, this_agent, target_env)
Execute this behaviour component "migrate" by this_agent agent.
Definition: m_behav.f90:4468
elemental subroutine walk_random_init_zero(this)
Initialise the walk_random behaviour component to a zero state.
Definition: m_behav.f90:803
subroutine escape_dart_do_execute(this, this_agent, predator_object, environment_limits)
Execute this behaviour component "escape" by this_agent agent.
Definition: m_behav.f90:1801
elemental real(srp) function depth_walk_default(length, walk_factor)
Calculate the default upward and downward walk step size. This function is called from the_behaviour:...
Definition: m_behav.f90:4783
subroutine approach_do_execute(this, this_agent, target_object, is_random, target_offset, environment_limits)
Execute this behaviour component "approach" by this_agent agent.
Definition: m_behav.f90:2347
elemental subroutine debug_base_init_zero(this)
Initialise the fake debug behaviour behaviour component to a zero state.
Definition: m_behav.f90:6484
elemental subroutine eat_food_item_init_zero(this)
Initialise the eat food item behaviour component to a zero state.
Definition: m_behav.f90:775
subroutine behaviour_do_walk(this, distance, distance_cv)
Perform a random Gaussian walk to a specific average distance with certain variance (set by the CV).
Definition: m_behav.f90:9832
subroutine approach_conspecifics_motivations_expect(this, this_agent, target_object, target_offset, time_step_model, rescale_max_motivation)
the_behaviour::approach_conspec::expectancies_calculate() (re)calculates motivations from fake expect...
Definition: m_behav.f90:3111
integer function behaviour_select_food_item_nearest(this)
Select the nearest food item among (possibly) several ones that are available in the perception objec...
Definition: m_behav.f90:9676
subroutine walk_random_do_this(this, this_agent, distance, distance_cv, predict_window_pred, predict_window_food, time_step_model)
The "do" procedure component of the behaviour element performs the behaviour without affecting the ac...
Definition: m_behav.f90:8269
subroutine reproduce_motivations_expect(this, this_agent, time_step_model, reprod_prob, non_stochastic, rescale_max_motivation)
reproduce::motivations_expect() is a subroutine (re)calculating motivations from fake expected percep...
Definition: m_behav.f90:7694
subroutine go_down_do_this(this, this_agent, max_depth, depth_walk, predict_window_food, time_step_model)
Do go down by this_agent (the actor agent). Subjective assessment of the motivational value for this ...
Definition: m_behav.f90:4840
elemental subroutine behaviour_whole_agent_deactivate(this)
Deactivate all behaviour units that compose the behaviour repertoire of the agent.
Definition: m_behav.f90:9343
elemental subroutine escape_dart_init_zero(this)
Initialise the escape dart behaviour component to a zero state. Dart is a quick high speed active esc...
Definition: m_behav.f90:1267
subroutine eat_food_item_do_this(this, this_agent, food_item_eaten, time_step_model, distance_food_item, capture_prob, is_captured)
Eat a food item defined by the object food_item_eaten. The "do" procedure component of the behaviour ...
Definition: m_behav.f90:6727
logical function behaviour_try_migrate_random(this, target_env, max_dist, prob)
Perform a simplistic random migration. If the agent is within a specific distance to the target envir...
Definition: m_behav.f90:10129
subroutine behaviour_do_approach(this, target_object, is_random, target_offset)
Approach a specific the_environment::spatial class target, i.e. execute the the_behaviour::approach b...
Definition: m_behav.f90:9988
subroutine approach_motivations_expect(this, this_agent, target_object, target_offset, time_step_model, rescale_max_motivation)
the_behaviour::approach::expectancies_calculate() (re)calculates motivations from fake expected perce...
Definition: m_behav.f90:2075
Definition the physical properties and condition of the agent.
Definition: m_body.f90:19
Definition of environmental objects.
Definition: m_env.f90:19
Definition of the decision making and behavioural the architecture.
Definition: m_neuro.f90:17
Approach conspecifics is directed movement towards a conspecific.
Definition: m_behav.f90:323
Approach an arbitrary spatial object is a directed movement to an arbitrary the_environment::spatial ...
Definition: m_behav.f90:290
This type is an "umbrella" for all the lower-level classes.
Definition: m_behav.f90:627
Root behaviour abstract type. Several different discrete behaviours encompass the behavioural reperto...
Definition: m_behav.f90:36
The behaviour of the agent is defined by the the_behaviour::behaviour class. This class defines the b...
Definition: m_behav.f90:514
This is a test fake behaviour unit that is used only for debugging. It cannot be "execute"'d,...
Definition: m_behav.f90:474
Eat food is consuming food item(s) perceived.
Definition: m_behav.f90:112
Escape dart is a very fast long distance movement, normally in response to a direct predation threat.
Definition: m_behav.f90:251
Freeze is stop any locomotion completely.
Definition: m_behav.f90:214
Go down dive deeper.
Definition: m_behav.f90:394
Go up raise to a smaller depth. TODO: abstract type linking both Up and Down.
Definition: m_behav.f90:433
Migrate is move quickly directing to the other habitat
Definition: m_behav.f90:355
Movement is an umbrella abstract type linked with spatial movement.
Definition: m_behav.f90:83
Reproduce is do a single reproduction.
Definition: m_behav.f90:144
Walk_random is a single step of a Gaussian random walk.
Definition: m_behav.f90:176
Definition of a spatial object. Spatial object determines the position of the agent,...
Definition: m_env.f90:50
The appraisal level. At this level, perception objects are feed into the commondata::gamma2gene() sig...
Definition: m_neuro.f90:1222
Global organismic state (GOS) level. GOS is defined by the dominant motivational state component (STA...
Definition: m_neuro.f90:1304
Motivation is a collection of all internal motivational states of the agent. This type is also used i...
Definition: m_neuro.f90:1101