module Futhark.CodeGen.OpenCL.Heuristics
  ( SizeHeuristic (..),
    DeviceType (..),
    WhichSize (..),
    DeviceInfo (..),
    sizeHeuristicsTable,
  )
where
import Futhark.Analysis.PrimExp
import Futhark.Util.Pretty
data DeviceType = DeviceCPU | DeviceGPU
newtype DeviceInfo = DeviceInfo String
instance Pretty DeviceInfo where
  pretty :: forall ann. DeviceInfo -> Doc ann
pretty (DeviceInfo String
s) = Doc ann
"device_info" forall a. Semigroup a => a -> a -> a
<> forall ann. Doc ann -> Doc ann
parens (forall a ann. Pretty a => a -> Doc ann
pretty String
s)
data WhichSize = LockstepWidth | NumGroups | GroupSize | TileSize | RegTileSize | Threshold
data SizeHeuristic = SizeHeuristic
  { SizeHeuristic -> String
platformName :: String,
    SizeHeuristic -> DeviceType
deviceType :: DeviceType,
    SizeHeuristic -> WhichSize
heuristicSize :: WhichSize,
    SizeHeuristic -> TPrimExp Int32 DeviceInfo
heuristicValue :: TPrimExp Int32 DeviceInfo
  }
sizeHeuristicsTable :: [SizeHeuristic]
sizeHeuristicsTable :: [SizeHeuristic]
sizeHeuristicsTable =
  [ String
-> DeviceType
-> WhichSize
-> TPrimExp Int32 DeviceInfo
-> SizeHeuristic
SizeHeuristic String
"NVIDIA CUDA" DeviceType
DeviceGPU WhichSize
LockstepWidth TPrimExp Int32 DeviceInfo
32,
    String
-> DeviceType
-> WhichSize
-> TPrimExp Int32 DeviceInfo
-> SizeHeuristic
SizeHeuristic String
"AMD Accelerated Parallel Processing" DeviceType
DeviceGPU WhichSize
LockstepWidth TPrimExp Int32 DeviceInfo
32,
    String
-> DeviceType
-> WhichSize
-> TPrimExp Int32 DeviceInfo
-> SizeHeuristic
SizeHeuristic String
"" DeviceType
DeviceGPU WhichSize
LockstepWidth TPrimExp Int32 DeviceInfo
1,
    
    
    
    String
-> DeviceType
-> WhichSize
-> TPrimExp Int32 DeviceInfo
-> SizeHeuristic
SizeHeuristic String
"" DeviceType
DeviceGPU WhichSize
NumGroups forall a b. (a -> b) -> a -> b
$ TPrimExp Int32 DeviceInfo
4 forall a. Num a => a -> a -> a
* forall {k} {t :: k}. TPrimExp t DeviceInfo
max_compute_units,
    String
-> DeviceType
-> WhichSize
-> TPrimExp Int32 DeviceInfo
-> SizeHeuristic
SizeHeuristic String
"" DeviceType
DeviceGPU WhichSize
GroupSize TPrimExp Int32 DeviceInfo
256,
    String
-> DeviceType
-> WhichSize
-> TPrimExp Int32 DeviceInfo
-> SizeHeuristic
SizeHeuristic String
"" DeviceType
DeviceGPU WhichSize
TileSize TPrimExp Int32 DeviceInfo
16,
    String
-> DeviceType
-> WhichSize
-> TPrimExp Int32 DeviceInfo
-> SizeHeuristic
SizeHeuristic String
"" DeviceType
DeviceGPU WhichSize
RegTileSize TPrimExp Int32 DeviceInfo
4,
    String
-> DeviceType
-> WhichSize
-> TPrimExp Int32 DeviceInfo
-> SizeHeuristic
SizeHeuristic String
"" DeviceType
DeviceGPU WhichSize
Threshold forall a b. (a -> b) -> a -> b
$ TPrimExp Int32 DeviceInfo
32 forall a. Num a => a -> a -> a
* TPrimExp Int32 DeviceInfo
1024,
    String
-> DeviceType
-> WhichSize
-> TPrimExp Int32 DeviceInfo
-> SizeHeuristic
SizeHeuristic String
"" DeviceType
DeviceCPU WhichSize
LockstepWidth TPrimExp Int32 DeviceInfo
1,
    String
-> DeviceType
-> WhichSize
-> TPrimExp Int32 DeviceInfo
-> SizeHeuristic
SizeHeuristic String
"" DeviceType
DeviceCPU WhichSize
NumGroups forall {k} {t :: k}. TPrimExp t DeviceInfo
max_compute_units,
    String
-> DeviceType
-> WhichSize
-> TPrimExp Int32 DeviceInfo
-> SizeHeuristic
SizeHeuristic String
"" DeviceType
DeviceCPU WhichSize
GroupSize TPrimExp Int32 DeviceInfo
32,
    String
-> DeviceType
-> WhichSize
-> TPrimExp Int32 DeviceInfo
-> SizeHeuristic
SizeHeuristic String
"" DeviceType
DeviceCPU WhichSize
TileSize TPrimExp Int32 DeviceInfo
4,
    String
-> DeviceType
-> WhichSize
-> TPrimExp Int32 DeviceInfo
-> SizeHeuristic
SizeHeuristic String
"" DeviceType
DeviceCPU WhichSize
RegTileSize TPrimExp Int32 DeviceInfo
1,
    String
-> DeviceType
-> WhichSize
-> TPrimExp Int32 DeviceInfo
-> SizeHeuristic
SizeHeuristic String
"" DeviceType
DeviceCPU WhichSize
Threshold forall {k} {t :: k}. TPrimExp t DeviceInfo
max_compute_units
  ]
  where
    max_compute_units :: TPrimExp t DeviceInfo
max_compute_units =
      forall {k} (t :: k) v. PrimExp v -> TPrimExp t v
TPrimExp forall a b. (a -> b) -> a -> b
$ forall v. v -> PrimType -> PrimExp v
LeafExp (String -> DeviceInfo
DeviceInfo String
"MAX_COMPUTE_UNITS") forall a b. (a -> b) -> a -> b
$ IntType -> PrimType
IntType IntType
Int32