Ignore:
Timestamp:
Dec 18, 2018 12:31:28 PM (5 years ago)
Author:
knoop
Message:

OpenACC port for SPEC

File:
1 edited

Legend:

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

    r3241 r3634  
    2525! -----------------
    2626! $Id$
     27! OpenACC port for SPEC
     28!
     29! 3241 2018-09-12 15:02:00Z raasch
    2730! unused variables removed,
    2831! declarations of omp_get_thread_num now as omp-directive
     
    250253       REAL(wp), DIMENSION(1:nz,nys:nyn,nxl:nxr) ::  ar      !<
    251254       REAL(wp), DIMENSION(nys:nyn,nxl:nxr,1:nz) ::  ar_inv  !<
     255       !$ACC DECLARE CREATE(ar_inv)
    252256
    253257       REAL(wp), DIMENSION(:,:,:),   ALLOCATABLE ::  ar1      !<
     
    262266       IF ( .NOT. poisfft_initialized )  CALL poisfft_init
    263267
     268#ifndef _OPENACC
    264269!
    265270!--    Two-dimensional Fourier Transformation in x- and y-direction.
     
    295300
    296301       ELSEIF ( .NOT. transpose_compute_overlap )  THEN
     302#endif
    297303
    298304!
     
    366372          CALL cpu_log( log_point_s(8), 'transpo invers', 'stop' )
    367373
     374#ifndef _OPENACC
    368375       ELSE
    369376
     
    698705
    699706       ENDIF
     707#endif
    700708
    701709       CALL cpu_log( log_point_s(3), 'poisfft', 'stop' )
Note: See TracChangeset for help on using the changeset viewer.