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

Juan 03/03/2022:ZSOLVER/gdiv.f90, nvhpc22.2 bug/optimisation -> replace...

Juan 03/03/2022:ZSOLVER/gdiv.f90, nvhpc22.2 bug/optimisation -> replace WHERE+ARRAY SYNTAX -> DO CONCURRENT
parent 1ac8453d
No related branches found
No related tags found
No related merge requests found
...@@ -129,7 +129,7 @@ REAL, DIMENSION(:,:,:), INTENT(INOUT) :: PU ! along x ...@@ -129,7 +129,7 @@ REAL, DIMENSION(:,:,:), INTENT(INOUT) :: PU ! along x
REAL, DIMENSION(:,:,:), INTENT(INOUT) :: PV ! along y REAL, DIMENSION(:,:,:), INTENT(INOUT) :: PV ! along y
REAL, DIMENSION(:,:,:), INTENT(INOUT) :: PW ! along z REAL, DIMENSION(:,:,:), INTENT(INOUT) :: PW ! along z
! !
REAL, DIMENSION(:,:,:), INTENT(OUT) :: PGDIV ! divergence at REAL, DIMENSION(:,:,:), INTENT(OUT) :: PGDIV ! divergence at
! a mass point ! a mass point
! !
!* 0.2 declarations of local variables !* 0.2 declarations of local variables
...@@ -181,6 +181,7 @@ CALL MNH_MEM_GET( ZWC, IIU, IJU, IKU ) ...@@ -181,6 +181,7 @@ CALL MNH_MEM_GET( ZWC, IIU, IJU, IKU )
CALL MNH_MEM_GET( Z1, IIU, IJU, IKU ) CALL MNH_MEM_GET( Z1, IIU, IJU, IKU )
CALL MNH_MEM_GET( Z2, IIU, IJU, IKU ) CALL MNH_MEM_GET( Z2, IIU, IJU, IKU )
CALL MNH_MEM_GET( Z3, IIU, IJU, IKU ) CALL MNH_MEM_GET( Z3, IIU, IJU, IKU )
!$acc data present(ZUC,ZVC,ZWC,Z1,Z2,Z3)
#endif #endif
! !
GWEST = ( HLBCX(1) /= 'CYCL' .AND. LWEST_ll() ) GWEST = ( HLBCX(1) /= 'CYCL' .AND. LWEST_ll() )
...@@ -195,6 +196,7 @@ GNORTH = ( .NOT. L2D .AND. HLBCY(2) /= 'CYCL' .AND. LNORTH_ll() ) ...@@ -195,6 +196,7 @@ GNORTH = ( .NOT. L2D .AND. HLBCY(2) /= 'CYCL' .AND. LNORTH_ll() )
! !
!* 2.1 prepare the boundary conditions !* 2.1 prepare the boundary conditions
! !
! !
!$acc kernels !$acc kernels
DO CONCURRENT ( JI=1:IIU,JJ=1:IJU ) DO CONCURRENT ( JI=1:IIU,JJ=1:IJU )
...@@ -221,11 +223,31 @@ CALL CONTRAV_DEVICE(HLBCX,HLBCY,PU,PV,PW,PDXX,PDYY,PDZZ,PDZX,PDZY,ZUC,ZVC,ZWC,4, ...@@ -221,11 +223,31 @@ CALL CONTRAV_DEVICE(HLBCX,HLBCY,PU,PV,PW,PDXX,PDYY,PDZZ,PDZX,PDZY,ZUC,ZVC,ZWC,4,
! ---------------------- ! ----------------------
! !
!$acc kernels !$acc kernels
PGDIV=0. !usefull for the four corners and halo zones #ifdef MNH_COMPILER_NVHPC
!$acc loop independent collapse(3)
#endif
DO CONCURRENT (JI=1:IIU,JJ=1:IJU,JK=1:IKU)
PGDIV(JI,JJ,JK)=0. !usefull for the four corners and halo zones
ENDDO
! !
Z1(IIB:IIE,:,:)=ZUC(IIB+1:IIE+1,:,:)-ZUC(IIB:IIE,:,:) #ifdef MNH_COMPILER_NVHPC
Z2(:,IJB:IJE,:)=ZVC(:,IJB+1:IJE+1,:)-ZVC(:,IJB:IJE,:) !$acc loop independent collapse(3)
Z3(:,:,IKB:IKE)=ZWC(:,:,IKB+1:IKE+1)-ZWC(:,:,IKB:IKE) #endif
DO CONCURRENT (JI=IIB:IIE,JJ=1:IJU,JK=1:IKU)
Z1(JI,JJ,JK)=ZUC(JI+IIB+1-(IIB) ,JJ,JK)-ZUC(JI,JJ,JK)
ENDDO
#ifdef MNH_COMPILER_NVHPC
!$acc loop independent collapse(3)
#endif
DO CONCURRENT (JI=1:IIU,JJ=IJB:IJE,JK=1:IKU)
Z2(JI,JJ,JK)=ZVC(JI,JJ+IJB+1-(IJB) ,JK)-ZVC(JI,JJ,JK)
ENDDO
#ifdef MNH_COMPILER_NVHPC
!$acc loop independent collapse(3)
#endif
DO CONCURRENT (JI=1:IIU,JJ=1:IJU,JK=IKB:IKE)
Z3(JI,JJ,JK)=ZWC(JI,JJ,JK+IKB+1-(IKB) )-ZWC(JI,JJ,JK)
ENDDO
! !
PGDIV(IIB:IIE,IJB:IJE,IKB:IKE)= Z1(IIB:IIE,IJB:IJE,IKB:IKE) + & PGDIV(IIB:IIE,IJB:IJE,IKB:IKE)= Z1(IIB:IIE,IJB:IJE,IKB:IKE) + &
Z2(IIB:IIE,IJB:IJE,IKB:IKE) + & Z2(IIB:IIE,IJB:IJE,IKB:IKE) + &
...@@ -341,6 +363,7 @@ END IF ...@@ -341,6 +363,7 @@ END IF
#ifndef MNH_OPENACC #ifndef MNH_OPENACC
DEALLOCATE( ZUC, ZVC, ZWC, Z1, Z2, Z3 ) DEALLOCATE( ZUC, ZVC, ZWC, Z1, Z2, Z3 )
#else #else
!$acc end data
!Release all memory allocated with MNH_MEM_GET calls since last call to MNH_MEM_POSITION_PIN !Release all memory allocated with MNH_MEM_GET calls since last call to MNH_MEM_POSITION_PIN
CALL MNH_MEM_RELEASE() CALL MNH_MEM_RELEASE()
#endif #endif
......
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