Skip to content
Snippets Groups Projects
Commit ef8ba1d7 authored by WAUTELET Philippe's avatar WAUTELET Philippe
Browse files

Philippe 27/10/2016: OpenACC: use BITREP library to get same results on CPU and GPU

parent 4bbbefbc
No related branches found
No related tags found
No related merge requests found
...@@ -372,6 +372,10 @@ USE MODI_ETHETA ...@@ -372,6 +372,10 @@ USE MODI_ETHETA
! !
USE MODI_SECOND_MNH USE MODI_SECOND_MNH
! !
#ifdef MNH_BITREP
USE MODI_BITREP
#endif
!
!! use, intrinsic :: ISO_C_BINDING !! use, intrinsic :: ISO_C_BINDING
! !
IMPLICIT NONE IMPLICIT NONE
...@@ -662,20 +666,20 @@ END DO ...@@ -662,20 +666,20 @@ END DO
DO JRR = 2+KRRL,1+KRRL+KRRI ! loop on the solid components DO JRR = 2+KRRL,1+KRRL+KRRI ! loop on the solid components
ZCP(:,:,:) = ZCP(:,:,:) + XCI * PRT(:,:,:,JRR) ZCP(:,:,:) = ZCP(:,:,:) + XCI * PRT(:,:,:,JRR)
END DO END DO
!$acc end kernels
! !
!* 2.2 Exner function at t !* 2.2 Exner function at t
! !
!PW: "BUG" PGI : results different on CPU and GPU due to the power function !PW: "BUG" PGI : results different on CPU and GPU due to the power function
!See http://www.pgroup.com/userforum/viewtopic.php?t=5364&sid=ec7b762b17fb9bb3332a47f0db57af55 !See http://www.pgroup.com/userforum/viewtopic.php?t=5364&sid=ec7b762b17fb9bb3332a47f0db57af55
!!$acc kernels !Use of own functions allow bit-reproducible results
#ifndef MNH_BITREP
ZEXN(:,:,:) = (PPABST(:,:,:)/XP00) ** (XRD/XCPD) ZEXN(:,:,:) = (PPABST(:,:,:)/XP00) ** (XRD/XCPD)
!!$acc end kernels #else
!$acc update device(ZEXN) ZEXN(:,:,:) = BR_POW(PPABST(:,:,:)/XP00,XRD/XCPD)
#endif
! !
!* 2.3 dissipative heating coeff a t !* 2.3 dissipative heating coeff a t
! !
!$acc kernels
ZCOEF_DISS(:,:,:) = 1/(ZCP(:,:,:) * ZEXN(:,:,:)) ZCOEF_DISS(:,:,:) = 1/(ZCP(:,:,:) * ZEXN(:,:,:))
! !
! !
...@@ -1515,21 +1519,20 @@ REAL, DIMENSION(SIZE(PEXN,1),SIZE(PEXN,2),SIZE(PEXN,3)) :: ZDRVSATDT ...@@ -1515,21 +1519,20 @@ REAL, DIMENSION(SIZE(PEXN,1),SIZE(PEXN,2),SIZE(PEXN,3)) :: ZDRVSATDT
! !
!$acc kernels !$acc kernels
PLOCPEXN(:,:,:) = ( PLTT + (XCPV-PC) * (PT(:,:,:)-XTT) ) / PCP(:,:,:) PLOCPEXN(:,:,:) = ( PLTT + (XCPV-PC) * (PT(:,:,:)-XTT) ) / PCP(:,:,:)
!$acc end kernels
! !
!* 1.2 Saturation vapor pressure at t !* 1.2 Saturation vapor pressure at t
! !
!PW: "BUG" PGI : results different on CPU and GPU due to the EXP and LOG functions !PW: "BUG" PGI : results different on CPU and GPU due to the EXP and LOG functions
!See http://www.pgroup.com/userforum/viewtopic.php?t=5364&sid=ec7b762b17fb9bb3332a47f0db57af55 !See http://www.pgroup.com/userforum/viewtopic.php?t=5364&sid=ec7b762b17fb9bb3332a47f0db57af55
!$acc update self(PT) !Use of own functions allow bit-reproducible results
!!!$acc kernels #ifndef MNH_BITREP
ZRVSAT(:,:,:) = EXP( PALP - PBETA/PT(:,:,:) - PGAM*ALOG( PT(:,:,:) ) ) ZRVSAT(:,:,:) = EXP( PALP - PBETA/PT(:,:,:) - PGAM*ALOG( PT(:,:,:) ) )
!!!$acc end kernels #else
ZRVSAT(:,:,:) = BR_EXP( PALP - PBETA/PT(:,:,:) - PGAM*BR_LOG( PT(:,:,:) ) )
#endif
! !
!* 1.3 saturation mixing ratio at t !* 1.3 saturation mixing ratio at t
! !
!$acc update device(ZRVSAT)
!$acc kernels
ZRVSAT(:,:,:) = ZRVSAT(:,:,:) * ZEPS / ( PPABST(:,:,:) - ZRVSAT(:,:,:) ) ZRVSAT(:,:,:) = ZRVSAT(:,:,:) * ZEPS / ( PPABST(:,:,:) - ZRVSAT(:,:,:) )
! !
!* 1.4 compute the saturation mixing ratio derivative (rvs') !* 1.4 compute the saturation mixing ratio derivative (rvs')
...@@ -1696,25 +1699,33 @@ IF ( HTURBDIM /= '1DIM' ) THEN ! 3D turbulence scheme ...@@ -1696,25 +1699,33 @@ IF ( HTURBDIM /= '1DIM' ) THEN ! 3D turbulence scheme
!$acc end kernels !$acc end kernels
#endif #endif
ELSE ELSE
!PW: "BUG" PGI : results different on CPU and GPU due to the power function
!See http://www.pgroup.com/userforum/viewtopic.php?t=5364&sid=ec7b762b17fb9bb3332a47f0db57af55
!Use of own functions allow bit-reproducible results
#ifndef MNH_BITREP
!
#ifndef _OPENACC #ifndef _OPENACC
PLM(:,:,:) = (PLM(:,:,:)*MXF(PDXX(:,:,:))*MYF(PDYY(:,:,:)) ) ** (1./3.) PLM(:,:,:) = (PLM(:,:,:)*MXF(PDXX(:,:,:))*MYF(PDYY(:,:,:)) ) ** (1./3.)
#else #else
#if 0
!PW: "BUG" PGI : results different on CPU and GPU due to the power function
!See http://www.pgroup.com/userforum/viewtopic.php?t=5364&sid=ec7b762b17fb9bb3332a47f0db57af55
CALL MXF_DEVICE(PDXX,ZTMP1_DEVICE) CALL MXF_DEVICE(PDXX,ZTMP1_DEVICE)
CALL MYF_DEVICE(PDYY,ZTMP2_DEVICE) CALL MYF_DEVICE(PDYY,ZTMP2_DEVICE)
!$acc update self(ZTMP1_DEVICE,ZTMP2_DEVICE) !$acc kernels
!!$acc kernels
PLM(:,:,:) = (PLM(:,:,:)*ZTMP1_DEVICE*ZTMP2_DEVICE ) ** (1./3.) PLM(:,:,:) = (PLM(:,:,:)*ZTMP1_DEVICE*ZTMP2_DEVICE ) ** (1./3.)
!!$acc end kernels !$acc end kernels
!$acc update device(PLM) #endif !_OPENACC
!
#else !MNH_BITREP
!
#ifndef _OPENACC
PLM(:,:,:) = BR_POW( PLM(:,:,:)*MXF(PDXX(:,:,:))*MYF(PDYY(:,:,:)) , 1./3. )
#else #else
!$acc update self(PLM) CALL MXF_DEVICE(PDXX,ZTMP1_DEVICE)
PLM(:,:,:) = (PLM(:,:,:)*MXF(PDXX(:,:,:))*MYF(PDYY(:,:,:)) ) ** (1./3.) CALL MYF_DEVICE(PDYY,ZTMP2_DEVICE)
!$acc update device(PLM) !$acc kernels
#endif PLM(:,:,:) = BR_POW( PLM(:,:,:)*ZTMP1_DEVICE *ZTMP2_DEVICE , 1./3. )
#endif !$acc end kernels
#endif !_OPENACC
#endif !MNH_BITREP
END IF END IF
END IF END IF
! compute a mixing length limited by the stability ! compute a mixing length limited by the stability
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Please register or to comment