{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE TypeSynonymInstances #-}

module Data.SpirV.Enum.KernelProfilingInfo where

import Data.Bits (Bits, FiniteBits, (.|.))
import Data.Word (Word32)
import Foreign.Storable (Storable)

type KernelProfilingInfo = KernelProfilingInfoBits

newtype KernelProfilingInfoBits = KernelProfilingInfoBits Word32
  deriving newtype (KernelProfilingInfoBits -> KernelProfilingInfoBits -> Bool
(KernelProfilingInfoBits -> KernelProfilingInfoBits -> Bool)
-> (KernelProfilingInfoBits -> KernelProfilingInfoBits -> Bool)
-> Eq KernelProfilingInfoBits
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: KernelProfilingInfoBits -> KernelProfilingInfoBits -> Bool
== :: KernelProfilingInfoBits -> KernelProfilingInfoBits -> Bool
$c/= :: KernelProfilingInfoBits -> KernelProfilingInfoBits -> Bool
/= :: KernelProfilingInfoBits -> KernelProfilingInfoBits -> Bool
Eq, Eq KernelProfilingInfoBits
Eq KernelProfilingInfoBits =>
(KernelProfilingInfoBits -> KernelProfilingInfoBits -> Ordering)
-> (KernelProfilingInfoBits -> KernelProfilingInfoBits -> Bool)
-> (KernelProfilingInfoBits -> KernelProfilingInfoBits -> Bool)
-> (KernelProfilingInfoBits -> KernelProfilingInfoBits -> Bool)
-> (KernelProfilingInfoBits -> KernelProfilingInfoBits -> Bool)
-> (KernelProfilingInfoBits
    -> KernelProfilingInfoBits -> KernelProfilingInfoBits)
-> (KernelProfilingInfoBits
    -> KernelProfilingInfoBits -> KernelProfilingInfoBits)
-> Ord KernelProfilingInfoBits
KernelProfilingInfoBits -> KernelProfilingInfoBits -> Bool
KernelProfilingInfoBits -> KernelProfilingInfoBits -> Ordering
KernelProfilingInfoBits
-> KernelProfilingInfoBits -> KernelProfilingInfoBits
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: KernelProfilingInfoBits -> KernelProfilingInfoBits -> Ordering
compare :: KernelProfilingInfoBits -> KernelProfilingInfoBits -> Ordering
$c< :: KernelProfilingInfoBits -> KernelProfilingInfoBits -> Bool
< :: KernelProfilingInfoBits -> KernelProfilingInfoBits -> Bool
$c<= :: KernelProfilingInfoBits -> KernelProfilingInfoBits -> Bool
<= :: KernelProfilingInfoBits -> KernelProfilingInfoBits -> Bool
$c> :: KernelProfilingInfoBits -> KernelProfilingInfoBits -> Bool
> :: KernelProfilingInfoBits -> KernelProfilingInfoBits -> Bool
$c>= :: KernelProfilingInfoBits -> KernelProfilingInfoBits -> Bool
>= :: KernelProfilingInfoBits -> KernelProfilingInfoBits -> Bool
$cmax :: KernelProfilingInfoBits
-> KernelProfilingInfoBits -> KernelProfilingInfoBits
max :: KernelProfilingInfoBits
-> KernelProfilingInfoBits -> KernelProfilingInfoBits
$cmin :: KernelProfilingInfoBits
-> KernelProfilingInfoBits -> KernelProfilingInfoBits
min :: KernelProfilingInfoBits
-> KernelProfilingInfoBits -> KernelProfilingInfoBits
Ord, Ptr KernelProfilingInfoBits -> IO KernelProfilingInfoBits
Ptr KernelProfilingInfoBits -> Int -> IO KernelProfilingInfoBits
Ptr KernelProfilingInfoBits
-> Int -> KernelProfilingInfoBits -> IO ()
Ptr KernelProfilingInfoBits -> KernelProfilingInfoBits -> IO ()
KernelProfilingInfoBits -> Int
(KernelProfilingInfoBits -> Int)
-> (KernelProfilingInfoBits -> Int)
-> (Ptr KernelProfilingInfoBits
    -> Int -> IO KernelProfilingInfoBits)
-> (Ptr KernelProfilingInfoBits
    -> Int -> KernelProfilingInfoBits -> IO ())
-> (forall b. Ptr b -> Int -> IO KernelProfilingInfoBits)
-> (forall b. Ptr b -> Int -> KernelProfilingInfoBits -> IO ())
-> (Ptr KernelProfilingInfoBits -> IO KernelProfilingInfoBits)
-> (Ptr KernelProfilingInfoBits
    -> KernelProfilingInfoBits -> IO ())
-> Storable KernelProfilingInfoBits
forall b. Ptr b -> Int -> IO KernelProfilingInfoBits
forall b. Ptr b -> Int -> KernelProfilingInfoBits -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (Ptr a -> Int -> IO a)
-> (Ptr a -> Int -> a -> IO ())
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> (Ptr a -> IO a)
-> (Ptr a -> a -> IO ())
-> Storable a
$csizeOf :: KernelProfilingInfoBits -> Int
sizeOf :: KernelProfilingInfoBits -> Int
$calignment :: KernelProfilingInfoBits -> Int
alignment :: KernelProfilingInfoBits -> Int
$cpeekElemOff :: Ptr KernelProfilingInfoBits -> Int -> IO KernelProfilingInfoBits
peekElemOff :: Ptr KernelProfilingInfoBits -> Int -> IO KernelProfilingInfoBits
$cpokeElemOff :: Ptr KernelProfilingInfoBits
-> Int -> KernelProfilingInfoBits -> IO ()
pokeElemOff :: Ptr KernelProfilingInfoBits
-> Int -> KernelProfilingInfoBits -> IO ()
$cpeekByteOff :: forall b. Ptr b -> Int -> IO KernelProfilingInfoBits
peekByteOff :: forall b. Ptr b -> Int -> IO KernelProfilingInfoBits
$cpokeByteOff :: forall b. Ptr b -> Int -> KernelProfilingInfoBits -> IO ()
pokeByteOff :: forall b. Ptr b -> Int -> KernelProfilingInfoBits -> IO ()
$cpeek :: Ptr KernelProfilingInfoBits -> IO KernelProfilingInfoBits
peek :: Ptr KernelProfilingInfoBits -> IO KernelProfilingInfoBits
$cpoke :: Ptr KernelProfilingInfoBits -> KernelProfilingInfoBits -> IO ()
poke :: Ptr KernelProfilingInfoBits -> KernelProfilingInfoBits -> IO ()
Storable, Eq KernelProfilingInfoBits
KernelProfilingInfoBits
Eq KernelProfilingInfoBits =>
(KernelProfilingInfoBits
 -> KernelProfilingInfoBits -> KernelProfilingInfoBits)
-> (KernelProfilingInfoBits
    -> KernelProfilingInfoBits -> KernelProfilingInfoBits)
-> (KernelProfilingInfoBits
    -> KernelProfilingInfoBits -> KernelProfilingInfoBits)
-> (KernelProfilingInfoBits -> KernelProfilingInfoBits)
-> (KernelProfilingInfoBits -> Int -> KernelProfilingInfoBits)
-> (KernelProfilingInfoBits -> Int -> KernelProfilingInfoBits)
-> KernelProfilingInfoBits
-> (Int -> KernelProfilingInfoBits)
-> (KernelProfilingInfoBits -> Int -> KernelProfilingInfoBits)
-> (KernelProfilingInfoBits -> Int -> KernelProfilingInfoBits)
-> (KernelProfilingInfoBits -> Int -> KernelProfilingInfoBits)
-> (KernelProfilingInfoBits -> Int -> Bool)
-> (KernelProfilingInfoBits -> Maybe Int)
-> (KernelProfilingInfoBits -> Int)
-> (KernelProfilingInfoBits -> Bool)
-> (KernelProfilingInfoBits -> Int -> KernelProfilingInfoBits)
-> (KernelProfilingInfoBits -> Int -> KernelProfilingInfoBits)
-> (KernelProfilingInfoBits -> Int -> KernelProfilingInfoBits)
-> (KernelProfilingInfoBits -> Int -> KernelProfilingInfoBits)
-> (KernelProfilingInfoBits -> Int -> KernelProfilingInfoBits)
-> (KernelProfilingInfoBits -> Int -> KernelProfilingInfoBits)
-> (KernelProfilingInfoBits -> Int)
-> Bits KernelProfilingInfoBits
Int -> KernelProfilingInfoBits
KernelProfilingInfoBits -> Bool
KernelProfilingInfoBits -> Int
KernelProfilingInfoBits -> Maybe Int
KernelProfilingInfoBits -> KernelProfilingInfoBits
KernelProfilingInfoBits -> Int -> Bool
KernelProfilingInfoBits -> Int -> KernelProfilingInfoBits
KernelProfilingInfoBits
-> KernelProfilingInfoBits -> KernelProfilingInfoBits
forall a.
Eq a =>
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> a
-> (Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> Bool)
-> (a -> Maybe Int)
-> (a -> Int)
-> (a -> Bool)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int)
-> Bits a
$c.&. :: KernelProfilingInfoBits
-> KernelProfilingInfoBits -> KernelProfilingInfoBits
.&. :: KernelProfilingInfoBits
-> KernelProfilingInfoBits -> KernelProfilingInfoBits
$c.|. :: KernelProfilingInfoBits
-> KernelProfilingInfoBits -> KernelProfilingInfoBits
.|. :: KernelProfilingInfoBits
-> KernelProfilingInfoBits -> KernelProfilingInfoBits
$cxor :: KernelProfilingInfoBits
-> KernelProfilingInfoBits -> KernelProfilingInfoBits
xor :: KernelProfilingInfoBits
-> KernelProfilingInfoBits -> KernelProfilingInfoBits
$ccomplement :: KernelProfilingInfoBits -> KernelProfilingInfoBits
complement :: KernelProfilingInfoBits -> KernelProfilingInfoBits
$cshift :: KernelProfilingInfoBits -> Int -> KernelProfilingInfoBits
shift :: KernelProfilingInfoBits -> Int -> KernelProfilingInfoBits
$crotate :: KernelProfilingInfoBits -> Int -> KernelProfilingInfoBits
rotate :: KernelProfilingInfoBits -> Int -> KernelProfilingInfoBits
$czeroBits :: KernelProfilingInfoBits
zeroBits :: KernelProfilingInfoBits
$cbit :: Int -> KernelProfilingInfoBits
bit :: Int -> KernelProfilingInfoBits
$csetBit :: KernelProfilingInfoBits -> Int -> KernelProfilingInfoBits
setBit :: KernelProfilingInfoBits -> Int -> KernelProfilingInfoBits
$cclearBit :: KernelProfilingInfoBits -> Int -> KernelProfilingInfoBits
clearBit :: KernelProfilingInfoBits -> Int -> KernelProfilingInfoBits
$ccomplementBit :: KernelProfilingInfoBits -> Int -> KernelProfilingInfoBits
complementBit :: KernelProfilingInfoBits -> Int -> KernelProfilingInfoBits
$ctestBit :: KernelProfilingInfoBits -> Int -> Bool
testBit :: KernelProfilingInfoBits -> Int -> Bool
$cbitSizeMaybe :: KernelProfilingInfoBits -> Maybe Int
bitSizeMaybe :: KernelProfilingInfoBits -> Maybe Int
$cbitSize :: KernelProfilingInfoBits -> Int
bitSize :: KernelProfilingInfoBits -> Int
$cisSigned :: KernelProfilingInfoBits -> Bool
isSigned :: KernelProfilingInfoBits -> Bool
$cshiftL :: KernelProfilingInfoBits -> Int -> KernelProfilingInfoBits
shiftL :: KernelProfilingInfoBits -> Int -> KernelProfilingInfoBits
$cunsafeShiftL :: KernelProfilingInfoBits -> Int -> KernelProfilingInfoBits
unsafeShiftL :: KernelProfilingInfoBits -> Int -> KernelProfilingInfoBits
$cshiftR :: KernelProfilingInfoBits -> Int -> KernelProfilingInfoBits
shiftR :: KernelProfilingInfoBits -> Int -> KernelProfilingInfoBits
$cunsafeShiftR :: KernelProfilingInfoBits -> Int -> KernelProfilingInfoBits
unsafeShiftR :: KernelProfilingInfoBits -> Int -> KernelProfilingInfoBits
$crotateL :: KernelProfilingInfoBits -> Int -> KernelProfilingInfoBits
rotateL :: KernelProfilingInfoBits -> Int -> KernelProfilingInfoBits
$crotateR :: KernelProfilingInfoBits -> Int -> KernelProfilingInfoBits
rotateR :: KernelProfilingInfoBits -> Int -> KernelProfilingInfoBits
$cpopCount :: KernelProfilingInfoBits -> Int
popCount :: KernelProfilingInfoBits -> Int
Bits, Bits KernelProfilingInfoBits
Bits KernelProfilingInfoBits =>
(KernelProfilingInfoBits -> Int)
-> (KernelProfilingInfoBits -> Int)
-> (KernelProfilingInfoBits -> Int)
-> FiniteBits KernelProfilingInfoBits
KernelProfilingInfoBits -> Int
forall b.
Bits b =>
(b -> Int) -> (b -> Int) -> (b -> Int) -> FiniteBits b
$cfiniteBitSize :: KernelProfilingInfoBits -> Int
finiteBitSize :: KernelProfilingInfoBits -> Int
$ccountLeadingZeros :: KernelProfilingInfoBits -> Int
countLeadingZeros :: KernelProfilingInfoBits -> Int
$ccountTrailingZeros :: KernelProfilingInfoBits -> Int
countTrailingZeros :: KernelProfilingInfoBits -> Int
FiniteBits)

instance Semigroup KernelProfilingInfo where
  (KernelProfilingInfoBits Word32
a) <> :: KernelProfilingInfoBits
-> KernelProfilingInfoBits -> KernelProfilingInfoBits
<> (KernelProfilingInfoBits Word32
b) = Word32 -> KernelProfilingInfoBits
KernelProfilingInfoBits (Word32
a Word32 -> Word32 -> Word32
forall a. Bits a => a -> a -> a
.|. Word32
b)

instance Monoid KernelProfilingInfo where
  mempty :: KernelProfilingInfoBits
mempty = Word32 -> KernelProfilingInfoBits
KernelProfilingInfoBits Word32
0

pattern CmdExecTime :: KernelProfilingInfoBits
pattern $mCmdExecTime :: forall {r}.
KernelProfilingInfoBits -> ((# #) -> r) -> ((# #) -> r) -> r
$bCmdExecTime :: KernelProfilingInfoBits
CmdExecTime = KernelProfilingInfoBits 0x00000001