Ignore:
Timestamp:
Jan 17, 2017 4:38:49 PM (7 years ago)
Author:
raasch
Message:

all OpenACC directives and related parts removed from the code

File:
1 edited

Legend:

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

    r2108 r2118  
    2020! Current revisions:
    2121! ------------------
    22 !
     22! -acc_rank, background_communication, i_left, i_right, j_south, j_north,
     23!  num_acc_per_node, on_device
    2324!
    2425! Former revisions:
     
    11421143    LOGICAL ::  nudging = .FALSE.                            !<
    11431144    LOGICAL ::  ocean = .FALSE.                              !<
    1144     LOGICAL ::  on_device = .FALSE.                          !<
    11451145    LOGICAL ::  outflow_l = .FALSE.                          !<
    11461146    LOGICAL ::  outflow_n = .FALSE.                          !<
     
    15571557    USE kinds
    15581558
    1559     INTEGER(iwp) ::  i_left       !<
    1560     INTEGER(iwp) ::  i_right      !<
    1561     INTEGER(iwp) ::  j_north      !<
    1562     INTEGER(iwp) ::  j_south      !<
    15631559    INTEGER(iwp) ::  nbgp = 3     !<
    15641560    INTEGER(iwp) ::  ngp_sums     !<
     
    18011797    CHARACTER(LEN=7) ::  myid_char = ''
    18021798   
    1803     INTEGER(iwp) ::  acc_rank                    !<
    18041799    INTEGER(iwp) ::  comm1dx                     !<
    18051800    INTEGER(iwp) ::  comm1dy                     !<
     
    18241819    INTEGER(iwp) ::  numprocs = 1                !<
    18251820    INTEGER(iwp) ::  numprocs_previous_run = -1  !<
    1826     INTEGER(iwp) ::  num_acc_per_node = 0        !<
    18271821    INTEGER(iwp) ::  pleft                       !<
    18281822    INTEGER(iwp) ::  pnorth                      !<
     
    18481842    INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  hor_index_bounds_previous_run  !<
    18491843
    1850     LOGICAL ::  background_communication =.FALSE.  !<
    18511844    LOGICAL ::  collective_wait = .FALSE.          !<
    18521845    LOGICAL ::  sendrecv_in_background = .FALSE.   !<
Note: See TracChangeset for help on using the changeset viewer.