11{-# LANGUAGE MagicHash #-}
22{-# LANGUAGE RecordWildCards #-}
3+ {-# LANGUAGE LambdaCase #-}
4+ {-# LANGUAGE TupleSections #-}
35-- |
46-- Module : Data.Array.Accelerate.Math.FFT.LLVM.PTX.Plans
57-- Copyright : [2017..2020] The Accelerate Team
@@ -19,26 +21,32 @@ module Data.Array.Accelerate.Math.FFT.LLVM.PTX.Plans (
1921) where
2022
2123import Data.Array.Accelerate.Lifetime
22- import Data.Array.Accelerate.LLVM.PTX
24+ import Data.Array.Accelerate.LLVM.PTX hiding ( stream , poll )
2325import Data.Array.Accelerate.LLVM.PTX.Foreign
2426
2527import Data.Array.Accelerate.Math.FFT.LLVM.PTX.Base
2628
2729import Control.Concurrent.MVar
30+ import Control.Monad.Catch
2831import Control.Monad.State
29- import Data.HashMap.Strict
32+ import Data.HashMap.Strict hiding ( map , update )
3033import qualified Data.HashMap.Strict as Map
3134
3235import qualified Foreign.CUDA.Driver.Context as CUDA
36+ import qualified Foreign.CUDA.Driver.Stream as CUDA
3337import qualified Foreign.CUDA.FFT as FFT
3438
3539import GHC.Ptr
3640import GHC.Base
37- import Prelude hiding ( lookup )
41+ import Prelude hiding ( lookup , mapM )
42+ import Data.Maybe
43+ import Control.Arrow (second )
44+ import Data.Function ((&) )
45+ import Control.Monad.Reader (asks )
3846
3947
4048data Plans a = Plans
41- { plans :: {-# UNPACK #-} ! (MVar ( HashMap (Int , Int ) (Lifetime FFT. Handle) ))
49+ { plans :: {-# UNPACK #-} ! (MVar ( HashMap (Int , Int ) [ (Lifetime FFT. Handle, Maybe ( Par PTX Bool , CUDA. Stream ))] ))
4250 , create :: a -> IO FFT. Handle
4351 , hash :: a -> Int
4452 }
@@ -62,30 +70,57 @@ createPlan via mix =
6270--
6371-- <http://docs.nvidia.com/cuda/cufft/index.html#thread-safety>
6472--
73+ -- TODO: Determine if this handle is used in the same stream.
6574{-# INLINE withPlan #-}
66- withPlan :: Plans a -> a -> (FFT. Handle -> LLVM PTX b ) -> LLVM PTX b
75+ withPlan :: Plans a -> a -> (FFT. Handle -> Par PTX ( Future b )) -> Par PTX ( Future b )
6776withPlan Plans {.. } a k = do
6877 lc <- gets (deviceContext . ptxContext)
69- h <- liftIO $
70- withLifetime lc $ \ ctx ->
71- modifyMVar plans $ \ pm ->
72- let key = (toKey ctx, hash a) in
73- case Map. lookup key pm of
74- -- handle does not exist yet; create it and add to the global
75- -- state for reuse
76- Nothing -> do
77- h <- create a
78- l <- newLifetime h
79- addFinalizer lc $ modifyMVar plans (\ pm' -> return (Map. delete key pm', () ))
80- addFinalizer l $ FFT. destroy h
81- return ( Map. insert key l pm, l )
82-
83- -- return existing handle
84- Just h -> return (pm, h)
85- --
86- withLifetime' h k
78+ ls <- asks ptxStream
79+ withLifetime' ls $ \ stream ->
80+ withLifetime' lc $ \ ctx -> do
81+ let key = (toKey ctx, hash a)
82+ -- Extract an existing cuFFT plan handle from our plan cache that isn't busy,
83+ -- if one cannot be found, create a new cuFFT handle.
84+ h <- modifyMVar' plans $ \ pm -> do
85+ let maybeHandles = pm !? key
86+ handles = fromMaybe [] maybeHandles
87+
88+ update Nothing = pure Nothing
89+ update orig@ (Just (isReady, _)) = isReady >>= \ case
90+ True -> pure Nothing
91+ False -> pure orig
92+
93+ updatedHandles <- zip (map fst handles) <$> mapM (update . snd ) handles
94+
95+ -- Extract first handle which is either entirely ready or is used but within the same stream
96+ let extractFirstReady [] = (Nothing , [] )
97+ extractFirstReady (x@ (_, Nothing ): xs) = (Just x, xs)
98+ extractFirstReady (x@ (_, Just (_, s)): xs) | stream == s = (Just x, xs)
99+ extractFirstReady (x@ (_, Just _): xs) = second (x: ) $ extractFirstReady xs
100+
101+ (maybeReadyHandle, otherHandles) = extractFirstReady updatedHandles
102+
103+ newHandle = liftIO $ do
104+ h <- create a
105+ l <- newLifetime h
106+ addFinalizer l $ FFT. destroy h
107+ when (isNothing maybeHandles) $
108+ addFinalizer lc $ modifyMVar_ plans $ pure . Map. delete key
109+ pure l
110+
111+ maybeReadyHandle & maybe newHandle (pure . fst )
112+ & fmap (Map. insert key otherHandles pm,)
113+ -- Ensure the handle is always returned back to the plan cache
114+ let returnHandle = liftIO $ modifyMVar_ plans $ pure . Map. adjust ((h, Nothing ): ) key
115+ flip onException returnHandle $ do
116+ -- Invoke user-provided function with cuFFT handle
117+ future <- withLifetime' h k
118+ -- Push new cuFFT plan-handle onto list of plan-handles of equal settings,
119+ -- w/ callback to check if the cuFFT handle is ready to use again.
120+ planHandleEntry <- (h,) . Just . (,stream) . fmap isJust . poll <$> statusHandle future
121+ liftIO $ modifyMVar_ plans $ pure . Map. adjust (planHandleEntry: ) key
122+ pure future
87123
88124{-# INLINE toKey #-}
89125toKey :: CUDA. Context -> Int
90126toKey (CUDA. Context (Ptr addr# )) = I # (addr2Int# addr# )
91-
0 commit comments