{-# language CPP #-}
module OpenXR.Extensions.XR_MSFT_holographic_window_attachment ( HolographicWindowAttachmentMSFT(..)
, MSFT_holographic_window_attachment_SPEC_VERSION
, pattern MSFT_holographic_window_attachment_SPEC_VERSION
, MSFT_HOLOGRAPHIC_WINDOW_ATTACHMENT_EXTENSION_NAME
, pattern MSFT_HOLOGRAPHIC_WINDOW_ATTACHMENT_EXTENSION_NAME
, IUnknown
) where
import Foreign.Marshal.Alloc (allocaBytesAligned)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
import OpenXR.CStruct (FromCStruct)
import OpenXR.CStruct (FromCStruct(..))
import OpenXR.CStruct (ToCStruct)
import OpenXR.CStruct (ToCStruct(..))
import OpenXR.Zero (Zero(..))
import Data.String (IsString)
import Data.Typeable (Typeable)
import Foreign.Storable (Storable)
import Foreign.Storable (Storable(peek))
import Foreign.Storable (Storable(poke))
import qualified Foreign.Storable (Storable(..))
import GHC.Generics (Generic)
import Foreign.Ptr (Ptr)
import Data.Kind (Type)
import OpenXR.Extensions.XR_MSFT_perception_anchor_interop (IUnknown)
import OpenXR.Core10.Enums.StructureType (StructureType)
import OpenXR.Core10.Enums.StructureType (StructureType(TYPE_HOLOGRAPHIC_WINDOW_ATTACHMENT_MSFT))
import OpenXR.Extensions.XR_MSFT_perception_anchor_interop (IUnknown)
data HolographicWindowAttachmentMSFT = HolographicWindowAttachmentMSFT
{
HolographicWindowAttachmentMSFT -> Ptr IUnknown
holographicSpace :: Ptr IUnknown
,
HolographicWindowAttachmentMSFT -> Ptr IUnknown
coreWindow :: Ptr IUnknown
}
deriving (Typeable, HolographicWindowAttachmentMSFT
-> HolographicWindowAttachmentMSFT -> Bool
(HolographicWindowAttachmentMSFT
-> HolographicWindowAttachmentMSFT -> Bool)
-> (HolographicWindowAttachmentMSFT
-> HolographicWindowAttachmentMSFT -> Bool)
-> Eq HolographicWindowAttachmentMSFT
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: HolographicWindowAttachmentMSFT
-> HolographicWindowAttachmentMSFT -> Bool
$c/= :: HolographicWindowAttachmentMSFT
-> HolographicWindowAttachmentMSFT -> Bool
== :: HolographicWindowAttachmentMSFT
-> HolographicWindowAttachmentMSFT -> Bool
$c== :: HolographicWindowAttachmentMSFT
-> HolographicWindowAttachmentMSFT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (HolographicWindowAttachmentMSFT)
#endif
deriving instance Show HolographicWindowAttachmentMSFT
instance ToCStruct HolographicWindowAttachmentMSFT where
withCStruct :: HolographicWindowAttachmentMSFT
-> (Ptr HolographicWindowAttachmentMSFT -> IO b) -> IO b
withCStruct x :: HolographicWindowAttachmentMSFT
x f :: Ptr HolographicWindowAttachmentMSFT -> IO b
f = Int -> Int -> (Ptr HolographicWindowAttachmentMSFT -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 32 8 ((Ptr HolographicWindowAttachmentMSFT -> IO b) -> IO b)
-> (Ptr HolographicWindowAttachmentMSFT -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr HolographicWindowAttachmentMSFT
p -> Ptr HolographicWindowAttachmentMSFT
-> HolographicWindowAttachmentMSFT -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr HolographicWindowAttachmentMSFT
p HolographicWindowAttachmentMSFT
x (Ptr HolographicWindowAttachmentMSFT -> IO b
f Ptr HolographicWindowAttachmentMSFT
p)
pokeCStruct :: Ptr HolographicWindowAttachmentMSFT
-> HolographicWindowAttachmentMSFT -> IO b -> IO b
pokeCStruct p :: Ptr HolographicWindowAttachmentMSFT
p HolographicWindowAttachmentMSFT{..} f :: IO b
f = do
Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr HolographicWindowAttachmentMSFT
p Ptr HolographicWindowAttachmentMSFT -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
TYPE_HOLOGRAPHIC_WINDOW_ATTACHMENT_MSFT)
Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr HolographicWindowAttachmentMSFT
p Ptr HolographicWindowAttachmentMSFT -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
Ptr (Ptr IUnknown) -> Ptr IUnknown -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr HolographicWindowAttachmentMSFT
p Ptr HolographicWindowAttachmentMSFT -> Int -> Ptr (Ptr IUnknown)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr (Ptr IUnknown))) (Ptr IUnknown
holographicSpace)
Ptr (Ptr IUnknown) -> Ptr IUnknown -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr HolographicWindowAttachmentMSFT
p Ptr HolographicWindowAttachmentMSFT -> Int -> Ptr (Ptr IUnknown)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr (Ptr IUnknown))) (Ptr IUnknown
coreWindow)
IO b
f
cStructSize :: Int
cStructSize = 32
cStructAlignment :: Int
cStructAlignment = 8
pokeZeroCStruct :: Ptr HolographicWindowAttachmentMSFT -> IO b -> IO b
pokeZeroCStruct p :: Ptr HolographicWindowAttachmentMSFT
p f :: IO b
f = do
Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr HolographicWindowAttachmentMSFT
p Ptr HolographicWindowAttachmentMSFT -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
TYPE_HOLOGRAPHIC_WINDOW_ATTACHMENT_MSFT)
Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr HolographicWindowAttachmentMSFT
p Ptr HolographicWindowAttachmentMSFT -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
Ptr (Ptr IUnknown) -> Ptr IUnknown -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr HolographicWindowAttachmentMSFT
p Ptr HolographicWindowAttachmentMSFT -> Int -> Ptr (Ptr IUnknown)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr (Ptr IUnknown))) (Ptr IUnknown
forall a. Zero a => a
zero)
Ptr (Ptr IUnknown) -> Ptr IUnknown -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr HolographicWindowAttachmentMSFT
p Ptr HolographicWindowAttachmentMSFT -> Int -> Ptr (Ptr IUnknown)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr (Ptr IUnknown))) (Ptr IUnknown
forall a. Zero a => a
zero)
IO b
f
instance FromCStruct HolographicWindowAttachmentMSFT where
peekCStruct :: Ptr HolographicWindowAttachmentMSFT
-> IO HolographicWindowAttachmentMSFT
peekCStruct p :: Ptr HolographicWindowAttachmentMSFT
p = do
Ptr IUnknown
holographicSpace <- Ptr (Ptr IUnknown) -> IO (Ptr IUnknown)
forall a. Storable a => Ptr a -> IO a
peek @(Ptr IUnknown) ((Ptr HolographicWindowAttachmentMSFT
p Ptr HolographicWindowAttachmentMSFT -> Int -> Ptr (Ptr IUnknown)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr (Ptr IUnknown)))
Ptr IUnknown
coreWindow <- Ptr (Ptr IUnknown) -> IO (Ptr IUnknown)
forall a. Storable a => Ptr a -> IO a
peek @(Ptr IUnknown) ((Ptr HolographicWindowAttachmentMSFT
p Ptr HolographicWindowAttachmentMSFT -> Int -> Ptr (Ptr IUnknown)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr (Ptr IUnknown)))
HolographicWindowAttachmentMSFT
-> IO HolographicWindowAttachmentMSFT
forall (f :: * -> *) a. Applicative f => a -> f a
pure (HolographicWindowAttachmentMSFT
-> IO HolographicWindowAttachmentMSFT)
-> HolographicWindowAttachmentMSFT
-> IO HolographicWindowAttachmentMSFT
forall a b. (a -> b) -> a -> b
$ Ptr IUnknown -> Ptr IUnknown -> HolographicWindowAttachmentMSFT
HolographicWindowAttachmentMSFT
Ptr IUnknown
holographicSpace Ptr IUnknown
coreWindow
instance Storable HolographicWindowAttachmentMSFT where
sizeOf :: HolographicWindowAttachmentMSFT -> Int
sizeOf ~HolographicWindowAttachmentMSFT
_ = 32
alignment :: HolographicWindowAttachmentMSFT -> Int
alignment ~HolographicWindowAttachmentMSFT
_ = 8
peek :: Ptr HolographicWindowAttachmentMSFT
-> IO HolographicWindowAttachmentMSFT
peek = Ptr HolographicWindowAttachmentMSFT
-> IO HolographicWindowAttachmentMSFT
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr HolographicWindowAttachmentMSFT
-> HolographicWindowAttachmentMSFT -> IO ()
poke ptr :: Ptr HolographicWindowAttachmentMSFT
ptr poked :: HolographicWindowAttachmentMSFT
poked = Ptr HolographicWindowAttachmentMSFT
-> HolographicWindowAttachmentMSFT -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr HolographicWindowAttachmentMSFT
ptr HolographicWindowAttachmentMSFT
poked (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero HolographicWindowAttachmentMSFT where
zero :: HolographicWindowAttachmentMSFT
zero = Ptr IUnknown -> Ptr IUnknown -> HolographicWindowAttachmentMSFT
HolographicWindowAttachmentMSFT
Ptr IUnknown
forall a. Zero a => a
zero
Ptr IUnknown
forall a. Zero a => a
zero
type MSFT_holographic_window_attachment_SPEC_VERSION = 1
pattern MSFT_holographic_window_attachment_SPEC_VERSION :: forall a . Integral a => a
pattern $bMSFT_holographic_window_attachment_SPEC_VERSION :: a
$mMSFT_holographic_window_attachment_SPEC_VERSION :: forall r a. Integral a => a -> (Void# -> r) -> (Void# -> r) -> r
MSFT_holographic_window_attachment_SPEC_VERSION = 1
type MSFT_HOLOGRAPHIC_WINDOW_ATTACHMENT_EXTENSION_NAME = "XR_MSFT_holographic_window_attachment"
pattern MSFT_HOLOGRAPHIC_WINDOW_ATTACHMENT_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bMSFT_HOLOGRAPHIC_WINDOW_ATTACHMENT_EXTENSION_NAME :: a
$mMSFT_HOLOGRAPHIC_WINDOW_ATTACHMENT_EXTENSION_NAME :: forall r a.
(Eq a, IsString a) =>
a -> (Void# -> r) -> (Void# -> r) -> r
MSFT_HOLOGRAPHIC_WINDOW_ATTACHMENT_EXTENSION_NAME = "XR_MSFT_holographic_window_attachment"