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

    r2101 r2118  
    2020! Current revisions:
    2121! -----------------
    22 !
     22! OpenACC directives and related code removed
    2323!
    2424! Former revisions:
     
    242242       REAL(wp), DIMENSION(1:nz,nys:nyn,nxl:nxr) ::  ar      !<
    243243       REAL(wp), DIMENSION(nys:nyn,nxl:nxr,1:nz) ::  ar_inv  !<
    244        !$acc declare create( ar_inv )
    245244
    246245       REAL(wp), DIMENSION(:,:,:),   ALLOCATABLE ::  ar1      !<
     
    257256!
    258257!--    Two-dimensional Fourier Transformation in x- and y-direction.
    259        IF ( pdims(2) == 1  .AND.  pdims(1) > 1  .AND.  num_acc_per_node == 0 ) &
    260        THEN
     258       IF ( pdims(2) == 1  .AND.  pdims(1) > 1 )  THEN
    261259
    262260!
     
    273271          CALL tr_xy_ffty( ar, ar )
    274272
    275        ELSEIF ( pdims(1) == 1 .AND. pdims(2) > 1 .AND. num_acc_per_node == 0 ) &
    276        THEN
     273       ELSEIF ( pdims(1) == 1 .AND. pdims(2) > 1 )  THEN
    277274
    278275!
     
    300297
    301298          CALL cpu_log( log_point_s(4), 'fft_x', 'start' )
    302           IF ( fft_method /= 'system-specific' )  THEN
    303              !$acc update host( ar )
    304           ENDIF
    305299          CALL fft_x( ar, 'forward' )
    306           IF ( fft_method /= 'system-specific' )  THEN
    307              !$acc update device( ar )
    308           ENDIF
    309300          CALL cpu_log( log_point_s(4), 'fft_x', 'pause' )
    310301
     
    317308
    318309          CALL cpu_log( log_point_s(7), 'fft_y', 'start' )
    319           IF ( fft_method /= 'system-specific' )  THEN
    320              !$acc update host( ar )
    321           ENDIF
    322310          CALL fft_y( ar, 'forward', ar_tr = ar,                &
    323311                      nxl_y_bound = nxl_y, nxr_y_bound = nxr_y, &
    324312                      nxl_y_l = nxl_y, nxr_y_l = nxr_y )
    325           IF ( fft_method /= 'system-specific' )  THEN
    326              !$acc update device( ar )
    327           ENDIF
    328313          CALL cpu_log( log_point_s(7), 'fft_y', 'pause' )
    329314
     
    350335
    351336          CALL cpu_log( log_point_s(7), 'fft_y', 'continue' )
    352           IF ( fft_method /= 'system-specific' )  THEN
    353              !$acc update host( ar )
    354           ENDIF
    355337          CALL fft_y( ar, 'backward', ar_tr = ar,               &
    356338                      nxl_y_bound = nxl_y, nxr_y_bound = nxr_y, &
    357339                      nxl_y_l = nxl_y, nxr_y_l = nxr_y )
    358           IF ( fft_method /= 'system-specific' )  THEN
    359              !$acc update device( ar )
    360           ENDIF
    361340          CALL cpu_log( log_point_s(7), 'fft_y', 'stop' )
    362341
     
    369348
    370349          CALL cpu_log( log_point_s(4), 'fft_x', 'continue' )
    371           IF ( fft_method /= 'system-specific' )  THEN
    372              !$acc update host( ar )
    373           ENDIF
    374350          CALL fft_x( ar, 'backward' )
    375           IF ( fft_method /= 'system-specific' )  THEN
    376              !$acc update device( ar )
    377           ENDIF
    378351          CALL cpu_log( log_point_s(4), 'fft_x', 'stop' )
    379352
Note: See TracChangeset for help on using the changeset viewer.