Skip to content
Snippets Groups Projects
Commit 9906bd7b authored by ESCOBAR MUNOZ Juan's avatar ESCOBAR MUNOZ Juan
Browse files

Juan 21/09/2021:zsolver.f90, use MNH_ALLOCATE + pointer contiguous for GPU opt

parent 39ad7dee
No related branches found
No related tags found
No related merge requests found
......@@ -153,6 +153,11 @@ USE MODI_FLAT_INV
USE MODI_ZSOLVER_INV
USE MODI_DOTPROD
!
#ifdef MNH_OPENACC
USE MODE_MNH_ZWORK , ONLY : MNH_ALLOCATE_ZT3D , MNH_REL_ZT3D
#endif
!
!
IMPLICIT NONE
!
!* 0.1 declarations of arguments
......@@ -209,23 +214,39 @@ REAL, DIMENSION(:) , INTENT(IN) :: A_K,B_K,C_K,D_K
!
INTEGER :: JM ! loop index
!
REAL, DIMENSION(SIZE(PPHI,1),SIZE(PPHI,2),SIZE(PPHI,3)) :: ZDELTA, ZKSI
REAL, DIMENSION(:,:,:), pointer , contiguous :: ZDELTA, ZKSI
! array containing the auxilary fields DELTA and KSI of the CR method
REAL, DIMENSION(SIZE(PPHI,1),SIZE(PPHI,2),SIZE(PPHI,3)) :: ZP, ZQ
REAL, DIMENSION(:,:,:), pointer , contiguous :: ZP, ZQ
! array containing the auxilary fields P and Q of the CR method
REAL, DIMENSION(SIZE(PPHI,1),SIZE(PPHI,2),SIZE(PPHI,3)) :: ZRESIDUE
REAL, DIMENSION(:,:,:), pointer , contiguous :: ZRESIDUE
! array containing the error field at each iteration Q(PHI) - Y
INTEGER :: IZDELTA, IZKSI, IZP, IZQ, IZRESIDUE
!
REAL :: ZALPHA, ZLAMBDA ! amplitude of the descent in the Conjugate
! directions
REAL :: ZDOT_DELTA ! dot product of ZDELTA by itself
!
INTEGER :: JIU,JJU,JKU
INTEGER :: JI,JJ,JK
!-------------------------------------------------------------------------------
!
!* 1. INITIALIZATIONS
! ---------------
!
!
JIU = size(PPHI, 1 )
JJU = size(PPHI, 2 )
JKU = size(PPHI, 3 )
!
#ifndef MNH_OPENACC
ALLOCATE(ZDELTA(JIU,JJU,JKU),ZKSI(JIU,JJU,JKU),ZP(JIU,JJU,JKU),ZQ(JIU,JJU,JKU),ZRESIDUE(JIU,JJU,JKU))
#else
IZDELTA = MNH_ALLOCATE_ZT3D(ZDELTA ,JIU,JJU,JKU )
IZKSI = MNH_ALLOCATE_ZT3D(ZKSI ,JIU,JJU,JKU )
IZP = MNH_ALLOCATE_ZT3D(ZP ,JIU,JJU,JKU )
IZQ = MNH_ALLOCATE_ZT3D(ZQ ,JIU,JJU,JKU )
IZRESIDUE = MNH_ALLOCATE_ZT3D(ZRESIDUE ,JIU,JJU,JKU )
#endif
!* 1.1 compute the vector: r^(0) = Q(PHI) - Y
!
#ifndef MNH_OPENACC
......@@ -308,7 +329,12 @@ DO JM = 1,KITR
!
END DO ! end of the loop for the iterative solver
!
!
!
#ifndef MNH_OPENACC
DEALLOCATE(ZDELTA,ZKSI,ZP,ZQ,ZRESIDUE)
#else
CALL MNH_REL_ZT3D(IZDELTA,IZKSI,IZP,IZQ,IZRESIDUE)
#endif
!-------------------------------------------------------------------------------
!
END SUBROUTINE ZSOLVER
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Please register or to comment