Skip to content
Snippets Groups Projects
Commit 367dada9 authored by jtra's avatar jtra
Browse files

Fixed redefinition of cpp variables __PREC and __ROUTINE in fft routines

Removed ' from Green's as this caused warnings


git-svn-id: https://ppm.inf.ethz.ch/svn/ppmnumerics/branches/ngtopo/libppmnumerics@889 7c7fe9aa-52eb-4d9e-b0a8-ba7d787348e9
parent 83ac556d
No related branches found
No related tags found
No related merge requests found
......@@ -117,3 +117,5 @@
RETURN
END SUBROUTINE __ROUTINE
#undef __ROUTINE
#undef __PREC
......@@ -122,3 +122,5 @@
RETURN
END SUBROUTINE __ROUTINE
#undef __ROUTINE
#undef __PREC
......@@ -101,3 +101,5 @@
RETURN
END SUBROUTINE __ROUTINE
#undef __ROUTINE
#undef __PREC
......@@ -125,3 +125,5 @@
END SUBROUTINE __ROUTINE
#undef __ROUTINE
#undef __PREC
......@@ -126,3 +126,5 @@
END SUBROUTINE __ROUTINE
#undef __ROUTINE
#undef __PREC
......@@ -147,3 +147,5 @@
RETURN
END SUBROUTINE __ROUTINE
#undef __ROUTINE
#undef __PREC
......@@ -152,3 +152,5 @@
RETURN
END SUBROUTINE __ROUTINE
#undef __ROUTINE
#undef __PREC
......@@ -147,3 +147,5 @@
RETURN
END SUBROUTINE __ROUTINE
#undef __ROUTINE
#undef __PREC
......@@ -151,3 +151,5 @@
RETURN
END SUBROUTINE __ROUTINE
#undef __ROUTINE
#undef __PREC
......@@ -7,14 +7,14 @@
!-------------------------------------------------------------------------
SUBROUTINE __ROUTINE(topoid,meshid,ppmpoisson,fieldin,fieldout,green,info&
&,bc,derive)
!!! Routine to initialise Green's function solution of the Poisson
!!! equation. green is the flag defining which Green's function to use:
!!! Routine to initialise Greens function solution of the Poisson
!!! equation. green is the flag defining which Greens function to use:
!!! * ppm_poisson_grn_pois_per - Poisson equation, periodic boundaries
!!! * ppm_poisson_grn_pois_fre - Poisson equation, freespace boundaries (not implemented)
!!! * ppm_poisson_grn_reprojec - Do vorticity reprojection to kill divergence
!!! Eventually the routine should be overloaded to accept custom Green's
!!! Eventually the routine should be overloaded to accept custom Greens
!!! functions such that more general convolutions can be performed.
!!! green should be expanded to include more buildin Green's functions.
!!! green should be expanded to include more buildin Greens functions.
!!!
!!! The routine should accept an optional flag to toggle deallocation of
!!! work arrays between calls to ppm_poisson_solve
......@@ -53,7 +53,7 @@
!!!ppm_poisson_grn_pois_fre - Poisson equation, freespace boundaries (not implemented)
!!!ppm_poisson_grn_reprojec - Do vorticity reprojection to kill divergence
!!!
!!!Eventually this should also accept custom Green's function
!!!Eventually this should also accept custom Greens function
INTEGER, INTENT(OUT) :: info
INTEGER,INTENT(IN),OPTIONAL :: bc
!!!boundary condition for the convolution. Can be on of the following:
......@@ -93,7 +93,7 @@
INTEGER ,DIMENSION(__DIM) :: indl,indu
INTEGER,PARAMETER :: MK = __PREC
REAL(__PREC),PARAMETER :: PI=ACOS(-1.0_MK) !@ use ppm pi
!factor for the Green's function, including FFT normalization
!factor for the Greens function, including FFT normalization
REAL(__PREC) :: normfac
INTEGER :: i,j,k
INTEGER :: kx,ky,kz
......@@ -512,7 +512,7 @@
! then FFTed in those directions, mapped to z-pencils, FFTed in z and
! finally copied to ppmpoisson%fldgrnc. The real xy slabs have already
! been setup for FFTs etc so they offer a convenient container for the
! FFTing the Green's function instead of setting up the whole apparatus
! FFTing the Greens function instead of setting up the whole apparatus
! for this one-time affair.
! These loops must run over the padded(extended) domain thus %ndataxy
! \nabla \Psi = -\omega
......@@ -521,7 +521,7 @@
!-------------------------------------------------------------------------
ELSE IF (green .EQ. ppm_poisson_grn_pois_fre) THEN
!-----------------------------------------------------------------------
! First initialise the real Green's function
! First initialise the real Greens function
!@alternatively this could come from as input
!-----------------------------------------------------------------------
!@write(*,*) 'what the fuck?'
......@@ -532,7 +532,7 @@
& REAL((ppmpoisson%nmxy(1))*(ppmpoisson%nmxy(2))*(ppmpoisson%nmxy(3)),MK))*dx*dy*dz
!& REAL((ppmpoisson%nmxy(1))*(ppmpoisson%nmxy(2))*(ppmpoisson%nmxy(3)),MK)& !this is the correct normalization to bring one field back and forth.
!remembering FFT normalization of ALL points: !vertex
!!& REAL((ppmpoisson%nmxy(1))*(ppmpoisson%nmxy(2))*(ppmpoisson%nmxy(3)),MK)& !this should be correct normalization. When back and forth transforming the green's function is correct
!!& REAL((ppmpoisson%nmxy(1))*(ppmpoisson%nmxy(2))*(ppmpoisson%nmxy(3)),MK)& !this should be correct normalization. When back and forth transforming the greens function is correct
!!& *REAL((ppmpoisson%nmxy(1))*(ppmpoisson%nmxy(2))*(ppmpoisson%nmxy(3))/8,MK)) !this line is probably not necessary
!!!& *REAL((ppmpoisson%nmxy(1))*(ppmpoisson%nmxy(2))*(ppmpoisson%nmxy(3)),MK)) !this line is probably not necessary
!@write(*,*) ppmpoisson%nmxy, 'johannes'
......
......@@ -9,10 +9,10 @@
!-------------------------------------------------------------------------
SUBROUTINE __ROUTINE(topoid,meshid,ppmpoisson,fieldin,fieldout,gstw,info,&
& tmpcase)
!!! Routine to perform the Green's function solution of the Poisson
!!! Routine to perform the Greens function solution of the Poisson
!!! equation. All settings are defined in ppm_poisson_initdef and stored
!!! in the ppmpoisson plan. The tmpcase argument allows the use of a
!!! different Green's function or operation than initialised. This is
!!! different Greens function or operation than initialised. This is
!!! particularly useful for vorticity reprojection
!!! (ppm_poisson_grn_reprojec).
!!!
......@@ -21,9 +21,6 @@
USE ppm_module_map_field
USE ppm_module_map_field_global
USE ppm_module_map
USE ppm_module_typedef !@
USE ppm_module_data !@
USE ppm_module_finalize !@
IMPLICIT NONE
include 'mpif.h'
......@@ -62,10 +59,6 @@
REAL(__PREC) :: kx,ky,kz
REAL(__PREC) :: phix,phiy,phiz
REAL(__PREC) :: normfac
TYPE(ppm_t_equi_mesh), POINTER :: mesh => NULL()
TYPE(ppm_t_equi_mesh), POINTER :: target_mesh => NULL()
TYPE(ppm_t_topo), POINTER :: topo => NULL()
TYPE(ppm_t_topo), POINTER :: target_topo => NULL()
#ifndef __NOPE
INTEGER :: trank !@
......@@ -353,7 +346,7 @@ trank =0
#endif
!-----------------------------------------------------------------------
! Apply the periodic Green's function
! Apply the periodic Greens function
!-----------------------------------------------------------------------
IF (presentcase .EQ. ppm_poisson_grn_pois_per) THEN
DO isub=1,ppmpoisson%nsublistz
......@@ -372,7 +365,7 @@ trank =0
ENDDO
ENDDO
!-----------------------------------------------------------------------
! Apply the free-space Green's function
! Apply the free-space Greens function
!-----------------------------------------------------------------------
ELSE IF (presentcase .EQ. ppm_poisson_grn_pois_fre) THEN
DO isub=1,ppmpoisson%nsublistz
......@@ -646,20 +639,6 @@ trank =0
CALL ppm_write(ppm_rank, 'ppm_poisson_solve','Failed to push vector field.',info2)
GOTO 9999
ENDIF
topo => ppm_topo(topoid)%t!@
mesh => topo%mesh(meshid) !@
target_topo => ppm_topo(ppmpoisson%topoidxy)%t !@
target_mesh => target_topo%mesh(ppmpoisson%meshidxy) !@
DO isub=1,topo%nsublist
isubl=topo%isublist(isub)
!@write(*,*) 'johannestest rank', ppm_rank,'istart', mesh%istart(:,isubl), &
!@'nnodes',mesh%nnodes(:,isubl), mesh%nm
ENDDO
DO isub=1,ppmpoisson%nsublistxy
isubl=ppmpoisson%isublistxy(isub)
!@write(*,*) 'johannestestxy rank', ppm_rank,'istart', target_mesh%istart(:,isubl), &
!@'nnodes', target_mesh%nnodes(:,isubl), target_mesh%nm
ENDDO
!Send
CALL ppm_map_field_send(info)
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment