Ignore:
Timestamp:
Aug 15, 2018 9:23:10 AM (6 years ago)
Author:
sward
Message:

Added MAS end time, used time_since_reference_point, corrected tolerance_dp in nav_mesh

File:
1 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/SOURCE/multi_agent_system_mod.f90

    r3187 r3198  
    2525! -----------------
    2626! $Id$
     27! Now using time_since_reference_point; moved multi_agent_system_start and
     28! multi_agent_system_end to control_parameters; renamed NAMELIST agents_par to
     29! agent_parameters
     30!
     31! 3187 2018-07-31 10:32:34Z sward
    2732! Reworked agent pathfinding to avoid collisions with walls
    2833!
     
    5661
    5762    USE control_parameters,                                                    &
    58         ONLY:  dt_3d, message_string, simulated_time, dt_write_agent_data
     63        ONLY:  dt_3d, message_string, time_since_reference_point, dt_write_agent_data
    5964
    6065    USE cpulog,                                                                &
     
    121126    LOGICAL, DIMENSION(max_number_of_agent_groups) ::  a_rand_target = .FALSE. !< namelist parameter (see documentation)
    122127
    123     REAL(wp) ::  agent_maximum_age = 9999999.9_wp    !< namelist parameter (see documentation)
    124     REAL(wp) ::  alloc_factor_mas = 20.0_wp          !< namelist parameter (see documentation)
    125     REAL(wp) ::  coll_t_0 = 3.                       !< namelist parameter (see documentation)
    126     REAL(wp) ::  corner_gate_start = 0.5_wp          !< namelist parameter (see documentation)
    127     REAL(wp) ::  corner_gate_width = 1.0_wp          !< namelist parameter (see documentation)   
    128     REAL(wp) ::  d_sigma_rep_agent                   !< inverse of sigma_rep_agent
    129     REAL(wp) ::  d_sigma_rep_wall                    !< inverse of sigma_rep_wall
    130     REAL(wp) ::  d_tau_accel_agent                   !< inverse of tau_accel_agent
    131     REAL(wp) ::  desired_speed = 1.2_wp              !< namelist parameter (see documentation)
    132     REAL(wp) ::  des_sp_sig = .2_wp                  !< namelist parameter (see documentation)
    133     REAL(wp) ::  dist_target_reached = 2.0_wp        !< distance at which target counts as reached
    134     REAL(wp) ::  dist_to_int_target = .25_wp         !< namelist parameter (see documentation)
    135     REAL(wp) ::  dt_agent = 0.02_wp                  !< namelist parameter (see documentation)
    136     REAL(wp) ::  dt_arel = 9999999.9_wp              !< namelist parameter (see documentation)
    137     REAL(wp) ::  end_time_arel = 9999999.9_wp        !< namelist parameter (see documentation)
    138     REAL(wp) ::  force_x                             !< dummy value for force on current agent in x-direction
    139     REAL(wp) ::  force_y                             !< dummy value for force on current agent in y-direction
    140     REAL(wp) ::  max_dist_from_path = 0.25_wp        !< distance from current path at which a new path is calculated
    141     REAL(wp) ::  multi_agent_system_start = 0.0_wp   !< namelist parameter (see documentation)
    142     REAL(wp) ::  radius_agent = .25_wp               !< namelist parameter (see documentation)
    143     REAL(wp) ::  repuls_agent = 1.5_wp               !< namelist parameter (see documentation)
    144     REAL(wp) ::  repuls_wall = 7.0_wp                !< namelist parameter (see documentation)
    145     REAL(wp) ::  scan_radius_agent = 3.0_wp          !< namelist parameter (see documentation)
    146     REAL(wp) ::  scan_radius_wall = 2.0_wp           !< namelist parameter (see documentation)
    147     REAL(wp) ::  sigma_rep_agent = 0.3_wp            !< namelist parameter (see documentation)
    148     REAL(wp) ::  sigma_rep_wall = 0.1_wp             !< namelist parameter (see documentation)
    149     REAL(wp) ::  tau_accel_agent = 0.5_wp            !< namelist parameter (see documentation)
    150     REAL(wp) ::  time_arel = 0.0_wp                  !< time for agent release
    151     REAL(wp) ::  time_write_agent_data = 0.0_wp      !< write agent data at current time on file
    152     REAL(wp) ::  v_max_agent = 1.3_wp                !< namelist parameter (see documentation)
     128    REAL(wp) ::  agent_maximum_age = 9999999.9_wp          !< namelist parameter (see documentation)
     129    REAL(wp) ::  alloc_factor_mas = 20.0_wp                !< namelist parameter (see documentation)
     130    REAL(wp) ::  coll_t_0 = 3.                             !< namelist parameter (see documentation)
     131    REAL(wp) ::  corner_gate_start = 0.5_wp                !< namelist parameter (see documentation)
     132    REAL(wp) ::  corner_gate_width = 1.0_wp                !< namelist parameter (see documentation)   
     133    REAL(wp) ::  d_sigma_rep_agent                         !< inverse of sigma_rep_agent
     134    REAL(wp) ::  d_sigma_rep_wall                          !< inverse of sigma_rep_wall
     135    REAL(wp) ::  d_tau_accel_agent                         !< inverse of tau_accel_agent
     136    REAL(wp) ::  desired_speed = 1.2_wp                    !< namelist parameter (see documentation)
     137    REAL(wp) ::  des_sp_sig = .2_wp                        !< namelist parameter (see documentation)
     138    REAL(wp) ::  dist_target_reached = 2.0_wp              !< distance at which target counts as reached
     139    REAL(wp) ::  dist_to_int_target = .25_wp               !< namelist parameter (see documentation)
     140    REAL(wp) ::  dt_agent = 0.02_wp                        !< namelist parameter (see documentation)
     141    REAL(wp) ::  dt_arel = 9999999.9_wp                    !< namelist parameter (see documentation)
     142    REAL(wp) ::  end_time_arel = 9999999.9_wp              !< namelist parameter (see documentation)
     143    REAL(wp) ::  force_x                                   !< dummy value for force on current agent in x-direction
     144    REAL(wp) ::  force_y                                   !< dummy value for force on current agent in y-direction
     145    REAL(wp) ::  max_dist_from_path = 0.25_wp              !< distance from current path at which a new path is calculated
     146    REAL(wp) ::  radius_agent = .25_wp                     !< namelist parameter (see documentation)
     147    REAL(wp) ::  repuls_agent = 1.5_wp                     !< namelist parameter (see documentation)
     148    REAL(wp) ::  repuls_wall = 7.0_wp                      !< namelist parameter (see documentation)
     149    REAL(wp) ::  scan_radius_agent = 3.0_wp                !< namelist parameter (see documentation)
     150    REAL(wp) ::  scan_radius_wall = 2.0_wp                 !< namelist parameter (see documentation)
     151    REAL(wp) ::  sigma_rep_agent = 0.3_wp                  !< namelist parameter (see documentation)
     152    REAL(wp) ::  sigma_rep_wall = 0.1_wp                   !< namelist parameter (see documentation)
     153    REAL(wp) ::  tau_accel_agent = 0.5_wp                  !< namelist parameter (see documentation)
     154    REAL(wp) ::  time_arel = 0.0_wp                        !< time for agent release
     155    REAL(wp) ::  time_write_agent_data = 0.0_wp            !< write agent data at current time on file
     156    REAL(wp) ::  v_max_agent = 1.3_wp                      !< namelist parameter (see documentation)
    153157
    154158    REAL(wp), DIMENSION(:), ALLOCATABLE ::  dummy_path_x  !<  dummy path (x-coordinate)
     
    269273!
    270274!-- Public parameters, constants and initial values
    271     PUBLIC agents_active, multi_agent_system_start
     275    PUBLIC agents_active
    272276
    273277    INTERFACE mas_parin
     
    318322!
    319323!-- If necessary, release new set of agents
    320     IF ( time_arel >= dt_arel  .AND.  end_time_arel > simulated_time )  THEN
     324    IF ( time_arel >= dt_arel  .AND.  end_time_arel > time_since_reference_point )  THEN
    321325
    322326       CALL mas_create_agent(PHASE_RELEASE)
     
    12231227
    12241228          nc_stat = NF90_PUT_VAR( id_set_agt, id_var_time_agt, &
    1225                                   (/ simulated_time /),        &
     1229                                  (/ time_since_reference_point /),        &
    12261230                                  start = (/ agt_time_count /), count = (/ 1 /) )
    12271231          CALL netcdf_handle_error( 'mas_data_output_agents', 1 )
     
    36383642
    36393643       USE control_parameters,                                                 &
    3640            ONLY: agent_time_unlimited
     3644           ONLY: agent_time_unlimited, multi_agent_system_end,                 &
     3645                 multi_agent_system_start
    36413646
    36423647       IMPLICIT NONE
     
    36443649       CHARACTER (LEN=80) ::  line  !<
    36453650
    3646        NAMELIST /agents_par/  a_rand_target, adx, ady, agent_maximum_age,      &
    3647                               agent_time_unlimited, alloc_factor_mas, asl, asn,&
    3648                               asr, ass, at_x, at_y, bc_mas_lr, bc_mas_ns,      &
    3649                               coll_t_0, corner_gate_start, corner_gate_width,  &
    3650                               deallocate_memory_mas, dist_to_int_target,       &
    3651                               dt_agent, dt_arel, dt_write_agent_data,&
    3652                               end_time_arel, max_dist_from_path, min_nr_agent, &
    3653                               multi_agent_system_start, number_of_agent_groups,&
    3654                               radius_agent, random_start_position_agents,      &
    3655                               read_agents_from_restartfile, repuls_agent,      &
    3656                               repuls_wall, scan_radius_agent, sigma_rep_agent, &
    3657                               sigma_rep_wall, step_dealloc_mas, tau_accel_agent
     3651       NAMELIST /agent_parameters/  a_rand_target,                             &
     3652                                    adx,                                       &
     3653                                    ady,                                       &
     3654                                    agent_maximum_age,                         &
     3655                                    agent_time_unlimited,                      &
     3656                                    alloc_factor_mas,                          &
     3657                                    asl,                                       &
     3658                                    asn,                                       &
     3659                                    asr,                                       &
     3660                                    ass,                                       &
     3661                                    at_x,                                      &
     3662                                    at_y,                                      &
     3663                                    bc_mas_lr,                                 &
     3664                                    bc_mas_ns,                                 &
     3665                                    coll_t_0,                                  &
     3666                                    corner_gate_start,                         &
     3667                                    corner_gate_width,                         &
     3668                                    deallocate_memory_mas,                     &
     3669                                    dist_to_int_target,                        &
     3670                                    dt_agent,                                  &
     3671                                    dt_arel,                                   &
     3672                                    dt_write_agent_data,                       &
     3673                                    end_time_arel,                             &
     3674                                    max_dist_from_path,                        &
     3675                                    min_nr_agent,                              &
     3676                                    multi_agent_system_end,                    &
     3677                                    multi_agent_system_start,                  &
     3678                                    number_of_agent_groups,                    &
     3679                                    radius_agent,                              &
     3680                                    random_start_position_agents,              &
     3681                                    read_agents_from_restartfile,              &
     3682                                    repuls_agent,                              &
     3683                                    repuls_wall,                               &
     3684                                    scan_radius_agent,                         &
     3685                                    sigma_rep_agent,                           &
     3686                                    sigma_rep_wall,                            &
     3687                                    step_dealloc_mas,                          &
     3688                                    tau_accel_agent
    36583689
    36593690!
     
    36613692       REWIND ( 11 )
    36623693       line = ' '
    3663        DO   WHILE ( INDEX( line, '&agents_par' ) == 0 )
     3694       DO   WHILE ( INDEX( line, '&agent_parameters' ) == 0 )
    36643695          READ ( 11, '(A)', END=20 )  line
    36653696       ENDDO
     
    36683699!
    36693700!--    Read user-defined namelist
    3670        READ ( 11, agents_par )
     3701       READ ( 11, agent_parameters )
    36713702
    36723703!
Note: See TracChangeset for help on using the changeset viewer.