Ignore:
Timestamp:
Mar 5, 2020 3:59:50 PM (4 years ago)
Author:
raasch
Message:

bugfix: cpp-directives for serial mode added

File:
1 edited

Legend:

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

    r4346 r4444  
    2525! -----------------
    2626! $Id$
     27! bugfix: cpp-directives for serial mode added
     28!
     29! 4346 2019-12-18 11:55:56Z motisi
    2730! Removed wall_flags_static_0 from USE statements as it's not used within
    2831! the module
     
    115118    INTEGER(iwp) ::  iran_agent = -1234567             !< number for random generator
    116119    INTEGER(iwp) ::  min_nr_agent = 2                  !< namelist parameter (see documentation)
     120#if defined( __parallel )
    117121    INTEGER(iwp) ::  ghla_count_recv                   !< number of agents in left ghost layer
    118122    INTEGER(iwp) ::  ghna_count_recv                   !< number of agents in north ghost layer
    119123    INTEGER(iwp) ::  ghra_count_recv                   !< number of agents in right ghost layer
    120124    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
    122125    INTEGER(iwp) ::  nr_move_north                     !< number of agts to move north during exchange_horiz
    123126    INTEGER(iwp) ::  nr_move_south                     !< number of agts to move south during exchange_horiz
     127#endif
     128    INTEGER(iwp) ::  maximum_number_of_agents = 0      !< maximum number of agents during run
    124129    INTEGER(iwp) ::  number_of_agents = 0              !< number of agents for each grid box (3d array is saved on agt_count)
    125130    INTEGER(iwp) ::  number_of_agent_groups = 1        !< namelist parameter (see documentation)
     
    239244    TYPE(agent_type), DIMENSION(:), POINTER ::  agents               !< Agent array for this grid cell
    240245    TYPE(agent_type)                        ::  zero_agent           !< zero agent to avoid weird thing
     246#if defined( __parallel )
    241247    TYPE(agent_type), DIMENSION(:), ALLOCATABLE ::  move_also_north  !< for agent exchange between PEs
    242248    TYPE(agent_type), DIMENSION(:), ALLOCATABLE ::  move_also_south  !< for agent exchange between PEs
     
    245251    TYPE(agent_type), DIMENSION(:), ALLOCATABLE ::  agt_gh_r         !< ghost layer right of pe domain
    246252    TYPE(agent_type), DIMENSION(:), ALLOCATABLE ::  agt_gh_s         !< ghost layer south of pe domain
     253#endif
    247254!
    248255!-- Type for 2D grid on which agents are stored
     
    12161223       IMPLICIT NONE
    12171224
     1225#if defined( __parallel )
    12181226       INTEGER(iwp) ::  agt_size !< Agent size in bytes
     1227       INTEGER(iwp) ::  n        !< counter (number of PEs)
     1228       INTEGER(iwp) ::  noa_rcv  !< received number of agents
     1229#endif
    12191230       INTEGER(iwp) ::  dummy    !< dummy
    12201231       INTEGER(iwp) ::  ii       !< counter (x)
    12211232       INTEGER(iwp) ::  ip       !< counter (x)
    12221233       INTEGER(iwp) ::  jp       !< counter (y)
    1223        INTEGER(iwp) ::  n        !< counter (number of PEs)
    12241234       INTEGER(iwp) ::  noa      !< number of agents
    1225        INTEGER(iwp) ::  noa_rcv  !< received number of agents
    12261235       INTEGER(iwp) ::  out_noa  !< number of agents for output
    12271236
     1237#if defined( __parallel )
    12281238       INTEGER(iwp), DIMENSION(0:numprocs-1) ::  noa_arr !< number of agents on each PE
     1239#endif
    12291240!
    12301241!--    SAVE attribute required to avoid compiler warning about pointer outlive the pointer target
    12311242       TYPE(agent_type), DIMENSION(:), ALLOCATABLE, TARGET, SAVE ::  trf_agents !< all agents on current PE
     1243#if defined( __parallel )
    12321244       TYPE(agent_type), DIMENSION(:), ALLOCATABLE, TARGET, SAVE ::  out_agents !< all agents in entire domain
     1245#endif
    12331246
    12341247       LOGICAL, INTENT (INOUT) :: ftest
     
    14541467    END SUBROUTINE mas_data_output_agents
    14551468
     1469#if defined( __parallel )
    14561470!------------------------------------------------------------------------------!
    14571471! Description:
     
    15961610
    15971611    END SUBROUTINE mas_eh_add_agents_to_gridcell
    1598 
     1612#endif
     1613
     1614
     1615#if defined( __parallel )
    15991616!------------------------------------------------------------------------------!
    16001617! Description:
     
    16481665       ENDDO
    16491666    END SUBROUTINE mas_eh_add_ghost_agents_to_gridcell
     1667#endif
    16501668
    16511669!------------------------------------------------------------------------------!
     
    17421760       IMPLICIT NONE
    17431761
     1762       INTEGER(iwp) ::  ip               !< index variable along x
     1763       INTEGER(iwp) ::  jp               !< index variable along y
     1764       INTEGER(iwp) ::  n                !< agent index variable
     1765
     1766#if defined( __parallel )
     1767
    17441768       INTEGER(iwp) ::  i                !< grid index (x) of agent positition
    1745        INTEGER(iwp) ::  ip               !< index variable along x
    17461769       INTEGER(iwp) ::  j                !< grid index (y) of agent positition
    1747        INTEGER(iwp) ::  jp               !< index variable along y
    1748        INTEGER(iwp) ::  n                !< agent index variable
    17491770       INTEGER(iwp) ::  par_size         !< Agent size in bytes
     1771
    17501772       INTEGER(iwp) ::  trla_count       !< number of agents send to left PE
    17511773       INTEGER(iwp) ::  trla_count_recv  !< number of agents receive from right PE
     
    17651787       TYPE(agent_type), DIMENSION(:), ALLOCATABLE ::  trra  !< agents send to right PE
    17661788       TYPE(agent_type), DIMENSION(:), ALLOCATABLE ::  trsa  !< agents send to south PE
    1767 
    1768 #if defined( __parallel )
    17691789
    17701790!
     
    22282248       DEALLOCATE( move_also_south )
    22292249
     2250!
     2251!--    Accumulate the number of agents transferred between the subdomains)
     2252       CALL mas_eh_ghost_exchange
     2253
    22302254#else
    22312255
     
    23162340#endif
    23172341
    2318 !
    2319 !--    Accumulate the number of agents transferred between the subdomains)
    2320        CALL mas_eh_ghost_exchange
    2321 
    23222342    END SUBROUTINE mas_eh_exchange_horiz
    23232343
     2344
     2345#if defined( __parallel )
    23242346!------------------------------------------------------------------------------!
    23252347! Description:
     
    23322354
    23332355       IMPLICIT NONE
    2334 
    2335 #if defined( __parallel )
    23362356
    23372357       INTEGER(iwp) ::  ip          !< index variable along x
     
    26172637       ENDIF
    26182638
     2639    END SUBROUTINE mas_eh_ghost_exchange
    26192640#endif
    2620 
    2621     END SUBROUTINE mas_eh_ghost_exchange
    26222641
    26232642!------------------------------------------------------------------------------!
     
    39223941    END SUBROUTINE mas_ps_sort_in_subboxes
    39233942
     3943#if defined( __parallel )
    39243944!------------------------------------------------------------------------------!
    39253945! Description:
     
    39623982       number_of_agents = nn
    39633983
    3964     END SUBROUTINE mas_ps_pack
     3984    END SUBROUTINE mas_ps_pack
     3985#endif
    39653986
    39663987!------------------------------------------------------------------------------!
Note: See TracChangeset for help on using the changeset viewer.