Skip to content

Commit

Permalink
Major update: to context creation and device selection.
Browse files Browse the repository at this point in the history
Add quick setup function fclInit which selects a device from across all available platforms based on criteria and sets the default context accordingly.
Also add vendor and extensions filter to device selection criteria.
Fix device selection bug in sorting.
Update examples to use new fclInit function.
  • Loading branch information
LKedward committed Mar 5, 2020
1 parent d09e145 commit 391281b
Show file tree
Hide file tree
Showing 7 changed files with 249 additions and 52 deletions.
1 change: 1 addition & 0 deletions .gitignore
Original file line number Diff line number Diff line change
Expand Up @@ -4,6 +4,7 @@
*.smod
*.a
doc/*
bin/*
*fclKernels.cl
test/testSummary
test/test_outputs*
Expand Down
29 changes: 13 additions & 16 deletions examples/nbody.f90
Original file line number Diff line number Diff line change
Expand Up @@ -20,11 +20,11 @@ program nbody
character(*), parameter :: cl_vendor = 'nvidia,amd,intel' ! Vendors for which to create OpenCL context in order of preference

! ---------Program variables ---------
integer :: i, nBlock
integer :: i
integer(c_size_t) :: kern1T, kern2T
real :: Tavg, perf
character(:), allocatable :: kernelSrc ! Kernel source string
type(fclDevice), allocatable :: devices(:) ! List of focal devices
type(fclDevice) :: device ! OpenCL device on which to run
type(fclProgram) :: prog ! Focal program object
type(fclKernel) :: kern1, kern2 ! Focal kernel object
type(fclEvent) :: e
Expand All @@ -40,32 +40,29 @@ program nbody
write(*,*) ('-',i=1,72)
write(*,*)

! Create context with nvidia platform
call fclSetDefaultContext(fclCreateContext(vendor=cl_vendor))
! Initialise OpenCL context and select device with most cores
device = fclInit(vendor=cl_vendor,sortBy='cores')

! Select device with most cores and create command queue
devices = fclFindDevices(sortBy='cores')
call fclSetDefaultCommandQ(fclCreateCommandQ(devices(1),enableProfiling=.true., &
call fclSetDefaultCommandQ(fclCreateCommandQ(device,enableProfiling=.true., &
outOfOrderExec=.true.,blockingWrite=.false.))

write(*,*) ' Created OpenCL command queue on device: "',devices(1)%name,'"'
write(*,'(A,I6,A,I6,A,I4,A,A,A)') ' (', devices(1)%nComputeUnits,' cores, ', &
devices(1)%global_memory/1024/1024,'MB, ', &
devices(1)%clock_freq, 'MHz, ',&
devices(1)%version,')'
write(*,*) ' Created OpenCL command queue on device: "',device%name,'"'
write(*,'(A,I6,A,I6,A,I4,A,A,A)') ' (', device%nComputeUnits,' cores, ', &
device%global_memory/1024/1024,'MB, ', &
device%clock_freq, 'MHz, ',&
device%version,')'
write(*,*) ''

! Set profiler device
profiler%device = devices(1)
profiler%device = device

! Load kernels from file and compile
call fclGetKernelResource(kernelSrc)
prog = fclCompileProgram(kernelSrc)

! Get kernel objects and set local/global work sizes
nBlock = (N+blockSize-1)/blockSize
kern1 = fclGetProgramKernel(prog,'bodyForces',[nBlock*blockSize],[blockSize])
kern2 = fclGetProgramKernel(prog,'integrateBodies',[nBlock*blockSize],[blockSize])
kern1 = fclGetProgramKernel(prog,'bodyForces',[N],[blockSize])
kern2 = fclGetProgramKernel(prog,'integrateBodies',[N],[blockSize])

call fclProfilerAdd(profiler,Niter,kern1,kern2)

Expand Down
1 change: 1 addition & 0 deletions examples/platform_query.f90
Original file line number Diff line number Diff line change
Expand Up @@ -37,6 +37,7 @@ program platform_query
platforms(i)%devices(j)%global_memory/1024/1024,'MB, ', &
platforms(i)%devices(j)%clock_freq, 'MHz, ',&
platforms(i)%devices(j)%version
! write(*,*) platforms(i)%devices(j)%extensions

end do

Expand Down
11 changes: 5 additions & 6 deletions examples/sum.f90
Original file line number Diff line number Diff line change
Expand Up @@ -9,21 +9,20 @@ program sum

integer :: i ! Counter variable
character(:), allocatable :: kernelSrc ! Kernel source string
type(fclDevice), allocatable :: devices(:) ! List of focal devices
type(fclDevice) :: device ! OpenCL device on which to run
type(fclProgram) :: prog ! Focal program object
type(fclKernel) :: sumKernel ! Focal kernel object
real(c_float) :: array1(Nelem) ! Host array 1
real(c_float) :: array2(Nelem) ! Host array 2
type(fclDeviceFloat) :: array1_d ! Device array 1
type(fclDeviceFloat) :: array2_d ! Device array 2

! Create context with nvidia platform
call fclSetDefaultContext(fclCreateContext(vendor='nvidia,amd,intel'))
! Initialise OpenCL context and select device with most cores
device = fclInit(vendor='nvidia,amd,intel',sortBy='cores')

! Select device with most cores and create command queue
devices = fclFindDevices(sortBy='cores') !,type='cpu')
write(*,*) 'Using device: ',devices(1)%name
call fclSetDefaultCommandQ(fclCreateCommandQ(devices(1),enableProfiling=.true.))
write(*,*) 'Using device: ',device%name
call fclSetDefaultCommandQ(fclCreateCommandQ(device,enableProfiling=.true.))

! Load kernel from file and compile
! call fclSourceFromFile('examples/sum.cl',kernelSrc)
Expand Down
85 changes: 83 additions & 2 deletions src/Focal.f90
Original file line number Diff line number Diff line change
Expand Up @@ -63,6 +63,11 @@ module Focal
integer(c_int64_t) :: global_memory !! Total global memory, bytes
integer(c_int32_t) :: clock_freq !! Max clock frequency, MHz
character(:), allocatable :: version !! OpenCL version
character(:), allocatable :: extensions !! Supported OpenCL extensions
type(fclPlatform), pointer :: platform !! Pointer to containing platform
integer(c_intptr_t) :: cl_platform_id !! OpenCL platform pointer
character(:), allocatable :: platformName !! Name of containing platform
character(:), allocatable :: platformVendor !! Vendor of containing platform
end type fclDevice

type :: fclPlatform
Expand Down Expand Up @@ -1008,23 +1013,99 @@ module subroutine fclSetDefaultContext(ctx)
!! Set the global default context
type(fclContext), intent(in) :: ctx
end subroutine fclSetDefaultContext

module function fclFilterDevices(devices,vendor,type,nameLike,extensions,sortBy) result(deviceList)
!! Filter and sort list of devices based on criteria
type(fclDevice), intent(in) :: devices(:)
character(*), intent(in), optional :: vendor
!! Filter device list based on platform vendor.
!! Specify multiple possible vendors in comma-separate list
character(*), intent(in), optional :: type
!! Filter device list based on device type.
!! Specify at least one of 'cpu', 'gpu', default: 'cpu,gpu' (both)
character(*), intent(in), optional :: nameLike
!! Filter devices based on device name. Look for this substring in device name.
character(*), intent(in), optional :: extensions
!! Filter devices based on supported device extensions.
!! Specify comma-separated list of OpenCL extension names, e.g. cl_khr_fp64.
!! See [clGetDeviceInfo](https://www.khronos.org/registry/OpenCL/sdk/1.2/docs/man/xhtml/clGetDeviceInfo.html)
!! Extensions specified are requirements: devices are filtered-out if they don't support all extensions specified.
character(*), intent(in), optional :: sortBy
!! Sort device list based on either 'memory': total global memory,
!! 'cores': total number of compute units, 'clock': maximum clock speed
type(fclDevice), allocatable :: deviceList(:)
!! Filtered and sorted list. Unallocated if no matching devices found.
end function fclFilterDevices

module function fclInit(vendor,type,nameLike,extensions,sortBy) result(device)
!! Quick setup helper function: find a single device based on criteria
!! and set the default context accordingly.
!! Raises runtime error if no matching device is found.
character(*), intent(in), optional :: vendor
!! Filter device based on platform vendor
!! Specify multiple possible vendors in comma-separate list
character(*), intent(in), optional :: type
!! Filter device list based on device type.
!! Specify at least one of 'cpu', 'gpu', default: 'cpu,gpu' (both)
character(*), intent(in), optional :: nameLike
!! Filter devices based on device name. Look for this substring in device name.
character(*), intent(in), optional :: extensions
!! Filter devices based on supported device extensions.
!! Specify comma-separated list of OpenCL extension names, e.g. cl_khr_fp64.
!! See [clGetDeviceInfo](https://www.khronos.org/registry/OpenCL/sdk/1.2/docs/man/xhtml/clGetDeviceInfo.html)
!! Extensions specified are requirements: devices are filtered-out if they don't support all extensions specified.
character(*), intent(in), optional :: sortBy
!! Sort device list based on either 'memory': total global memory,
!! 'cores': total number of compute units, 'clock': maximum clock speed
type(fclDevice), allocatable :: device
!! The device chosen based on the user criteria
end function fclInit

end interface

interface fclFindDevices
!! Generic interface to list devices, sorted and filtered by properties
!! Raises runtime error if no matching device is found.

module function fclFindDevices_1(ctx,type,nameLike,sortBy) result(deviceList)
module function fclFindDevices_1(ctx,vendor,type,nameLike,extensions,sortBy) result(deviceList)
type(fclContext), intent(in), target :: ctx
!! Context containing device for command queue
character(*), intent(in), optional :: vendor
!! Filter device list based on platform vendor.
!! Specify multiple possible vendors in comma-separate list
character(*), intent(in), optional :: type
!! Filter device list based on device type.
!! Specify at least one of 'cpu', 'gpu', default: 'cpu,gpu' (both)
character(*), intent(in), optional :: nameLike
!! Filter devices based on device name. Look for this substring in device name.
character(*), intent(in), optional :: extensions
!! Filter devices based on supported device extensions.
!! Specify comma-separated list of OpenCL extension names, e.g. cl_khr_fp64.
!! See [clGetDeviceInfo](https://www.khronos.org/registry/OpenCL/sdk/1.2/docs/man/xhtml/clGetDeviceInfo.html)
!! Extensions specified are requirements: devices are filtered-out if they don't support all extensions specified.
character(*), intent(in), optional :: sortBy
!! Sort device list based on either 'memory': total global memory,
!! 'cores': total number of compute units, 'clock': maximum clock speed
type(fclDevice), allocatable :: deviceList(:)
end function fclFindDevices_1

module function fclFindDevices_2(type,nameLike,sortBy) result(deviceList)
module function fclFindDevices_2(vendor,type,nameLike,extensions,sortBy) result(deviceList)
character(*), intent(in), optional :: vendor
!! Filter device list based on platform vendor.
!! Specify multiple possible vendors in comma-separate list
character(*), intent(in), optional :: type
!! Filter device list based on device type.
!! Specify at least one of 'cpu', 'gpu', default: 'cpu,gpu' (both)
character(*), intent(in), optional :: nameLike
!! Filter devices based on device name. Look for this substring in device name.
character(*), intent(in), optional :: extensions
!! Filter devices based on supported device extensions.
!! Specify comma-separated list of OpenCL extension names, e.g. cl_khr_fp64.
!! See [clGetDeviceInfo](https://www.khronos.org/registry/OpenCL/sdk/1.2/docs/man/xhtml/clGetDeviceInfo.html)
!! Extensions specified are requirements: devices are filtered-out if they don't support all extensions specified.
character(*), intent(in), optional :: sortBy
!! Sort device list based on either 'memory': total global memory,
!! 'cores': total number of compute units, 'clock': maximum clock speed
type(fclDevice), allocatable :: deviceList(:)
end function fclFindDevices_2

Expand Down
17 changes: 11 additions & 6 deletions src/Focal_Query.f90
Original file line number Diff line number Diff line change
Expand Up @@ -274,19 +274,23 @@
C_LOC(platform%cl_device_ids), int32_ret)
call fclErrorHandler(errcode,'fclGetPlatform','clGetDeviceIDs')

! --- Populate fclPlatform info strings ---
call fclGetPlatformInfo(platform,CL_PLATFORM_PROFILE,platform%profile)
call fclGetPlatformInfo(platform,CL_PLATFORM_VERSION,platform%version)
call fclGetPlatformInfo(platform,CL_PLATFORM_NAME,platform%name)
call fclGetPlatformInfo(platform,CL_PLATFORM_VENDOR,platform%vendor)
call fclGetPlatformInfo(platform,CL_PLATFORM_EXTENSIONS,platform%extensions)

! --- Populate fclDevice structure array ---
do i=1,platform%numDevice

platform%devices(i) = fclGetDevice(platform%cl_device_ids(i))
platform%devices(i)%platformName = platform%name
platform%devices(i)%platformVendor = platform%vendor
platform%devices(i)%cl_platform_id = platform_id

end do

! --- Populate fclPlatform info strings ---
call fclGetPlatformInfo(platform,CL_PLATFORM_PROFILE,platform%profile)
call fclGetPlatformInfo(platform,CL_PLATFORM_VERSION,platform%version)
call fclGetPlatformInfo(platform,CL_PLATFORM_NAME,platform%name)
call fclGetPlatformInfo(platform,CL_PLATFORM_VENDOR,platform%vendor)
call fclGetPlatformInfo(platform,CL_PLATFORM_EXTENSIONS,platform%extensions)

end procedure fclGetPlatform
! ---------------------------------------------------------------------------
Expand All @@ -303,6 +307,7 @@
call fclGetDeviceInfo(device,CL_DEVICE_GLOBAL_MEM_SIZE,device%global_memory)
call fclGetDeviceInfo(device,CL_DEVICE_MAX_CLOCK_FREQUENCY,device%clock_freq)
call fclGetDeviceInfo(device,CL_DEVICE_VERSION,device%version)
call fclGetDeviceInfo(device,CL_DEVICE_EXTENSIONS,device%extensions)

end procedure fclGetDevice
! ---------------------------------------------------------------------------
Expand Down
Loading

0 comments on commit 391281b

Please sign in to comment.