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/palm.f90

    r2101 r2118  
    2020! Current revisions:
    2121! -----------------
    22 !
     22! OpenACC directives and related code removed
    2323!
    2424! Former revisions:
     
    213213        ONLY:  usm_write_restart_data       
    214214
    215 #if defined( __openacc )
    216     USE OPENACC
    217 #endif
    218 
    219215    IMPLICIT NONE
    220216
     
    226222    INTEGER(iwp)      ::  i               !<
    227223    INTEGER(iwp)      ::  myid_openmpi    !< OpenMPI local rank for CUDA aware MPI
    228 #if defined( __openacc )
    229     REAL(wp), DIMENSION(100) ::  acc_dum     !<
    230 #endif
    231224
    232225    version = 'PALM 4.0'
     
    265258    ENDIF
    266259#endif
    267 
    268 #if defined( __openacc )
    269 !
    270 !-- Get the local MPI rank in case of CUDA aware OpenMPI. Important, if there
    271 !-- is more than one accelerator board on the node
    272     CALL GET_ENVIRONMENT_VARIABLE('OMPI_COMM_WORLD_LOCAL_RANK',                &
    273          VALUE=env_string, STATUS=env_stat )
    274     READ( env_string, '(I1)' )  myid_openmpi
    275     PRINT*, '### local_rank = ', myid_openmpi, '  status=',env_stat
    276 !
    277 !-- Get the number of accelerator boards per node and assign the MPI processes
    278 !-- to these boards
    279     PRINT*, '*** ACC_DEVICE_NVIDIA = ', ACC_DEVICE_NVIDIA
    280     num_acc_per_node  = ACC_GET_NUM_DEVICES( ACC_DEVICE_NVIDIA )
    281     IF ( numprocs == 1  .AND.  num_acc_per_node > 0 )  num_acc_per_node = 1
    282     PRINT*, '*** myid = ', myid_openmpi, ' num_acc_per_node = ', num_acc_per_node
    283     acc_rank = MOD( myid_openmpi, num_acc_per_node )
    284     CALL ACC_SET_DEVICE_NUM ( acc_rank, ACC_DEVICE_NVIDIA )
    285 !
    286 !-- Test output (to be removed later)
    287     WRITE (*,'(A,I6,A,I3,A,I3,A,I3)') '*** Connect MPI-Task ', myid_openmpi,   &
    288                                       ' to CPU ', acc_rank, ' Devices: ',      &
    289                                       num_acc_per_node, ' connected to:',      &
    290                                       ACC_GET_DEVICE_NUM( ACC_DEVICE_NVIDIA )
    291 #endif
    292 
    293 !
    294 !-- Ensure that OpenACC first attaches the GPU devices by copying a dummy data
    295 !-- region
    296     !$acc data copyin( acc_dum )
    297260
    298261!
     
    422385    ENDIF
    423386
    424 !
    425 !-- Declare and initialize variables in the accelerator memory with their
    426 !-- host values
    427     !$acc  data copyin( d, diss, e, e_p, kh, km, p, pt, pt_p, q, ql, tend, te_m, tpt_m, tu_m, tv_m, tw_m, u, u_p, v, vpt, v_p, w, w_p )          &
    428     !$acc       copyin( tri, tric, dzu, ddzu, ddzw, dd2zu, l_grid, l_wall, ptdf_x, ptdf_y, pt_init, rdf, rdf_sc, ref_state, ug, u_init, vg, v_init, zu, zw )   &
    429     !$acc       copyin( hom, ol, pt1, qs, qsws, qswst, qv1, rif_wall, shf, ts, tswst, us, usws, uswst, uv_total, vsws, vswst, z0, z0h )      &
    430     !$acc       copyin( fxm, fxp, fym, fyp, fwxm, fwxp, fwym, fwyp, nzb_diff_s_inner, nzb_diff_s_outer, nzb_diff_u )       &
    431     !$acc       copyin( nzb_diff_v, nzb_s_inner, nzb_s_outer, nzb_u_inner )    &
    432     !$acc       copyin( nzb_u_outer, nzb_v_inner, nzb_v_outer, nzb_w_inner )   &
    433     !$acc       copyin( nzb_w_outer, rflags_invers, rflags_s_inner, rmask, wall_heatflux, wall_e_x, wall_e_y, wall_u, wall_v, wall_w_x, wall_w_y, wall_flags_0, wall_flags_00 )  &
    434     !$acc       copyin( ngp_2dh, ngp_2dh_s_inner )  &
    435     !$acc       copyin( weight_pres, weight_substep )
    436387!
    437388!-- Integration of the model equations using timestep-scheme
     
    513464
    514465!
    515 !-- Close the OpenACC dummy data region
    516     !$acc end data
    517     !$acc end data
    518 
    519 !
    520466!-- Take final CPU-time for CPU-time analysis
    521467    CALL cpu_log( log_point(1), 'total', 'stop' )
Note: See TracChangeset for help on using the changeset viewer.