source: palm/trunk/SOURCE/multi_agent_system_mod.f90 @ 3359

Last change on this file since 3359 was 3274, checked in by knoop, 6 years ago

Modularization of all bulk cloud physics code components

  • Property svn:keywords set to Id
File size: 193.4 KB
Line 
1!> @file multi_agent_system_mod.f90
2!--------------------------------------------------------------------------------!
3! This file is part of PALM-4U.
4!
5! PALM-4U is free software: you can redistribute it and/or modify it under the
6! terms of the GNU General Public License as published by the Free Software
7! Foundation, either version 3 of the License, or (at your option) any later
8! version.
9!
10! PALM-4U is distributed in the hope that it will be useful, but WITHOUT ANY
11! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
12! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
13!
14! You should have received a copy of the GNU General Public License along with
15! PALM. If not, see <http://www.gnu.org/licenses/>.
16!
17! Copyright 2016 Leibniz Universitaet Hannover
18!------------------------------------------------------------------------------!
19!
20! Current revisions:
21! ------------------
22!
23!
24! Former revisions:
25! -----------------
26! $Id: multi_agent_system_mod.f90 3274 2018-09-24 15:42:55Z knoop $
27! Modularization of all bulk cloud physics code components
28!
29! 3268 2018-09-21 13:45:37Z sward
30! Cleaned up agent pointer assignment in output routine
31!
32! 3248 2018-09-14 09:42:06Z sward
33! Minor formating changes
34!
35! 3246 2018-09-13 15:14:50Z sward
36! Added error handling for input namelist via parin_fail_message
37!
38! 3241 2018-09-12 15:02:00Z raasch
39! unused variables removed
40!
41! 3235 2018-09-07 14:06:15Z sward
42! Bugfix in output, added agent-number dimension and related messages and
43! input parameters, updated cpu logging, added mas_last_actions
44!
45! 3201 2018-08-20 11:45:01Z sward
46! Bugfix, missing pre-processor directive. Set default
47! read_agents_from_restartfile = .FALSE. restarts not yet implemented.
48!
49! 3198 2018-08-15 09:23:10Z sward
50! Now using time_since_reference_point; moved multi_agent_system_start and
51! multi_agent_system_end to control_parameters; renamed NAMELIST agents_par to
52! agent_parameters
53!
54! 3187 2018-07-31 10:32:34Z sward
55! Reworked agent pathfinding to avoid collisions with walls
56!
57! 3165 2018-07-24 13:12:42Z sward
58! Added agent ID output
59!
60! 3160 2018-07-20 11:52:56Z sward
61! Changed C_SIZEOF to STORAGE_SIZE
62!
63! 3159 2018-07-20 11:20:01Z sward
64! Initial revision
65!
66!
67!
68! Authors:
69! --------
70! @author sward
71!
72!
73! Description:
74! ------------
75!> Multi Agent System for the simulation of pedestrian movement in urban
76!> environments
77!------------------------------------------------------------------------------!
78 MODULE multi_agent_system_mod
79
80    USE, INTRINSIC ::  ISO_C_BINDING
81
82    USE basic_constants_and_equations_mod,                                     &
83        ONLY:  pi
84
85    USE control_parameters,                                                    &
86        ONLY:  dt_3d, message_string, time_since_reference_point, dt_write_agent_data
87
88    USE cpulog,                                                                &
89        ONLY:  cpu_log, log_point, log_point_s
90
91    USE grid_variables,                                                        &
92        ONLY:  ddx, ddy, dx, dy
93
94    USE indices,                                                               &
95        ONLY:  nx, nxl, nxlg, nxr, nxrg, ny, nyn, nyng, nys, nysg, nzb,        &
96               wall_flags_0
97
98    USE random_function_mod,                                                   &
99        ONLY:  random_function
100
101    USE kinds
102
103    USE pegrid
104
105    CHARACTER(LEN=15) ::  bc_mas_lr = 'absorb'  !< left/right boundary condition
106    CHARACTER(LEN=15) ::  bc_mas_ns = 'absorb'  !< north/south boundary condition
107
108    INTEGER(iwp) ::  deleted_agents = 0                !< number of deleted agents per time step
109    INTEGER(iwp) ::  dim_size_agtnum_manual = 9999999  !< namelist parameter (see documentation)
110    INTEGER(iwp) ::  heap_count                        !< number of items in binary heap (for pathfinding)
111    INTEGER(iwp) ::  ibc_mas_lr                        !< agent left/right boundary condition dummy
112    INTEGER(iwp) ::  ibc_mas_ns                        !< agent north/south boundary condition dummy
113!    INTEGER(iwp) ::  ind_pm10 = -9                     !< chemical species index of PM10
114!    INTEGER(iwp) ::  ind_pm25 = -9                     !< chemical species index of PM2.5
115    INTEGER(iwp) ::  iran_agent = -1234567             !< number for random generator
116    INTEGER(iwp) ::  min_nr_agent = 2                  !< namelist parameter (see documentation)
117    INTEGER(iwp) ::  ghla_count_recv                   !< number of agents in left ghost layer
118    INTEGER(iwp) ::  ghna_count_recv                   !< number of agents in north ghost layer
119    INTEGER(iwp) ::  ghra_count_recv                   !< number of agents in right ghost layer
120    INTEGER(iwp) ::  ghsa_count_recv                   !< number of agents in south ghost layer
121    INTEGER(iwp) ::  maximum_number_of_agents = 0      !< maximum number of agents during run
122    INTEGER(iwp) ::  nr_move_north                     !< number of agts to move north during exchange_horiz
123    INTEGER(iwp) ::  nr_move_south                     !< number of agts to move south during exchange_horiz
124    INTEGER(iwp) ::  number_of_agents = 0              !< number of agents for each grid box (3d array is saved on agt_count)
125    INTEGER(iwp) ::  number_of_agent_groups = 1        !< namelist parameter (see documentation)
126    INTEGER(iwp) ::  sort_count_mas = 0                !< counter for sorting agents
127    INTEGER(iwp) ::  agt_path_size = 15                !< size of agent path array
128    INTEGER(iwp) ::  step_dealloc_mas = 100            !< namelist parameter (see documentation)
129    INTEGER(iwp) ::  total_number_of_agents            !< total number of agents in the whole model domain
130
131    INTEGER(iwp), PARAMETER ::  NR_2_direction_move = 10000 !< parameter for agent exchange
132    INTEGER(iwp), PARAMETER ::  PHASE_INIT    = 1           !< phase parameter
133    INTEGER(iwp), PARAMETER ::  PHASE_RELEASE = 2           !< phase parameter
134
135    INTEGER(iwp), PARAMETER ::  max_number_of_agent_groups = 100 !< maximum allowed number of agent groups
136
137    INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  agt_count         !< 3d array of number of agents of every grid box
138    INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  s_measure_height  !< k-index(s-grid) for measurement
139    INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  top_top_s         !< k-index of first s-gridpoint above topography
140    INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  top_top_w         !< k-index of first v-gridpoint above topography
141    INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  obstacle_flags    !< flags to identify corners and edges of topography that cannot be crossed by agents
142
143    LOGICAL ::  deallocate_memory_mas = .TRUE.          !< namelist parameter (see documentation)
144    LOGICAL ::  dt_3d_reached_mas                       !< flag: agent timestep has reached model timestep
145    LOGICAL ::  dt_3d_reached_l_mas                     !< flag: agent timestep has reached model timestep
146    LOGICAL ::  agents_active = .FALSE.                 !< flag for agent system
147    LOGICAL ::  random_start_position_agents = .TRUE.   !< namelist parameter (see documentation)
148    LOGICAL ::  read_agents_from_restartfile = .FALSE.  !< namelist parameter (see documentation)
149    LOGICAL ::  agent_own_timestep = .FALSE.            !< namelist parameter (see documentation)
150
151    LOGICAL, DIMENSION(max_number_of_agent_groups) ::  a_rand_target = .FALSE. !< namelist parameter (see documentation)
152
153    REAL(wp) ::  agent_maximum_age = 9999999.9_wp          !< namelist parameter (see documentation)
154    REAL(wp) ::  alloc_factor_mas = 20.0_wp                !< namelist parameter (see documentation)
155    REAL(wp) ::  coll_t_0 = 3.                             !< namelist parameter (see documentation)
156    REAL(wp) ::  corner_gate_start = 0.5_wp                !< namelist parameter (see documentation)
157    REAL(wp) ::  corner_gate_width = 1.0_wp                !< namelist parameter (see documentation)
158    REAL(wp) ::  dim_size_factor_agtnum = 1.0_wp           !< namelist parameter (see documentation)
159    REAL(wp) ::  d_sigma_rep_agent                         !< inverse of sigma_rep_agent
160    REAL(wp) ::  d_sigma_rep_wall                          !< inverse of sigma_rep_wall
161    REAL(wp) ::  d_tau_accel_agent                         !< inverse of tau_accel_agent
162    REAL(wp) ::  desired_speed = 1.2_wp                    !< namelist parameter (see documentation)
163    REAL(wp) ::  des_sp_sig = .2_wp                        !< namelist parameter (see documentation)
164    REAL(wp) ::  dist_target_reached = 2.0_wp              !< distance at which target counts as reached
165    REAL(wp) ::  dist_to_int_target = .25_wp               !< namelist parameter (see documentation)
166    REAL(wp) ::  dt_agent = 0.02_wp                        !< namelist parameter (see documentation)
167    REAL(wp) ::  dt_arel = 9999999.9_wp                    !< namelist parameter (see documentation)
168    REAL(wp) ::  end_time_arel = 9999999.9_wp              !< namelist parameter (see documentation)
169    REAL(wp) ::  force_x                                   !< dummy value for force on current agent in x-direction
170    REAL(wp) ::  force_y                                   !< dummy value for force on current agent in y-direction
171    REAL(wp) ::  max_dist_from_path = 0.25_wp              !< distance from current path at which a new path is calculated
172    REAL(wp) ::  radius_agent = .25_wp                     !< namelist parameter (see documentation)
173    REAL(wp) ::  repuls_agent = 1.5_wp                     !< namelist parameter (see documentation)
174    REAL(wp) ::  repuls_wall = 7.0_wp                      !< namelist parameter (see documentation)
175    REAL(wp) ::  scan_radius_agent = 3.0_wp                !< namelist parameter (see documentation)
176    REAL(wp) ::  scan_radius_wall = 2.0_wp                 !< namelist parameter (see documentation)
177    REAL(wp) ::  sigma_rep_agent = 0.3_wp                  !< namelist parameter (see documentation)
178    REAL(wp) ::  sigma_rep_wall = 0.1_wp                   !< namelist parameter (see documentation)
179    REAL(wp) ::  tau_accel_agent = 0.5_wp                  !< namelist parameter (see documentation)
180    REAL(wp) ::  time_arel = 0.0_wp                        !< time for agent release
181    REAL(wp) ::  time_write_agent_data = 0.0_wp            !< write agent data at current time on file
182    REAL(wp) ::  v_max_agent = 1.3_wp                      !< namelist parameter (see documentation)
183
184    REAL(wp), DIMENSION(:), ALLOCATABLE ::  dummy_path_x  !<  dummy path (x-coordinate)
185    REAL(wp), DIMENSION(:), ALLOCATABLE ::  dummy_path_y  !<  dummy path (y-coordinate)
186
187    REAL(wp), DIMENSION(max_number_of_agent_groups) ::  adx = 9999999.9_wp  !< namelist parameter (see documentation)
188    REAL(wp), DIMENSION(max_number_of_agent_groups) ::  ady = 9999999.9_wp  !< namelist parameter (see documentation)
189    REAL(wp), DIMENSION(max_number_of_agent_groups) ::  asl = 9999999.9_wp  !< namelist parameter (see documentation)
190    REAL(wp), DIMENSION(max_number_of_agent_groups) ::  asn = 9999999.9_wp  !< namelist parameter (see documentation)
191    REAL(wp), DIMENSION(max_number_of_agent_groups) ::  asr = 9999999.9_wp  !< namelist parameter (see documentation)
192    REAL(wp), DIMENSION(max_number_of_agent_groups) ::  ass = 9999999.9_wp  !< namelist parameter (see documentation)
193    REAL(wp), DIMENSION(max_number_of_agent_groups) ::  at_x = 9999999.9_wp !< namelist parameter (see documentation)
194    REAL(wp), DIMENSION(max_number_of_agent_groups) ::  at_y = 9999999.9_wp !< namelist parameter (see documentation)
195!
196!-- Type for the definition of an agent
197    TYPE agent_type
198        INTEGER(iwp) ::  block_nr             !< number for sorting
199        INTEGER(iwp) ::  group                !< number of agent group
200        INTEGER(idp) ::  id                   !< particle ID (64 bit integer)
201        INTEGER(iwp) ::  path_counter         !< current target along path (path_x/y)
202        LOGICAL      ::  agent_mask           !< if this parameter is set to false the agent will be deleted
203        REAL(wp)     ::  age                  !< age of agent
204        REAL(wp)     ::  age_m                !< age of agent
205        REAL(wp)     ::  dt_sum               !< sum of agents subtimesteps
206        REAL(wp)     ::  clo                  !< clothing index
207        REAL(wp)     ::  energy_storage       !< energy stored by agent
208        REAL(wp)     ::  force_x              !< force term x-direction
209        REAL(wp)     ::  force_y              !< force term y-direction
210        REAL(wp)     ::  origin_x             !< origin x-position of agent
211        REAL(wp)     ::  origin_y             !< origin y-position of agent
212        REAL(wp)     ::  pm10                 !< PM10 concentration at agent position
213        REAL(wp)     ::  pm25                 !< PM25 concentration at agent position
214        REAL(wp)     ::  speed_abs            !< absolute value of agent speed
215        REAL(wp)     ::  speed_e_x            !< normalized speed of agent in x
216        REAL(wp)     ::  speed_e_y            !< normalized speed of agent in y
217        REAL(wp)     ::  speed_des            !< agent's desired speed
218        REAL(wp)     ::  speed_x              !< speed of agent in x
219        REAL(wp)     ::  speed_y              !< speed of agent in y
220        REAL(wp)     ::  thermal_index        !< the dynamic thermal index
221        REAL(wp)     ::  windspeed            !< absolute value of windspeed at agent position
222        REAL(wp)     ::  x                    !< x-position
223        REAL(wp)     ::  y                    !< y-position
224        REAL(wp)     ::  t                    !< temperature
225        REAL(wp)     ::  t_x                  !< x-position
226        REAL(wp)     ::  t_y                  !< y-position
227        REAL(wp), DIMENSION(0:15) ::  path_x  !< agent path to target (x)
228        REAL(wp), DIMENSION(0:15) ::  path_y  !< agent path to target (y)
229    END TYPE agent_type
230
231    TYPE(agent_type), DIMENSION(:), POINTER ::  agents               !< Agent array for this grid cell
232    TYPE(agent_type)                        ::  zero_agent           !< zero agent to avoid weird thing
233    TYPE(agent_type), DIMENSION(:), ALLOCATABLE ::  move_also_north  !< for agent exchange between PEs
234    TYPE(agent_type), DIMENSION(:), ALLOCATABLE ::  move_also_south  !< for agent exchange between PEs
235    TYPE(agent_type), DIMENSION(:), ALLOCATABLE ::  agt_gh_l         !< ghost layer left of pe domain
236    TYPE(agent_type), DIMENSION(:), ALLOCATABLE ::  agt_gh_n         !< ghost layer north of pe domain
237    TYPE(agent_type), DIMENSION(:), ALLOCATABLE ::  agt_gh_r         !< ghost layer right of pe domain
238    TYPE(agent_type), DIMENSION(:), ALLOCATABLE ::  agt_gh_s         !< ghost layer south of pe domain
239!
240!-- Type for 2D grid on which agents are stored
241    TYPE  grid_agent_def
242        INTEGER(iwp), DIMENSION(0:3)            ::  start_index        !< start agent index for current block
243        INTEGER(iwp), DIMENSION(0:3)            ::  end_index          !< end agent index for current block
244        INTEGER(iwp)                            ::  id_counter         !< agent id counter (removeable?)
245        LOGICAL                                 ::  time_loop_done     !< timestep loop for agent advection
246        TYPE(agent_type), POINTER, DIMENSION(:) ::  agents             !< Particle array for this grid cell
247    END TYPE grid_agent_def
248
249    TYPE(grid_agent_def), DIMENSION(:,:), ALLOCATABLE, TARGET ::  grid_agents !< 2D grid on which agents are stored
250!
251!-- Item in a priority queue (binary heap)
252    TYPE heap_item
253       INTEGER(iwp) ::  mesh_id       !< id of the submitted mesh point
254       REAL(wp)     ::  priority      !< priority of the mesh point (= distance so far + heuristic to goal)
255    END TYPE heap_item
256
257    TYPE(heap_item), DIMENSION(:), ALLOCATABLE ::  queue  !< priority queue realized as binary heap
258!
259!-- Type for mesh point in visibility graph
260    TYPE  mesh_point
261        INTEGER(iwp)                            ::  polygon_id          !< Polygon the point belongs to
262        INTEGER(iwp)                            ::  vertex_id           !< Vertex in the polygon
263        INTEGER(iwp)                            ::  noc                 !< number of connections
264        INTEGER(iwp)                            ::  origin_id           !< ID of previous mesh point on path (A*)
265        INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  connected_vertices  !< Index of connected vertices
266        REAL(wp)                                ::  cost_so_far         !< Cost to reach this mesh point (A*)
267        REAL(wp)                                ::  x                   !< x-coordinate
268        REAL(wp)                                ::  y                   !< y-coordinate
269        REAL(wp)                                ::  x_s                 !< corner shifted outward from building by 1m (x)
270        REAL(wp)                                ::  y_s                 !< corner shifted outward from building by 1m (y)
271        REAL(wp), DIMENSION(:), ALLOCATABLE     ::  distance_to_vertex  !< Distance to each vertex
272    END TYPE mesh_point
273
274    TYPE(mesh_point), DIMENSION(:), ALLOCATABLE ::  mesh     !< navigation mesh
275    TYPE(mesh_point), DIMENSION(:), ALLOCATABLE ::  tmp_mesh !< temporary navigation mesh
276!
277!-- Vertex of a polygon
278    TYPE  vertex_type
279        LOGICAL               ::  delete  !< Flag to mark vertex for deletion
280        REAL(wp)              ::  x       !< x-coordinate
281        REAL(wp)              ::  y       !< y-coordinate
282    END TYPE vertex_type
283!
284!-- Polygon containing a number of vertices
285    TYPE  polygon_type
286        INTEGER(iwp)                                 ::  nov       !< Number of vertices in this polygon
287        TYPE(vertex_type), DIMENSION(:), ALLOCATABLE ::  vertices  !< Array of vertices
288    END TYPE polygon_type
289
290    TYPE(polygon_type), DIMENSION(:), ALLOCATABLE ::  polygons  !< Building data in polygon form
291
292    SAVE
293
294    PRIVATE
295!
296!-- Public functions
297    PUBLIC mas_init, mas_last_actions, mas_parin, multi_agent_system
298
299!
300!-- Public parameters, constants and initial values
301    PUBLIC agents_active
302
303    INTERFACE mas_parin
304       MODULE PROCEDURE mas_parin
305    END INTERFACE mas_parin
306
307    INTERFACE mas_init
308       MODULE PROCEDURE mas_init
309    END INTERFACE mas_init
310
311    INTERFACE mas_last_actions
312       MODULE PROCEDURE mas_last_actions
313    END INTERFACE mas_last_actions
314
315    INTERFACE multi_agent_system
316       MODULE PROCEDURE multi_agent_system
317    END INTERFACE multi_agent_system
318
319    CONTAINS
320
321
322!------------------------------------------------------------------------------!
323! Description:
324! ------------
325!> Multi Agent System:
326!> executes a number of agents sub-timesteps until the model timestep is reached.
327!> The agent timestep is usually smaller than the model timestep
328!------------------------------------------------------------------------------!
329 SUBROUTINE multi_agent_system
330
331!     USE htcm_mod,                                                              &
332!         ONLY:  htcm_dynamic
333
334    IMPLICIT NONE
335
336    INTEGER(iwp)       ::  i                  !< counter
337    INTEGER(iwp)       ::  ie                 !< counter
338    INTEGER(iwp)       ::  is                 !< counter
339    INTEGER(iwp)       ::  j                  !< counter
340    INTEGER(iwp)       ::  je                 !< counter
341    INTEGER(iwp)       ::  js                 !< counter
342    INTEGER(iwp), SAVE ::  mas_count = 0      !< counts the mas-calls
343
344    LOGICAL       ::  first_loop_stride   !< flag for first loop stride of agent sub-timesteps
345    LOGICAL, SAVE ::  first_call = .TRUE. !< first call of mas flag for output
346
347    CALL cpu_log( log_point(9), 'mas', 'start' )
348!
349!-- Initialize variables for the next (sub-) timestep, i.e., for marking
350!-- those agents to be deleted after the timestep
351    deleted_agents = 0
352!
353!-- If necessary, release new set of agents
354    IF ( time_arel >= dt_arel  .AND.  end_time_arel > time_since_reference_point )  THEN
355
356       CALL mas_create_agent(PHASE_RELEASE)
357!
358!--    The MOD function allows for changes in the output interval with
359!--    restart runs.
360       time_arel = MOD( time_arel, MAX( dt_arel, dt_3d ) )
361
362    ENDIF
363
364    first_loop_stride = .TRUE.
365    grid_agents(:,:)%time_loop_done = .TRUE.
366!
367!-- Set timestep variable
368    IF ( .NOT. agent_own_timestep ) dt_agent = dt_3d
369!
370!-- Timestep loop for agent transport.
371!-- This loop has to be repeated until the transport time of every agent
372!-- (within the total domain!) has reached the LES timestep (dt_3d).
373!-- Timestep scheme is Euler-forward
374    DO
375!
376!--    Write agent data at current time on file.
377       time_write_agent_data = time_write_agent_data + dt_agent
378       IF ( time_write_agent_data >= dt_write_agent_data )  THEN
379#if defined( __netcdf )
380          IF ( first_loop_stride ) CALL mas_get_prognostic_quantities
381          CALL mas_data_output_agents ( first_call )
382#else
383          WRITE( message_string, * ) 'NetCDF is needed for agent output. ',    &
384                                     'Set __netcdf in compiler options'
385          CALL message( 'multi_agent_system', 'PA0071', 1, 2, 0, 6, 0 )
386#endif
387          IF(first_call) first_call = .FALSE.
388          time_write_agent_data = time_write_agent_data - dt_write_agent_data
389       ENDIF
390!
391!--    Flag is true by default, will be set to false if an agent has not yet
392!--    reached the model timestep
393       grid_agents(:,:)%time_loop_done = .TRUE.
394
395!
396!--    First part of agent transport:
397!--    Evaluate social forces for all agents at current positions
398       CALL cpu_log( log_point_s(9), 'mas_social_forces', 'start' )
399       DO  i = nxl, nxr
400          DO  j = nys, nyn
401
402             number_of_agents = agt_count(j,i)
403!
404!--          If grid cell is empty, cycle
405             IF ( number_of_agents <= 0 ) CYCLE
406
407             agents => grid_agents(j,i)%agents(1:number_of_agents)
408!
409!--          Evaluation of social forces
410             CALL mas_timestep_forces_call(i,j)
411
412          ENDDO
413       ENDDO
414       CALL cpu_log( log_point_s(9), 'mas_social_forces', 'stop' )
415!
416!--    Second part of agent transport:
417!--    timestep
418       CALL cpu_log( log_point_s(16), 'mas_timestep', 'start' )
419       DO  i = nxl, nxr
420          DO  j = nys, nyn
421
422             number_of_agents = agt_count(j,i)
423!
424!--          If grid cell is empty, flag must be true
425             IF ( number_of_agents <= 0 )  THEN
426                grid_agents(j,i)%time_loop_done = .TRUE.
427                CYCLE
428             ENDIF
429
430             agents => grid_agents(j,i)%agents(1:number_of_agents)
431
432             agents(1:number_of_agents)%agent_mask = .TRUE.
433!
434!--          Initialize the variable storing the total time that an agent
435!--          has advanced within the timestep procedure
436             IF ( first_loop_stride )  THEN
437                agents(1:number_of_agents)%dt_sum = 0.0_wp
438             ENDIF
439!
440!--          Initialize the switch used for the loop exit condition checked
441!--          at the end of this loop. If at least one agent has failed to
442!--          reach the LES timestep, this switch will be set false in
443!--          mas_transport.
444             dt_3d_reached_l_mas = .TRUE.
445!
446!--          Timestep
447             CALL mas_timestep
448!
449!--          Delete agents that have been simulated longer than allowed
450             CALL mas_boundary_conds( 'max_sim_time' )
451!
452!--          Delete agents that have reached target area
453             CALL mas_boundary_conds( 'target_area' )
454!
455!---         If not all agents of the actual grid cell have reached the
456!--          LES timestep, this cell has to to another loop iteration. Due to
457!--          the fact that agents can move into neighboring grid cell,
458!--          these neighbor cells also have to perform another loop iteration
459             IF ( .NOT. dt_3d_reached_l_mas )  THEN
460                js = MAX(nys,j-1)
461                je = MIN(nyn,j+1)
462                is = MAX(nxl,i-1)
463                ie = MIN(nxr,i+1)
464                grid_agents(js:je,is:ie)%time_loop_done = .FALSE.
465             ENDIF
466
467          ENDDO
468       ENDDO
469       CALL cpu_log( log_point_s(16), 'mas_timestep', 'stop' )
470
471!
472!--    Find out, if all agents on every PE have completed the LES timestep
473!--    and set the switch corespondingly
474       dt_3d_reached_l_mas = ALL(grid_agents(:,:)%time_loop_done)
475#if defined( __parallel )
476       IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
477       CALL MPI_ALLREDUCE( dt_3d_reached_l_mas, dt_3d_reached_mas, 1, MPI_LOGICAL, &
478                           MPI_LAND, comm2d, ierr )
479#else
480       dt_3d_reached_mas = dt_3d_reached_l_mas
481#endif
482
483!
484!--    Increment time since last release
485       IF ( dt_3d_reached_mas )  time_arel = time_arel + dt_3d
486
487!
488!--    Move Agents local to PE to a different grid cell
489       CALL cpu_log( log_point_s(18), 'mas_move_exch_sort', 'start' )
490       CALL mas_eh_move_agent
491!
492!--    Horizontal boundary conditions including exchange between subdmains
493       CALL mas_eh_exchange_horiz
494!
495!--    Pack agents (eliminate those marked for deletion),
496!--    determine new number of agents
497       CALL mas_ps_sort_in_subboxes
498       CALL cpu_log( log_point_s(18), 'mas_move_exch_sort', 'stop' )
499!
500!--    Initialize variables for the next (sub-) timestep, i.e., for marking
501!--    those agents to be deleted after the timestep
502       deleted_agents = 0
503!
504!--    to be included here: call of human thermal comfort mod (and UV exposure)
505!        DO  i = nxl, nxr
506!           DO  j = nys, nyn
507!
508!              number_of_agents = agt_count(j,i)
509! !
510! !--          If grid cell gets empty, cycle
511!              IF ( number_of_agents <= 0 ) CYCLE
512!
513!              agents => grid_agents(j,i)%agents(1:number_of_agents)
514! !
515! !--          Evaluation of social forces
516!              CALL htcm_dynamic(i,j)
517!
518!           ENDDO
519!        ENDDO
520
521       IF ( dt_3d_reached_mas )  EXIT
522
523       first_loop_stride = .FALSE.
524    ENDDO   ! timestep loop
525
526!
527!-- Deallocate unused memory
528    IF ( deallocate_memory_mas  .AND.  mas_count == step_dealloc_mas )  THEN
529       CALL mas_eh_dealloc_agents_array
530       mas_count = 0
531    ELSEIF ( deallocate_memory_mas )  THEN
532       mas_count = mas_count + 1
533    ENDIF
534
535    CALL cpu_log( log_point(9), 'mas', 'stop' )
536
537 END SUBROUTINE multi_agent_system
538
539!------------------------------------------------------------------------------!
540! Description:
541! ------------
542!> Calculation of the direction vector from each agent to its current
543!> intermittent target
544!------------------------------------------------------------------------------!
545    SUBROUTINE mas_agent_direction
546
547       IMPLICIT NONE
548
549       LOGICAL ::  path_flag !< true if new path must be calculated
550
551       INTEGER(iwp) ::  n  !< loop variable over all agents in a grid box
552       INTEGER(iwp) ::  pc !< agent path counter
553
554       REAL(wp) ::  abs_dir         !< length of direction vector (for normalization)
555!       REAL(wp) ::  d_curr_target   !< rounding influence expressed as x speed component
556!       REAL(wp) ::  d_prev_target   !< rounding influence expressed as x speed component
557       REAL(wp) ::  dir_x           !< direction of agent (x)
558       REAL(wp) ::  dir_y           !< direction of agent (y)
559!       REAL(wp) ::  dist_round = 3. !< distance at which agents start rounding a corner
560       REAL(wp) ::  dtit            !< distance to intermittent target
561!       REAL(wp) ::  round_fac  = 0.2 !< factor for rounding influence
562!       REAL(wp) ::  speed_round_x   !< rounding influence expressed as x speed component
563!       REAL(wp) ::  speed_round_y   !< rounding influence expressed as x speed component
564
565!
566!--    loop over all agents in the current grid box
567       DO n = 1, number_of_agents
568          path_flag = .FALSE.
569          pc = agents(n)%path_counter
570!
571!--       If no path was calculated for agent yet, do it
572          IF ( pc >= 999 ) THEN
573             CALL mas_nav_find_path(n)
574             pc = agents(n)%path_counter
575!
576!--       Check if new path must be calculated and if so, do it
577          ELSE
578!
579!--          Case one: Agent has come close enough to intermittent target.
580!--                    -> chose new int target and calculate rest of path if no
581!--                       new intermittent targets are left
582             dtit = SQRT((agents(n)%x - agents(n)%path_x(pc))**2               &
583                       + (agents(n)%y - agents(n)%path_y(pc))**2)
584             IF ( dtit < dist_to_int_target ) THEN
585                agents(n)%path_counter = agents(n)%path_counter + 1
586                pc = agents(n)%path_counter
587!
588!--             Path counter out of scope (each agent can store a maximum of 15
589!--             intermittent targets on the way to her final target); new path
590!--             must be calculated
591                IF ( pc >= SIZE(agents(n)%path_x) ) THEN
592                   path_flag = .TRUE.
593                ENDIF
594!
595!--          Case two: Agent too far from path
596!--                    -> set flag for new path to be calculated
597             ELSEIF ( dist_point_to_edge(agents(n)%path_x(pc-1),               &
598                                         agents(n)%path_y(pc-1),               &
599                                         agents(n)%path_x(pc),                 &
600                                         agents(n)%path_y(pc),                 &
601                                         agents(n)%x, agents(n)%y)             &
602                      > max_dist_from_path )                                   &
603             THEN
604                path_flag = .TRUE.
605             ENDIF
606!
607!--          If either of the above two cases was true, calculate new path and
608!--          reset 0th path point. This point (the last target the agent had)
609!--          is needed for the agents rounding of corners and the calculation
610!--          of her deviation from her current path
611             IF ( path_flag ) THEN
612                CALL mas_nav_find_path(n)
613                pc = agents(n)%path_counter
614             ENDIF
615          ENDIF
616!
617!--       Normalize direction vector
618          abs_dir             = 1.0d-12
619          dir_x               = agents(n)%path_x(pc) - agents(n)%x
620          dir_y               = agents(n)%path_y(pc) - agents(n)%y
621          abs_dir             = SQRT(dir_x**2 + dir_y**2)+1.0d-12
622!--         needed later for corner rounding
623!           dir_x               = dir_x/abs_dir
624!           dir_y               = dir_y/abs_dir
625!           dir_x               = dir_x + speed_round_x
626!           dir_y               = dir_y + speed_round_y
627!           abs_dir             = SQRT(dir_x**2 + dir_y**2)+1.0d-12
628          agents(n)%speed_e_x = dir_x/abs_dir
629          agents(n)%speed_e_y = dir_y/abs_dir
630       ENDDO
631
632!
633!-- corner rounding; to be added
634!
635!--       Calculate direction change due to rounding of corners
636
637!           speed_round_x = 0.
638!           speed_round_y = 0.
639!           
640!           d_curr_target = SQRT( (agents(n)%path_x(pc) - agents(n)%x)**2 +      &
641!                                 (agents(n)%path_y(pc) - agents(n)%y)**2 )
642!           d_prev_target = SQRT( (agents(n)%path_x(pc-1) - agents(n)%x)**2 +    &
643!                                 (agents(n)%path_y(pc-1) - agents(n)%y)**2 )
644! !
645! !--       Agent is close to next target and that target is not the final one
646!           IF ( d_curr_target < dist_round .AND. dist_round <                   &
647!                           SQRT( (agents(n)%path_x(pc) - agents(n)%t_x)**2 +    &
648!                                 (agents(n)%path_y(pc) - agents(n)%t_y)**2 ) )  &
649!           THEN
650!              speed_round_x = (agents(n)%path_x(pc+1) - agents(n)%path_x(pc)) / &
651!                              ABS( agents(n)%path_x(pc)                         &
652!                                 - agents(n)%path_x(pc+1)) * round_fac *        &
653!                              SIN( pi/dist_round*d_curr_target )
654!              speed_round_y = (agents(n)%path_y(pc+1) - agents(n)%path_y(pc)) / &
655!                              ABS( agents(n)%path_y(pc)                         &
656!                                 - agents(n)%path_y(pc+1)) * round_fac *        &
657!                              SIN( pi/dist_round*d_curr_target )
658!           ENDIF
659!
660!           IF ( d_prev_target < dist_round ) THEN
661!              IF ( agents(n)%path_x(pc) /= agents(n)%path_x(pc+1) ) THEN
662!                 speed_round_x = speed_round_x +                                   &
663!                                 (agents(n)%path_x(pc) - agents(n)%path_x(pc+1)) / &
664!                                 ABS( agents(n)%path_x(pc)                         &
665!                                    - agents(n)%path_x(pc+1)) * round_fac *        &
666!                                 SIN( pi/dist_round*d_prev_target )
667!              ENDIF
668!             
669!              IF ( agents(n)%path_y(pc) /= agents(n)%path_y(pc+1) ) THEN
670!                 speed_round_y = speed_round_y +                                   &
671!                              (agents(n)%path_y(pc) - agents(n)%path_y(pc+1)) / &
672!                              ABS( agents(n)%path_y(pc)                         &
673!                                 - agents(n)%path_y(pc+1)) * round_fac *        &
674!                              SIN( pi/dist_round*d_prev_target )
675!              ENDIF
676             
677!           ENDIF
678
679
680    END SUBROUTINE mas_agent_direction
681
682!------------------------------------------------------------------------------!
683! Description:
684! ------------
685!> Boundary conditions for maximum time, target reached and out of domain
686!------------------------------------------------------------------------------!
687    SUBROUTINE mas_boundary_conds( location )
688
689       IMPLICIT NONE
690
691       CHARACTER (LEN=*) ::  location !< Identifier
692
693       INTEGER(iwp) ::  n   !< agent number
694       INTEGER(iwp) ::  grp !< agent group
695
696       REAL(wp) ::  dist_to_target !< distance to target
697
698       IF ( location == 'max_sim_time' )  THEN
699
700!
701!--       Delete agents that have been simulated longer than allowed
702          DO  n = 1, number_of_agents
703
704             IF ( agents(n)%age > agent_maximum_age  .AND.                     &
705                  agents(n)%agent_mask )                                       &
706             THEN
707                agents(n)%agent_mask  = .FALSE.
708                deleted_agents = deleted_agents + 1
709             ENDIF
710
711          ENDDO
712       ENDIF
713
714       IF ( location == 'target_area' )  THEN
715
716!
717!--       Delete agents that entered target region
718          DO  n = 1, number_of_agents
719             grp = agents(n)%group
720             dist_to_target = SQRT((agents(n)%x-at_x(grp))**2                  &
721                                 + (agents(n)%y-at_y(grp))**2)
722             IF ( dist_to_target < dist_target_reached ) THEN
723                agents(n)%agent_mask  = .FALSE.
724                deleted_agents = deleted_agents + 1
725             ENDIF
726
727          ENDDO
728       ENDIF
729
730    END SUBROUTINE mas_boundary_conds
731
732!------------------------------------------------------------------------------!
733! Description:
734! ------------
735!> Release new agents at their respective sources
736!------------------------------------------------------------------------------!
737    SUBROUTINE mas_create_agent (phase)
738
739       IMPLICIT  NONE
740
741       INTEGER(iwp) ::  alloc_size  !< relative increase of allocated memory for agents
742       INTEGER(iwp) ::  i           !< loop variable ( agent groups )
743       INTEGER(iwp) ::  ip          !< index variable along x
744       INTEGER(iwp) ::  jp          !< index variable along y
745       INTEGER(iwp) ::  loop_stride !< loop variable for initialization
746       INTEGER(iwp) ::  n           !< loop variable ( number of agents )
747       INTEGER(iwp) ::  new_size    !< new size of allocated memory for agents
748       INTEGER(iwp) ::  rn_side     !< index of agent path
749
750       INTEGER(iwp), INTENT(IN) ::  phase       !< mode of inititialization
751
752       INTEGER(iwp), DIMENSION(nysg:nyng,nxlg:nxrg) ::  local_count !< start address of new agent
753       INTEGER(iwp), DIMENSION(nysg:nyng,nxlg:nxrg) ::  local_start !< start address of new agent
754
755       LOGICAL ::  first_stride !< flag for initialization
756
757       REAL(wp) ::  pos_x       !< increment for agent position in x
758       REAL(wp) ::  pos_y       !< increment for agent position in y
759       REAL(wp) ::  rand_contr  !< dummy argument for random position
760       REAL(wp) ::  rn_side_dum !< index of agent path
761
762       TYPE(agent_type),TARGET ::  tmp_agent !< temporary agent used for initialization
763
764!
765!--    Calculate agent positions and store agent attributes, if
766!--    agent is situated on this PE
767       DO  loop_stride = 1, 2
768          first_stride = (loop_stride == 1)
769          IF ( first_stride )   THEN
770             local_count = 0           ! count number of agents
771          ELSE
772             local_count = agt_count   ! Start address of new agents
773          ENDIF
774
775          DO  i = 1, number_of_agent_groups
776
777             pos_y = ass(i)
778
779             DO WHILE ( pos_y <= asn(i) )
780
781                IF ( pos_y >= nys * dy  .AND.                                  &
782                           pos_y <  ( nyn + 1 ) * dy  )                        &
783                THEN
784
785                   pos_x = asl(i)
786
787            xloop: DO WHILE ( pos_x <= asr(i) )
788
789                      IF ( pos_x >= nxl * dx  .AND.                            &
790                                 pos_x <  ( nxr + 1) * dx )                    &
791                      THEN
792
793                         tmp_agent%agent_mask = .TRUE.
794                         tmp_agent%group         = i
795                         tmp_agent%id            = 0_idp
796                         tmp_agent%block_nr      = -1
797                         tmp_agent%path_counter  = 999 !SIZE(tmp_agent%path_x)
798                         tmp_agent%age           = 0.0_wp
799                         tmp_agent%age_m         = 0.0_wp
800                         tmp_agent%dt_sum        = 0.0_wp
801                         tmp_agent%clo           = 99999.0_wp
802                         tmp_agent%energy_storage= 0.0_wp
803                         tmp_agent%force_x       = 0.0_wp
804                         tmp_agent%force_y       = 0.0_wp
805                         tmp_agent%origin_x      = pos_x
806                         tmp_agent%origin_y      = pos_y
807                         tmp_agent%speed_abs     = 0.0_wp
808                         tmp_agent%speed_e_x     = 0.0_wp
809                         tmp_agent%speed_e_y     = 0.0_wp
810                         tmp_agent%speed_des     = random_normal(desired_speed,&
811                                                                 des_sp_sig)
812                         tmp_agent%speed_x       = 0.0_wp
813                         tmp_agent%speed_y       = 0.0_wp
814                         tmp_agent%thermal_index = 99999.0_wp
815                         tmp_agent%x             = pos_x
816                         tmp_agent%y             = pos_y
817                         tmp_agent%path_x        = -1.0_wp
818                         tmp_agent%path_y        = -1.0_wp
819                         tmp_agent%t_x           = - pi
820                         tmp_agent%t_y           = - pi
821!
822!--                      Determine the grid indices of the agent position
823                         ip = tmp_agent%x * ddx
824                         jp = tmp_agent%y * ddy
825!
826!--                      Give each agent its target
827                         IF ( a_rand_target(i) ) THEN
828!
829!--                         Agent shall receive random target just outside
830!--                         simulated area
831                            rn_side_dum = random_function(iran_agent)
832                            rn_side     = FLOOR(4.*rn_side_dum)
833                            IF ( rn_side < 2 ) THEN
834                               IF ( rn_side == 0 ) THEN
835                                  tmp_agent%t_y = -2*dy
836                               ELSE
837                                  tmp_agent%t_y = (ny+3)*dy
838                               ENDIF
839                               tmp_agent%t_x = random_function(iran_agent) *   &
840                                               (nx+1)*dx
841                            ELSE
842                               IF ( rn_side == 2 ) THEN
843                                  tmp_agent%t_x = -2*dx
844                               ELSE
845                                  tmp_agent%t_x = (nx+3)*dx
846                               ENDIF
847                               tmp_agent%t_y = random_function(iran_agent) *   &
848                                               (ny+1)*dy
849                            ENDIF
850!
851!--                      Agent gets target of her group
852                         ELSE
853                            tmp_agent%t_x = at_x(i)
854                            tmp_agent%t_y = at_y(i)
855                         ENDIF
856
857                         local_count(jp,ip) = local_count(jp,ip) + 1
858
859                         IF ( .NOT. first_stride )  THEN
860                            grid_agents(jp,ip)%agents(local_count(jp,ip))      &
861                                              = tmp_agent
862                         ENDIF
863
864                      ENDIF
865
866                      pos_x = pos_x + adx(i)
867
868                   ENDDO xloop
869
870                ENDIF
871
872                pos_y = pos_y + ady(i)
873
874             ENDDO
875
876          ENDDO
877
878!
879!--       Allocate or reallocate agents array to new size
880          IF ( first_stride )  THEN
881             DO  ip = nxlg, nxrg
882                DO  jp = nysg, nyng
883                   IF ( phase == PHASE_INIT )  THEN
884                      IF ( local_count(jp,ip) > 0 )  THEN
885                         alloc_size = MAX( INT( local_count(jp,ip) *           &
886                            ( 1.0_wp + alloc_factor_mas / 100.0_wp ) ),        &
887                            min_nr_agent )
888                      ELSE
889                         alloc_size = min_nr_agent
890                      ENDIF
891                      ALLOCATE(grid_agents(jp,ip)%agents(1:alloc_size))
892                      DO  n = 1, alloc_size
893                         grid_agents(jp,ip)%agents(n) = zero_agent
894                      ENDDO
895                   ELSEIF ( phase == PHASE_RELEASE )  THEN
896                      IF ( local_count(jp,ip) > 0 )  THEN
897                         new_size   = local_count(jp,ip) + agt_count(jp,ip)
898                         alloc_size = MAX( INT( new_size * ( 1.0_wp +          &
899                            alloc_factor_mas / 100.0_wp ) ), min_nr_agent )
900                         IF( alloc_size > SIZE( grid_agents(jp,ip)%agents) )   &
901                         THEN
902                            CALL mas_eh_realloc_agents_array(ip,jp,alloc_size)
903                         ENDIF
904                      ENDIF
905                   ENDIF
906                ENDDO
907             ENDDO
908          ENDIF
909
910       ENDDO
911
912       local_start = agt_count+1
913       agt_count   = local_count
914
915!
916!--    Calculate agent IDs
917       DO  ip = nxl, nxr
918          DO  jp = nys, nyn
919             number_of_agents = agt_count(jp,ip)
920             IF ( number_of_agents <= 0 )  CYCLE
921             agents => grid_agents(jp,ip)%agents(1:number_of_agents)
922
923             DO  n = local_start(jp,ip), number_of_agents  !only new agents
924
925                agents(n)%id = 10000_idp**2 * grid_agents(jp,ip)%id_counter +  &
926                               10000_idp * jp + ip
927!
928!--             Count the number of agents that have been released before
929                grid_agents(jp,ip)%id_counter = grid_agents(jp,ip)%id_counter  &
930                                                + 1
931
932             ENDDO
933
934          ENDDO
935       ENDDO
936
937!
938!--    Add random fluctuation to agent positions.
939       IF ( random_start_position_agents )  THEN
940          DO  ip = nxl, nxr
941             DO  jp = nys, nyn
942                number_of_agents = agt_count(jp,ip)
943                IF ( number_of_agents <= 0 )  CYCLE
944                agents => grid_agents(jp,ip)%agents(1:number_of_agents)
945!
946!--             Move only new agents. Moreover, limit random fluctuation
947!--             in order to prevent that agents move more than one grid box,
948!--             which would lead to problems concerning agent exchange
949!--             between processors in case adx/ady are larger than dx/dy,
950!--             respectively. 
951                DO  n = local_start(jp,ip), number_of_agents
952                   IF ( asl(agents(n)%group) /= asr(agents(n)%group) )  THEN
953                      rand_contr = ( random_function( iran_agent ) - 0.5_wp ) *&
954                                     adx(agents(n)%group)
955                      agents(n)%x = agents(n)%x +                        &
956                              MERGE( rand_contr, SIGN( dx, rand_contr ),       &
957                                     ABS( rand_contr ) < dx                    &
958                                   ) 
959                   ENDIF
960                   IF ( ass(agents(n)%group) /= asn(agents(n)%group) )  THEN
961                      rand_contr = ( random_function( iran_agent ) - 0.5_wp ) *&
962                                     ady(agents(n)%group)
963                      agents(n)%y = agents(n)%y +                        &
964                              MERGE( rand_contr, SIGN( dy, rand_contr ),       &
965                                     ABS( rand_contr ) < dy )
966                   ENDIF
967                ENDDO
968!
969!--             Delete agents that have been simulated longer than allowed
970                CALL mas_boundary_conds( 'max_sim_time' )
971!
972!--             Delete agents that have reached target area
973                CALL mas_boundary_conds( 'target_area' )
974
975             ENDDO
976          ENDDO
977!
978!--       Exchange agents between grid cells and processors
979          CALL mas_eh_move_agent
980          CALL mas_eh_exchange_horiz
981
982       ENDIF
983!
984!--    In case of random_start_position_agents, delete agents identified by
985!--    mas_eh_exchange_horiz and mas_boundary_conds. Then sort agents into
986!--    blocks, which is needed for a fast interpolation of the LES fields
987!--    on the agent position.
988       CALL mas_ps_sort_in_subboxes
989
990!
991!--    Determine the current number of agents
992       number_of_agents = 0
993       DO  ip = nxl, nxr
994          DO  jp = nys, nyn
995             number_of_agents = number_of_agents + agt_count(jp,ip)
996          ENDDO
997       ENDDO
998!
999!--    Calculate the number of agents of the total domain
1000#if defined( __parallel )
1001       IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
1002       CALL MPI_ALLREDUCE( number_of_agents, total_number_of_agents, 1, &
1003       MPI_INTEGER, MPI_SUM, comm2d, ierr )
1004#else
1005       total_number_of_agents = number_of_agents
1006#endif
1007
1008       RETURN
1009
1010    END SUBROUTINE mas_create_agent
1011
1012!------------------------------------------------------------------------------!
1013! Description:
1014! ------------
1015!> Creates flags that indicate if a gridbox contains edges or corners. These
1016!> flags are used for agents to check if obstacles are close to them.
1017!------------------------------------------------------------------------------!
1018    SUBROUTINE mas_create_obstacle_flags
1019
1020       USE arrays_3d,                                                          &
1021           ONLY:  zw
1022
1023       IMPLICIT NONE
1024
1025       INTEGER(iwp) ::  il
1026       INTEGER(iwp) ::  jl
1027
1028       ALLOCATE(obstacle_flags(nysg:nyng,nxlg:nxrg))
1029
1030       obstacle_flags = 0
1031
1032       DO il = nxlg, nxrg
1033          DO jl = nysg, nyng
1034!
1035!--          Exclude cyclic topography boundary
1036             IF ( il < 0 .OR. il > nx .OR. jl < 0 .OR. jl > ny ) CYCLE
1037!
1038!--          North edge
1039             IF ( jl < nyng ) THEN
1040                IF ( ( top_top_s(jl,il) - top_top_s(jl+1,il) ) > 1 .AND.       &
1041                     ( zw( top_top_w(jl,il) ) -                                &
1042                       zw( top_top_w(jl+1,il) ) ) > .51_wp )                   &
1043                THEN
1044                   obstacle_flags(jl,il) = IBSET( obstacle_flags(jl,il), 0 )
1045                ENDIF
1046             ENDIF
1047!
1048!--          North right corner
1049             IF ( jl < nyng .AND. il < nxrg ) THEN
1050                IF ( ( top_top_s(jl,il) - top_top_s(jl+1,il) )   > 1 .AND.     &
1051                     ( top_top_s(jl,il) - top_top_s(jl+1,il+1) ) > 1 .AND.     &
1052                     ( top_top_s(jl,il) - top_top_s(jl,il+1) )   > 1 .AND.     &
1053                     ( zw( top_top_w(jl,il) ) -                                &
1054                       zw( top_top_w(jl+1,il+1) ) ) > .51_wp )                 &
1055                THEN
1056                   obstacle_flags(jl,il) = IBSET( obstacle_flags(jl,il), 1 )
1057                ENDIF
1058             ENDIF
1059!
1060!--          Right edge
1061             IF ( il < nxrg ) THEN
1062                IF ( ( top_top_s(jl,il) - top_top_s(jl,il+1) ) > 1 .AND.       &
1063                     ( zw( top_top_w(jl,il) ) -                                &
1064                       zw( top_top_w(jl,il+1) ) ) > .51_wp )                   &
1065                THEN
1066                   obstacle_flags(jl,il) = IBSET( obstacle_flags(jl,il), 2 )
1067                ENDIF
1068             ENDIF
1069!
1070!--          South right corner
1071             IF ( jl > nysg .AND. il < nxrg ) THEN
1072                IF ( ( top_top_s(jl,il) - top_top_s(jl,il+1) )   > 1 .AND.     &
1073                     ( top_top_s(jl,il) - top_top_s(jl-1,il+1) ) > 1 .AND.     &
1074                     ( top_top_s(jl,il) - top_top_s(jl-1,il) )   > 1 .AND.     &
1075                     ( zw(top_top_w(jl,il)) -                                  &
1076                       zw( top_top_w(jl-1,il+1) ) ) > .51_wp )                 &
1077                THEN
1078                   obstacle_flags(jl,il) = IBSET( obstacle_flags(jl,il), 3 )
1079                ENDIF
1080             ENDIF
1081!
1082!--          South edge
1083             IF ( jl > nysg ) THEN
1084                IF ( ( top_top_s(jl,il) - top_top_s(jl-1,il) ) > 1 .AND.       &
1085                     ( zw( top_top_w(jl,il) ) -                                &
1086                       zw( top_top_w(jl-1,il) ) ) > .51_wp )                   &
1087                THEN
1088                   obstacle_flags(jl,il) = IBSET( obstacle_flags(jl,il), 4 )
1089                ENDIF
1090             ENDIF
1091!
1092!--          South left corner
1093             IF ( jl > nysg .AND. il > nxlg ) THEN
1094                IF ( ( top_top_s(jl,il) - top_top_s(jl-1,il) )   > 1 .AND.     &
1095                     ( top_top_s(jl,il) - top_top_s(jl-1,il-1) ) > 1 .AND.     &
1096                     ( top_top_s(jl,il) - top_top_s(jl,il-1) )   > 1 .AND.     &
1097                     ( zw( top_top_w(jl,il) ) -                                &
1098                       zw(top_top_w(jl-1,il-1) ) ) > .51_wp )                  &
1099                THEN
1100                   obstacle_flags(jl,il) = IBSET( obstacle_flags(jl,il), 5 )
1101                ENDIF
1102             ENDIF
1103!
1104!--          Left edge
1105             IF ( il > nxlg ) THEN
1106                IF ( ( top_top_s(jl,il) - top_top_s(jl,il-1) ) > 1 .AND.       &
1107                     ( zw(top_top_w(jl,il) ) -                                 &
1108                       zw(top_top_w(jl,il-1) ) ) > .51_wp )                 &
1109                THEN
1110                   obstacle_flags(jl,il) = IBSET( obstacle_flags(jl,il), 6 )
1111                ENDIF
1112             ENDIF
1113!
1114!--          North left corner
1115             IF ( jl < nyng .AND. il > nxlg ) THEN
1116                IF ( ( top_top_s(jl,il) - top_top_s(jl,il-1) )   > 1 .AND.     &
1117                     ( top_top_s(jl,il) - top_top_s(jl+1,il-1) ) > 1 .AND.     &
1118                     ( top_top_s(jl,il) - top_top_s(jl+1,il) )   > 1 .AND.     &
1119                     ( zw( top_top_w(jl,il) ) -                                &
1120                       zw( top_top_w(jl+1,il-1) ) ) > .51_wp )                 &
1121                THEN
1122                   obstacle_flags(jl,il) = IBSET( obstacle_flags(jl,il), 7 )
1123                ENDIF
1124             ENDIF
1125
1126          ENDDO
1127       ENDDO
1128
1129    END SUBROUTINE mas_create_obstacle_flags
1130
1131!------------------------------------------------------------------------------!
1132! Description:
1133! ------------
1134!> Write agent data in netCDF format
1135!------------------------------------------------------------------------------!
1136    SUBROUTINE mas_data_output_agents( ftest )
1137
1138       USE control_parameters,                                                 &
1139           ONLY:  agt_time_count, end_time, message_string,                    &
1140                  multi_agent_system_end, multi_agent_system_start
1141
1142       USE netcdf_interface,                                                   &
1143           ONLY:  nc_stat, id_set_agt, id_var_time_agt,        &
1144                  id_var_agt, netcdf_handle_error
1145
1146       USE pegrid
1147
1148#if defined( __netcdf )
1149       USE NETCDF
1150#endif
1151       USE mas_global_attributes,                                              &
1152           ONLY:  dim_size_agtnum
1153
1154       IMPLICIT NONE
1155
1156       INTEGER(iwp) ::  agt_size !< Agent size in bytes
1157       INTEGER(iwp) ::  dummy    !< dummy
1158       INTEGER(iwp) ::  ii       !< counter (x)
1159       INTEGER(iwp) ::  ip       !< counter (x)
1160       INTEGER(iwp) ::  jp       !< counter (y)
1161       INTEGER(iwp) ::  n        !< counter (number of PEs)
1162       INTEGER(iwp) ::  noa      !< number of agents
1163       INTEGER(iwp) ::  noa_rcv  !< received number of agents
1164       INTEGER(iwp) ::  out_noa  !< number of agents for output
1165
1166       INTEGER(iwp), DIMENSION(0:numprocs-1) ::  noa_arr !< number of agents on each PE
1167
1168       TYPE(agent_type), DIMENSION(:), ALLOCATABLE, TARGET ::  trf_agents !< all agents on current PE
1169       TYPE(agent_type), DIMENSION(:), ALLOCATABLE, TARGET ::  out_agents !< all agents in entire domain
1170
1171       LOGICAL, INTENT (INOUT) :: ftest
1172
1173       LOGICAL, SAVE :: agt_dimension_exceeded = .FALSE.
1174
1175       CALL cpu_log( log_point_s(17), 'mas_data_output', 'start' )
1176!
1177!--    Get total number of agents and put all agents on one PE in one array
1178       noa = 0
1179       DO  ip = nxl, nxr
1180          DO  jp = nys, nyn
1181             noa  = noa  + agt_count(jp,ip)
1182          ENDDO
1183       ENDDO
1184       IF(noa > 0) THEN
1185          ALLOCATE(trf_agents(1:noa))
1186          dummy = 1
1187          DO  ip = nxl, nxr
1188             DO  jp = nys, nyn
1189                IF ( agt_count(jp,ip) == 0 ) CYCLE
1190                agents => grid_agents(jp,ip)%agents(1:agt_count(jp,ip))
1191                trf_agents(dummy:(dummy-1+agt_count(jp,ip))) = agents
1192                dummy = dummy + agt_count(jp,ip)
1193             ENDDO
1194          ENDDO
1195       ENDIF
1196#if defined( __parallel )
1197!
1198!--    Gather all agents on PE0 for output
1199       IF ( myid == 0 )  THEN
1200          noa_arr(0) = noa
1201!
1202!--       Receive data from all other PEs.
1203          DO  n = 1, numprocs-1
1204              CALL MPI_RECV( noa_arr(n), 1, MPI_INTEGER,                       &
1205                              n, 0, comm2d, status, ierr )
1206          ENDDO
1207       ELSE
1208          CALL MPI_SEND( noa, 1, MPI_INTEGER, 0, 0, comm2d, ierr )
1209       ENDIF
1210       CALL MPI_BARRIER( comm2d, ierr )
1211       agt_size = STORAGE_SIZE(zero_agent)/8
1212       IF ( myid == 0 )  THEN
1213!
1214!--       Receive data from all other PEs.
1215          out_noa = SUM(noa_arr)
1216          IF ( out_noa > 0 ) THEN
1217             ALLOCATE( out_agents(1:out_noa) )
1218             IF ( noa > 0 ) THEN
1219                out_agents(1:noa) = trf_agents
1220             ENDIF
1221             noa_rcv = noa
1222             DO n = 1, numprocs-1
1223                IF ( noa_arr(n) > 0 ) THEN
1224                   CALL MPI_RECV( out_agents(noa_rcv+1), noa_arr(n)*agt_size,  &
1225                                  MPI_BYTE, n, 0, comm2d, status, ierr )
1226                   noa_rcv = noa_rcv + noa_arr(n)
1227                ENDIF
1228             ENDDO
1229          ELSE
1230             ALLOCATE( out_agents(1:2) )
1231             out_agents = zero_agent
1232             out_noa    = 2
1233          ENDIF
1234       ELSE
1235          IF ( noa > 0 ) THEN
1236             CALL MPI_SEND( trf_agents(1), noa*agt_size, MPI_BYTE, 0, 0,       &
1237                                        comm2d, ierr )
1238          ENDIF
1239       ENDIF
1240!
1241!--    A barrier has to be set, because otherwise some PEs may
1242!--    proceed too fast so that PE0 may receive wrong data on
1243!--    tag 0
1244       CALL MPI_BARRIER( comm2d, ierr )
1245#endif
1246       IF ( myid == 0 ) THEN
1247#if defined( __parallel )
1248          agents => out_agents
1249#else
1250          agents => trf_agents
1251#endif
1252
1253#if defined( __netcdf )
1254!
1255!--       Update maximum number of agents
1256          maximum_number_of_agents = MAX(maximum_number_of_agents, out_noa)
1257!
1258!--       Output in netCDF format
1259          IF ( ftest ) THEN
1260!
1261!--          First, define size of agent number dimension from amount of agents
1262!--          released, release interval, time of agent simulation and max
1263!--          age of agents
1264             dim_size_agtnum = MIN( MIN( multi_agent_system_end, end_time )    &
1265                                       - multi_agent_system_start,             &
1266                                    agent_maximum_age)
1267
1268             DO ii = 1, number_of_agent_groups
1269                dim_size_agtnum = dim_size_agtnum                              &
1270                                + (FLOOR( ( asr(ii)-asl(ii) ) / adx(ii) ) + 1) &
1271                                * (FLOOR( ( asn(ii)-ass(ii) ) / ady(ii) ) + 1) &
1272                                * (FLOOR( dim_size_agtnum / dt_arel )     + 1) &
1273                                * dim_size_factor_agtnum
1274                dim_size_agtnum = MIN( dim_size_agtnum, dim_size_agtnum_manual )
1275             ENDDO
1276             CALL check_open( 118 )
1277          ENDIF
1278
1279!
1280!--       Update the NetCDF time axis
1281          agt_time_count = agt_time_count + 1
1282
1283          IF ( .NOT. agt_dimension_exceeded ) THEN
1284!
1285!--          if number of agents to be output exceeds dimension, set flag and
1286!--          print warning
1287             IF ( out_noa > dim_size_agtnum ) THEN
1288
1289                agt_dimension_exceeded = .TRUE.
1290                WRITE(message_string,'(A,F11.1,2(A,I8))')                      &
1291                                'Number of agents exceeds agent dimension.' // &
1292                                '&Starting at time_since_reference_point = ',  &
1293                                time_since_reference_point,                    &
1294                                ' s, &data may be missing.'//                  &
1295                                '&Number of agents:     ', out_noa,            &
1296                                '&Agent dimension size: ', dim_size_agtnum
1297
1298                CALL message( 'mas_data_output_agents',                        &
1299                              'PA0420', 0, 1, 0, 6, 0 )
1300
1301             ENDIF
1302          ENDIF
1303
1304!
1305!--       reduce number of output agents to dimension size, if necessary
1306          IF ( agt_dimension_exceeded ) THEN
1307
1308             out_noa = MIN( out_noa, dim_size_agtnum )
1309
1310          ENDIF
1311
1312          nc_stat = NF90_PUT_VAR( id_set_agt, id_var_time_agt,                 &
1313                                  (/ time_since_reference_point /),            &
1314                                  start = (/ agt_time_count /),                &
1315                                  count = (/ 1 /) )
1316          CALL netcdf_handle_error( 'mas_data_output_agents', 1 )
1317
1318!
1319!--       Output agent attributes
1320
1321          nc_stat = NF90_PUT_VAR( id_set_agt, id_var_agt(1), agents%id,        &
1322                                  start = (/ 1, agt_time_count /),             &
1323                                  count = (/ out_noa /) )
1324          CALL netcdf_handle_error( 'mas_data_output_agents', 2 )
1325 
1326          nc_stat = NF90_PUT_VAR( id_set_agt, id_var_agt(2), agents%x,         &
1327                                  start = (/ 1, agt_time_count /),             &
1328                                  count = (/ out_noa /) )
1329          CALL netcdf_handle_error( 'mas_data_output_agents', 3 )
1330
1331          nc_stat = NF90_PUT_VAR( id_set_agt, id_var_agt(3), agents%y,         &
1332                                  start = (/ 1, agt_time_count /),             &
1333                                  count = (/ out_noa /) )
1334          CALL netcdf_handle_error( 'mas_data_output_agents', 4 )
1335
1336          nc_stat = NF90_PUT_VAR( id_set_agt, id_var_agt(4), agents%windspeed, &
1337                                  start = (/ 1, agt_time_count /),             &
1338                                  count = (/ out_noa /) )
1339          CALL netcdf_handle_error( 'mas_data_output_agents', 5 )
1340
1341          nc_stat = NF90_PUT_VAR( id_set_agt, id_var_agt(5), agents%t,         &
1342                                  start = (/ 1, agt_time_count /),             &
1343                                  count = (/ out_noa /) )
1344          CALL netcdf_handle_error( 'mas_data_output_agents', 6 )
1345
1346          nc_stat = NF90_PUT_VAR( id_set_agt, id_var_agt(6), agents%group,     &
1347                                  start = (/ 1, agt_time_count /),             &
1348                                  count = (/ out_noa /) )
1349          CALL netcdf_handle_error( 'mas_data_output_agents', 7 )
1350          CALL cpu_log( log_point_s(17), 'mas_data_output', 'stop' )
1351
1352
1353!           nc_stat = NF90_PUT_VAR( id_set_agt, id_var_agt(6), agents%pm10,      &
1354!                                   start = (/ 1, agt_time_count /),             &
1355!                                   count = (/ out_noa /) )
1356!           CALL netcdf_handle_error( 'mas_data_output_agents', 8 )
1357!
1358!           nc_stat = NF90_PUT_VAR( id_set_agt, id_var_agt(7), agents%pm25,      &
1359!                                   start = (/ 1, agt_time_count /),             &
1360!                                   count = (/ out_noa /) )
1361!           CALL netcdf_handle_error( 'mas_data_output_agents', 9 )
1362!
1363!           nc_stat = NF90_PUT_VAR( id_set_agt, id_var_agt(8), agents%therm_comf,&
1364!                                   start = (/ 1, agt_time_count /),             &
1365!                                   count = (/ out_noa /) )
1366!
1367!           nc_stat = NF90_PUT_VAR( id_set_agt, id_var_agt(9), agents%uv,        &
1368!                                   start = (/ 1, agt_time_count /),             &
1369!                                   count = (/ out_noa /) )
1370!           CALL netcdf_handle_error( 'mas_data_output_agents', 10 )
1371
1372#endif
1373          agents => NULL()
1374#if defined( __parallel )
1375          IF ( ALLOCATED( out_agents ) ) DEALLOCATE( out_agents )
1376#endif
1377       ELSE
1378          CALL cpu_log( log_point_s(17), 'mas_data_output', 'stop' )
1379       ENDIF
1380
1381       IF ( ALLOCATED( trf_agents ) ) DEALLOCATE( trf_agents )
1382
1383    END SUBROUTINE mas_data_output_agents
1384
1385!------------------------------------------------------------------------------!
1386! Description:
1387! ------------
1388!> If an agent moves from one processor to another, this subroutine moves
1389!> the corresponding elements from the agent arrays of the old grid cells
1390!> to the agent arrays of the new grid cells.
1391!------------------------------------------------------------------------------!
1392    SUBROUTINE mas_eh_add_agents_to_gridcell (agent_array)
1393
1394       IMPLICIT NONE
1395
1396       INTEGER(iwp) ::  aindex !< dummy argument for new number of agents per grid box
1397       INTEGER(iwp) ::  ip     !< grid index (x) of agent
1398       INTEGER(iwp) ::  jp     !< grid index (x) of agent
1399       INTEGER(iwp) ::  n      !< index variable of agent
1400
1401       LOGICAL ::  pack_done !< flag to indicate that packing is done
1402
1403       TYPE(agent_type), DIMENSION(:), INTENT(IN)  ::  agent_array !< new agents in a grid box
1404       TYPE(agent_type), DIMENSION(:), ALLOCATABLE ::  temp_ns     !< temporary agent array for reallocation
1405
1406       pack_done     = .FALSE.
1407
1408       DO n = 1, SIZE(agent_array)
1409
1410          IF ( .NOT. agent_array(n)%agent_mask )  CYCLE
1411
1412          ip = agent_array(n)%x * ddx
1413          jp = agent_array(n)%y * ddy
1414
1415          IF ( ip >= nxl  .AND.  ip <= nxr  .AND.                              &
1416               jp >= nys  .AND.  jp <= nyn )  &
1417          THEN ! agent stays on processor
1418             number_of_agents = agt_count(jp,ip)
1419             agents => grid_agents(jp,ip)%agents(1:number_of_agents)
1420
1421             aindex = agt_count(jp,ip)+1
1422             IF( aindex > SIZE(grid_agents(jp,ip)%agents) )  THEN
1423                IF ( pack_done )  THEN
1424                   CALL mas_eh_realloc_agents_array (ip,jp)
1425                ELSE
1426                   CALL mas_ps_pack
1427                   agt_count(jp,ip) = number_of_agents
1428                   aindex = agt_count(jp,ip)+1
1429                   IF ( aindex > SIZE(grid_agents(jp,ip)%agents) )  THEN
1430                      CALL mas_eh_realloc_agents_array (ip,jp)
1431                   ENDIF
1432                   pack_done = .TRUE.
1433                ENDIF
1434             ENDIF
1435             grid_agents(jp,ip)%agents(aindex) = agent_array(n)
1436             agt_count(jp,ip) = aindex
1437          ELSE
1438             IF ( jp <= nys - 1 )  THEN
1439                nr_move_south = nr_move_south+1
1440!
1441!--             Before agent information is swapped to exchange-array, check
1442!--             if enough memory is allocated. If required, reallocate exchange
1443!--             array.
1444                IF ( nr_move_south > SIZE(move_also_south) )  THEN
1445!
1446!--                At first, allocate further temporary array to swap agent
1447!--                information.
1448                   ALLOCATE( temp_ns(SIZE(move_also_south)+NR_2_direction_move))
1449                   temp_ns(1:nr_move_south-1) = move_also_south                &
1450                                                (1:nr_move_south-1)
1451                   DEALLOCATE( move_also_south )
1452                   ALLOCATE( move_also_south(SIZE(temp_ns)) )
1453                   move_also_south(1:nr_move_south-1) = temp_ns                &
1454                                                        (1:nr_move_south-1)
1455                   DEALLOCATE( temp_ns )
1456
1457                ENDIF
1458
1459                move_also_south(nr_move_south) = agent_array(n)
1460
1461                IF ( jp == -1 )  THEN
1462!
1463!--                Apply boundary condition along y
1464                   IF ( ibc_mas_ns == 0 )  THEN
1465                      move_also_south(nr_move_south)%y =                       &
1466                                         move_also_south(nr_move_south)%y      &
1467                                       + ( ny + 1 ) * dy
1468                      move_also_south(nr_move_south)%origin_y =                &
1469                                       move_also_south(nr_move_south)%origin_y &
1470                                       + ( ny + 1 ) * dy
1471                   ELSEIF ( ibc_mas_ns == 1 )  THEN
1472!
1473!--                   Agent absorption
1474                      move_also_south(nr_move_south)%agent_mask = .FALSE.
1475                      deleted_agents = deleted_agents + 1
1476
1477                   ENDIF
1478                ENDIF
1479             ELSEIF ( jp >= nyn+1 )  THEN
1480                nr_move_north = nr_move_north+1
1481!
1482!--             Before agent information is swapped to exchange-array, check
1483!--             if enough memory is allocated. If required, reallocate exchange
1484!--             array.
1485                IF ( nr_move_north > SIZE(move_also_north) )  THEN
1486!
1487!--                At first, allocate further temporary array to swap agent
1488!--                information.
1489                   ALLOCATE( temp_ns(SIZE(move_also_north)+NR_2_direction_move))
1490                   temp_ns(1:nr_move_north-1) =                                &
1491                                move_also_south(1:nr_move_north-1)
1492                   DEALLOCATE( move_also_north )
1493                   ALLOCATE( move_also_north(SIZE(temp_ns)) )
1494                   move_also_north(1:nr_move_north-1) =                        &
1495                               temp_ns(1:nr_move_north-1)
1496                   DEALLOCATE( temp_ns )
1497
1498                ENDIF
1499
1500                move_also_north(nr_move_north) = agent_array(n)
1501                IF ( jp == ny+1 )  THEN
1502!
1503!--                Apply boundary condition along y
1504                   IF ( ibc_mas_ns == 0 )  THEN
1505
1506                      move_also_north(nr_move_north)%y =                       &
1507                         move_also_north(nr_move_north)%y                      &
1508                       - ( ny + 1 ) * dy
1509                      move_also_north(nr_move_north)%origin_y =                &
1510                         move_also_north(nr_move_north)%origin_y               &
1511                       - ( ny + 1 ) * dy
1512                   ELSEIF ( ibc_mas_ns == 1 )  THEN
1513!
1514!--                   Agent absorption
1515                      move_also_north(nr_move_north)%agent_mask = .FALSE.
1516                      deleted_agents = deleted_agents + 1
1517
1518                   ENDIF
1519                ENDIF
1520             ENDIF
1521          ENDIF
1522       ENDDO
1523
1524       RETURN
1525
1526    END SUBROUTINE mas_eh_add_agents_to_gridcell
1527
1528!------------------------------------------------------------------------------!
1529! Description:
1530! ------------
1531!> After ghost layer agents have been received from neighboring PEs, this
1532!> subroutine sorts them into the corresponding grid cells
1533!------------------------------------------------------------------------------!
1534    SUBROUTINE mas_eh_add_ghost_agents_to_gridcell (agent_array)
1535
1536       IMPLICIT NONE
1537
1538       INTEGER(iwp) ::  ip     !< grid index (x) of agent
1539       INTEGER(iwp) ::  jp     !< grid index (x) of agent
1540       INTEGER(iwp) ::  n      !< index variable of agent
1541       INTEGER(iwp) ::  aindex !< dummy argument for new number of agents per grid box
1542
1543       LOGICAL ::  pack_done !< flag to indicate that packing is done
1544
1545       TYPE(agent_type), DIMENSION(:), INTENT(IN)  ::  agent_array !< new agents in a grid box
1546
1547       pack_done     = .FALSE.
1548
1549       DO n = 1, SIZE(agent_array)
1550
1551          IF ( .NOT. agent_array(n)%agent_mask )  CYCLE
1552
1553          ip = agent_array(n)%x * ddx
1554          jp = agent_array(n)%y * ddy
1555
1556          IF ( ip < nxl  .OR.  ip > nxr  .OR.  jp < nys  .OR.  jp > nyn ) THEN
1557             number_of_agents = agt_count(jp,ip)
1558             agents => grid_agents(jp,ip)%agents(1:number_of_agents)
1559
1560             aindex = agt_count(jp,ip)+1
1561             IF( aindex > SIZE(grid_agents(jp,ip)%agents) )  THEN
1562                IF ( pack_done )  THEN
1563                   CALL mas_eh_realloc_agents_array (ip,jp)
1564                ELSE
1565                   CALL mas_ps_pack
1566                   agt_count(jp,ip) = number_of_agents
1567                   aindex = agt_count(jp,ip)+1
1568                   IF ( aindex > SIZE(grid_agents(jp,ip)%agents) )  THEN
1569                      CALL mas_eh_realloc_agents_array (ip,jp)
1570                   ENDIF
1571                   pack_done = .TRUE.
1572                ENDIF
1573             ENDIF
1574             grid_agents(jp,ip)%agents(aindex) = agent_array(n)
1575             agt_count(jp,ip) = aindex
1576          ENDIF
1577       ENDDO
1578    END SUBROUTINE mas_eh_add_ghost_agents_to_gridcell
1579
1580!------------------------------------------------------------------------------!
1581! Description:
1582! ------------
1583!> Resizing of agent arrays
1584!------------------------------------------------------------------------------!
1585    SUBROUTINE mas_eh_dealloc_agents_array
1586
1587       IMPLICIT NONE
1588
1589       INTEGER(iwp) ::  i         !< grid index (x) of agent
1590       INTEGER(iwp) ::  j         !< grid index (y) of agent
1591       INTEGER(iwp) ::  old_size  !< old array size
1592       INTEGER(iwp) ::  new_size  !< new array size
1593       INTEGER(iwp) ::  noa       !< number of agents
1594
1595       LOGICAL ::  dealloc  !< flag that indicates if reallocation is necessary
1596
1597       TYPE(agent_type), DIMENSION(10) ::  tmp_agents_s !< temporary static agent array
1598
1599       TYPE(agent_type), DIMENSION(:), ALLOCATABLE ::  tmp_agents_d !< temporary dynamic agent array
1600
1601       DO  i = nxlg, nxrg
1602          DO  j = nysg, nyng
1603!
1604!--          Determine number of active agents
1605             noa = agt_count(j,i)
1606!
1607!--          Determine allocated memory size
1608             old_size = SIZE( grid_agents(j,i)%agents )
1609!
1610!--          Check for large unused memory
1611             dealloc = ( ( noa < min_nr_agent .AND. old_size  > min_nr_agent ) &
1612                    .OR. ( noa > min_nr_agent .AND. old_size - noa *           &
1613                         ( 1.0_wp + 0.01_wp * alloc_factor_mas ) > 0.0_wp ) )
1614!
1615!--          If large unused memory was found, resize the corresponding array
1616             IF ( dealloc )  THEN
1617                IF ( noa < min_nr_agent )  THEN
1618                   new_size = min_nr_agent
1619                ELSE
1620                   new_size = INT( noa * ( 1.0_wp +                            &
1621                                            0.01_wp * alloc_factor_mas ) )
1622                ENDIF
1623
1624                IF ( noa <= 10 )  THEN
1625
1626                   tmp_agents_s(1:noa) = grid_agents(j,i)%agents(1:noa)
1627
1628                   DEALLOCATE(grid_agents(j,i)%agents)
1629                   ALLOCATE(grid_agents(j,i)%agents(1:new_size))
1630
1631                   grid_agents(j,i)%agents(1:noa)          = tmp_agents_s(1:noa)
1632                   grid_agents(j,i)%agents(noa+1:new_size) = zero_agent
1633
1634                ELSE
1635
1636                   ALLOCATE(tmp_agents_d(noa))
1637                   tmp_agents_d(1:noa) = grid_agents(j,i)%agents(1:noa)
1638
1639                   DEALLOCATE(grid_agents(j,i)%agents)
1640                   ALLOCATE(grid_agents(j,i)%agents(new_size))
1641
1642                   grid_agents(j,i)%agents(1:noa)          = tmp_agents_d(1:noa)
1643                   grid_agents(j,i)%agents(noa+1:new_size) = zero_agent
1644
1645                   DEALLOCATE(tmp_agents_d)
1646
1647                ENDIF
1648
1649             ENDIF
1650          ENDDO
1651       ENDDO
1652
1653    END SUBROUTINE mas_eh_dealloc_agents_array
1654
1655!------------------------------------------------------------------------------!
1656! Description:
1657! ------------
1658!> Exchange between subdomains.
1659!> As soon as one agent has moved beyond the boundary of the domain, it
1660!> is included in the relevant transfer arrays and marked for subsequent
1661!> deletion on this PE.
1662!> First sweep for crossings in x direction. Find out first the number of
1663!> agents to be transferred and allocate temporary arrays needed to store
1664!> them.
1665!> For a one-dimensional decomposition along y, no transfer is necessary,
1666!> because the agent remains on the PE, but the agent coordinate has to
1667!> be adjusted.
1668!------------------------------------------------------------------------------!
1669    SUBROUTINE mas_eh_exchange_horiz
1670
1671       IMPLICIT NONE
1672
1673       INTEGER(iwp) ::  i                !< grid index (x) of agent positition
1674       INTEGER(iwp) ::  ip               !< index variable along x
1675       INTEGER(iwp) ::  j                !< grid index (y) of agent positition
1676       INTEGER(iwp) ::  jp               !< index variable along y
1677       INTEGER(iwp) ::  n                !< agent index variable
1678       INTEGER(iwp) ::  par_size         !< Agent size in bytes
1679       INTEGER(iwp) ::  trla_count       !< number of agents send to left PE
1680       INTEGER(iwp) ::  trla_count_recv  !< number of agents receive from right PE
1681       INTEGER(iwp) ::  trna_count       !< number of agents send to north PE
1682       INTEGER(iwp) ::  trna_count_recv  !< number of agents receive from south PE
1683       INTEGER(iwp) ::  trra_count       !< number of agents send to right PE
1684       INTEGER(iwp) ::  trra_count_recv  !< number of agents receive from left PE
1685       INTEGER(iwp) ::  trsa_count       !< number of agents send to south PE
1686       INTEGER(iwp) ::  trsa_count_recv  !< number of agents receive from north PE
1687
1688       TYPE(agent_type), DIMENSION(:), ALLOCATABLE ::  rvla  !< agents received from right PE
1689       TYPE(agent_type), DIMENSION(:), ALLOCATABLE ::  rvna  !< agents received from south PE
1690       TYPE(agent_type), DIMENSION(:), ALLOCATABLE ::  rvra  !< agents received from left PE
1691       TYPE(agent_type), DIMENSION(:), ALLOCATABLE ::  rvsa  !< agents received from north PE
1692       TYPE(agent_type), DIMENSION(:), ALLOCATABLE ::  trla  !< agents send to left PE
1693       TYPE(agent_type), DIMENSION(:), ALLOCATABLE ::  trna  !< agents send to north PE
1694       TYPE(agent_type), DIMENSION(:), ALLOCATABLE ::  trra  !< agents send to right PE
1695       TYPE(agent_type), DIMENSION(:), ALLOCATABLE ::  trsa  !< agents send to south PE
1696
1697#if defined( __parallel )
1698
1699!
1700!--    Exchange between subdomains.
1701!--    As soon as one agent has moved beyond the boundary of the domain, it
1702!--    is included in the relevant transfer arrays and marked for subsequent
1703!--    deletion on this PE.
1704!--    First sweep for crossings in x direction. Find out first the number of
1705!--    agents to be transferred and allocate temporary arrays needed to store
1706!--    them.
1707!--    For a one-dimensional decomposition along y, no transfer is necessary,
1708!--    because the agent remains on the PE, but the agent coordinate has to
1709!--    be adjusted.
1710       trla_count  = 0
1711       trra_count  = 0
1712
1713       trla_count_recv   = 0
1714       trra_count_recv   = 0
1715
1716       IF ( pdims(1) /= 1 )  THEN
1717!
1718!--       First calculate the storage necessary for sending and receiving the data.
1719!--       Compute only first (nxl) and last (nxr) loop iterration.
1720          DO  ip = nxl, nxr, nxr - nxl
1721             DO  jp = nys, nyn
1722
1723                number_of_agents = agt_count(jp,ip)
1724                IF ( number_of_agents <= 0 )  CYCLE
1725                agents => grid_agents(jp,ip)%agents(1:number_of_agents)
1726                DO  n = 1, number_of_agents
1727                   IF ( agents(n)%agent_mask )  THEN
1728                      i = agents(n)%x * ddx
1729!
1730!--                   Above calculation does not work for indices less than zero
1731                      IF ( agents(n)%x < 0.0_wp )  i = -1
1732
1733                      IF ( i < nxl )  THEN
1734                         trla_count = trla_count + 1
1735                      ELSEIF ( i > nxr )  THEN
1736                         trra_count = trra_count + 1
1737                      ENDIF
1738                   ENDIF
1739                ENDDO
1740
1741             ENDDO
1742          ENDDO
1743
1744          IF ( trla_count  == 0 )  trla_count  = 1
1745          IF ( trra_count  == 0 )  trra_count  = 1
1746
1747          ALLOCATE( trla(trla_count), trra(trra_count) )
1748
1749          trla = zero_agent
1750          trra = zero_agent
1751
1752          trla_count  = 0
1753          trra_count  = 0
1754
1755       ENDIF
1756!
1757!--    Compute only first (nxl) and last (nxr) loop iterration
1758       DO  ip = nxl, nxr, nxr-nxl
1759          DO  jp = nys, nyn
1760             number_of_agents = agt_count(jp,ip)
1761             IF ( number_of_agents <= 0 ) CYCLE
1762             agents => grid_agents(jp,ip)%agents(1:number_of_agents)
1763             DO  n = 1, number_of_agents
1764!
1765!--             Only those agents that have not been marked as 'deleted' may
1766!--             be moved.
1767                IF ( agents(n)%agent_mask )  THEN
1768
1769                   i = agents(n)%x * ddx
1770!
1771!--                Above calculation does not work for indices less than zero
1772                   IF ( agents(n)%x < 0.0_wp )  i = -1
1773
1774                   IF ( i <  nxl )  THEN
1775                      IF ( i < 0 )  THEN
1776!
1777!--                      Apply boundary condition along x
1778                         IF ( ibc_mas_lr == 0 )  THEN
1779!
1780!--                         Cyclic condition
1781                            IF ( pdims(1) == 1 )  THEN
1782                               agents(n)%x        = ( nx + 1 ) * dx +          &
1783                                                    agents(n)%x
1784                               agents(n)%origin_x = ( nx + 1 ) * dx +          &
1785                                                    agents(n)%origin_x
1786                            ELSE
1787                               trla_count         = trla_count + 1
1788                               trla(trla_count)   = agents(n)
1789                               trla(trla_count)%x = ( nx + 1 ) * dx +          &
1790                                                    trla(trla_count)%x
1791                               trla(trla_count)%origin_x =                     &
1792                                                trla(trla_count)%origin_x +    &
1793                                                ( nx + 1 ) * dx
1794                               agents(n)%agent_mask  = .FALSE.
1795                               deleted_agents = deleted_agents + 1
1796
1797                               IF ( trla(trla_count)%x >=                      &
1798                                        (nx + 1)* dx - 1.0E-12_wp )            &
1799                               THEN
1800                                  trla(trla_count)%x = trla(trla_count)%x -    &
1801                                                   1.0E-10_wp
1802                                  trla(trla_count)%origin_x =                  &
1803                                                   trla(trla_count)%origin_x - 1
1804                               ENDIF
1805
1806                            ENDIF
1807
1808                         ELSEIF ( ibc_mas_lr == 1 )  THEN
1809!
1810!--                         Agent absorption
1811                            agents(n)%agent_mask = .FALSE.
1812                            deleted_agents = deleted_agents + 1
1813
1814                         ENDIF
1815                      ELSE
1816!
1817!--                      Store agent data in the transfer array, which will be
1818!--                      send to the neighbouring PE
1819                         trla_count = trla_count + 1
1820                         trla(trla_count) = agents(n)
1821                         agents(n)%agent_mask = .FALSE.
1822                         deleted_agents = deleted_agents + 1
1823
1824                      ENDIF
1825
1826                   ELSEIF ( i > nxr )  THEN
1827                      IF ( i > nx )  THEN
1828!
1829!--                      Apply boundary condition along x
1830                         IF ( ibc_mas_lr == 0 )  THEN
1831!
1832!--                         Cyclic condition
1833                            IF ( pdims(1) == 1 )  THEN
1834                               agents(n)%x = agents(n)%x - ( nx + 1 ) * dx
1835                               agents(n)%origin_x = agents(n)%origin_x - &
1836                               ( nx + 1 ) * dx
1837                            ELSE
1838                               trra_count = trra_count + 1
1839                               trra(trra_count) = agents(n)
1840                               trra(trra_count)%x = trra(trra_count)%x -       &
1841                                                    ( nx + 1 ) * dx
1842                               trra(trra_count)%origin_x =                     &
1843                                                   trra(trra_count)%origin_x - &
1844                                                   ( nx + 1 ) * dx
1845                               agents(n)%agent_mask = .FALSE.
1846                               deleted_agents = deleted_agents + 1
1847
1848                            ENDIF
1849
1850                         ELSEIF ( ibc_mas_lr == 1 )  THEN
1851!
1852!--                         Agent absorption
1853                            agents(n)%agent_mask = .FALSE.
1854                            deleted_agents = deleted_agents + 1
1855
1856                         ENDIF
1857                      ELSE
1858!
1859!--                      Store agent data in the transfer array, which will be send
1860!--                      to the neighbouring PE
1861                         trra_count = trra_count + 1
1862                         trra(trra_count) = agents(n)
1863                         agents(n)%agent_mask = .FALSE.
1864                         deleted_agents = deleted_agents + 1
1865
1866                      ENDIF
1867
1868                   ENDIF
1869                ENDIF
1870
1871             ENDDO
1872          ENDDO
1873       ENDDO
1874
1875!
1876!--    Allocate arrays required for north-south exchange, as these
1877!--    are used directly after agents are exchange along x-direction.
1878       ALLOCATE( move_also_north(1:NR_2_direction_move) )
1879       ALLOCATE( move_also_south(1:NR_2_direction_move) )
1880
1881       nr_move_north = 0
1882       nr_move_south = 0
1883!
1884!--    Send left boundary, receive right boundary (but first exchange how many
1885!--    and chec if agent storage must be extended)
1886       IF ( pdims(1) /= 1 )  THEN
1887
1888          CALL MPI_SENDRECV( trla_count,      1, MPI_INTEGER, pleft,  0, &
1889                             trra_count_recv, 1, MPI_INTEGER, pright, 0, &
1890                             comm2d, status, ierr )
1891
1892          ALLOCATE(rvra(MAX(1,trra_count_recv)))
1893!
1894!--       This MPI_SENDRECV should work even with odd mixture on 32 and 64 Bit
1895!--       variables in structure agent_type (due to the calculation of par_size)
1896          par_size = STORAGE_SIZE(trla(1))/8
1897          CALL MPI_SENDRECV( trla, max(1,trla_count)*par_size, MPI_BYTE, pleft,&
1898                    1, rvra, max(1,trra_count_recv)*par_size, MPI_BYTE, pright,&
1899                             1, comm2d, status, ierr )
1900
1901          IF ( trra_count_recv > 0 ) THEN
1902             CALL mas_eh_add_agents_to_gridcell(rvra(1:trra_count_recv))
1903          ENDIF
1904
1905          DEALLOCATE(rvra)
1906
1907!
1908!--       Send right boundary, receive left boundary
1909          CALL MPI_SENDRECV( trra_count,      1, MPI_INTEGER, pright, 0,       &
1910                             trla_count_recv, 1, MPI_INTEGER, pleft,  0,       &
1911                             comm2d, status, ierr )
1912
1913          ALLOCATE(rvla(MAX(1,trla_count_recv)))
1914!
1915!--       This MPI_SENDRECV should work even with odd mixture on 32 and 64 Bit
1916!--       variables in structure agent_type (due to the calculation of par_size)
1917          par_size = STORAGE_SIZE(trra(1))/8
1918          CALL MPI_SENDRECV( trra, max(1,trra_count)*par_size, MPI_BYTE,       &
1919                             pright, 1, rvla,                                  &
1920                             max(1,trla_count_recv)*par_size, MPI_BYTE,        &
1921                             pleft, 1, comm2d, status, ierr )
1922
1923          IF ( trla_count_recv > 0 ) THEN
1924             CALL mas_eh_add_agents_to_gridcell(rvla(1:trla_count_recv))
1925          ENDIF
1926
1927          DEALLOCATE( rvla )
1928          DEALLOCATE( trla, trra )
1929
1930       ENDIF
1931
1932!
1933!--    Check whether agents have crossed the boundaries in y direction. Note
1934!--    that this case can also apply to agents that have just been received
1935!--    from the adjacent right or left PE.
1936!--    Find out first the number of agents to be transferred and allocate
1937!--    temporary arrays needed to store them.
1938!--    For a one-dimensional decomposition along y, no transfer is necessary,
1939!--    because the agent remains on the PE.
1940       trsa_count  = nr_move_south
1941       trna_count  = nr_move_north
1942
1943       trsa_count_recv   = 0
1944       trna_count_recv   = 0
1945
1946       IF ( pdims(2) /= 1 )  THEN
1947!
1948!--       First calculate the storage necessary for sending and receiving the
1949!--       data
1950          DO  ip = nxl, nxr
1951             DO  jp = nys, nyn, nyn-nys    !compute only first (nys) and last (nyn) loop iterration
1952                number_of_agents = agt_count(jp,ip)
1953                IF ( number_of_agents <= 0 )  CYCLE
1954                agents => grid_agents(jp,ip)%agents(1:number_of_agents)
1955                DO  n = 1, number_of_agents
1956                   IF ( agents(n)%agent_mask )  THEN
1957                      j = agents(n)%y * ddy
1958!
1959!--                   Above calculation does not work for indices less than zero
1960                      IF ( agents(n)%y < 0.0_wp )  j = -1
1961
1962                      IF ( j < nys )  THEN
1963                         trsa_count = trsa_count + 1
1964                      ELSEIF ( j > nyn )  THEN
1965                         trna_count = trna_count + 1
1966                      ENDIF
1967                   ENDIF
1968                ENDDO
1969             ENDDO
1970          ENDDO
1971
1972          IF ( trsa_count  == 0 )  trsa_count  = 1
1973          IF ( trna_count  == 0 )  trna_count  = 1
1974
1975          ALLOCATE( trsa(trsa_count), trna(trna_count) )
1976
1977          trsa = zero_agent
1978          trna = zero_agent
1979
1980          trsa_count  = nr_move_south
1981          trna_count  = nr_move_north
1982
1983          trsa(1:nr_move_south) = move_also_south(1:nr_move_south)
1984          trna(1:nr_move_north) = move_also_north(1:nr_move_north)
1985
1986       ENDIF
1987
1988       DO  ip = nxl, nxr
1989          DO  jp = nys, nyn, nyn-nys ! compute only first (nys) and last (nyn) loop iterration
1990             number_of_agents = agt_count(jp,ip)
1991             IF ( number_of_agents <= 0 )  CYCLE
1992             agents => grid_agents(jp,ip)%agents(1:number_of_agents)
1993             DO  n = 1, number_of_agents
1994!
1995!--             Only those agents that have not been marked as 'deleted' may
1996!--             be moved.
1997                IF ( agents(n)%agent_mask )  THEN
1998
1999                   j = agents(n)%y * ddy
2000!
2001!--                Above calculation does not work for indices less than zero
2002                   IF ( agents(n)%y < 0.0_wp * dy )  j = -1
2003
2004                   IF ( j < nys )  THEN
2005                      IF ( j < 0 )  THEN
2006!
2007!--                      Apply boundary condition along y
2008                         IF ( ibc_mas_ns == 0 )  THEN
2009!
2010!--                         Cyclic condition
2011                            IF ( pdims(2) == 1 )  THEN
2012                               agents(n)%y = ( ny + 1 ) * dy + agents(n)%y
2013                               agents(n)%origin_y = ( ny + 1 ) * dy +          &
2014                                                     agents(n)%origin_y
2015                            ELSE
2016                               trsa_count         = trsa_count + 1
2017                               trsa(trsa_count)   = agents(n)
2018                               trsa(trsa_count)%y = ( ny + 1 ) * dy +          &
2019                                                 trsa(trsa_count)%y
2020                               trsa(trsa_count)%origin_y =                     &
2021                                                  trsa(trsa_count)%origin_y    &
2022                                                + ( ny + 1 ) * dy
2023                               agents(n)%agent_mask = .FALSE.
2024                               deleted_agents = deleted_agents + 1
2025
2026                               IF ( trsa(trsa_count)%y >=                      &
2027                                                    (ny+1)* dy - 1.0E-12_wp )  &
2028                               THEN
2029                                  trsa(trsa_count)%y = trsa(trsa_count)%y -    &
2030                                                       1.0E-10_wp
2031                                  trsa(trsa_count)%origin_y =                  &
2032                                                  trsa(trsa_count)%origin_y - 1
2033                               ENDIF
2034
2035                            ENDIF
2036
2037                         ELSEIF ( ibc_mas_ns == 1 )  THEN
2038!
2039!--                         Agent absorption
2040                            agents(n)%agent_mask = .FALSE.
2041                            deleted_agents          = deleted_agents + 1
2042
2043                         ENDIF
2044                      ELSE
2045!
2046!--                      Store agent data in the transfer array, which will
2047!--                      be send to the neighbouring PE
2048                         trsa_count = trsa_count + 1
2049                         trsa(trsa_count) = agents(n)
2050                         agents(n)%agent_mask = .FALSE.
2051                         deleted_agents = deleted_agents + 1
2052
2053                      ENDIF
2054
2055                   ELSEIF ( j > nyn )  THEN
2056                      IF ( j > ny )  THEN
2057!
2058!--                      Apply boundary condition along y
2059                         IF ( ibc_mas_ns == 0 )  THEN
2060!
2061!--                         Cyclic condition
2062                            IF ( pdims(2) == 1 )  THEN
2063                               agents(n)%y        = agents(n)%y -              &
2064                                                    ( ny + 1 ) * dy
2065                               agents(n)%origin_y = agents(n)%origin_y -       &
2066                                                    ( ny + 1 ) * dy
2067                            ELSE
2068                               trna_count         = trna_count + 1
2069                               trna(trna_count)   = agents(n)
2070                               trna(trna_count)%y =                            &
2071                                          trna(trna_count)%y - ( ny + 1 ) * dy
2072                               trna(trna_count)%origin_y =                     &
2073                                         trna(trna_count)%origin_y -           &
2074                                         ( ny + 1 ) * dy
2075                               agents(n)%agent_mask = .FALSE.
2076                               deleted_agents          = deleted_agents + 1
2077                            ENDIF
2078
2079                         ELSEIF ( ibc_mas_ns == 1 )  THEN
2080!
2081!--                         Agent absorption
2082                            agents(n)%agent_mask = .FALSE.
2083                            deleted_agents = deleted_agents + 1
2084
2085                         ENDIF
2086                      ELSE
2087!
2088!--                      Store agent data in the transfer array, which will
2089!--                      be send to the neighbouring PE
2090                         trna_count = trna_count + 1
2091                         trna(trna_count) = agents(n)
2092                         agents(n)%agent_mask = .FALSE.
2093                         deleted_agents = deleted_agents + 1
2094
2095                      ENDIF
2096
2097                   ENDIF
2098                ENDIF
2099             ENDDO
2100          ENDDO
2101       ENDDO
2102
2103!
2104!--    Send front boundary, receive back boundary (but first exchange how many
2105!--    and chec if agent storage must be extended)
2106       IF ( pdims(2) /= 1 )  THEN
2107
2108          CALL MPI_SENDRECV( trsa_count,      1, MPI_INTEGER, psouth, 0,       &
2109                             trna_count_recv, 1, MPI_INTEGER, pnorth, 0,       &
2110                             comm2d, status, ierr )
2111
2112          ALLOCATE(rvna(MAX(1,trna_count_recv)))
2113!
2114!--       This MPI_SENDRECV should work even with odd mixture on 32 and 64 Bit
2115!--       variables in structure agent_type (due to the calculation of par_size)
2116          par_size = STORAGE_SIZE(trsa(1))/8
2117          CALL MPI_SENDRECV( trsa, trsa_count*par_size, MPI_BYTE,              &
2118                             psouth, 1, rvna,                                  &
2119                             trna_count_recv*par_size, MPI_BYTE, pnorth, 1,    &
2120                             comm2d, status, ierr )
2121
2122          IF ( trna_count_recv  > 0 ) THEN
2123             CALL mas_eh_add_agents_to_gridcell(rvna(1:trna_count_recv))
2124          ENDIF
2125
2126          DEALLOCATE(rvna)
2127
2128!
2129!--       Send back boundary, receive front boundary
2130          CALL MPI_SENDRECV( trna_count,      1, MPI_INTEGER, pnorth, 0,       &
2131                             trsa_count_recv, 1, MPI_INTEGER, psouth, 0,       &
2132                             comm2d, status, ierr )
2133
2134          ALLOCATE(rvsa(MAX(1,trsa_count_recv)))
2135!
2136!--       This MPI_SENDRECV should work even with odd mixture on 32 and 64 Bit
2137!--       variables in structure agent_type (due to the calculation of par_size)
2138          par_size = STORAGE_SIZE(trna(1))/8
2139          CALL MPI_SENDRECV( trna, trna_count*par_size, MPI_BYTE,              &
2140                             pnorth, 1, rvsa,                                  &
2141                             trsa_count_recv*par_size, MPI_BYTE, psouth, 1,    &
2142                             comm2d, status, ierr )
2143
2144          IF ( trsa_count_recv > 0 ) THEN
2145             CALL mas_eh_add_agents_to_gridcell(rvsa(1:trsa_count_recv))
2146          ENDIF
2147
2148          DEALLOCATE(rvsa)
2149
2150          number_of_agents = number_of_agents + trsa_count_recv
2151
2152          DEALLOCATE( trsa, trna )
2153
2154       ENDIF
2155
2156       DEALLOCATE( move_also_north )
2157       DEALLOCATE( move_also_south )
2158
2159#else
2160
2161       DO  ip = nxl, nxr, nxr-nxl
2162          DO  jp = nys, nyn
2163             number_of_agents = agt_count(jp,ip)
2164             IF ( number_of_agents <= 0 )  CYCLE
2165             agents => grid_agents(jp,ip)%agents(1:number_of_agents)
2166             DO  n = 1, number_of_agents
2167!
2168!--             Apply boundary conditions
2169                IF ( agents(n)%x < 0.0_wp )  THEN
2170
2171                   IF ( ibc_mas_lr == 0 )  THEN
2172!
2173!--                   Cyclic boundary. Relevant coordinate has to be changed.
2174                      agents(n)%x = ( nx + 1 ) * dx + agents(n)%x
2175                      agents(n)%origin_x = ( nx + 1 ) * dx + &
2176                                  agents(n)%origin_x
2177                   ELSEIF ( ibc_mas_lr == 1 )  THEN
2178!
2179!--                   Agent absorption
2180                      agents(n)%agent_mask = .FALSE.
2181                      deleted_agents = deleted_agents + 1
2182                   ENDIF
2183
2184                ELSEIF ( agents(n)%x >= ( nx + 1 ) * dx )  THEN
2185
2186                   IF ( ibc_mas_lr == 0 )  THEN
2187!
2188!--                   Cyclic boundary. Relevant coordinate has to be changed.
2189                      agents(n)%x = agents(n)%x - ( nx + 1 ) * dx
2190
2191                   ELSEIF ( ibc_mas_lr == 1 )  THEN
2192!
2193!--                   Agent absorption
2194                      agents(n)%agent_mask = .FALSE.
2195                      deleted_agents = deleted_agents + 1
2196                   ENDIF
2197
2198                ENDIF
2199             ENDDO
2200          ENDDO
2201       ENDDO
2202
2203       DO  ip = nxl, nxr
2204          DO  jp = nys, nyn, nyn-nys
2205             number_of_agents = agt_count(jp,ip)
2206             IF ( number_of_agents <= 0 )  CYCLE
2207             agents => grid_agents(jp,ip)%agents(1:number_of_agents)
2208             DO  n = 1, number_of_agents
2209
2210                IF ( agents(n)%y < 0.0_wp )  THEN
2211
2212                   IF ( ibc_mas_ns == 0 )  THEN
2213!
2214!--                   Cyclic boundary. Relevant coordinate has to be changed.
2215                      agents(n)%y = ( ny + 1 ) * dy + agents(n)%y
2216                      agents(n)%origin_y = ( ny + 1 ) * dy + &
2217                           agents(n)%origin_y
2218
2219                   ELSEIF ( ibc_mas_ns == 1 )  THEN
2220!
2221!--                   Agent absorption
2222                      agents(n)%agent_mask = .FALSE.
2223                      deleted_agents = deleted_agents + 1
2224                   ENDIF
2225
2226                ELSEIF ( agents(n)%y >= ( ny + 0.5_wp ) * dy )  THEN
2227
2228                   IF ( ibc_mas_ns == 0 )  THEN
2229!
2230!--                   Cyclic boundary. Relevant coordinate has to be changed.
2231                      agents(n)%y = agents(n)%y - ( ny + 1 ) * dy
2232
2233                   ELSEIF ( ibc_mas_ns == 1 )  THEN
2234!
2235!--                   Agent absorption
2236                      agents(n)%agent_mask = .FALSE.
2237                      deleted_agents = deleted_agents + 1
2238                   ENDIF
2239
2240                ENDIF
2241
2242             ENDDO
2243          ENDDO
2244       ENDDO
2245#endif
2246
2247!
2248!--    Accumulate the number of agents transferred between the subdomains)
2249       CALL mas_eh_ghost_exchange
2250
2251    END SUBROUTINE mas_eh_exchange_horiz
2252
2253!------------------------------------------------------------------------------!
2254! Description:
2255! ------------
2256!> Sends the agents from the three gridcells closest to the
2257!> north/south/left/right border of a PE to the corresponding neighbors ghost
2258!> layer (which is three grid boxes deep)
2259!------------------------------------------------------------------------------!
2260    SUBROUTINE mas_eh_ghost_exchange
2261
2262       IMPLICIT NONE
2263
2264#if defined( __parallel )
2265
2266       INTEGER(iwp) ::  ip          !< index variable along x
2267       INTEGER(iwp) ::  jp          !< index variable along y
2268       INTEGER(iwp) ::  agt_size    !< Bit size of agent datatype
2269       INTEGER(iwp) ::  ghla_count  !< ghost points left agent
2270       INTEGER(iwp) ::  ghna_count  !< ghost points north agent
2271       INTEGER(iwp) ::  ghra_count  !< ghost points right agent
2272       INTEGER(iwp) ::  ghsa_count  !< ghost points south agent
2273
2274       LOGICAL ::  ghla_empty      !< ghost points left agent
2275       LOGICAL ::  ghla_empty_rcv  !< ghost points left agent
2276       LOGICAL ::  ghna_empty      !< ghost points north agent
2277       LOGICAL ::  ghna_empty_rcv  !< ghost points north agent
2278       LOGICAL ::  ghra_empty      !< ghost points right agent
2279       LOGICAL ::  ghra_empty_rcv  !< ghost points right agent
2280       LOGICAL ::  ghsa_empty      !< ghost points south agent
2281       LOGICAL ::  ghsa_empty_rcv  !< ghost points south agent
2282
2283       TYPE(agent_type), DIMENSION(:), ALLOCATABLE ::  ghla  !< agents received from right PE
2284       TYPE(agent_type), DIMENSION(:), ALLOCATABLE ::  ghna  !< agents received from south PE
2285       TYPE(agent_type), DIMENSION(:), ALLOCATABLE ::  ghra  !< agents received from left PE
2286       TYPE(agent_type), DIMENSION(:), ALLOCATABLE ::  ghsa  !< agents received from north PE
2287
2288       ghla_empty = .TRUE.
2289       ghna_empty = .TRUE.
2290       ghra_empty = .TRUE.
2291       ghsa_empty = .TRUE.
2292!
2293!--    reset ghost layer
2294       DO ip = nxlg, nxl-1
2295          DO jp = nysg, nyng
2296             agt_count(jp,ip) = 0
2297          ENDDO
2298       ENDDO
2299       DO ip = nxr+1, nxrg
2300          DO jp = nysg, nyng
2301             agt_count(jp,ip) = 0
2302          ENDDO
2303       ENDDO
2304       DO ip = nxl, nxr
2305          DO jp = nysg, nys-1
2306             agt_count(jp,ip) = 0
2307          ENDDO
2308       ENDDO
2309       DO ip = nxl, nxr
2310          DO jp = nyn+1, nyng
2311             agt_count(jp,ip) = 0
2312          ENDDO
2313       ENDDO
2314!
2315!--    Transfer of agents from left to right and vice versa
2316       IF ( pdims(1) /= 1 )  THEN
2317!
2318!--       Reset left and right ghost layers
2319          ghla_count  = 0
2320          ghra_count  = 0
2321!
2322!--       First calculate the storage necessary for sending
2323!--       and receiving the data.
2324          ghla_count = SUM(agt_count(nys:nyn,nxl:nxl+2))
2325          ghra_count = SUM(agt_count(nys:nyn,nxr-2:nxr))
2326!
2327!--       No cyclic boundaries for agents
2328          IF ( nxl == 0 .OR. ghla_count == 0 ) THEN
2329             ghla_count = 1
2330          ELSE
2331             ghla_empty = .FALSE.
2332          ENDIF
2333          IF ( nxr == nx .OR. ghra_count == 0 ) THEN
2334             ghra_count = 1
2335          ELSE
2336             ghra_empty = .FALSE.
2337          ENDIF
2338          ALLOCATE( ghla(1:ghla_count), ghra(1:ghra_count) )
2339          ghla = zero_agent
2340          ghra = zero_agent
2341!
2342!--       Get all agents that will be sent left into one array
2343          ghla_count = 0
2344          IF ( nxl /= 0 ) THEN
2345             DO ip = nxl, nxl+2
2346                DO jp = nys, nyn
2347
2348                   number_of_agents = agt_count(jp,ip)
2349                   IF ( number_of_agents <= 0 )  CYCLE
2350                   ghla(ghla_count+1:ghla_count+number_of_agents)              &
2351                       = grid_agents(jp,ip)%agents(1:number_of_agents)
2352                   ghla_count = ghla_count + number_of_agents
2353
2354                ENDDO
2355             ENDDO
2356          ENDIF
2357          IF ( ghla_count == 0 )  ghla_count = 1
2358!
2359!--       Get all agents that will be sent right into one array
2360          ghra_count = 0
2361          IF ( nxr /= nx ) THEN
2362             DO ip = nxr-2, nxr
2363                DO jp = nys, nyn
2364
2365                   number_of_agents = agt_count(jp,ip)
2366                   IF ( number_of_agents <= 0 )  CYCLE
2367                   ghra(ghra_count+1:ghra_count+number_of_agents)              &
2368                       = grid_agents(jp,ip)%agents(1:number_of_agents)
2369                   ghra_count = ghra_count + number_of_agents
2370
2371                ENDDO
2372             ENDDO
2373          ENDIF
2374          IF ( ghra_count == 0 ) ghra_count = 1
2375!
2376!--       Send/receive number of agents that
2377!--       will be transferred to/from left/right neighbor
2378          CALL MPI_SENDRECV( ghla_count,      1, MPI_INTEGER, pleft,  0,       &
2379                             ghra_count_recv, 1, MPI_INTEGER, pright, 0,       &
2380                             comm2d, status, ierr )
2381          ALLOCATE ( agt_gh_r(1:ghra_count_recv) )
2382!
2383!--       Send/receive number of agents that
2384!--       will be transferred to/from right/left neighbor
2385          CALL MPI_SENDRECV( ghra_count,      1, MPI_INTEGER, pright,  0,      &
2386                             ghla_count_recv, 1, MPI_INTEGER, pleft,   0,      &
2387                             comm2d, status, ierr )
2388!
2389!--       Send/receive flag that indicates if there are actually any agents
2390!--       in ghost  layer
2391          CALL MPI_SENDRECV( ghla_empty,     1, MPI_LOGICAL, pleft, 1,         &
2392                             ghra_empty_rcv, 1, MPI_LOGICAL, pright,1,         &
2393                             comm2d, status, ierr )
2394          CALL MPI_SENDRECV( ghra_empty,     1, MPI_LOGICAL, pright,1,         &
2395                             ghla_empty_rcv, 1, MPI_LOGICAL, pleft, 1,         &
2396                             comm2d, status, ierr )
2397
2398
2399          ALLOCATE ( agt_gh_l(1:ghla_count_recv) )
2400!
2401!--       Get bit size of one agent
2402          agt_size = STORAGE_SIZE(zero_agent)/8
2403!
2404!--       Send/receive agents to/from left/right neighbor
2405          CALL MPI_SENDRECV( ghla,     ghla_count      * agt_size, MPI_BYTE,   &
2406                                pleft, 1,                                      &
2407                             agt_gh_r, ghra_count_recv * agt_size, MPI_BYTE,   &
2408                                pright,1,                                      &
2409                             comm2d, status, ierr )
2410!
2411!--       Send/receive agents to/from left/right neighbor
2412          CALL MPI_SENDRECV( ghra,     ghra_count      * agt_size, MPI_BYTE,   &
2413                                pright,1,                                      &
2414                             agt_gh_l, ghla_count_recv * agt_size, MPI_BYTE,   &
2415                                pleft, 1,                                      &
2416                             comm2d, status, ierr )
2417!
2418!--       If agents were received, add them to the respective ghost layer cells
2419          IF ( .NOT. ghra_empty_rcv ) THEN
2420             CALL mas_eh_add_ghost_agents_to_gridcell(agt_gh_r)
2421          ENDIF
2422
2423          IF ( .NOT. ghla_empty_rcv ) THEN
2424             CALL mas_eh_add_ghost_agents_to_gridcell(agt_gh_l)
2425          ENDIF
2426
2427          DEALLOCATE( ghla, ghra, agt_gh_l, agt_gh_r )
2428
2429       ENDIF
2430
2431!
2432!--    Transfer of agents from south to north and vice versa
2433       IF ( pdims(2) /= 1 )  THEN
2434!
2435!--       Reset south and north ghost layers
2436          ghsa_count  = 0
2437          ghna_count  = 0
2438!
2439!--       First calculate the storage necessary for sending
2440!--       and receiving the data.
2441          ghsa_count = SUM(agt_count(nys:nys+2,nxlg:nxrg))
2442          ghna_count = SUM(agt_count(nyn-2:nyn,nxlg:nxrg))
2443!
2444!--       No cyclic boundaries for agents
2445          IF ( nys == 0 .OR. ghsa_count == 0 ) THEN
2446             ghsa_count = 1
2447          ELSE
2448             ghsa_empty = .FALSE.
2449          ENDIF
2450          IF ( nyn == ny .OR. ghna_count == 0 ) THEN
2451             ghna_count = 1
2452          ELSE
2453             ghna_empty = .FALSE.
2454          ENDIF
2455          ALLOCATE( ghsa(1:ghsa_count), ghna(1:ghna_count) )
2456          ghsa = zero_agent
2457          ghna = zero_agent
2458!
2459!--       Get all agents that will be sent south into one array
2460          ghsa_count = 0
2461          IF ( nys /= 0 ) THEN
2462             DO ip = nxlg, nxrg
2463                DO jp = nys, nys+2
2464
2465                   number_of_agents = agt_count(jp,ip)
2466                   IF ( number_of_agents <= 0 )  CYCLE
2467                   ghsa(ghsa_count+1:ghsa_count+number_of_agents)              &
2468                       = grid_agents(jp,ip)%agents(1:number_of_agents)
2469                   ghsa_count = ghsa_count + number_of_agents
2470
2471                ENDDO
2472             ENDDO
2473          ENDIF
2474          IF ( ghsa_count == 0 )  ghsa_count = 1
2475!
2476!--       Get all agents that will be sent north into one array
2477          ghna_count = 0
2478          IF ( nyn /= ny ) THEN
2479             DO ip = nxlg, nxrg
2480                DO jp = nyn-2, nyn
2481
2482                   number_of_agents = agt_count(jp,ip)
2483                   IF ( number_of_agents <= 0 )  CYCLE
2484                   ghna(ghna_count+1:ghna_count+number_of_agents)              &
2485                       = grid_agents(jp,ip)%agents(1:number_of_agents)
2486                   ghna_count = ghna_count + number_of_agents
2487
2488                ENDDO
2489             ENDDO
2490          ENDIF
2491          IF ( ghna_count == 0 ) ghna_count = 1
2492!
2493!--       Send/receive number of agents that
2494!--       will be transferred to/from south/north neighbor
2495          CALL MPI_SENDRECV( ghsa_count, 1, MPI_INTEGER, psouth, 0,            &
2496                             ghna_count_recv,   1, MPI_INTEGER, pnorth, 0,     &
2497                             comm2d, status, ierr )
2498          ALLOCATE ( agt_gh_n(1:ghna_count_recv) )
2499!
2500!--       Send/receive number of agents that
2501!--       will be transferred to/from north/south neighbor
2502          CALL MPI_SENDRECV( ghna_count, 1, MPI_INTEGER, pnorth, 0,            &
2503                             ghsa_count_recv,   1, MPI_INTEGER, psouth, 0,     &
2504                             comm2d, status, ierr )
2505!
2506!--       Send/receive flag that indicates if there are actually any agents
2507!--       in ghost  layer
2508          CALL MPI_SENDRECV( ghsa_empty,     1, MPI_LOGICAL, psouth, 1,        &
2509                             ghna_empty_rcv, 1, MPI_LOGICAL, pnorth, 1,        &
2510                             comm2d, status, ierr )
2511          CALL MPI_SENDRECV( ghna_empty,     1, MPI_LOGICAL, pnorth, 1,        &
2512                             ghsa_empty_rcv, 1, MPI_LOGICAL, psouth, 1,        &
2513                             comm2d, status, ierr )
2514
2515
2516          ALLOCATE ( agt_gh_s(1:ghsa_count_recv) )
2517!
2518!--       Get bit size of one agent
2519          agt_size = STORAGE_SIZE(zero_agent)/8
2520!
2521!--       Send/receive agents to/from south/north neighbor
2522          CALL MPI_SENDRECV( ghsa,     ghsa_count      * agt_size, MPI_BYTE,   &
2523                                psouth,1,                                      &
2524                             agt_gh_n, ghna_count_recv * agt_size, MPI_BYTE,   &
2525                                pnorth,1,                                      &
2526                             comm2d, status, ierr )
2527!
2528!--       Send/receive agents to/from south/north neighbor
2529          CALL MPI_SENDRECV( ghna,     ghna_count      * agt_size, MPI_BYTE,   &
2530                                pnorth,1,                                      &
2531                             agt_gh_s, ghsa_count_recv * agt_size, MPI_BYTE,   &
2532                                psouth,1,                                      &
2533                             comm2d, status, ierr )
2534!
2535!--       If agents were received, add them to the respective ghost layer cells
2536          IF ( .NOT. ghna_empty_rcv ) THEN
2537             CALL mas_eh_add_ghost_agents_to_gridcell(agt_gh_n)
2538          ENDIF
2539
2540          IF ( .NOT. ghsa_empty_rcv ) THEN
2541             CALL mas_eh_add_ghost_agents_to_gridcell(agt_gh_s)
2542          ENDIF
2543
2544          DEALLOCATE( ghna, ghsa, agt_gh_n, agt_gh_s )
2545
2546       ENDIF
2547
2548#endif
2549
2550    END SUBROUTINE mas_eh_ghost_exchange
2551
2552!------------------------------------------------------------------------------!
2553! Description:
2554! ------------
2555!> If an agent moves from one grid cell to another (on the current
2556!> processor!), this subroutine moves the corresponding element from the
2557!> agent array of the old grid cell to the agent array of the new grid
2558!> cell.
2559!------------------------------------------------------------------------------!
2560    SUBROUTINE mas_eh_move_agent
2561
2562       IMPLICIT NONE
2563
2564       INTEGER(iwp) ::  i              !< grid index (x) of agent position
2565       INTEGER(iwp) ::  ip             !< index variable along x
2566       INTEGER(iwp) ::  j              !< grid index (y) of agent position
2567       INTEGER(iwp) ::  jp             !< index variable along y
2568       INTEGER(iwp) ::  n              !< index variable for agent array
2569       INTEGER(iwp) ::  na_before_move !< number of agents per grid box before moving
2570       INTEGER(iwp) ::  aindex         !< dummy argument for number of new agent per grid box
2571
2572       TYPE(agent_type), DIMENSION(:), POINTER ::  agents_before_move !< agents before moving
2573
2574       DO  ip = nxl, nxr
2575          DO  jp = nys, nyn
2576
2577                na_before_move = agt_count(jp,ip)
2578                IF ( na_before_move <= 0 )  CYCLE
2579                agents_before_move => grid_agents(jp,ip)%agents(1:na_before_move)
2580
2581                DO  n = 1, na_before_move
2582                   i = agents_before_move(n)%x * ddx
2583                   j = agents_before_move(n)%y * ddy
2584
2585!--                For mas_eh_exchange_horiz to work properly agents need to be
2586!--                moved to the outermost gridboxes of the respective processor.
2587!--                If the agent index is inside the processor the following
2588!--                lines will not change the index
2589                   i = MIN ( i , nxr )
2590                   i = MAX ( i , nxl )
2591                   j = MIN ( j , nyn )
2592                   j = MAX ( j , nys )
2593
2594!
2595!--                Check if agent has moved to another grid cell.
2596                   IF ( i /= ip  .OR.  j /= jp )  THEN
2597!
2598!--                   If the agent stays on the same processor, the agent
2599!--                   will be added to the agent array of the new processor.
2600                      number_of_agents = agt_count(j,i)
2601                      agents => grid_agents(j,i)%agents(1:number_of_agents)
2602
2603                      aindex = number_of_agents+1
2604                      IF (  aindex > SIZE(grid_agents(j,i)%agents)  )     &
2605                      THEN
2606                         CALL mas_eh_realloc_agents_array(i,j)
2607                      ENDIF
2608
2609                      grid_agents(j,i)%agents(aindex) = agents_before_move(n)
2610                      agt_count(j,i) = aindex
2611
2612                      agents_before_move(n)%agent_mask = .FALSE.
2613                   ENDIF
2614                ENDDO
2615
2616          ENDDO
2617       ENDDO
2618
2619       RETURN
2620
2621    END SUBROUTINE mas_eh_move_agent
2622
2623!------------------------------------------------------------------------------!
2624! Description:
2625! ------------
2626!> If the allocated memory for the agent array do not suffice to add arriving
2627!> agents from neighbour grid cells, this subrouting reallocates the
2628!> agent array to assure enough memory is available.
2629!------------------------------------------------------------------------------!
2630    SUBROUTINE mas_eh_realloc_agents_array (i,j,size_in)
2631
2632       IMPLICIT NONE
2633
2634       INTEGER(iwp) :: old_size  !< old array size
2635       INTEGER(iwp) :: new_size  !< new array size
2636
2637       INTEGER(iwp), INTENT(in) ::  i  !< grid index (y)
2638       INTEGER(iwp), INTENT(in) ::  j  !< grid index (y)
2639
2640       INTEGER(iwp), INTENT(in), OPTIONAL ::  size_in  !< size of input array
2641
2642       TYPE(agent_type), DIMENSION(10) :: tmp_agents_s !< temporary static agent array
2643
2644       TYPE(agent_type), DIMENSION(:), ALLOCATABLE :: tmp_agents_d !< temporary dynamic agent array
2645
2646       old_size = SIZE(grid_agents(j,i)%agents)
2647
2648       IF ( PRESENT(size_in) )   THEN
2649          new_size = size_in
2650       ELSE
2651          new_size = old_size * ( 1.0_wp + alloc_factor_mas / 100.0_wp )
2652       ENDIF
2653
2654       new_size = MAX( new_size, min_nr_agent, old_size + 1 )
2655
2656       IF ( old_size <= 10 )  THEN
2657
2658          tmp_agents_s(1:old_size) = grid_agents(j,i)%agents(1:old_size)
2659
2660          DEALLOCATE(grid_agents(j,i)%agents)
2661          ALLOCATE(grid_agents(j,i)%agents(new_size))
2662
2663          grid_agents(j,i)%agents(1:old_size)         = tmp_agents_s(1:old_size)
2664          grid_agents(j,i)%agents(old_size+1:new_size) = zero_agent
2665
2666       ELSE
2667
2668          ALLOCATE(tmp_agents_d(new_size))
2669          tmp_agents_d(1:old_size) = grid_agents(j,i)%agents
2670
2671          DEALLOCATE(grid_agents(j,i)%agents)
2672          ALLOCATE(grid_agents(j,i)%agents(new_size))
2673
2674          grid_agents(j,i)%agents(1:old_size)         = tmp_agents_d(1:old_size)
2675          grid_agents(j,i)%agents(old_size+1:new_size) = zero_agent
2676
2677          DEALLOCATE(tmp_agents_d)
2678
2679       ENDIF
2680       agents => grid_agents(j,i)%agents(1:number_of_agents)
2681
2682       RETURN
2683    END SUBROUTINE mas_eh_realloc_agents_array
2684
2685!------------------------------------------------------------------------------!
2686! Description:
2687! ------------
2688!> Inquires prognostic model quantities at the position of each agent and
2689!> stores them in that agent for later output
2690!------------------------------------------------------------------------------!
2691    SUBROUTINE mas_get_prognostic_quantities
2692
2693       USE arrays_3d,                                                          &
2694           ONLY:  u, v, pt, hyp, exner
2695
2696!       USE chemistry_model_mod,                                                &
2697!           ONLY:  chem_species
2698
2699!       USE control_parameters,                                                 &
2700!              ONLY:  air_chemistry
2701
2702       IMPLICIT NONE
2703
2704       INTEGER(iwp) ::  i_offset  !<  index offset for windspeed measurement
2705       INTEGER(iwp) ::  il        !<  x-index
2706       INTEGER(iwp) ::  is        !<  subgrid box counter
2707       INTEGER(iwp) ::  j_offset  !<  index offset for windspeed measurement
2708       INTEGER(iwp) ::  jl        !<  y-index
2709       INTEGER(iwp) ::  kl        !<  z-index
2710       INTEGER(iwp) ::  nl        !<  agent counter
2711       INTEGER(iwp) ::  se        !<  subgrid box end index
2712       INTEGER(iwp) ::  si        !<  subgrid box start index
2713
2714       REAL(wp) ::  u_a  !< windspeed at agent position (x)
2715       REAL(wp) ::  v_a  !< windspeed at agent position (y)
2716
2717       DO  il = nxl, nxr
2718          DO  jl = nys, nyn
2719
2720             number_of_agents = agt_count(jl,il)
2721!
2722!--          If grid cell is empty, cycle
2723             IF ( number_of_agents <= 0 ) CYCLE
2724             kl = s_measure_height(jl,il)
2725
2726             agents => grid_agents(jl,il)%agents(1:number_of_agents)
2727!
2728!--          loop over the four subgrid boxes
2729             DO is = 0,3
2730!
2731!--             Set indices
2732                si = grid_agents(jl,il)%start_index(is)
2733                se = grid_agents(jl,il)%end_index(is)
2734                DO nl = si, se
2735!
2736!--                Calculate index offset in x-direction:
2737!--                Left value if wall right of grid box
2738!--                Right value if wall left of grid box
2739!--                Else the one that is closer to the agent
2740                   IF ( BTEST( obstacle_flags( jl, il+1 ), 6 ) ) THEN
2741                      i_offset = 0
2742                   ELSEIF ( BTEST( obstacle_flags( jl, il-1 ), 2 ) ) THEN
2743                      i_offset = 1
2744                   ELSE
2745                      i_offset = MERGE( 0, 1, BTEST(is,1) )
2746                   ENDIF
2747                   u_a = u( kl, jl, il + i_offset )
2748!
2749!--                Calculate index offset in y-direction:
2750!--                South value if wall north of grid box
2751!--                North value if wall south of grid box
2752!--                Else the one that is closer to the agent
2753                   IF ( BTEST( obstacle_flags( jl+1, il ), 4 ) ) THEN
2754                      j_offset = 0
2755                   ELSEIF ( BTEST( obstacle_flags( jl-1, il ), 0 ) ) THEN
2756                      j_offset = 1
2757                   ELSE
2758                      j_offset = MERGE( 0, 1, BTEST(is,0) )
2759                   ENDIF
2760                   v_a = v( kl, jl + j_offset, il )
2761!
2762!--                Calculate windspeed at agent postion
2763                   agents(nl)%windspeed = SQRT(u_a**2 + v_a**2)
2764!
2765!--                Calculate temperature at agent position
2766                   agents(nl)%t = pt(kl,jl,il) * exner(kl)
2767! !
2768! !--                Get PM10 concentration at agent position, if possible
2769!                    IF ( ind_pm10 == -9 ) THEN
2770!                       agents(nl)%pm10 = 0.0_wp
2771!                    ELSE
2772!                       agents(nl)%pm10 = chem_species(ind_pm10)%conc(kl,jl,il)
2773!                    ENDIF
2774! !
2775! !--                Get PM10 concentration at agent position, if possible
2776!                    IF ( ind_pm25 == -9 ) THEN
2777!                       agents(nl)%pm25 = 0.0_wp
2778!                    ELSE
2779!                       agents(nl)%pm25 = chem_species(ind_pm25)%conc(kl,jl,il)
2780!                    ENDIF
2781                ENDDO
2782
2783             ENDDO
2784
2785          ENDDO
2786       ENDDO
2787
2788    END SUBROUTINE mas_get_prognostic_quantities
2789
2790!------------------------------------------------------------------------------!
2791! Description:
2792! ------------
2793!> Adds an item to the priority queue (binary heap) at the correct position
2794!------------------------------------------------------------------------------!
2795    SUBROUTINE mas_heap_insert_item( id, priority )
2796
2797       IMPLICIT NONE
2798
2799       INTEGER(iwp) ::  cur_pos !< current position
2800       INTEGER(iwp) ::  id      !< mesh ID of item
2801
2802       REAL(wp) ::  priority !< item priority
2803
2804       TYPE(heap_item) ::  item !< heap item
2805
2806       item%mesh_id  = id
2807       item%priority = priority
2808!
2809!--    Extend heap, if necessary
2810       IF ( heap_count + 1 > SIZE(queue) ) THEN
2811          CALL mas_heap_extend
2812       ENDIF
2813!
2814!--    Insert item at first unoccupied postion (highest index) of heap
2815       cur_pos = heap_count
2816       queue(cur_pos) = item
2817!
2818!--    Sort while inserted item is not at top of heap
2819       DO WHILE ( cur_pos /= 0 )
2820!
2821!--       If priority < its parent's priority, swap them.
2822!--       Else, sorting is done.
2823          IF ( queue(cur_pos)%priority                                         &
2824              < queue(FLOOR((cur_pos)/2.))%priority )                          &
2825          THEN
2826             item = queue(cur_pos)
2827             queue(cur_pos) = queue(FLOOR((cur_pos)/2.))
2828             queue(FLOOR((cur_pos)/2.)) = item
2829             cur_pos = FLOOR((cur_pos)/2.)
2830          ELSE
2831             EXIT
2832          ENDIF
2833       ENDDO
2834!
2835!--    Item was added to heap, so the heap count increases
2836       heap_count = heap_count + 1
2837
2838    END SUBROUTINE mas_heap_insert_item
2839
2840!------------------------------------------------------------------------------!
2841! Description:
2842! ------------
2843!> Extends the size of the priority queue (binary heap)
2844!------------------------------------------------------------------------------!
2845    SUBROUTINE mas_heap_extend
2846
2847       IMPLICIT NONE
2848
2849       INTEGER(iwp) ::  soh !< size of heap
2850
2851       TYPE(heap_item), DIMENSION(:), ALLOCATABLE ::  dummy_heap !< dummy heap
2852
2853       soh = SIZE(queue)-1
2854       ALLOCATE(dummy_heap(0:soh))
2855       dummy_heap = queue
2856       DEALLOCATE(queue)
2857       ALLOCATE(queue(0:2*soh+1))
2858       queue(0:soh) = dummy_heap(0:soh)
2859
2860    END SUBROUTINE mas_heap_extend
2861
2862!------------------------------------------------------------------------------!
2863! Description:
2864! ------------
2865!> Removes first (smallest) element from the priority queue, reorders the rest
2866!> and returns the ID of the removed mesh point
2867!------------------------------------------------------------------------------!
2868    SUBROUTINE mas_heap_extract_item ( id )
2869
2870       IMPLICIT NONE
2871
2872       INTEGER(iwp) ::  id      !< ID of item extracted item
2873       INTEGER(iwp) ::  child   !< child of item in heap
2874       INTEGER(iwp) ::  cur_pos !< current position of item in heap
2875
2876       TYPE(heap_item) ::  dummy
2877!
2878!--    Get ID of mesh point with lowest priority (extracted item: top of heap)
2879       id = queue(0)%mesh_id
2880!
2881!--    Put last item in heap at first position
2882       queue(0) = queue(heap_count-1)
2883       cur_pos = 0
2884       DO
2885!
2886!--       If current item has no children, sorting is done
2887          IF( 2*cur_pos+1 > heap_count - 1 ) THEN
2888             EXIT
2889!
2890!--       If current item has only one child, check if item and its child are
2891!--       ordered correctly. Else, swap them.
2892          ELSEIF ( 2*cur_pos+2 > heap_count - 1 ) THEN
2893             IF ( queue(cur_pos)%priority > queue(2*cur_pos+1)%priority ) THEN
2894                dummy = queue(cur_pos)
2895                queue(cur_pos) = queue(2*cur_pos+1)
2896                queue(2*cur_pos+1) = dummy
2897                cur_pos = 2*cur_pos+1
2898             ELSE
2899                EXIT
2900             ENDIF
2901          ELSE
2902!
2903!--          determine the smaller child
2904             IF ( queue(2*cur_pos+1)%priority                                  &
2905                 >= queue(2*cur_pos+2)%priority )                              &
2906             THEN
2907                child = 2
2908             ELSE
2909                child = 1
2910             ENDIF
2911!
2912!--          Check if item and its smaller child are ordered falsely. If so,
2913!--          swap them. Else, sorting is done.
2914             IF ( queue(cur_pos)%priority > queue(2*cur_pos+child )%priority ) &
2915             THEN
2916                dummy = queue(cur_pos)
2917                queue(cur_pos) = queue(2*cur_pos+child)
2918                queue(2*cur_pos+child) = dummy
2919                cur_pos = 2*cur_pos+child
2920             ELSE
2921                EXIT
2922             ENDIF
2923          ENDIF
2924       ENDDO
2925!
2926!--    Top item was removed from heap, thus, heap_cout decreases by one
2927       heap_count = heap_count-1
2928
2929    END SUBROUTINE mas_heap_extract_item
2930
2931!------------------------------------------------------------------------------!
2932! Description:
2933! ------------
2934!> Initialization of Multi Agent System
2935!------------------------------------------------------------------------------!
2936    SUBROUTINE mas_init
2937
2938!       USE chem_gasphase_mod,                                                  &
2939!           ONLY:  nspec
2940
2941!       USE chemistry_model_mod,                                                &
2942!           ONLY:  chem_species
2943
2944       USE control_parameters,                                                 &
2945           ONLY:  coupling_char, initializing_actions, io_blocks, io_group
2946
2947       USE surface_mod,                                                        &
2948           ONLY:  get_topography_top_index, get_topography_top_index_ji
2949
2950       USE arrays_3d,                                                          &
2951           ONLY:  zu, zw
2952
2953       USE indices,                                                            &
2954           ONLY:  nzt 
2955
2956       IMPLICIT NONE
2957
2958       INTEGER(iwp) ::  i             !< grid cell (x)
2959       INTEGER(iwp) ::  ii            !< io-block counter
2960       INTEGER(iwp) ::  il            !< io-block counter
2961       INTEGER(iwp) ::  jl            !< io-block counter
2962       INTEGER(iwp) ::  kl            !< io-block counter
2963       INTEGER(iwp) ::  kdum            !< io-block counter
2964       INTEGER(iwp) ::  locdum            !< io-block counter
2965       INTEGER(iwp) ::  j             !< grid cell (y)
2966       INTEGER(iwp) ::  size_of_mesh  !< temporary value for read
2967       INTEGER(iwp) ::  size_of_pols  !< temporary value for read
2968       INTEGER(iwp) ::  ioerr         !< IOSTAT flag for IO-commands ( 0 = no error )
2969
2970       REAL(wp) ::  zdum  !< dummy for measurement height
2971       REAL(wp) ::  avg_agt_height = 1.8_wp
2972
2973
2974!
2975!--    Check the number of agent groups.
2976       IF ( number_of_agent_groups > max_number_of_agent_groups )  THEN
2977          WRITE( message_string, * ) 'max_number_of_agent_groups =',      &
2978                                     max_number_of_agent_groups ,         &
2979                                     '&number_of_agent_groups reset to ', &
2980                                     max_number_of_agent_groups
2981          CALL message( 'mas_init', 'PA0072', 0, 1, 0, 6, 0 )
2982          number_of_agent_groups = max_number_of_agent_groups
2983       ENDIF
2984
2985!
2986!--    Set some parameters
2987       d_sigma_rep_agent = 1.0_wp/sigma_rep_agent
2988       d_sigma_rep_wall  = 1.0_wp/sigma_rep_wall
2989       d_tau_accel_agent = 1.0_wp/tau_accel_agent
2990       IF ( dt_agent /= 999.0_wp ) THEN
2991          agent_own_timestep = .TRUE.
2992       ENDIF
2993
2994!
2995!--    Get index of first grid box above topography
2996       ALLOCATE( top_top_s(nysg:nyng,nxlg:nxrg),                               &
2997                 top_top_w(nysg:nyng,nxlg:nxrg),                               &
2998                 s_measure_height(nys:nyn,nxl:nxr) )
2999!
3000!--    Get first index above topography for scalar grid and last index in
3001!--    topography for z-component of wind
3002       DO il = nxlg, nxrg
3003          DO jl = nysg, nyng
3004             top_top_s(jl,il) = get_topography_top_index_ji(jl,il,'s') + 1
3005             top_top_w(jl,il) = get_topography_top_index_ji(jl,il,'w')
3006          ENDDO
3007       ENDDO
3008!
3009!--    Create 2D array containing the index at which measurements are done by
3010!--    agents. The height of this measurement is given by avg_agt_height.
3011       DO il = nxl, nxr
3012          DO jl = nys, nyn
3013
3014             kdum = top_top_w(jl,il)
3015             zdum = zw(kdum)
3016             zdum = zdum + avg_agt_height
3017             locdum = 0
3018!
3019!--          Locate minimum distance from u-grid to measurement height (zdum)
3020             DO kl = 1, nzt
3021                IF ( ABS(zu(kl)-zdum) < ABS(zu(locdum)-zdum) ) locdum = kl
3022             ENDDO
3023             s_measure_height(jl,il) = locdum
3024
3025          ENDDO
3026       ENDDO
3027! !
3028! !--    Get indices of PM10 and PM2.5 species, if active
3029!        IF ( air_chemistry ) THEN
3030!           DO il = 1, nspec
3031! print*,chem_species(il)%name
3032! !              IF ( spec_name(1:4) == 'PM10' ) THEN 
3033! !                 ind_pm10 = il
3034! !              ELSEIF ( spec_name(1:4) == 'PM25' ) THEN
3035! !                 ind_pm25 = il
3036! !              ENDIF
3037!
3038!           ENDDO
3039!        ENDIF
3040! stop
3041       CALL mas_create_obstacle_flags
3042
3043!
3044!--    Set default start positions, if necessary
3045       IF ( asl(1) == 9999999.9_wp )  asl(1) = 0.0_wp
3046       IF ( asr(1) == 9999999.9_wp )  asr(1) = ( nx + 1 ) * dx
3047       IF ( ass(1) == 9999999.9_wp )  ass(1) = 0.0_wp
3048       IF ( asn(1) == 9999999.9_wp )  asn(1) = ( ny + 1 ) * dy
3049       IF ( adx(1) == 9999999.9_wp .OR. adx(1) == 0.0_wp ) adx(1) = dx
3050       IF ( ady(1) == 9999999.9_wp .OR. ady(1) == 0.0_wp ) ady(1) = dy
3051
3052       DO  j = 2, number_of_agent_groups
3053          IF ( asl(j) == 9999999.9_wp )  asl(j) = asl(j-1)
3054          IF ( asr(j) == 9999999.9_wp )  asr(j) = asr(j-1)
3055          IF ( ass(j) == 9999999.9_wp )  ass(j) = ass(j-1)
3056          IF ( asn(j) == 9999999.9_wp )  asn(j) = asn(j-1)
3057          IF ( adx(j) == 9999999.9_wp .OR. adx(j) == 0.0_wp ) adx(j) = adx(j-1)
3058          IF ( ady(j) == 9999999.9_wp .OR. ady(j) == 0.0_wp ) ady(j) = ady(j-1)
3059       ENDDO
3060
3061!
3062!--    Check boundary condition and set internal variables
3063       SELECT CASE ( bc_mas_lr )
3064
3065          CASE ( 'cyclic' )
3066             ibc_mas_lr = 0
3067
3068          CASE ( 'absorb' )
3069             ibc_mas_lr = 1
3070
3071          CASE DEFAULT
3072             WRITE( message_string, * ) 'unknown boundary condition ',         &
3073                                        'bc_mas_lr = "', TRIM( bc_mas_lr ), '"'
3074             CALL message( 'mas_init', 'PA0073', 1, 2, 0, 6, 0 )
3075
3076       END SELECT
3077       SELECT CASE ( bc_mas_ns )
3078
3079          CASE ( 'cyclic' )
3080             ibc_mas_ns = 0
3081
3082          CASE ( 'absorb' )
3083             ibc_mas_ns = 1
3084
3085          CASE DEFAULT
3086             WRITE( message_string, * ) 'unknown boundary condition ',         &
3087                                        'bc_mas_ns = "', TRIM( bc_mas_ns ), '"'
3088             CALL message( 'mas_init', 'PA0074', 1, 2, 0, 6, 0 )
3089
3090       END SELECT
3091
3092!
3093!--    For the first model run of a possible job chain initialize the
3094!--    agents, otherwise read the agent data from restart file.
3095       IF ( TRIM( initializing_actions ) == 'read_restart_data'                &
3096            .AND.  read_agents_from_restartfile )  THEN
3097
3098!           CALL mas_read_restart_file
3099
3100       ELSE
3101!
3102!--       Read preprocessed data of navigation mesh and building polygons
3103!--       for agent pathfinding
3104          DO ii = 0, io_blocks-1
3105             IF ( ii == io_group )  THEN
3106                OPEN ( 119, FILE='NAVIGATION_DATA'//TRIM( coupling_char ),     &
3107                            FORM='UNFORMATTED', IOSTAT=ioerr )
3108!
3109!--             Read mesh data
3110                READ(119) size_of_mesh
3111                ALLOCATE( mesh(1:size_of_mesh))
3112                DO i = 1, size_of_mesh
3113                   READ(119) mesh(i)%polygon_id, mesh(i)%vertex_id,            &
3114                             mesh(i)%noc, mesh(i)%origin_id,                   &
3115                             mesh(i)%cost_so_far, mesh(i)%x,                   &
3116                             mesh(i)%y, mesh(i)%x_s, mesh(i)%y_s
3117                   ALLOCATE( mesh(i)%connected_vertices(1:mesh(i)%noc),        &
3118                             mesh(i)%distance_to_vertex(1:mesh(i)%noc) )
3119                   DO j = 1, mesh(i)%noc
3120                      READ(119) mesh(i)%connected_vertices(j),                 &
3121                                mesh(i)%distance_to_vertex(j)
3122                   ENDDO
3123                ENDDO
3124!
3125!--             Read polygon data
3126                READ(119) size_of_pols
3127                ALLOCATE( polygons(1:size_of_pols) )
3128                DO i = 1, size_of_pols
3129                   READ(119) polygons(i)%nov
3130                   ALLOCATE( polygons(i)%vertices(0:polygons(i)%nov+1) )
3131                   DO j = 0, polygons(i)%nov+1
3132                      READ(119) polygons(i)%vertices(j)%delete,                &
3133                                polygons(i)%vertices(j)%x,                     &
3134                                polygons(i)%vertices(j)%y
3135                   ENDDO
3136                ENDDO
3137                CLOSE(119)
3138
3139             ENDIF
3140#if defined( __parallel ) && ! defined ( __check )
3141             CALL MPI_BARRIER( comm2d, ierr )
3142#endif
3143          ENDDO
3144
3145!
3146!--       Allocate agent arrays and set attributes of the initial set of
3147!--       agents, which can be also periodically released at later times.
3148          ALLOCATE( agt_count  (nysg:nyng,nxlg:nxrg),                          &
3149                    grid_agents(nysg:nyng,nxlg:nxrg) )
3150!
3151!--       Allocate dummy arrays for pathfinding
3152          ALLOCATE( dummy_path_x(0:agt_path_size),                 &
3153                    dummy_path_y(0:agt_path_size) )
3154
3155          number_of_agents = 0
3156          sort_count_mas   = 0
3157          agt_count        = 0
3158
3159!
3160!--       initialize counter for agent IDs
3161          grid_agents%id_counter = 1
3162
3163!
3164!--       Initialize all agents with dummy values (otherwise errors may
3165!--       occur within restart runs). The reason for this is still not clear
3166!--       and may be presumably caused by errors in the respective user-interface.
3167          zero_agent%agent_mask = .FALSE.
3168          zero_agent%block_nr      = -1
3169          zero_agent%group         = 0
3170          zero_agent%id            = 0_idp
3171          zero_agent%path_counter  = agt_path_size
3172          zero_agent%age           = 0.0_wp
3173          zero_agent%age_m         = 0.0_wp
3174          zero_agent%dt_sum        = 0.0_wp
3175          zero_agent%clo           = 0.0_wp
3176          zero_agent%energy_storage= 0.0_wp
3177          zero_agent%force_x       = 0.0_wp
3178          zero_agent%force_y       = 0.0_wp
3179          zero_agent%origin_x      = 0.0_wp
3180          zero_agent%origin_y      = 0.0_wp
3181          zero_agent%speed_abs     = 0.0_wp
3182          zero_agent%speed_e_x     = 0.0_wp
3183          zero_agent%speed_e_y     = 0.0_wp
3184          zero_agent%speed_des     = random_normal(desired_speed, des_sp_sig)
3185          zero_agent%speed_x       = 0.0_wp
3186          zero_agent%speed_y       = 0.0_wp
3187          zero_agent%thermal_index = 0.0_wp
3188          zero_agent%x             = 0.0_wp
3189          zero_agent%y             = 0.0_wp
3190          zero_agent%path_x        = 0.0_wp
3191          zero_agent%path_y        = 0.0_wp
3192          zero_agent%t_x           = 0.0_wp
3193          zero_agent%t_y           = 0.0_wp
3194
3195!
3196!--    Set a seed value for the random number generator to be exclusively
3197!--    used for the agent code. The generated random numbers should be
3198!--    different on the different PEs.
3199          iran_agent = iran_agent + myid
3200
3201          CALL mas_create_agent (PHASE_INIT)
3202
3203       ENDIF
3204
3205!
3206!--    To avoid programm abort, assign agents array to the local version of
3207!--    first grid cell
3208       number_of_agents = agt_count(nys,nxl)
3209       agents => grid_agents(nys,nxl)%agents(1:number_of_agents)
3210
3211    END SUBROUTINE mas_init
3212
3213!------------------------------------------------------------------------------!
3214! Description:
3215! ------------
3216!> Output of informative message about maximum agent number
3217!------------------------------------------------------------------------------!
3218    SUBROUTINE mas_last_actions
3219
3220       USE control_parameters,                                                 &
3221           ONLY:  message_string
3222
3223       IMPLICIT NONE
3224
3225       WRITE(message_string,'(A,I8,A)')                                        &
3226                         'The maximumn number of agents durin this run was',   &
3227                         maximum_number_of_agents,                             &
3228                         '&Consider adjusting the INPUT parameter'//           &
3229                         '&dim_size_agtnum_manual accordingly for the next run.'
3230
3231       CALL message( 'mas_data_output_agents', 'PA0457', 0, 0, 0, 6, 0 )
3232
3233    END SUBROUTINE mas_last_actions
3234
3235!------------------------------------------------------------------------------!
3236! Description:
3237! ------------
3238!> Finds the shortest path from a start position to a target position using the
3239!> A*-algorithm
3240!------------------------------------------------------------------------------!
3241    SUBROUTINE mas_nav_a_star( start_x, start_y, target_x, target_y, nsteps )
3242
3243       IMPLICIT NONE
3244
3245       LOGICAL ::  target_reached !< flag
3246
3247       INTEGER(iwp) ::  cur_node     !< current node of binary heap
3248       INTEGER(iwp) ::  il           !< counter (x)
3249       INTEGER(iwp) ::  neigh_node   !< neighbor node
3250       INTEGER(iwp) ::  node_counter !< binary heap node counter
3251       INTEGER(iwp) ::  path_ag      !< index of agent path
3252       INTEGER(iwp) ::  som          !< size of mesh
3253       INTEGER(iwp) ::  steps        !< steps along the path
3254       INTEGER(iwp) ::  nsteps        !< number of steps
3255
3256       REAL(wp) ::  start_x      !< x-coordinate agent
3257       REAL(wp) ::  start_y      !< y-coordinate agent
3258       REAL(wp) ::  new_cost     !< updated cost to reach node
3259       REAL(wp) ::  new_priority !< priority of node to be added to queue
3260       REAL(wp) ::  rn_gate      !< random number for corner gate
3261       REAL(wp) ::  target_x     !< x-coordinate target
3262       REAL(wp) ::  target_y     !< y-coordinate target
3263!
3264!--    Coordinate Type
3265       TYPE coord
3266          REAL(wp) ::  x   !< x-coordinate
3267          REAL(wp) ::  x_s !< x-coordinate (shifted)
3268          REAL(wp) ::  y   !< y-coordinate
3269          REAL(wp) ::  y_s !< y-coordinate (shifted)
3270       END TYPE coord
3271
3272       TYPE(coord), DIMENSION(:), ALLOCATABLE, TARGET ::  path     !< path array
3273       TYPE(coord), DIMENSION(:), ALLOCATABLE, TARGET ::  tmp_path !< temporary path for resizing
3274
3275       node_counter = 0
3276!
3277!--    Create temporary navigation mesh including agent and target positions
3278       CALL mas_nav_create_tmp_mesh( start_x, start_y, target_x, target_y, som )
3279       tmp_mesh(som)%cost_so_far = 0.0_wp
3280!
3281!--    Initialize priority queue
3282       heap_count = 0_iwp
3283       ALLOCATE(queue(0:100))
3284       target_reached = .FALSE.
3285!
3286!--    Add starting point (agent position) to frontier (the frontier consists
3287!--    of all the nodes that are to be visited. The node with the smallest
3288!--    priority will be visited first. The priority consists of the distance
3289!--    from the start node to this node plus a minimal guess (direct distance)
3290!--    from this node to the goal). For the starting node, the priority is set
3291!--    to 0, as it's the only node thus far
3292       CALL mas_heap_insert_item(som,0.0_wp)
3293       cur_node = som
3294       DO WHILE ( heap_count > 0 )
3295!
3296!--       Step one: Pick lowest priority item from queue
3297          node_counter = node_counter + 1
3298          CALL mas_heap_extract_item(cur_node)
3299!
3300!--       Node 0 is the goal node
3301          IF ( cur_node == 0 ) THEN
3302             EXIT
3303          ENDIF
3304!
3305!--       Loop over all of cur_node's neighbors
3306          DO il = 1, tmp_mesh(cur_node)%noc
3307             neigh_node = tmp_mesh(cur_node)%connected_vertices(il)
3308!
3309!--          Check, if the way from the start node to this neigh_node via
3310!--          cur_node is shorter than the previously found shortest path to it.
3311!--          If so, replace said cost and add neigh_node to the frontier.
3312!--          cost_so_far is initialized as 1.d12 so that all found distances
3313!--          should be smaller.
3314             new_cost   = tmp_mesh(cur_node)%cost_so_far                       &
3315                         + tmp_mesh(cur_node)%distance_to_vertex(il)
3316             IF ( new_cost < tmp_mesh(neigh_node)%cost_so_far ) THEN
3317                tmp_mesh(neigh_node)%cost_so_far = new_cost
3318                tmp_mesh(neigh_node)%origin_id   = cur_node
3319!
3320!--             Priority in the queue is cost_so_far + heuristic to goal
3321                new_priority = new_cost                                        &
3322                              + heuristic(tmp_mesh(neigh_node)%x,              &
3323                                tmp_mesh(neigh_node)%y, tmp_mesh(0)%x,         &
3324                                tmp_mesh(0)%y)
3325                CALL mas_heap_insert_item(neigh_node,new_priority)
3326             ENDIF
3327          ENDDO
3328       ENDDO
3329!
3330!--    Add nodes to a path array. To do this, we must backtrack from the target
3331!--    node to its origin to its origin and so on until an node is reached that
3332!--    has no origin (%origin_id == -1). This is the starting node.
3333       DEALLOCATE(queue)
3334       cur_node = 0
3335       steps = 0
3336       ALLOCATE(path(1:100))
3337       DO WHILE ( cur_node /= -1 )
3338          steps = steps + 1
3339!
3340!--       Resize path array if necessary
3341          IF ( steps > SIZE(path) ) THEN
3342             ALLOCATE(tmp_path(1:steps-1))
3343             tmp_path(1:steps-1) = path(1:steps-1)
3344             DEALLOCATE(path)
3345             ALLOCATE(path(1:2*(steps-1)))
3346             path(1:steps-1) = tmp_path(1:steps-1)
3347             DEALLOCATE(tmp_path)
3348          ENDIF
3349          path(steps)%x = tmp_mesh(cur_node)%x
3350          path(steps)%y = tmp_mesh(cur_node)%y
3351          path(steps)%x_s = tmp_mesh(cur_node)%x_s
3352          path(steps)%y_s = tmp_mesh(cur_node)%y_s
3353          cur_node = tmp_mesh(cur_node)%origin_id
3354       ENDDO
3355!
3356!--    Add calculated intermittent targets to the path until either the
3357!--    target or the maximum number of intermittent targets is reached.
3358!--    Ignore starting point (reduce index by one), it is agent position.
3359       dummy_path_x = -1
3360       dummy_path_y = -1
3361       path_ag = 1
3362       steps = steps - 1
3363       nsteps = 0
3364       DO WHILE( steps > 0 .AND. path_ag <= agt_path_size )
3365!
3366!--       Each target point is randomly chosen along a line target along the
3367!--       bisector of the building corner that starts at corner_gate_start
3368!--       and has a width of corner_gate_width. This is to avoid clustering
3369!--       when opposing agent groups try to reach the same corner target.
3370          rn_gate = random_function(iran_agent) * corner_gate_width            &
3371                                                + corner_gate_start
3372          dummy_path_x(path_ag) = path(steps)%x + rn_gate                      &
3373                         * (path(steps)%x_s - path(steps)%x)
3374          dummy_path_y(path_ag) = path(steps)%y + rn_gate                      &
3375                         * (path(steps)%y_s - path(steps)%y)
3376          steps = steps - 1
3377          path_ag = path_ag + 1
3378          nsteps = nsteps + 1
3379       ENDDO
3380!
3381!--    Set current intermittent target of this agent
3382       DEALLOCATE(tmp_mesh, path)
3383
3384    END SUBROUTINE mas_nav_a_star
3385
3386!------------------------------------------------------------------------------!
3387! Description:
3388! ------------
3389!> Adds a connection between two points of the navigation mesh
3390!> (one-way: in_mp1 to in_mp2)
3391!------------------------------------------------------------------------------!
3392    SUBROUTINE mas_nav_add_connection ( in_mp1, id2, in_mp2 )
3393
3394       IMPLICIT NONE
3395
3396       LOGICAL ::  connection_established  !< Flag to indicate if connection has already been established
3397
3398       INTEGER(iwp) ::  id2  !< ID of in_mp2
3399       INTEGER(iwp) ::  il   !< local counter
3400       INTEGER(iwp) ::  noc1 !< number of connections in in_mp1
3401
3402       INTEGER, DIMENSION(:), ALLOCATABLE ::  dum_cv !< dummy array for connected_vertices
3403
3404       REAL(wp) ::  dist  !< Distance between the two points
3405
3406       REAL(wp), DIMENSION(:), ALLOCATABLE ::  dum_dtv
3407
3408       TYPE(mesh_point) ::  in_mp1  !< mesh point that gets a new connection
3409       TYPE(mesh_point) ::  in_mp2  !< mesh point in_mp1 will be connected to
3410
3411       connection_established = .FALSE.
3412!
3413!--    Check if connection has already been established
3414       noc1 = SIZE(in_mp1%connected_vertices)
3415       DO il = 1, in_mp1%noc
3416          IF ( in_mp1%connected_vertices(il) == id2 ) THEN
3417             connection_established = .TRUE.
3418             EXIT
3419          ENDIF
3420       ENDDO
3421
3422       IF ( .NOT. connection_established ) THEN
3423!
3424!--       Resize arrays, if necessary
3425          IF ( in_mp1%noc >= noc1 ) THEN
3426             ALLOCATE( dum_cv(1:noc1),dum_dtv(1:noc1) )
3427             dum_cv  = in_mp1%connected_vertices
3428             dum_dtv = in_mp1%distance_to_vertex
3429             DEALLOCATE( in_mp1%connected_vertices, in_mp1%distance_to_vertex )
3430             ALLOCATE( in_mp1%connected_vertices(1:2*noc1),                    &
3431                       in_mp1%distance_to_vertex(1:2*noc1) )
3432             in_mp1%connected_vertices         = -999
3433             in_mp1%distance_to_vertex         = -999.
3434             in_mp1%connected_vertices(1:noc1) = dum_cv
3435             in_mp1%distance_to_vertex(1:noc1) = dum_dtv
3436          ENDIF
3437
3438!
3439!--       Add connection
3440          in_mp1%noc = in_mp1%noc+1
3441          dist = SQRT( (in_mp1%x - in_mp2%x)**2 + (in_mp1%y - in_mp2%y)**2 )
3442          in_mp1%connected_vertices(in_mp1%noc) = id2
3443          in_mp1%distance_to_vertex(in_mp1%noc) = dist
3444       ENDIF
3445
3446    END SUBROUTINE mas_nav_add_connection
3447
3448!------------------------------------------------------------------------------!
3449! Description:
3450! ------------
3451!> Adds a vertex (curren position of agent or target) to the existing tmp_mesh
3452!------------------------------------------------------------------------------!
3453    SUBROUTINE mas_nav_add_vertex_to_mesh ( in_mp, in_id )
3454
3455       IMPLICIT NONE
3456
3457       LOGICAL ::  intersection_found !< flag
3458
3459       INTEGER(iwp) ::  jl    !< mesh point counter
3460       INTEGER(iwp) ::  pl    !< polygon counter
3461       INTEGER(iwp) ::  vl    !< vertex counter
3462       INTEGER(iwp) ::  pid_t !< polygon id of tested mesh point
3463       INTEGER(iwp) ::  vid_t !< vertex id of tested mesh point
3464       INTEGER(iwp) ::  in_id !< vertex id of tested mesh point
3465
3466       REAL(wp) ::  v1x !< x-coordinate of test vertex 1 for intersection test
3467       REAL(wp) ::  v1y !< y-coordinate of test vertex 1 for intersection test
3468       REAL(wp) ::  v2x !< x-coordinate of test vertex 2 for intersection test
3469       REAL(wp) ::  v2y !< y-coordinate of test vertex 2 for intersection test
3470       REAL(wp) ::  x   !< x-coordinate of current mesh point
3471       REAL(wp) ::  x_t !< x-coordinate of tested mesh point
3472       REAL(wp) ::  y   !< y-coordinate of current mesh point
3473       REAL(wp) ::  y_t !< y-coordinate of tested mesh point
3474
3475       TYPE(mesh_point) ::  in_mp !< Input mesh point
3476!
3477!--
3478       x = in_mp%x
3479       y = in_mp%y
3480       DO jl = 0, SIZE(tmp_mesh)-2
3481          IF ( in_id == jl ) CYCLE
3482!
3483!--       Ignore mesh points with 0 connections
3484          IF ( tmp_mesh(jl)%polygon_id /= -1 ) THEN
3485             IF ( tmp_mesh(jl)%noc == 0 ) CYCLE
3486          ENDIF
3487          x_t = tmp_mesh(jl)%x
3488          y_t = tmp_mesh(jl)%y
3489          pid_t = tmp_mesh(jl)%polygon_id
3490          vid_t = tmp_mesh(jl)%vertex_id
3491!
3492!--       If the connecting line between the target and a mesh point points
3493!--       into the mesh point's polygon, no connection will be
3494!--       established between the two points. This is the case if the
3495!--       previous (next) vertex of the polygon is right of the connecting
3496!--       line and the next (previous) vertex of the polygon is left of the
3497!--       connecting line.
3498          IF ( pid_t > 0 .AND. pid_t <= SIZE(polygons) ) THEN
3499             IF ( (((is_left(x,y,x_t,y_t,polygons(pid_t)%vertices(vid_t-1)%x,  &
3500                                       polygons(pid_t)%vertices(vid_t-1)%y)    &
3501                  .AND. is_right(x,y,x_t,y_t,                                  &
3502                                       polygons(pid_t)%vertices(vid_t+1)%x,    &
3503                                       polygons(pid_t)%vertices(vid_t+1)%y) )  &
3504                  .OR. (is_right(x,y,x_t,y_t,                                  &
3505                                       polygons(pid_t)%vertices(vid_t-1)%x,    &
3506                                       polygons(pid_t)%vertices(vid_t-1)%y)    &
3507                  .AND. is_left(x,y,x_t,y_t,                                   &
3508                                       polygons(pid_t)%vertices(vid_t+1)%x,    &
3509                                       polygons(pid_t)%vertices(vid_t+1)%y)))))&
3510             THEN
3511                CYCLE
3512             ENDIF
3513          ENDIF
3514!
3515!--       For each edge of each polygon, check if it intersects with the
3516!--       potential connection. If at least one intersection is found,
3517!--       no connection can be made
3518          intersection_found = .FALSE.
3519          DO pl = 1, SIZE(polygons)
3520             DO vl = 1, polygons(pl)%nov
3521                v1x = polygons(pl)%vertices(vl)%x
3522                v1y = polygons(pl)%vertices(vl)%y
3523                v2x = polygons(pl)%vertices(vl+1)%x
3524                v2y = polygons(pl)%vertices(vl+1)%y
3525                intersection_found = intersect(x,y,x_t,y_t,v1x,v1y,v2x,v2y)
3526                IF ( intersection_found ) THEN
3527                   EXIT
3528                ENDIF
3529             ENDDO
3530             IF ( intersection_found ) EXIT
3531          ENDDO
3532          IF ( intersection_found ) CYCLE
3533!
3534!--       If neither of the above two test was true, a connection will be
3535!--       established between the two mesh points.
3536          CALL mas_nav_add_connection(in_mp,jl, tmp_mesh(jl))
3537          CALL mas_nav_add_connection(tmp_mesh(jl),in_id, in_mp)
3538       ENDDO
3539       CALL mas_nav_reduce_connections(in_mp)
3540
3541    END SUBROUTINE mas_nav_add_vertex_to_mesh
3542
3543!------------------------------------------------------------------------------!
3544! Description:
3545! ------------
3546!> Creates a temporary copy of the navigation mesh to be used for pathfinding
3547!------------------------------------------------------------------------------!
3548    SUBROUTINE mas_nav_create_tmp_mesh( a_x, a_y, t_x, t_y, som )
3549
3550       IMPLICIT NONE
3551
3552       INTEGER(iwp) ::  som !< size of mesh
3553       INTEGER(iwp) ::  noc !< number of connetions
3554       INTEGER(iwp) ::  im  !< local mesh point counter
3555
3556       REAL(wp) ::  a_x !< x-coordinate agent
3557       REAL(wp) ::  a_y !< y-coordinate agent
3558       REAL(wp) ::  t_x !< x-coordinate target
3559       REAL(wp) ::  t_y !< y-coordinate target
3560!
3561!--    give tmp_mesh the size of mesh
3562       som = SIZE(mesh)+1
3563       ALLOCATE(tmp_mesh(0:som))
3564!
3565!--    give the allocatable variables in tmp_mesh their respctive sizes
3566       DO im = 1, som-1
3567          noc = mesh(im)%noc
3568          ALLOCATE(tmp_mesh(im)%connected_vertices(1:noc))
3569          ALLOCATE(tmp_mesh(im)%distance_to_vertex(1:noc))
3570       ENDDO
3571!
3572!--    copy mesh to tmp_mesh
3573       tmp_mesh(1:som-1) = mesh(1:som-1)
3574!
3575!--    Add target point ...
3576       CALL mas_nav_init_mesh_point(tmp_mesh(0),-1_iwp,-1_iwp,t_x, t_y)
3577       CALL mas_nav_add_vertex_to_mesh(tmp_mesh(0),0_iwp)
3578!
3579!--    ... and start point to temp mesh
3580       CALL mas_nav_init_mesh_point(tmp_mesh(som),-1_iwp,-1_iwp,a_x, a_y)
3581       CALL mas_nav_add_vertex_to_mesh(tmp_mesh(som),som)
3582
3583    END SUBROUTINE mas_nav_create_tmp_mesh
3584   
3585
3586!------------------------------------------------------------------------------!
3587! Description:
3588! ------------
3589!> Finds the shortest path from an agents' position to her target. As the
3590!> actual pathfinding algorithm uses the obstacle corners and then shifts them
3591!> outward after pathfinding, cases can uccur in which the connection between
3592!> these intermittent targets then intersect with obstacles. To remedy this
3593!> the pathfinding algorithm is then run on every two subsequent intermittent
3594!> targets iteratively and new intermittent targets may be added to the path
3595!> this way.
3596!------------------------------------------------------------------------------!
3597    SUBROUTINE mas_nav_find_path( nl )
3598
3599       IMPLICIT NONE
3600
3601       INTEGER(iwp) ::  nl            !< local agent counter
3602       INTEGER(iwp) ::  il            !< local counter
3603       INTEGER(iwp) ::  jl            !< local counter
3604       INTEGER(iwp) ::  kl            !< local counter
3605       INTEGER(iwp) ::  nsteps_total  !< number of steps on path
3606       INTEGER(iwp) ::  nsteps_dummy  !< number of steps on path
3607       
3608       REAL(wp), DIMENSION(0:30) ::  ld_path_x !< local dummy agent path to target (x)
3609       REAL(wp), DIMENSION(0:30) ::  ld_path_y !< local dummy agent path to target (y)
3610!
3611!--    Initialize agent path arrays
3612       agents(nl)%path_x    = -1
3613       agents(nl)%path_y    = -1
3614       agents(nl)%path_x(0) = agents(nl)%x
3615       agents(nl)%path_y(0) = agents(nl)%y
3616!
3617!--    Calculate initial path
3618       CALL mas_nav_a_star( agents(nl)%x,   agents(nl)%y,                      &
3619                            agents(nl)%t_x, agents(nl)%t_y, nsteps_total )
3620!
3621!--    Set the rest of the agent path that was just calculated
3622       agents(nl)%path_x(1:nsteps_total) = dummy_path_x(1:nsteps_total)
3623       agents(nl)%path_y(1:nsteps_total) = dummy_path_y(1:nsteps_total)
3624!
3625!--    Iterate through found path and check more intermittent targets need
3626!--    to be added. For this, run pathfinding between every two consecutive
3627!--    intermittent targets.
3628       DO il = 0, MIN(agt_path_size-1, nsteps_total-1)
3629!
3630!--       pathfinding between two consecutive intermittent targets
3631          CALL mas_nav_a_star( agents(nl)%path_x(il),   agents(nl)%path_y(il), &
3632                              agents(nl)%path_x(il+1), agents(nl)%path_y(il+1),&
3633                              nsteps_dummy )
3634          nsteps_dummy = nsteps_dummy - 1
3635!
3636!--       If additional intermittent targets are found, add them to the path
3637          IF ( nsteps_dummy > 0 ) THEN
3638             ld_path_x = -1
3639             ld_path_y = -1
3640             ld_path_x(il+1:il+nsteps_dummy) = dummy_path_x(1:nsteps_dummy)
3641             ld_path_y(il+1:il+nsteps_dummy) = dummy_path_y(1:nsteps_dummy)
3642             kl = 1
3643             DO jl = il+1,nsteps_total
3644               ld_path_x( il+nsteps_dummy+kl ) = agents(nl)%path_x(jl)
3645               ld_path_y( il+nsteps_dummy+kl ) = agents(nl)%path_y(jl)
3646               kl = kl + 1
3647               IF ( kl > agt_path_size ) EXIT
3648             ENDDO
3649             nsteps_total = MIN(nsteps_total + nsteps_dummy, agt_path_size)
3650             agents(nl)%path_x(il+1:nsteps_total) = ld_path_x(il+1:nsteps_total)
3651             agents(nl)%path_y(il+1:nsteps_total) = ld_path_y(il+1:nsteps_total)
3652          ENDIF
3653
3654       ENDDO
3655!
3656!--    reset path counter to first intermittent target
3657       agents(nl)%path_counter = 1
3658
3659    END SUBROUTINE mas_nav_find_path
3660
3661!------------------------------------------------------------------------------!
3662! Description:
3663! ------------
3664!> Reduces the size of connection array to the amount of actual connections
3665!> after all connetions were added to a mesh point
3666!------------------------------------------------------------------------------!
3667    SUBROUTINE mas_nav_reduce_connections ( in_mp )
3668
3669       IMPLICIT NONE
3670
3671       INTEGER(iwp) ::  noc  !< number of connections
3672
3673       INTEGER, DIMENSION(:), ALLOCATABLE ::  dum_cv   !< dummy connected_vertices
3674
3675       REAL(wp), DIMENSION(:), ALLOCATABLE ::  dum_dtv !< dummy distance_to_vertex
3676
3677       TYPE(mesh_point) ::  in_mp
3678
3679       noc = in_mp%noc
3680       ALLOCATE( dum_cv(1:noc),dum_dtv(1:noc) )
3681       dum_cv  = in_mp%connected_vertices(1:noc)
3682       dum_dtv = in_mp%distance_to_vertex(1:noc)
3683       DEALLOCATE( in_mp%connected_vertices, in_mp%distance_to_vertex )
3684       ALLOCATE( in_mp%connected_vertices(1:noc),                    &
3685                 in_mp%distance_to_vertex(1:noc) )
3686       in_mp%connected_vertices(1:noc) = dum_cv(1:noc)
3687       in_mp%distance_to_vertex(1:noc) = dum_dtv(1:noc)
3688
3689    END SUBROUTINE mas_nav_reduce_connections
3690
3691!------------------------------------------------------------------------------!
3692! Description:
3693! ------------
3694!> Initializes a point of the navigation mesh
3695!------------------------------------------------------------------------------!
3696    SUBROUTINE mas_nav_init_mesh_point ( in_mp, pid, vid, x, y )
3697
3698       IMPLICIT NONE
3699
3700       INTEGER(iwp) ::  pid !< polygon ID
3701       INTEGER(iwp) ::  vid !< vertex ID
3702
3703       REAL(wp) ::  x !< x-coordinate
3704       REAL(wp) ::  y !< y-coordinate
3705
3706       TYPE(mesh_point) ::  in_mp !< mesh point to be initialized
3707
3708       in_mp%origin_id          = -1
3709       in_mp%polygon_id         = pid
3710       in_mp%vertex_id          = vid
3711       in_mp%cost_so_far        = 1.d12
3712       in_mp%x                  = x
3713       in_mp%y                  = y
3714       in_mp%x_s                = x
3715       in_mp%y_s                = y
3716       ALLOCATE(in_mp%connected_vertices(1:100),                               &
3717                in_mp%distance_to_vertex(1:100))
3718       in_mp%connected_vertices = -999
3719       in_mp%distance_to_vertex = -999.
3720       in_mp%noc                = 0
3721
3722    END SUBROUTINE mas_nav_init_mesh_point
3723
3724!------------------------------------------------------------------------------!
3725! Description:
3726! ------------
3727!> Reading of namlist from parin file
3728!------------------------------------------------------------------------------!
3729    SUBROUTINE mas_parin
3730
3731       USE control_parameters,                                                 &
3732           ONLY: agent_time_unlimited, multi_agent_system_end,                 &
3733                 multi_agent_system_start
3734
3735       IMPLICIT NONE
3736
3737       CHARACTER (LEN=80) ::  line  !<
3738
3739       NAMELIST /agent_parameters/  a_rand_target,                             &
3740                                    adx,                                       &
3741                                    ady,                                       &
3742                                    agent_maximum_age,                         &
3743                                    agent_time_unlimited,                      &
3744                                    alloc_factor_mas,                          &
3745                                    asl,                                       &
3746                                    asn,                                       &
3747                                    asr,                                       &
3748                                    ass,                                       &
3749                                    at_x,                                      &
3750                                    at_y,                                      &
3751                                    bc_mas_lr,                                 &
3752                                    bc_mas_ns,                                 &
3753                                    coll_t_0,                                  &
3754                                    corner_gate_start,                         &
3755                                    corner_gate_width,                         &
3756                                    dim_size_agtnum_manual,                    &
3757                                    dim_size_factor_agtnum,                    &
3758                                    deallocate_memory_mas,                     &
3759                                    dist_to_int_target,                        &
3760                                    dt_agent,                                  &
3761                                    dt_arel,                                   &
3762                                    dt_write_agent_data,                       &
3763                                    end_time_arel,                             &
3764                                    max_dist_from_path,                        &
3765                                    min_nr_agent,                              &
3766                                    multi_agent_system_end,                    &
3767                                    multi_agent_system_start,                  &
3768                                    number_of_agent_groups,                    &
3769                                    radius_agent,                              &
3770                                    random_start_position_agents,              &
3771                                    read_agents_from_restartfile,              &
3772                                    repuls_agent,                              &
3773                                    repuls_wall,                               &
3774                                    scan_radius_agent,                         &
3775                                    sigma_rep_agent,                           &
3776                                    sigma_rep_wall,                            &
3777                                    step_dealloc_mas,                          &
3778                                    tau_accel_agent
3779
3780!
3781!--    Try to find agent package
3782       REWIND ( 11 )
3783       line = ' '
3784       DO WHILE ( INDEX( line, '&agent_parameters' ) == 0 )
3785          READ ( 11, '(A)', END=20 )  line
3786       ENDDO
3787       BACKSPACE ( 11 )
3788
3789!
3790!--    Read user-defined namelist
3791       READ ( 11, agent_parameters, ERR = 10, END = 20 )
3792
3793!
3794!--    Set flag that indicates that agents are switched on
3795       agents_active = .TRUE.
3796       GOTO 20
3797
3798 10    BACKSPACE( 11 )
3799       READ( 11 , '(A)') line
3800       CALL parin_fail_message( 'agent_parameters', line )
3801
3802 20    CONTINUE
3803
3804    END SUBROUTINE mas_parin
3805
3806!------------------------------------------------------------------------------!
3807! Description:
3808! ------------
3809!> Routine for the whole processor
3810!> Sort all agents into the 4 respective subgrid boxes
3811!------------------------------------------------------------------------------!
3812    SUBROUTINE mas_ps_sort_in_subboxes
3813
3814       IMPLICIT NONE
3815
3816       INTEGER(iwp) ::  i           !< grid box (x)
3817       INTEGER(iwp) ::  ip          !< counter (x)
3818       INTEGER(iwp) ::  is          !< box counter
3819       INTEGER(iwp) ::  j           !< grid box (y)
3820       INTEGER(iwp) ::  jp          !< counter (y)
3821       INTEGER(iwp) ::  m           !< sorting index
3822       INTEGER(iwp) ::  n           !< agent index
3823       INTEGER(iwp) ::  nn          !< agent counter
3824       INTEGER(iwp) ::  sort_index  !< sorting index
3825
3826       INTEGER(iwp), DIMENSION(0:3) ::  sort_count  !< number of agents in one subbox
3827
3828       TYPE(agent_type), DIMENSION(:,:), ALLOCATABLE ::  sort_agents  !< sorted agent array
3829
3830       DO  ip = nxl, nxr
3831          DO  jp = nys, nyn
3832             number_of_agents = agt_count(jp,ip)
3833             IF ( number_of_agents <= 0 )  CYCLE
3834             agents => grid_agents(jp,ip)%agents(1:number_of_agents)
3835
3836             nn = 0
3837             sort_count = 0
3838             ALLOCATE( sort_agents(number_of_agents, 0:3) )
3839
3840             DO  n = 1, number_of_agents
3841                sort_index = 0
3842
3843                IF ( agents(n)%agent_mask )  THEN
3844                   nn = nn + 1
3845!
3846!--                Sorting agents with a binary scheme
3847!--                sort_index=11_2=3_10 -> agent at the left,south subgridbox
3848!--                sort_index=10_2=2_10 -> agent at the left,north subgridbox
3849!--                sort_index=01_2=1_10 -> agent at the right,south subgridbox
3850!--                sort_index=00_2=0_10 -> agent at the right,north subgridbox
3851!--                For this the center of the gridbox is calculated
3852                   i = (agents(n)%x + 0.5_wp * dx) * ddx
3853                   j = (agents(n)%y + 0.5_wp * dy) * ddy
3854
3855                   IF ( i == ip )  sort_index = sort_index + 2
3856                   IF ( j == jp )  sort_index = sort_index + 1
3857
3858                   sort_count(sort_index) = sort_count(sort_index) + 1
3859                   m = sort_count(sort_index)
3860                   sort_agents(m,sort_index) = agents(n)
3861                   sort_agents(m,sort_index)%block_nr = sort_index
3862                ENDIF
3863             ENDDO
3864
3865             nn = 0
3866             DO is = 0,3
3867                grid_agents(jp,ip)%start_index(is) = nn + 1
3868                DO n = 1,sort_count(is)
3869                   nn = nn + 1
3870                   agents(nn) = sort_agents(n,is)
3871                ENDDO
3872                grid_agents(jp,ip)%end_index(is) = nn
3873             ENDDO
3874
3875             number_of_agents = nn
3876             agt_count(jp,ip) = number_of_agents
3877             DEALLOCATE(sort_agents)
3878          ENDDO
3879       ENDDO
3880
3881    END SUBROUTINE mas_ps_sort_in_subboxes
3882
3883!------------------------------------------------------------------------------!
3884! Description:
3885! ------------
3886!> Move all agents not marked for deletion to lowest indices (packing)
3887!------------------------------------------------------------------------------!
3888    SUBROUTINE mas_ps_pack
3889
3890       IMPLICIT NONE
3891
3892       INTEGER(iwp) ::  n  !< agent counter
3893       INTEGER(iwp) ::  nn !< number of agents
3894!
3895!--    Find out elements marked for deletion and move data from highest index
3896!--    values to these free indices
3897       nn = number_of_agents
3898
3899       DO WHILE ( .NOT. agents(nn)%agent_mask )
3900          nn = nn-1
3901          IF ( nn == 0 )  EXIT
3902       ENDDO
3903
3904       IF ( nn > 0 )  THEN
3905          DO  n = 1, number_of_agents
3906             IF ( .NOT. agents(n)%agent_mask )  THEN
3907                agents(n) = agents(nn)
3908                nn = nn - 1
3909                DO WHILE ( .NOT. agents(nn)%agent_mask )
3910                   nn = nn-1
3911                   IF ( n == nn )  EXIT
3912                ENDDO
3913             ENDIF
3914             IF ( n == nn )  EXIT
3915          ENDDO
3916       ENDIF
3917
3918!
3919!--    The number of deleted agents has been determined in routines
3920!--    mas_boundary_conds, mas_droplet_collision, and mas_eh_exchange_horiz
3921       number_of_agents = nn
3922
3923    END SUBROUTINE mas_ps_pack 
3924
3925!------------------------------------------------------------------------------!
3926! Description:
3927! ------------
3928!> Sort agents in each sub-grid box into two groups: agents that already
3929!> completed the LES timestep, and agents that need further timestepping to
3930!> complete the LES timestep.
3931!------------------------------------------------------------------------------!
3932!    SUBROUTINE mas_ps_sort_timeloop_done
3933!
3934!       IMPLICIT NONE
3935!
3936!       INTEGER(iwp) :: end_index     !< agent end index for each sub-box
3937!       INTEGER(iwp) :: i             !< index of agent grid box in x-direction
3938!       INTEGER(iwp) :: j             !< index of agent grid box in y-direction
3939!       INTEGER(iwp) :: n             !< running index for number of agents
3940!       INTEGER(iwp) :: nb            !< index of subgrid boux
3941!       INTEGER(iwp) :: nf            !< indices for agents in each sub-box that already finalized their substeps
3942!       INTEGER(iwp) :: nnf           !< indices for agents in each sub-box that need further treatment
3943!       INTEGER(iwp) :: num_finalized !< number of agents in each sub-box that already finalized their substeps
3944!       INTEGER(iwp) :: start_index   !< agent start index for each sub-box
3945!
3946!       TYPE(agent_type), DIMENSION(:), ALLOCATABLE :: sort_agents  !< temporary agent array
3947!
3948!       DO  i = nxl, nxr
3949!          DO  j = nys, nyn
3950!
3951!             number_of_agents = agt_count(j,i)
3952!             IF ( number_of_agents <= 0 )  CYCLE
3953!
3954!             agents => grid_agents(j,i)%agents(1:number_of_agents)
3955!
3956!             DO  nb = 0, 3
3957!
3958!--             Obtain start and end index for each subgrid box
3959!                start_index = grid_agents(j,i)%start_index(nb)
3960!                end_index   = grid_agents(j,i)%end_index(nb)
3961!
3962!--             Allocate temporary array used for sorting
3963!                ALLOCATE( sort_agents(start_index:end_index) )
3964!
3965!--             Determine number of agents already completed the LES
3966!--             timestep, and write them into a temporary array
3967!                nf = start_index
3968!                num_finalized = 0
3969!                DO  n = start_index, end_index
3970!                   IF ( dt_3d - agents(n)%dt_sum < 1E-8_wp )  THEN
3971!                      sort_agents(nf) = agents(n)
3972!                      nf              = nf + 1
3973!                      num_finalized   = num_finalized + 1
3974!                   ENDIF
3975!                ENDDO
3976!
3977!--             Determine number of agents that not completed the LES
3978!--             timestep, and write them into a temporary array
3979!                nnf = nf
3980!                DO  n = start_index, end_index
3981!                   IF ( dt_3d - agents(n)%dt_sum > 1E-8_wp )  THEN
3982!                      sort_agents(nnf) = agents(n)
3983!                      nnf              = nnf + 1
3984!                   ENDIF
3985!                ENDDO
3986!
3987!--             Write back sorted agents
3988!                agents(start_index:end_index) =                          &
3989!                                        sort_agents(start_index:end_index)
3990!
3991!--             Determine updated start_index, used to masked already
3992!--             completed agents.
3993!                grid_agents(j,i)%start_index(nb) =                     &
3994!                                   grid_agents(j,i)%start_index(nb)    &
3995!                                 + num_finalized
3996!
3997!--             Deallocate dummy array
3998!                DEALLOCATE ( sort_agents )
3999!
4000!--             Finally, if number of non-completed agents is non zero
4001!--             in any of the sub-boxes, set control flag appropriately.
4002!                IF ( nnf > nf )                                             &
4003!                   grid_agents(j,i)%time_loop_done = .FALSE.
4004!
4005!             ENDDO
4006!          ENDDO
4007!       ENDDO
4008!
4009!    END SUBROUTINE mas_ps_sort_timeloop_done
4010
4011!------------------------------------------------------------------------------!
4012! Description:
4013! ------------
4014!> Calls social forces calculations
4015!------------------------------------------------------------------------------!
4016    SUBROUTINE mas_timestep_forces_call ( ip, jp )
4017
4018       IMPLICIT NONE
4019
4020       INTEGER(iwp) ::  ip  !< counter, x-direction
4021       INTEGER(iwp) ::  jp  !< counter, y-direction
4022       INTEGER(iwp) ::  n   !< loop variable over all agents in a grid box
4023
4024!
4025!--    Get direction for all agents in current grid cell
4026       CALL mas_agent_direction
4027
4028       DO n = 1, number_of_agents
4029
4030          force_x = 0.0_wp
4031          force_y = 0.0_wp
4032
4033          CALL mas_timestep_social_forces ( 'acceleration', n, ip, jp )
4034
4035          CALL mas_timestep_social_forces ( 'other_agents', n, ip, jp )
4036
4037          CALL mas_timestep_social_forces ( 'walls',        n, ip, jp )
4038!
4039!--       Update forces
4040          agents(n)%force_x = force_x
4041          agents(n)%force_y = force_y
4042       ENDDO
4043
4044    END SUBROUTINE mas_timestep_forces_call
4045
4046!------------------------------------------------------------------------------!
4047! Description:
4048! ------------
4049!> Euler timestep of agent transport
4050!------------------------------------------------------------------------------!
4051    SUBROUTINE mas_timestep
4052
4053       IMPLICIT NONE
4054
4055       INTEGER(iwp) ::  n !< loop variable over all agents in a grid box
4056
4057       REAL(wp) ::  abs_v !< absolute value of velocity
4058       REAL(wp) ::  abs_f !< absolute value of force
4059
4060       DO n = 1, number_of_agents
4061!
4062!--       Limit absolute force to a maximum to prevent unrealistic acceleration
4063          abs_f = SQRT((agents(n)%force_x)**2 + (agents(n)%force_y)**2)
4064          IF ( abs_f > 20. ) THEN
4065             agents(n)%force_x = agents(n)%force_x * 20. / abs_f
4066             agents(n)%force_y = agents(n)%force_y * 20. / abs_f
4067          ENDIF
4068!
4069!--       Update agent speed
4070          agents(n)%speed_x = agents(n)%speed_x + agents(n)%force_x * dt_agent
4071          agents(n)%speed_y = agents(n)%speed_y + agents(n)%force_y * dt_agent
4072!
4073!--       Reduction of agent speed to maximum agent speed
4074          abs_v = SQRT((agents(n)%speed_x)**2 + (agents(n)%speed_y)**2)
4075          IF ( abs_v > v_max_agent ) THEN
4076             agents(n)%speed_x = agents(n)%speed_x * v_max_agent / abs_v
4077             agents(n)%speed_y = agents(n)%speed_y * v_max_agent / abs_v
4078          ENDIF
4079!
4080!--       Update agent position
4081          agents(n)%x = agents(n)%x + agents(n)%speed_x * dt_agent
4082          agents(n)%y = agents(n)%y + agents(n)%speed_y * dt_agent
4083!
4084!--       Update absolute value of agent speed
4085          agents(n)%speed_abs = abs_v
4086!
4087!--       Increment the agent age and the total time that the agent
4088!--       has advanced within the agent timestep procedure
4089          agents(n)%age_m  = agents(n)%age
4090          agents(n)%age    = agents(n)%age    + dt_agent
4091          agents(n)%dt_sum = agents(n)%dt_sum + dt_agent
4092!
4093!--       Check whether there is still an agent that has not yet completed
4094!--       the total LES timestep
4095          IF ( ( dt_3d - agents(n)%dt_sum ) > 1E-8_wp )  THEN
4096             dt_3d_reached_l_mas = .FALSE.
4097          ENDIF
4098
4099       ENDDO
4100
4101    END SUBROUTINE mas_timestep
4102
4103!------------------------------------------------------------------------------!
4104! Description:
4105! ------------
4106!> Calculates the Social Forces (Helbing and Molnar, 1995) that the agent
4107!> experiences due to acceleration towards target and repulsion by obstacles
4108!------------------------------------------------------------------------------!
4109    SUBROUTINE mas_timestep_social_forces ( mode, nl, ip, jp )
4110
4111       IMPLICIT NONE
4112
4113       CHARACTER (LEN=*) ::  mode  !< identifier for the mode of calculation
4114
4115       INTEGER(iwp) ::  ij_dum      !< index of nearest wall
4116       INTEGER(iwp) ::  il          !< index variable along x
4117       INTEGER(iwp) ::  ip          !< index variable along x
4118       INTEGER(iwp) ::  jl          !< index variable along y
4119       INTEGER(iwp) ::  jp          !< index variable along y
4120       INTEGER(iwp) ::  nl          !< loop variable over all agents in a grid box
4121       INTEGER(iwp) ::  no          !< loop variable over all agents in a grid box
4122       INTEGER(iwp) ::  noa         !< amount of agents in a grid box
4123       INTEGER(iwp) ::  sc_x_end    !< index for scan for topography/other agents
4124       INTEGER(iwp) ::  sc_x_start  !< index for scan for topography/other agents
4125       INTEGER(iwp) ::  sc_y_end    !< index for scan for topography/other agents
4126       INTEGER(iwp) ::  sc_y_start  !< index for scan for topography/other agents
4127
4128       LOGICAL ::  corner_found  !< flag that indicates a corner has been found near agent
4129
4130       REAL(wp) ::  a_pl             !< factor for collision avoidance
4131       REAL(wp) ::  ax_semimaj       !< semiminor axis of repulsive ellipse
4132       REAL(wp) ::  b_pl             !< factor for collision avoidance
4133       REAL(wp) ::  c_pl             !< factor for collision avoidance
4134       REAL(wp) ::  coll_t           !< time at which the next collision would happen
4135       REAL(wp) ::  d_coll_t_0       !< inverse of collision cutoff time
4136       REAL(wp) ::  d_pl             !< factor for collision avoidance
4137       REAL(wp) ::  ddum_f           !< dummy devisor collision avoidance
4138       REAL(wp) ::  dist             !< distance to obstacle
4139       REAL(wp) ::  dist_sq          !< distance to obstacle squared
4140       REAL(wp) ::  pos_rel_x        !< relative position of two agents (x)
4141       REAL(wp) ::  pos_rel_y        !< relative position of two agents (y)
4142       REAL(wp) ::  r_sq             !< y-position
4143       REAL(wp) ::  sra              !< scan radius (agents)
4144       REAL(wp) ::  srw              !< local variable for scan radius (walls)
4145       REAL(wp) ::  v_rel_x          !< relative velocity (x); collision avoidance
4146       REAL(wp) ::  v_rel_y          !< relative velocity (y); collision avoidance
4147       REAL(wp) ::  x_a              !< x-position
4148       REAL(wp) ::  x_wall           !< x-position of wall
4149       REAL(wp) ::  y_a              !< y-position
4150       REAL(wp) ::  y_wall           !< y-position of wall
4151
4152       REAL(wp), PARAMETER ::  k_pl = 1.5  !< factor for collision avoidance
4153
4154       TYPE(agent_type), DIMENSION(:), POINTER ::  l_agts !< agents that repulse current agent
4155
4156!
4157!--    Initialization
4158       x_a = agents(nl)%x
4159       y_a = agents(nl)%y
4160
4161       SELECT CASE ( TRIM( mode ) )
4162!
4163!--       Calculation of force due to agent trying to approach desired velocity
4164          CASE ( 'acceleration' )
4165
4166             force_x = force_x + d_tau_accel_agent                             &
4167                          * ( agents(nl)%speed_des*agents(nl)%speed_e_x        &
4168                             -agents(nl)%speed_x )
4169
4170             force_y = force_y + d_tau_accel_agent                             &
4171                          * ( agents(nl)%speed_des*agents(nl)%speed_e_y        &
4172                             -agents(nl)%speed_y )
4173
4174!
4175!--       Calculation of repulsive forces by other agents in a radius around the
4176!--       current one
4177          CASE ( 'other_agents' )
4178
4179             sra = scan_radius_agent
4180             d_coll_t_0 = 1./coll_t_0
4181!
4182!--          Find relevant gridboxes (those that could contain agents within
4183!--          scan radius)
4184             sc_x_start = FLOOR( (x_a - sra) * ddx )
4185             sc_x_end   = FLOOR( (x_a + sra) * ddx )
4186             sc_y_start = FLOOR( (y_a - sra) * ddx )
4187             sc_y_end   = FLOOR( (y_a + sra) * ddx )
4188             IF ( sc_x_start < nxlg ) sc_x_start = nxlg
4189             IF ( sc_x_end   > nxrg ) sc_x_end   = nxrg
4190             IF ( sc_y_start < nysg ) sc_y_start = nysg
4191             IF ( sc_y_end   > nyng ) sc_y_end   = nyng
4192
4193             sra = sra**2
4194!
4195!--          Loop over all previously found relevant gridboxes
4196             DO il = sc_x_start, sc_x_end
4197                DO jl = sc_y_start, sc_y_end
4198                   noa = agt_count(jl,il)
4199                   IF ( noa <= 0 )  CYCLE
4200                   l_agts => grid_agents(jl,il)%agents(1:noa)
4201                   DO no = 1, noa
4202!
4203!--                   Skip self
4204                      IF ( jl == jp .AND. il == ip .AND. no == nl ) CYCLE
4205                      pos_rel_x = l_agts(no)%x - x_a
4206                      pos_rel_y = l_agts(no)%y - y_a
4207                      dist_sq = pos_rel_x**2 + pos_rel_y**2
4208                      IF ( dist_sq > sra ) CYCLE
4209                      r_sq    = (2*radius_agent)**2
4210                      v_rel_x   = agents(nl)%speed_x - l_agts(no)%speed_x
4211                      v_rel_y   = agents(nl)%speed_y - l_agts(no)%speed_y
4212!
4213!--                   Collision is already occuring, default to standard
4214!--                   social forces
4215                      IF ( dist_sq <= r_sq ) THEN
4216                         dist = SQRT(dist_sq) + 1.0d-12
4217                         ax_semimaj = .5_wp*SQRT( dist )
4218
4219                         force_x = force_x - 0.125_wp * repuls_agent           &
4220                                        * d_sigma_rep_agent / ax_semimaj       &
4221                                        * EXP( -ax_semimaj*d_sigma_rep_agent ) &
4222                                        * (pos_rel_x/dist)
4223
4224                         force_y = force_y - 0.125_wp * repuls_agent           &
4225                                        * d_sigma_rep_agent / ax_semimaj       &
4226                                        * EXP( -ax_semimaj*d_sigma_rep_agent ) &
4227                                        * (pos_rel_y/dist)
4228!
4229!--                   Currently no collision, calculate collision avoidance
4230!--                   force according to Karamouzas et al (2014, PRL 113,238701)
4231                      ELSE
4232!
4233!--                     factors
4234                         a_pl = v_rel_x**2 +  v_rel_y**2
4235                         b_pl = pos_rel_x*v_rel_x + pos_rel_y*v_rel_y
4236                         c_pl = dist_sq - r_sq
4237                         d_pl = b_pl**2 - a_pl*c_pl
4238!
4239!--                      If the two agents are moving non-parallel, calculate
4240!--                      collision avoidance social force
4241                         IF ( d_pl > 0.0_wp .AND.                              &
4242                            ( a_pl < -0.00001 .OR. a_pl > 0.00001 ) )          &
4243                         THEN
4244
4245                            d_pl   = SQRT(d_pl)
4246                            coll_t = (b_pl - d_pl)/a_pl
4247                            IF ( coll_t > 0.0_wp ) THEN
4248!
4249!--                            Dummy factor
4250                               ddum_f = 1. / ( a_pl * coll_t**2 )              &
4251                                           * ( 2. / coll_t + 1.0 * d_coll_t_0 )
4252!
4253!--                            x-component of social force
4254                               force_x = force_x - k_pl *                      &
4255                                         EXP( -coll_t * d_coll_t_0 ) *         &
4256                                         ( v_rel_x -                           &
4257                                           ( b_pl * v_rel_x -                  &
4258                                             a_pl * pos_rel_x ) / d_pl ) *     &
4259                                         ddum_f
4260!
4261!--                            y-component of social force
4262                               force_y = force_y - k_pl *                      &
4263                                         EXP( -coll_t * d_coll_t_0 ) *         &
4264                                         ( v_rel_y -                           &
4265                                           ( b_pl * v_rel_y -                  &
4266                                             a_pl * pos_rel_y ) / d_pl ) *     &
4267                                         ddum_f
4268
4269                            ENDIF
4270                         ENDIF
4271                      ENDIF
4272                   ENDDO
4273                ENDDO
4274             ENDDO
4275
4276          CASE ( 'walls' )
4277
4278             srw = scan_radius_wall
4279             corner_found = .FALSE.
4280!
4281!--          find relevant grid boxes (those that could contain topography
4282!--          within radius)
4283             sc_x_start = (x_a - srw) * ddx
4284             sc_x_end   = (x_a + srw) * ddx
4285             sc_y_start = (y_a - srw) * ddx
4286             sc_y_end   = (y_a + srw) * ddx
4287             IF ( sc_x_start < nxlg ) sc_x_start = nxlg
4288             IF ( sc_x_end   > nxrg ) sc_x_end   = nxrg
4289             IF ( sc_y_start < nysg ) sc_y_start = nysg
4290             IF ( sc_y_end   > nyng ) sc_y_end   = nyng
4291!
4292!--          Find "walls" ( i.e. topography steps (up or down) higher than one
4293!--          grid box ) that are perpendicular to the agent within the defined
4294!--          search radius. Such obstacles cannot be passed and a social force
4295!--          to that effect is applied.
4296!--          Walls only apply a force perpendicular to the wall to the agent.
4297!--          There is therefore a search for walls directly right, left, south
4298!--          and north of the agent. All other walls are ignored.
4299!--
4300!--          Check for wall left of current agent
4301             ij_dum = 0
4302             IF ( sc_x_start < ip ) THEN
4303                DO il = ip - 1, sc_x_start, -1
4304!
4305!--                Going left from the agent, check for a right wall
4306                   IF ( BTEST( obstacle_flags(jp,il), 2 ) ) THEN
4307!
4308!--                   obstacle found in grid box il, wall at right side
4309                      x_wall = (il+1)*dx
4310!
4311!--                   Calculate force of found wall on agent
4312                      CALL mas_timestep_wall_corner_force( x_a, x_wall, y_a,   &
4313                                                           y_a )
4314!
4315!--                   calculate new x starting index for later scan for corners
4316                      ij_dum = il + 1
4317                      EXIT
4318                   ENDIF
4319                ENDDO
4320             ENDIF
4321             IF ( ij_dum /= 0 ) sc_x_start = ij_dum 
4322
4323!
4324!--          Check for wall right of current agent
4325             ij_dum = 0
4326             IF ( sc_x_end > ip ) THEN
4327                DO il = ip + 1, sc_x_end
4328!
4329!--                Going right from the agent, check for a left wall
4330                   IF ( BTEST( obstacle_flags(jp,il), 6 ) ) THEN
4331!
4332!--                   obstacle found in grid box il, wall at left side
4333                      x_wall = il*dx
4334!
4335!--                   Calculate force of found wall on agent
4336                      CALL mas_timestep_wall_corner_force( x_a, x_wall, y_a,   &
4337                                                           y_a )
4338!
4339!--                   calculate new x end index for later scan for corners
4340                      ij_dum = il - 1
4341                      EXIT
4342                   ENDIF
4343                ENDDO
4344             ENDIF
4345             IF ( ij_dum /= 0 ) sc_x_end = ij_dum 
4346
4347!
4348!--          Check for wall south of current agent
4349             ij_dum = 0
4350             IF ( sc_y_start < jp ) THEN
4351                DO jl = jp - 1, sc_y_start, -1
4352!
4353!--                Going south from the agent, check for a north wall
4354                   IF ( BTEST( obstacle_flags(jl,ip), 0 ) ) THEN
4355!
4356!--                   obstacle found in grid box jl, wall at left side
4357                      y_wall = (jl+1)*dy
4358
4359                      CALL mas_timestep_wall_corner_force( x_a, x_a, y_a,      &
4360                                                           y_wall )
4361!
4362!--                   calculate new y starting index for later scan for corners
4363                      ij_dum = jl + 1
4364                      EXIT
4365                   ENDIF
4366                ENDDO
4367             ENDIF
4368             IF ( ij_dum /= 0 ) sc_y_start = ij_dum 
4369
4370!
4371!--          Check for wall north of current agent
4372             ij_dum = 0
4373             IF ( sc_y_end > jp ) THEN
4374                DO jl = jp + 1, sc_y_end 
4375!
4376!--                Going north from the agent, check for a south wall
4377                   IF ( BTEST( obstacle_flags(jl,ip), 4 ) ) THEN
4378!
4379!--                   obstacle found in grid box jl, wall at left side
4380                      y_wall = jl*dy
4381
4382                      CALL mas_timestep_wall_corner_force( x_a, x_a, y_a,      &
4383                                                           y_wall )
4384!
4385!--                   calculate new y end index for later scan for corners
4386                      ij_dum = jl - 1
4387                   ENDIF
4388                ENDDO
4389             ENDIF
4390             IF ( ij_dum /= 0 ) sc_y_end = ij_dum 
4391
4392!
4393!--          Scan for corners surrounding current agent.
4394!--          Only gridcells that are closer than the closest wall in each
4395!--          direction (n,s,r,l) are considered in the search since those
4396!--          further away would have a significantly smaller resulting force
4397!--          than the closer wall.
4398             DO il = sc_x_start, sc_x_end
4399                DO jl = sc_y_start, sc_y_end
4400                   IF ( il == ip .OR. jl == jp ) CYCLE
4401!
4402!--                corners left of agent
4403                   IF ( il < ip ) THEN
4404!
4405!--                   south left quadrant: look for north right corner
4406                      IF ( jl < jp ) THEN
4407                         IF ( BTEST( obstacle_flags(jl,il), 1 ) ) THEN
4408!
4409!--                         calculate coordinates of the found corner
4410                            x_wall = (il+1)*dx
4411                            y_wall = (jl+1)*dy
4412
4413                            CALL mas_timestep_wall_corner_force( x_a, x_wall,  &
4414                                                                 y_a, y_wall )
4415
4416                         ENDIF
4417!
4418!--                   north left quadrant: look for south right corner
4419                      ELSEIF ( jl > jp ) THEN
4420                         IF ( BTEST( obstacle_flags(jl,il), 3 ) ) THEN
4421!
4422!--                         calculate coordinates of the corner of said gridcell
4423!--                         that is closest to the current agent
4424                            x_wall = (il+1)*dx
4425                            y_wall = jl*dy
4426
4427                            CALL mas_timestep_wall_corner_force( x_a, x_wall,  &
4428                                                                 y_a, y_wall )
4429
4430                         ENDIF
4431                      ENDIF
4432                   ELSEIF ( il > ip ) THEN
4433!
4434!--                   south right quadrant: look for north left corner
4435                      IF ( jl < jp ) THEN
4436                         IF ( BTEST( obstacle_flags(jl,il), 7 ) ) THEN
4437!
4438!--                         calculate coordinates of the corner of said gridcell
4439!--                         that is closest to the current agent
4440                            x_wall = il*dx
4441                            y_wall = (jl+1)*dy
4442
4443                            CALL mas_timestep_wall_corner_force( x_a, x_wall,  &
4444                                                                 y_a, y_wall )
4445
4446                         ENDIF
4447!
4448!--                   north right quadrant: look for south left corner
4449                      ELSEIF ( jl > jp ) THEN
4450                         IF ( BTEST( obstacle_flags(jl,il), 5 ) ) THEN
4451!
4452!--                         calculate coordinates of the corner of said gridcell
4453!--                         that is closest to the current agent
4454                            x_wall = il*dx
4455                            y_wall = jl*dy
4456
4457                            CALL mas_timestep_wall_corner_force( x_a, x_wall,  &
4458                                                                 y_a, y_wall )
4459
4460                         ENDIF
4461                      ENDIF
4462                   ENDIF
4463                ENDDO
4464             ENDDO
4465
4466          CASE DEFAULT
4467
4468       END SELECT
4469
4470    END SUBROUTINE mas_timestep_social_forces
4471
4472!------------------------------------------------------------------------------!
4473! Description:
4474! ------------
4475!> Given a distance to the current agent, calculates the force a found corner
4476!> or wall exerts on that agent
4477!------------------------------------------------------------------------------!
4478    SUBROUTINE mas_timestep_wall_corner_force( xa, xw, ya, yw )
4479
4480       IMPLICIT NONE
4481
4482       REAL(wp) ::  dist_l     !< distance to obstacle
4483       REAL(wp) ::  force_d_x  !< increment of social force, x-direction
4484       REAL(wp) ::  force_d_y  !< increment of social force, x-direction
4485       REAL(wp) ::  xa         !< x-position of agent
4486       REAL(wp) ::  xw         !< x-position of wall
4487       REAL(wp) ::  ya         !< x-position of agent
4488       REAL(wp) ::  yw         !< y-position of wall
4489
4490       force_d_x = 0.0_wp
4491       force_d_y = 0.0_wp
4492!
4493!--    calculate coordinates of corner relative to agent
4494!--    postion and distance between corner and agent
4495       xw = xa - xw
4496       yw = ya - yw
4497       dist_l = SQRT( (xw)**2 + (yw)**2 )
4498!
4499!--    calculate x and y component of repulsive force
4500!--    induced by previously found corner
4501       IF ( dist_l > 0 ) THEN
4502          force_d_x = repuls_wall * d_sigma_rep_wall         &
4503                      * EXP( -dist_l * d_sigma_rep_wall )      &
4504                      * xw / (dist_l)
4505          force_d_y = repuls_wall * d_sigma_rep_wall         &
4506                      * EXP( -dist_l * d_sigma_rep_wall )      &
4507                      * yw / (dist_l)
4508       ENDIF
4509
4510! !--    forces that are located outside of a sight radius of
4511! !--    200° (-> COS(100./180.*pi) = COS(.555*pi)) of
4512! !--    current agent are considered to have an effect of 50%
4513!        IF ( force_d_x * agents(nl)%speed_e_x +               &
4514!             force_d_y * agents(nl)%speed_e_y <               &
4515!             SQRT(force_d_x**2 + force_d_y**2) *              &
4516!             COS( .55555555 * 3.1415 ) )                      &
4517!        THEN
4518!           force_d_x = force_d_x * .5_wp
4519!           force_d_y = force_d_y * .5_wp
4520!        ENDIF
4521
4522!
4523!--    add force increment to total force of current agent
4524       force_x = force_x + force_d_x
4525       force_y = force_y + force_d_y
4526
4527    END SUBROUTINE mas_timestep_wall_corner_force
4528
4529!
4530!-- Calculates distance of point P to edge (A,B). If A = B, calculates
4531!-- point-to-point distance from A/B to P
4532    FUNCTION dist_point_to_edge ( a_x, a_y, b_x, b_y, p_x, p_y )
4533
4534       IMPLICIT NONE
4535
4536       REAL(wp)  :: ab_x                !< x-coordinate of vector from A to B
4537       REAL(wp)  :: ab_y                !< y-coordinate of vector from A to B
4538       REAL(wp)  :: ab_d                !< inverse length of vector from A to B
4539       REAL(wp)  :: ab_u_x              !< x-coordinate of vector with direction of ab and length 1
4540       REAL(wp)  :: ab_u_y              !< y-coordinate of vector with direction of ab and length 1
4541       REAL(wp)  :: ba_x                !< x-coordinate of vector from B to A
4542       REAL(wp)  :: ba_y                !< y-coordinate of vector from B to A
4543       REAL(wp)  :: ap_x                !< x-coordinate of vector from A to P
4544       REAL(wp)  :: ap_y                !< y-coordinate of vector from A to P
4545       REAL(wp)  :: bp_x                !< x-coordinate of vector from B to P
4546       REAL(wp)  :: bp_y                !< y-coordinate of vector from B to P
4547       REAL(wp)  :: a_x                 !< x-coordinate of point A of edge
4548       REAL(wp)  :: a_y                 !< y-coordinate of point A of edge
4549       REAL(wp)  :: b_x                 !< x-coordinate of point B of edge
4550       REAL(wp)  :: b_y                 !< y-coordinate of point B of edge
4551       REAL(wp)  :: p_x                 !< x-coordinate of point P
4552       REAL(wp)  :: p_y                 !< y-coordinate of point P
4553       REAL(wp)  :: dist_x              !< x-coordinate of point P
4554       REAL(wp)  :: dist_y              !< y-coordinate of point P
4555       REAL(wp)  :: dist_point_to_edge  !< y-coordinate of point P
4556
4557       ab_x = - a_x + b_x
4558       ab_y = - a_y + b_y
4559       ba_x = - b_x + a_x 
4560       ba_y = - b_y + a_y 
4561       ap_x = - a_x + p_x
4562       ap_y = - a_y + p_y
4563       bp_x = - b_x + p_x
4564       bp_y = - b_y + p_y
4565
4566       IF ( ab_x * ap_x + ab_y * ap_y <= 0. ) THEN
4567          dist_point_to_edge = SQRT((a_x - p_x)**2 + (a_y - p_y)**2)
4568       ELSEIF ( ba_x * bp_x + ba_y * bp_y <= 0. ) THEN
4569          dist_point_to_edge = SQRT((b_x - p_x)**2 + (b_y - p_y)**2)
4570       ELSE
4571          ab_d = 1./SQRT((ab_x)**2+(ab_y)**2)
4572          ab_u_x = ab_x*ab_d
4573          ab_u_y = ab_y*ab_d
4574          dist_x = ap_x - (ap_x*ab_u_x+ap_y*ab_u_y)*ab_u_x
4575          dist_y = ap_y - (ap_x*ab_u_x+ap_y*ab_u_y)*ab_u_y
4576          dist_point_to_edge = SQRT( dist_x**2 + dist_y**2 )
4577       ENDIF
4578
4579    END FUNCTION dist_point_to_edge
4580
4581!
4582!-- Returns the heuristic between points A and B (currently the straight
4583!-- distance)
4584    FUNCTION heuristic ( ax, ay, bx, by )
4585
4586       IMPLICIT NONE
4587
4588       REAL(wp)  :: ax           !< x-coordinate of point A
4589       REAL(wp)  :: ay           !< y-coordinate of point A
4590       REAL(wp)  :: bx           !< x-coordinate of point B
4591       REAL(wp)  :: by           !< y-coordinate of point B
4592       REAL(wp)  :: heuristic    !< return value
4593
4594       heuristic = SQRT(( ax - bx )**2 + ( ay - by )**2)
4595
4596    END FUNCTION heuristic 
4597
4598!
4599!-- Calculates if point P is left of the infinite
4600!-- line that contains A and B (direction: A to B)
4601!-- Concept: 2D rotation of two vectors
4602    FUNCTION is_left ( ax, ay, bx, by, px, py )
4603
4604       IMPLICIT NONE
4605
4606       LOGICAL  :: is_left !< return value; TRUE if P is left of AB
4607
4608       REAL(wp)  :: ax     !< x-coordinate of point A
4609       REAL(wp)  :: ay     !< y-coordinate of point A
4610       REAL(wp)  :: bx     !< x-coordinate of point B
4611       REAL(wp)  :: by     !< y-coordinate of point B
4612       REAL(wp)  :: px     !< x-coordinate of point P
4613       REAL(wp)  :: py     !< y-coordinate of point P
4614
4615       is_left = (bx-ax)*(py-ay)-(px-ax)*(by-ay) > 0
4616       IF ( (ABS(ax-px) < .001 .AND. ABS(ay-py) < .001) .OR.                  &
4617            (ABS(bx-px) < .001 .AND. ABS(by-py) < .001) )                     &
4618       THEN
4619          is_left = .FALSE.
4620       ENDIF
4621
4622       RETURN
4623
4624    END FUNCTION is_left 
4625
4626!
4627!-- Calculates if point P is right of the infinite
4628!-- line that contains A and B (direction: A to B)
4629!-- Concept: 2D rotation of two vectors
4630    FUNCTION is_right ( ax, ay, bx, by, px, py )
4631
4632       IMPLICIT NONE
4633
4634       LOGICAL  :: is_right !< return value; TRUE if P is right of AB
4635
4636       REAL(wp), INTENT(IN)  :: ax     !< x-coordinate of point A
4637       REAL(wp), INTENT(IN)  :: ay     !< y-coordinate of point A
4638       REAL(wp), INTENT(IN)  :: bx     !< x-coordinate of point B
4639       REAL(wp), INTENT(IN)  :: by     !< y-coordinate of point B
4640       REAL(wp), INTENT(IN)  :: px     !< x-coordinate of point P
4641       REAL(wp), INTENT(IN)  :: py     !< y-coordinate of point P
4642
4643       is_right = (bx-ax)*(py-ay)-(px-ax)*(by-ay) < 0
4644       IF ( (ABS(ax-px) < .001 .AND. ABS(ay-py) < .001) .OR.                  &
4645            (ABS(bx-px) < .001 .AND. ABS(by-py) < .001) )                     &
4646       THEN
4647          is_right = .FALSE.
4648       ENDIF
4649
4650       RETURN
4651
4652    END FUNCTION is_right 
4653
4654!
4655!-- Returns true if the line segments AB and PQ share an intersection
4656    FUNCTION intersect ( ax, ay, bx, by, px, py, qx, qy )
4657
4658       IMPLICIT NONE
4659
4660       LOGICAL  :: intersect !< return value; TRUE if intersection was found
4661       LOGICAL  :: la        !< T if a is left of PQ
4662       LOGICAL  :: lb        !< T if b is left of PQ
4663       LOGICAL  :: lp        !< T if p is left of AB
4664       LOGICAL  :: lq        !< T if q is left of AB
4665       LOGICAL  :: poss      !< flag that indicates if an intersection is still possible
4666       LOGICAL  :: ra        !< T if a is right of PQ
4667       LOGICAL  :: rb        !< T if b is right of PQ
4668       LOGICAL  :: rp        !< T if p is right of AB
4669       LOGICAL  :: rq        !< T if q is right of AB
4670
4671       REAL(wp)  :: ax     !< x-coordinate of point A
4672       REAL(wp)  :: ay     !< y-coordinate of point A
4673       REAL(wp)  :: bx     !< x-coordinate of point B
4674       REAL(wp)  :: by     !< y-coordinate of point B
4675       REAL(wp)  :: px     !< x-coordinate of point P
4676       REAL(wp)  :: py     !< y-coordinate of point P
4677       REAL(wp)  :: qx     !< x-coordinate of point Q
4678       REAL(wp)  :: qy     !< y-coordinate of point Q
4679
4680       intersect = .FALSE.
4681       poss      = .FALSE.
4682!
4683!--    Intersection is possible only if P and Q are on opposing sides of AB
4684       lp = is_left(ax,ay,bx,by,px,py)
4685       rq = is_right(ax,ay,bx,by,qx,qy)
4686       IF ( lp .AND. rq ) poss = .TRUE.
4687       IF ( .NOT. poss ) THEN
4688          lq = is_left(ax,ay,bx,by,qx,qy)
4689          rp = is_right(ax,ay,bx,by,px,py)
4690          IF ( lq .AND. rp ) poss = .TRUE.
4691       ENDIF
4692!
4693!--    Intersection occurs only if above test (poss) was true AND
4694!--    A and B are on opposing sides of PQ
4695       IF ( poss ) THEN
4696          la = is_left(px,py,qx,qy,ax,ay)
4697          rb = is_right(px,py,qx,qy,bx,by)
4698          IF ( la .AND. rb ) intersect = .TRUE.
4699          IF ( .NOT. intersect ) THEN
4700             lb = is_left(px,py,qx,qy,bx,by)
4701             ra = is_right(px,py,qx,qy,ax,ay)
4702             IF ( lb .AND. ra ) intersect = .TRUE.
4703          ENDIF
4704       ENDIF
4705
4706       RETURN
4707
4708    END FUNCTION intersect 
4709
4710!
4711!-- Gives a nuber randomly distributed around an average
4712    FUNCTION random_normal ( avg, variation )
4713
4714       IMPLICIT NONE
4715
4716       REAL(wp)  :: avg            !< x-coordinate of vector from A to B
4717       REAL(wp)  :: variation      !< y-coordinate of vector from A to B
4718       REAL(wp)  :: random_normal  !< y-coordinate of vector from A to B
4719
4720       REAL(wp), DIMENSION(12)  :: random_arr  !< inverse length of vector from A to B
4721
4722       CALL RANDOM_NUMBER(random_arr)
4723       random_normal = avg + variation*(SUM(random_arr)-6.)
4724
4725    END FUNCTION random_normal
4726
4727
4728 END MODULE multi_agent_system_mod
Note: See TracBrowser for help on using the repository browser.