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

Juan 04/11/2022:mode_double_double.f90, CCE Optimization, declare...

Juan 04/11/2022:mode_double_double.f90, CCE Optimization, declare SUM_DD_R2_ll_DEVICE & use "!$acc parallel" to avoid multiple kernel lunch in seq loop
parent 2080de7c
No related branches found
No related tags found
No related merge requests found
...@@ -215,6 +215,58 @@ CONTAINS ...@@ -215,6 +215,58 @@ CONTAINS
c = ddc%R c = ddc%R
END FUNCTION SUM_DD_R2_LL END FUNCTION SUM_DD_R2_LL
FUNCTION SUM_DD_R2_ll_DEVICE (a) RESULT(c)
!----------------------------------------------------------------------
!
! Purpose:
! Modification of original codes written by David H. Bailey
! This subroutine computes ddc = ddb + a
! Could be inlined by compiler <=> elemental function
!
!----------------------------------------------------------------------
USE mode_reduce_sum, ONLY: REDUCESUM_ll
!
! Arguments
!
REAL :: c ! result
REAL,DIMENSION(:,:), INTENT(in) :: a ! input
!
! Local workspace
!
TYPE(DOUBLE_DOUBLE) :: ddc
TYPE(DOUBLE_DOUBLE),DIMENSION(SIZE(a,1)) :: ddb
REAL ,DIMENSION(SIZE(a,1)) :: e, t1, t2
INTEGER :: i,j
INTEGER :: IINFO_ll
!
!-----------------------------------------------------------------------
!
! Compute dda + ddb using Knuth's trick.
!$acc kernels
ddb%R = 0.0
ddb%E = 0.0
!$acc end kernels
!$acc parallel
!$acc loop seq
DO j=1,SIZE(a,2)
!$acc loop independent
DO i=1,SIZE(a,1)
t1(i) = a(i,j) + ddb(i)%R
e(i) = t1(i) - a(i,j)
t2(i) = ((ddb(i)%R - e(i)) + (a(i,j) - (t1(i) - e(i)))) &
+ ddb(i)%E
!
! The result is t1 + t2, after normalization.
ddb(i)%R = t1(i) + t2(i)
ddb(i)%E = t2(i) - ((t1(i) + t2(i)) - t1(i))
END DO
END DO
!$acc end parallel
ddc = SUM_DD_DD1(ddb)
CALL REDUCESUM_ll(ddc,IINFO_ll)
c = ddc%R
END FUNCTION SUM_DD_R2_LL_DEVICE
FUNCTION SUM_DD_R2_R1_ll (a) RESULT(c) FUNCTION SUM_DD_R2_R1_ll (a) RESULT(c)
!---------------------------------------------------------------------- !----------------------------------------------------------------------
! !
......
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