20
SC13 GPU Technology Theater Accessing New CUDA Features from CUDA Fortran Brent Leback, Compiler Manager, PGI

SC13 - GTC On Demand | NVIDIA GTC Digital...CUDA Fortran 2012/2013 Features PGI 2012 (CUDA 4.1 and 4.2) Texture memory support Support for double precision atomic add PGI 2013 (CUDA

  • Upload
    others

  • View
    9

  • Download
    1

Embed Size (px)

Citation preview

Page 1: SC13 - GTC On Demand | NVIDIA GTC Digital...CUDA Fortran 2012/2013 Features PGI 2012 (CUDA 4.1 and 4.2) Texture memory support Support for double precision atomic add PGI 2013 (CUDA

SC13 GPU Technology Theater

Accessing New CUDA Features from CUDA Fortran Brent Leback, Compiler Manager, PGI

Page 2: SC13 - GTC On Demand | NVIDIA GTC Digital...CUDA Fortran 2012/2013 Features PGI 2012 (CUDA 4.1 and 4.2) Texture memory support Support for double precision atomic add PGI 2013 (CUDA

The Case for Fortran

Clear, straight-forward syntax

Successful legacy in the scientific community

Large existing code base

Automatic vectorization and parallelization

Array descriptors

Modules

Abstraction features, high-level syntax, strongly-typed

Fortran 2003: encapsulation, type extension, polymorphism

Page 3: SC13 - GTC On Demand | NVIDIA GTC Digital...CUDA Fortran 2012/2013 Features PGI 2012 (CUDA 4.1 and 4.2) Texture memory support Support for double precision atomic add PGI 2013 (CUDA

attributes(global) subroutine mm_kernel

( A, B, C, N, M, L )

real :: A(N,M), B(M,L), C(N,L), Cij

integer, value :: N, M, L

integer :: i, j, kb, k, tx, ty

real, shared :: Asub(16,16),Bsub(16,16)

tx = threadidx%x

ty = threadidx%y

i = blockidx%x * 16 + tx

j = blockidx%y * 16 + ty

Cij = 0.0

do kb = 1, M, 16

Asub(tx,ty) = A(i,kb+tx-1)

Bsub(tx,ty) = B(kb+ty-1,j)

call syncthreads()

do k = 1,16

Cij = Cij + Asub(tx,k) * Bsub(k,ty)

enddo

call syncthreads()

enddo

C(i,j) = Cij

end subroutine mmul_kernel

real, device, allocatable, dimension(:,:) ::

Adev,Bdev,Cdev

. . .

allocate (Adev(N,M), Bdev(M,L), Cdev(N,L))

Adev = A(1:N,1:M)

Bdev = B(1:M,1:L)

call mm_kernel <<<dim3(N/16,M/16),dim3(16,16)>>>

( Adev, Bdev, Cdev, N, M, L)

C(1:N,1:L) = Cdev

deallocate ( Adev, Bdev, Cdev )

. . .

Host Code Device Code

What is CUDA Fortran?

Page 4: SC13 - GTC On Demand | NVIDIA GTC Digital...CUDA Fortran 2012/2013 Features PGI 2012 (CUDA 4.1 and 4.2) Texture memory support Support for double precision atomic add PGI 2013 (CUDA

!$CUF kernel directives

module madd_device_module

use cudafor

contains

subroutine madd_dev(a,b,c,sum,n1,n2)

real,dimension(:,:),device :: a,b,c

real :: sum

integer :: n1,n2

type(dim3) :: grid, block

!$cuf kernel do (2) <<<(*,*),(32,4)>>>

do j = 1,n2

do i = 1,n1

a(i,j) = b(i,j) + c(i,j)

sum = sum + a(i,j)

enddo

enddo

end subroutine

end module

module madd_device_module

use cudafor

implicit none

contains

attributes(global) subroutine madd_kernel(a,b,c,blocksum,n1,n2)

real, dimension(:,:) :: a,b,c

real, dimension(:) :: blocksum

integer, value :: n1,n2

integer :: i,j,tindex,tneighbor,bindex

real :: mysum

real, shared :: bsum(256)

! Do this thread's work

mysum = 0.0

do j = threadidx%y + (blockidx%y-1)*blockdim%y, n2, blockdim%y*griddim%y

do i = threadidx%x + (blockidx%x-1)*blockdim%x, n1, blockdim%x*griddim%x

a(i,j) = b(i,j) + c(i,j)

mysum = mysum + a(i,j) ! accumulates partial sum per thread

enddo

enddo

! Now add up all partial sums for the whole thread block

! Compute this thread's linear index in the thread block

! We assume 256 threads in the thread block

tindex = threadidx%x + (threadidx%y-1)*blockdim%x

! Store this thread's partial sum in the shared memory block

bsum(tindex) = mysum

call syncthreads()

! Accumulate all the partial sums for this thread block to a single value

tneighbor = 128

do while( tneighbor >= 1 )

if( tindex <= tneighbor ) &

bsum(tindex) = bsum(tindex) + bsum(tindex+tneighbor)

tneighbor = tneighbor / 2

call syncthreads()

enddo

! Store the partial sum for the thread block

bindex = blockidx%x + (blockidx%y-1)*griddim%x

if( tindex == 1 ) blocksum(bindex) = bsum(1)

end subroutine

! Add up partial sums for all thread blocks to a single cumulative sum

attributes(global) subroutine madd_sum_kernel(blocksum,dsum,nb)

real, dimension(:) :: blocksum

real :: dsum

integer, value :: nb

real, shared :: bsum(256)

integer :: tindex,tneighbor,i

! Again, we assume 256 threads in the thread block

! accumulate a partial sum for each thread

tindex = threadidx%x

bsum(tindex) = 0.0

do i = tindex, nb, blockdim%x

bsum(tindex) = bsum(tindex) + blocksum(i)

enddo

call syncthreads()

! This code is copied from the previous kernel

! Accumulate all the partial sums for this thread block to a single value

! Since there is only one thread block, this single value is the final result

tneighbor = 128

do while( tneighbor >= 1 )

if( tindex <= tneighbor ) &

bsum(tindex) = bsum(tindex) + bsum(tindex+tneighbor)

tneighbor = tneighbor / 2

call syncthreads()

enddo

if( tindex == 1 ) dsum = bsum(1)

end subroutine

subroutine madd_dev(a,b,c,dsum,n1,n2)

real, dimension(:,:), device :: a,b,c

real, device :: dsum

real, dimension(:), allocatable, device :: blocksum

integer :: n1,n2,nb

type(dim3) :: grid, block

integer :: r

! Compute grid/block size; block size must be 256 threads

grid = dim3((n1+31)/32, (n2+7)/8, 1)

block = dim3(32,8,1)

nb = grid%x * grid%y

allocate(blocksum(1:nb))

call madd_kernel<<< grid, block >>>(a,b,c,blocksum,n1,n2)

call madd_sum_kernel<<< 1, 256 >>>(blocksum,dsum,nb)

r = cudaThreadSynchronize() ! don't deallocate too early

deallocate(blocksum)

end subroutine

end module

Equivalent

hand-written

CUDA kernels

Page 5: SC13 - GTC On Demand | NVIDIA GTC Digital...CUDA Fortran 2012/2013 Features PGI 2012 (CUDA 4.1 and 4.2) Texture memory support Support for double precision atomic add PGI 2013 (CUDA

CUDA Fortran 2012/2013 Features

PGI 2012 (CUDA 4.1 and 4.2)

Texture memory support

Support for double precision atomic add

PGI 2013 (CUDA 5.0 and 5.5)

Support for dynamic parallelism

Relocatable device code, linking, device libraries

Full atomic datatype support

Kepler shuffle support

Page 6: SC13 - GTC On Demand | NVIDIA GTC Digital...CUDA Fortran 2012/2013 Features PGI 2012 (CUDA 4.1 and 4.2) Texture memory support Support for double precision atomic add PGI 2013 (CUDA

Latest Features in CUDA Fortran

PGI 2014 (CUDA 6.0 and beyond)

DWARF generation, GPU-side debugging

Full shuffle datatype support

Overloaded reduction intrinsics

Support for Unified Memory

Improved interoperability with OpenACC

Page 7: SC13 - GTC On Demand | NVIDIA GTC Digital...CUDA Fortran 2012/2013 Features PGI 2012 (CUDA 4.1 and 4.2) Texture memory support Support for double precision atomic add PGI 2013 (CUDA

Debugging CUDA Fortran with Allinea DDT

Page 8: SC13 - GTC On Demand | NVIDIA GTC Digital...CUDA Fortran 2012/2013 Features PGI 2012 (CUDA 4.1 and 4.2) Texture memory support Support for double precision atomic add PGI 2013 (CUDA

Dwarf Generation Enables Tools

% pgf90 -g -O0 -Mcuda=cc35 saxpy.cuf

% cuda-memcheck ./a.out

========= CUDA-MEMCHECK

0: copyout Memcpy (host=0x68e9e0, dev=0x500200200, size=124)

FAILED: 4(unspecified launch failure)

========= Invalid __global__ read of size 4

========= at 0x00000530 in /home/brentl/saxpy.cuf:10:m_saxpy_

========= by thread (31,0,0) in block (0,0,0)

9 ! if (i<=n) y(i) = alpha * x(i) + y(i)

10 y(i) = alpha * x(i) + y(i)

Page 9: SC13 - GTC On Demand | NVIDIA GTC Digital...CUDA Fortran 2012/2013 Features PGI 2012 (CUDA 4.1 and 4.2) Texture memory support Support for double precision atomic add PGI 2013 (CUDA

Extending F90 Intrinsics to Device Data

Evaluate sum() of device array and return result to host

Typical reduction uses two kernels

Calculate partial sum for threads within a block

Launch a one-block kernel to perform a final sum

! host code

sum_h = sum(a_d)

Page 10: SC13 - GTC On Demand | NVIDIA GTC Digital...CUDA Fortran 2012/2013 Features PGI 2012 (CUDA 4.1 and 4.2) Texture memory support Support for double precision atomic add PGI 2013 (CUDA

Extending F90 Intrinsics to Device Data

Small arrays transfer data to host and sum there

Limited parallelism for small array

Device to host transfer is mostly overhead

Large arrays perform partial sum on device, final sum on host

Cutoff for optimal performance depends on host system

Configurable via initialization routine

Page 11: SC13 - GTC On Demand | NVIDIA GTC Digital...CUDA Fortran 2012/2013 Features PGI 2012 (CUDA 4.1 and 4.2) Texture memory support Support for double precision atomic add PGI 2013 (CUDA

Stages of Partial Sum

Reduce to grid of threads using grid-stride loop

Reduce within warp using SHFL (shuffle) functions

One thread in each warp writes the value to shared memory,

all call syncthreads(), then warp 1 reads the values into registers

and uses a set of SHFL operations again

This results in gridDim%x partial sums which are moved to the

host

Page 12: SC13 - GTC On Demand | NVIDIA GTC Digital...CUDA Fortran 2012/2013 Features PGI 2012 (CUDA 4.1 and 4.2) Texture memory support Support for double precision atomic add PGI 2013 (CUDA

First Stage of Partial Sum

Reduce to grid of threads using grid-stride loop

nGrid = gridDim%x*blockDim%x

s = 0.0

ig = (blockIdx%x-1)*blockDim%x + threadIdx%x

do i = ig, n, nGrid

s = s + a(i)

end do

Page 13: SC13 - GTC On Demand | NVIDIA GTC Digital...CUDA Fortran 2012/2013 Features PGI 2012 (CUDA 4.1 and 4.2) Texture memory support Support for double precision atomic add PGI 2013 (CUDA

SHFL (shuffle) functions

Intra-warp data exchange

Threads can read other threads’ registers

No shared memory required, no synchronization barriers

Requires compute capability >= 3.0

Page 14: SC13 - GTC On Demand | NVIDIA GTC Digital...CUDA Fortran 2012/2013 Features PGI 2012 (CUDA 4.1 and 4.2) Texture memory support Support for double precision atomic add PGI 2013 (CUDA

t = __shfl_xor(s, 1)

s = threadIdx%x

t = __shfl_xor(s, 2)

s = s + t

1 2 3 4 5 6 7 8 9 10 11 12 13 14 15 16 s: . . .

2 1 4 3 6 5 8 7 10 9 12 11 14 13 16 15 t: . . .

s = s + t

3 3 7 7 11 11 15 15 19 19 23 23 27 27 31 31 s: . . .

10 10 10 10 26 26 26 26 42 42 42 42 58 58 58 58 s: . . .

Page 15: SC13 - GTC On Demand | NVIDIA GTC Digital...CUDA Fortran 2012/2013 Features PGI 2012 (CUDA 4.1 and 4.2) Texture memory support Support for double precision atomic add PGI 2013 (CUDA

Reduce within warp using SHFL functions

! reduce within warp

t = __shfl_xor(s, 1)

s = s + t

t = __shfl_xor(s, 2)

s = s + t

t = __shfl_xor(s, 4)

s = s + t

t = __shfl_xor(s, 8)

s = s + t

t = __shfl_xor(s, 16)

s = s + t

Page 16: SC13 - GTC On Demand | NVIDIA GTC Digital...CUDA Fortran 2012/2013 Features PGI 2012 (CUDA 4.1 and 4.2) Texture memory support Support for double precision atomic add PGI 2013 (CUDA

Last Stage of Partial Sum

Reduce to gridDim%x partial sums, one from each thread block

if (BlockDim%x == 32) then

if (threadIdx%x == 1) p(blockIdx%x) = s

else

warpID = (threadIdx%x-1)/32+1

laneID = iand(threadIdx%x,31)

if (laneID == 1) p_s(warpID) = s

call syncthreads()

if (warpID == 1) then ! Reduce in warp 1

width = blockDim%x/32

s = p_s(threadIdx%x)

i = 1

do while (i < width)

t = __shfl_xor(s, i, width)

s = s + t

i = i*2

end do

if (threadIdx%x == 1) p(blockIdx%x) = s

end if

end if

Page 17: SC13 - GTC On Demand | NVIDIA GTC Digital...CUDA Fortran 2012/2013 Features PGI 2012 (CUDA 4.1 and 4.2) Texture memory support Support for double precision atomic add PGI 2013 (CUDA

1.00E-07

1.00E-06

1.00E-05

1.00E-04

1.00E-03

1.00E-02

1.00E-01

1.00E+00

2**8 2**10 2**12 2**14 2**16 2**18 2**20 2**22 2**24

Host-h Host-d CUF Kernel SUM()

Summation Performance in Seconds

Page 18: SC13 - GTC On Demand | NVIDIA GTC Digital...CUDA Fortran 2012/2013 Features PGI 2012 (CUDA 4.1 and 4.2) Texture memory support Support for double precision atomic add PGI 2013 (CUDA

CUDA Fortran with Managed Data

program pgi14x

use cudafor

integer, parameter :: n = 100000

integer, managed :: a(n), b(n), c(n)

a = [(i,i=1,n)]

b = 1

!$cuf kernel do <<< *, * >>>

do i = 1, n

c(i) = a(i) + b(i)

end do

if (sum(c).ne.n*(n+1)/2+n) then

print *,c(1),c(n)

end if

end

Page 19: SC13 - GTC On Demand | NVIDIA GTC Digital...CUDA Fortran 2012/2013 Features PGI 2012 (CUDA 4.1 and 4.2) Texture memory support Support for double precision atomic add PGI 2013 (CUDA

CUDA Fortran/OpenACC Interoperability

Calling CUDA Fortran kernels from accelerator data regions

Using CUDA Fortran device data in compute regions

!$acc data create(x) copy(y)

a = 3.0

!$acc kernels loop

do i = 1, n

x(i) = x_dev(i) + 1.0

y(i) = y(i) + real(i)

end do

call mysaxpy <<<block, thread>>> (n, a, x, y)

!$acc end data

Support of arguments with the device attribute in our OpenACC

2.0 Runtime Library Routines

Page 20: SC13 - GTC On Demand | NVIDIA GTC Digital...CUDA Fortran 2012/2013 Features PGI 2012 (CUDA 4.1 and 4.2) Texture memory support Support for double precision atomic add PGI 2013 (CUDA

CUDA Fortran Literature

Book Released in 2013

PGInsider articles at

http://www.pgroup.com

CUDA Fortran Reference Manual