Ignore:
Timestamp:
Feb 9, 2011 2:25:15 PM (13 years ago)
Author:
raasch
Message:

New:
---

optional exchange of ghost points in synchronous mode via MPI_SENDRCV,
steered by d3par parameter synchronous_exchange
(cpu_statistics, exchange_horiz, modules, parin)

openMP-parallelization of pressure solver (fft-method) for 2d-domain-decomposition
(poisfft, transpose)

Changed:


Errors:


mpt bugfix for netCDF4 usage (mrun)

File:
1 edited

Legend:

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

    r668 r683  
    44! Current revisions:
    55! -----------------
     6! openMP parallelization for 2d-domain-decomposition
    67!
    78! Former revisions:
     
    287288!
    288289!--    Define constant elements of the tridiagonal matrix.
     290!$OMP  PARALLEL PRIVATE ( k, i )
     291!$OMP  DO
    289292       DO  k = 0, nz-1
    290293          DO  i = nxl_z, nxr_z
     
    293296          ENDDO
    294297       ENDDO
     298!$OMP  END PARALLEL
    295299
    296300#if defined( __parallel )
    297301!
    298302!--    Repeat for all y-levels.
     303!$OMP  PARALLEL FIRSTPRIVATE( tri ) PRIVATE ( ar1, j )
     304!$OMP  DO
    299305       DO  j = nys_z, nyn_z
    300306          IF ( j <= nnyh )  THEN
     
    306312          CALL substi( ar, ar1, tri, j )
    307313       ENDDO
     314!$OMP  END PARALLEL
    308315#else
    309316!
     
    527534!
    528535!--    Performing the fft with one of the methods implemented
     536!$OMP  PARALLEL PRIVATE ( j, k )
     537!$OMP  DO
    529538       DO  k = nzb_x, nzt_x
    530539          DO  j = nys_x, nyn_x
     
    532541          ENDDO
    533542       ENDDO
     543!$OMP  END PARALLEL
    534544
    535545    END SUBROUTINE fftxp
     
    550560!
    551561!--    Performing the fft with one of the methods implemented
     562!$OMP  PARALLEL PRIVATE ( j, k )
     563!$OMP  DO
    552564       DO  k = 1, nz
    553565          DO  j = 0, ny
     
    555567          ENDDO
    556568       ENDDO
     569!$OMP  END PARALLEL
    557570
    558571    END SUBROUTINE fftx
     
    575588!
    576589!--    Performing the fft with one of the methods implemented
     590!$OMP  PARALLEL PRIVATE ( i, k )
     591!$OMP  DO
    577592       DO  k = nzb_y, nzt_y
    578593          DO  i = nxl_y, nxr_y
     
    580595          ENDDO
    581596       ENDDO
     597!$OMP  END PARALLEL
    582598
    583599    END SUBROUTINE fftyp
     
    598614!
    599615!--    Performing the fft with one of the methods implemented
     616!$OMP  PARALLEL PRIVATE ( i, k )
     617!$OMP  DO
    600618       DO  k = 1, nz
    601619          DO  i = 0, nx
     
    603621          ENDDO
    604622       ENDDO
     623!$OMP  END PARALLEL
    605624
    606625    END SUBROUTINE ffty
Note: See TracChangeset for help on using the changeset viewer.