{-# language CPP #-}
-- | = Name
--
-- XR_KHR_composition_layer_equirect - instance extension
--
-- = Specification
--
-- See
-- <https://www.khronos.org/registry/OpenXR/specs/1.0/html/xrspec.html#XR_KHR_composition_layer_equirect  XR_KHR_composition_layer_equirect>
-- in the main specification for complete information.
--
-- = Registered Extension Number
--
-- 19
--
-- = Revision
--
-- 3
--
-- = Extension and Version Dependencies
--
-- -   Requires OpenXR 1.0
--
-- = See Also
--
-- 'CompositionLayerEquirectKHR'
--
-- = Document Notes
--
-- For more information, see the
-- <https://www.khronos.org/registry/OpenXR/specs/1.0/html/xrspec.html#XR_KHR_composition_layer_equirect OpenXR Specification>
--
-- This page is a generated document. Fixes and changes should be made to
-- the generator scripts, not directly.
module OpenXR.Extensions.XR_KHR_composition_layer_equirect  ( CompositionLayerEquirectKHR(..)
                                                            , KHR_composition_layer_equirect_SPEC_VERSION
                                                            , pattern KHR_composition_layer_equirect_SPEC_VERSION
                                                            , KHR_COMPOSITION_LAYER_EQUIRECT_EXTENSION_NAME
                                                            , pattern KHR_COMPOSITION_LAYER_EQUIRECT_EXTENSION_NAME
                                                            ) where

import Foreign.Marshal.Alloc (allocaBytesAligned)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
import Data.Coerce (coerce)
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.C.Types (CFloat)
import Foreign.C.Types (CFloat(..))
import Foreign.C.Types (CFloat(CFloat))
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.Core10.OtherTypes (CompositionLayerBaseHeader(..))
import OpenXR.Core10.Enums.CompositionLayerFlags (CompositionLayerFlags)
import OpenXR.Core10.Enums.EyeVisibility (EyeVisibility)
import OpenXR.Core10.OtherTypes (IsCompositionLayer(..))
import OpenXR.Core10.Space (Posef)
import OpenXR.Core10.Handles (Space_T)
import OpenXR.Core10.Enums.StructureType (StructureType)
import OpenXR.Core10.OtherTypes (SwapchainSubImage)
import OpenXR.Core10.Input (Vector2f)
import OpenXR.Core10.Enums.StructureType (StructureType(TYPE_COMPOSITION_LAYER_EQUIRECT_KHR))
-- | XrCompositionLayerEquirectKHR - Equirectangular layer composition info
--
-- == Member Descriptions
--
-- = Description
--
-- 'CompositionLayerEquirectKHR' contains the information needed to render
-- an equirectangular image onto a sphere when calling
-- 'OpenXR.Core10.DisplayTiming.endFrame'. 'CompositionLayerEquirectKHR' is
-- an alias type for the base struct
-- 'OpenXR.Core10.OtherTypes.CompositionLayerBaseHeader' used in
-- 'OpenXR.Core10.DisplayTiming.FrameEndInfo'.
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-XrCompositionLayerEquirectKHR-extension-notenabled# The @@
--     extension /must/ be enabled prior to using
--     'CompositionLayerEquirectKHR'
--
-- -   #VUID-XrCompositionLayerEquirectKHR-type-type# @type@ /must/ be
--     'OpenXR.Core10.Enums.StructureType.TYPE_COMPOSITION_LAYER_EQUIRECT_KHR'
--
-- -   #VUID-XrCompositionLayerEquirectKHR-next-next# @next@ /must/ be
--     @NULL@ or a valid pointer to the
--     <https://www.khronos.org/registry/OpenXR/specs/1.0/html/xrspec.html#valid-usage-for-structure-pointer-chains next structure in a structure chain>
--
-- -   #VUID-XrCompositionLayerEquirectKHR-layerFlags-parameter#
--     @layerFlags@ /must/ be @0@ or a valid combination of
--     <https://www.khronos.org/registry/OpenXR/specs/1.0/html/xrspec.html#XrCompositionLayerFlagBits XrCompositionLayerFlagBits>
--     values
--
-- -   #VUID-XrCompositionLayerEquirectKHR-space-parameter# @space@ /must/
--     be a valid 'OpenXR.Core10.Handles.Space' handle
--
-- -   #VUID-XrCompositionLayerEquirectKHR-eyeVisibility-parameter#
--     @eyeVisibility@ /must/ be a valid
--     'OpenXR.Core10.Enums.EyeVisibility.EyeVisibility' value
--
-- -   #VUID-XrCompositionLayerEquirectKHR-subImage-parameter# @subImage@
--     /must/ be a valid 'OpenXR.Core10.OtherTypes.SwapchainSubImage'
--     structure
--
-- = See Also
--
-- 'OpenXR.Core10.OtherTypes.CompositionLayerBaseHeader',
-- 'OpenXR.Core10.Enums.CompositionLayerFlags.CompositionLayerFlags',
-- 'OpenXR.Core10.Enums.EyeVisibility.EyeVisibility',
-- 'OpenXR.Core10.DisplayTiming.FrameEndInfo', 'OpenXR.Core10.Space.Posef',
-- 'OpenXR.Core10.Handles.Space',
-- 'OpenXR.Core10.Enums.StructureType.StructureType',
-- 'OpenXR.Core10.OtherTypes.SwapchainSubImage',
-- 'OpenXR.Core10.Input.Vector2f', 'OpenXR.Core10.DisplayTiming.endFrame'
data CompositionLayerEquirectKHR = CompositionLayerEquirectKHR
  { -- | @layerFlags@ specifies options for the layer.
    CompositionLayerEquirectKHR -> CompositionLayerFlags
layerFlags :: CompositionLayerFlags
  , -- | @space@ is the 'OpenXR.Core10.Handles.Space' in which the @pose@ of the
    -- equirect layer is evaluated over time.
    CompositionLayerEquirectKHR -> Ptr Space_T
space :: Ptr Space_T
  , -- No documentation found for Nested "XrCompositionLayerEquirectKHR" "eyeVisibility"
    CompositionLayerEquirectKHR -> EyeVisibility
eyeVisibility :: EyeVisibility
  , -- | @subImage@ identifies the image
    -- 'OpenXR.Core10.OtherTypes.SwapchainSubImage' to use.
    CompositionLayerEquirectKHR -> SwapchainSubImage
subImage :: SwapchainSubImage
  , -- | @pose@ is an 'OpenXR.Core10.Space.Posef' defining the position and
    -- orientation of the center point of the sphere onto which the equirect
    -- image data is mapped, relative to the reference frame of the @space@.
    CompositionLayerEquirectKHR -> Posef
pose :: Posef
  , -- | @radius@ is the non-negative radius of the sphere onto which the
    -- equirect image data is mapped. Values of zero or floating point positive
    -- infinity are treated as an infinite sphere.
    CompositionLayerEquirectKHR -> Float
radius :: Float
  , -- | @scale@ is an 'OpenXR.Core10.Input.Vector2f' indicating a scale of the
    -- texture coordinates after the mapping to 2D.
    CompositionLayerEquirectKHR -> Vector2f
scale :: Vector2f
  , -- | @bias@ is an 'OpenXR.Core10.Input.Vector2f' indicating a bias of the
    -- texture coordinates after the mapping to 2D.
    CompositionLayerEquirectKHR -> Vector2f
bias :: Vector2f
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (CompositionLayerEquirectKHR)
#endif
deriving instance Show CompositionLayerEquirectKHR

instance IsCompositionLayer CompositionLayerEquirectKHR where
  toCompositionLayerBaseHeader :: CompositionLayerEquirectKHR -> CompositionLayerBaseHeader '[]
toCompositionLayerBaseHeader CompositionLayerEquirectKHR{..} = $WCompositionLayerBaseHeader :: forall (es :: [*]).
StructureType
-> Chain es
-> CompositionLayerFlags
-> Ptr Space_T
-> CompositionLayerBaseHeader es
CompositionLayerBaseHeader{$sel:type':CompositionLayerBaseHeader :: StructureType
type' = StructureType
TYPE_COMPOSITION_LAYER_EQUIRECT_KHR, $sel:next:CompositionLayerBaseHeader :: Chain '[]
next = (), ..}

instance ToCStruct CompositionLayerEquirectKHR where
  withCStruct :: CompositionLayerEquirectKHR
-> (Ptr CompositionLayerEquirectKHR -> IO b) -> IO b
withCStruct x :: CompositionLayerEquirectKHR
x f :: Ptr CompositionLayerEquirectKHR -> IO b
f = Int -> Int -> (Ptr CompositionLayerEquirectKHR -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 120 8 ((Ptr CompositionLayerEquirectKHR -> IO b) -> IO b)
-> (Ptr CompositionLayerEquirectKHR -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr CompositionLayerEquirectKHR
p -> Ptr CompositionLayerEquirectKHR
-> CompositionLayerEquirectKHR -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr CompositionLayerEquirectKHR
p CompositionLayerEquirectKHR
x (Ptr CompositionLayerEquirectKHR -> IO b
f Ptr CompositionLayerEquirectKHR
p)
  pokeCStruct :: Ptr CompositionLayerEquirectKHR
-> CompositionLayerEquirectKHR -> IO b -> IO b
pokeCStruct p :: Ptr CompositionLayerEquirectKHR
p CompositionLayerEquirectKHR{..} f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr CompositionLayerEquirectKHR
p Ptr CompositionLayerEquirectKHR -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
TYPE_COMPOSITION_LAYER_EQUIRECT_KHR)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr CompositionLayerEquirectKHR
p Ptr CompositionLayerEquirectKHR -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr CompositionLayerFlags -> CompositionLayerFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr CompositionLayerEquirectKHR
p Ptr CompositionLayerEquirectKHR -> Int -> Ptr CompositionLayerFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr CompositionLayerFlags)) (CompositionLayerFlags
layerFlags)
    Ptr (Ptr Space_T) -> Ptr Space_T -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr CompositionLayerEquirectKHR
p Ptr CompositionLayerEquirectKHR -> Int -> Ptr (Ptr Space_T)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr (Ptr Space_T))) (Ptr Space_T
space)
    Ptr EyeVisibility -> EyeVisibility -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr CompositionLayerEquirectKHR
p Ptr CompositionLayerEquirectKHR -> Int -> Ptr EyeVisibility
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr EyeVisibility)) (EyeVisibility
eyeVisibility)
    Ptr SwapchainSubImage -> SwapchainSubImage -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr CompositionLayerEquirectKHR
p Ptr CompositionLayerEquirectKHR -> Int -> Ptr SwapchainSubImage
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr SwapchainSubImage)) (SwapchainSubImage
subImage)
    Ptr Posef -> Posef -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr CompositionLayerEquirectKHR
p Ptr CompositionLayerEquirectKHR -> Int -> Ptr Posef
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 72 :: Ptr Posef)) (Posef
pose)
    Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr CompositionLayerEquirectKHR
p Ptr CompositionLayerEquirectKHR -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 100 :: Ptr CFloat)) (Float -> CFloat
CFloat (Float
radius))
    Ptr Vector2f -> Vector2f -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr CompositionLayerEquirectKHR
p Ptr CompositionLayerEquirectKHR -> Int -> Ptr Vector2f
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 104 :: Ptr Vector2f)) (Vector2f
scale)
    Ptr Vector2f -> Vector2f -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr CompositionLayerEquirectKHR
p Ptr CompositionLayerEquirectKHR -> Int -> Ptr Vector2f
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 112 :: Ptr Vector2f)) (Vector2f
bias)
    IO b
f
  cStructSize :: Int
cStructSize = 120
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr CompositionLayerEquirectKHR -> IO b -> IO b
pokeZeroCStruct p :: Ptr CompositionLayerEquirectKHR
p f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr CompositionLayerEquirectKHR
p Ptr CompositionLayerEquirectKHR -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
TYPE_COMPOSITION_LAYER_EQUIRECT_KHR)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr CompositionLayerEquirectKHR
p Ptr CompositionLayerEquirectKHR -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr (Ptr Space_T) -> Ptr Space_T -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr CompositionLayerEquirectKHR
p Ptr CompositionLayerEquirectKHR -> Int -> Ptr (Ptr Space_T)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr (Ptr Space_T))) (Ptr Space_T
forall a. Zero a => a
zero)
    Ptr EyeVisibility -> EyeVisibility -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr CompositionLayerEquirectKHR
p Ptr CompositionLayerEquirectKHR -> Int -> Ptr EyeVisibility
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr EyeVisibility)) (EyeVisibility
forall a. Zero a => a
zero)
    Ptr SwapchainSubImage -> SwapchainSubImage -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr CompositionLayerEquirectKHR
p Ptr CompositionLayerEquirectKHR -> Int -> Ptr SwapchainSubImage
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr SwapchainSubImage)) (SwapchainSubImage
forall a. Zero a => a
zero)
    Ptr Posef -> Posef -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr CompositionLayerEquirectKHR
p Ptr CompositionLayerEquirectKHR -> Int -> Ptr Posef
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 72 :: Ptr Posef)) (Posef
forall a. Zero a => a
zero)
    Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr CompositionLayerEquirectKHR
p Ptr CompositionLayerEquirectKHR -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 100 :: Ptr CFloat)) (Float -> CFloat
CFloat (Float
forall a. Zero a => a
zero))
    Ptr Vector2f -> Vector2f -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr CompositionLayerEquirectKHR
p Ptr CompositionLayerEquirectKHR -> Int -> Ptr Vector2f
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 104 :: Ptr Vector2f)) (Vector2f
forall a. Zero a => a
zero)
    Ptr Vector2f -> Vector2f -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr CompositionLayerEquirectKHR
p Ptr CompositionLayerEquirectKHR -> Int -> Ptr Vector2f
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 112 :: Ptr Vector2f)) (Vector2f
forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct CompositionLayerEquirectKHR where
  peekCStruct :: Ptr CompositionLayerEquirectKHR -> IO CompositionLayerEquirectKHR
peekCStruct p :: Ptr CompositionLayerEquirectKHR
p = do
    CompositionLayerFlags
layerFlags <- Ptr CompositionLayerFlags -> IO CompositionLayerFlags
forall a. Storable a => Ptr a -> IO a
peek @CompositionLayerFlags ((Ptr CompositionLayerEquirectKHR
p Ptr CompositionLayerEquirectKHR -> Int -> Ptr CompositionLayerFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr CompositionLayerFlags))
    Ptr Space_T
space <- Ptr (Ptr Space_T) -> IO (Ptr Space_T)
forall a. Storable a => Ptr a -> IO a
peek @(Ptr Space_T) ((Ptr CompositionLayerEquirectKHR
p Ptr CompositionLayerEquirectKHR -> Int -> Ptr (Ptr Space_T)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr (Ptr Space_T)))
    EyeVisibility
eyeVisibility <- Ptr EyeVisibility -> IO EyeVisibility
forall a. Storable a => Ptr a -> IO a
peek @EyeVisibility ((Ptr CompositionLayerEquirectKHR
p Ptr CompositionLayerEquirectKHR -> Int -> Ptr EyeVisibility
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr EyeVisibility))
    SwapchainSubImage
subImage <- Ptr SwapchainSubImage -> IO SwapchainSubImage
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @SwapchainSubImage ((Ptr CompositionLayerEquirectKHR
p Ptr CompositionLayerEquirectKHR -> Int -> Ptr SwapchainSubImage
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr SwapchainSubImage))
    Posef
pose <- Ptr Posef -> IO Posef
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @Posef ((Ptr CompositionLayerEquirectKHR
p Ptr CompositionLayerEquirectKHR -> Int -> Ptr Posef
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 72 :: Ptr Posef))
    CFloat
radius <- Ptr CFloat -> IO CFloat
forall a. Storable a => Ptr a -> IO a
peek @CFloat ((Ptr CompositionLayerEquirectKHR
p Ptr CompositionLayerEquirectKHR -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 100 :: Ptr CFloat))
    Vector2f
scale <- Ptr Vector2f -> IO Vector2f
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @Vector2f ((Ptr CompositionLayerEquirectKHR
p Ptr CompositionLayerEquirectKHR -> Int -> Ptr Vector2f
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 104 :: Ptr Vector2f))
    Vector2f
bias <- Ptr Vector2f -> IO Vector2f
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @Vector2f ((Ptr CompositionLayerEquirectKHR
p Ptr CompositionLayerEquirectKHR -> Int -> Ptr Vector2f
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 112 :: Ptr Vector2f))
    CompositionLayerEquirectKHR -> IO CompositionLayerEquirectKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure (CompositionLayerEquirectKHR -> IO CompositionLayerEquirectKHR)
-> CompositionLayerEquirectKHR -> IO CompositionLayerEquirectKHR
forall a b. (a -> b) -> a -> b
$ CompositionLayerFlags
-> Ptr Space_T
-> EyeVisibility
-> SwapchainSubImage
-> Posef
-> Float
-> Vector2f
-> Vector2f
-> CompositionLayerEquirectKHR
CompositionLayerEquirectKHR
             CompositionLayerFlags
layerFlags Ptr Space_T
space EyeVisibility
eyeVisibility SwapchainSubImage
subImage Posef
pose (CFloat -> Float
forall a b. Coercible a b => a -> b
coerce @CFloat @Float CFloat
radius) Vector2f
scale Vector2f
bias

instance Storable CompositionLayerEquirectKHR where
  sizeOf :: CompositionLayerEquirectKHR -> Int
sizeOf ~CompositionLayerEquirectKHR
_ = 120
  alignment :: CompositionLayerEquirectKHR -> Int
alignment ~CompositionLayerEquirectKHR
_ = 8
  peek :: Ptr CompositionLayerEquirectKHR -> IO CompositionLayerEquirectKHR
peek = Ptr CompositionLayerEquirectKHR -> IO CompositionLayerEquirectKHR
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
  poke :: Ptr CompositionLayerEquirectKHR
-> CompositionLayerEquirectKHR -> IO ()
poke ptr :: Ptr CompositionLayerEquirectKHR
ptr poked :: CompositionLayerEquirectKHR
poked = Ptr CompositionLayerEquirectKHR
-> CompositionLayerEquirectKHR -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr CompositionLayerEquirectKHR
ptr CompositionLayerEquirectKHR
poked (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())

instance Zero CompositionLayerEquirectKHR where
  zero :: CompositionLayerEquirectKHR
zero = CompositionLayerFlags
-> Ptr Space_T
-> EyeVisibility
-> SwapchainSubImage
-> Posef
-> Float
-> Vector2f
-> Vector2f
-> CompositionLayerEquirectKHR
CompositionLayerEquirectKHR
           CompositionLayerFlags
forall a. Zero a => a
zero
           Ptr Space_T
forall a. Zero a => a
zero
           EyeVisibility
forall a. Zero a => a
zero
           SwapchainSubImage
forall a. Zero a => a
zero
           Posef
forall a. Zero a => a
zero
           Float
forall a. Zero a => a
zero
           Vector2f
forall a. Zero a => a
zero
           Vector2f
forall a. Zero a => a
zero


type KHR_composition_layer_equirect_SPEC_VERSION = 3

-- No documentation found for TopLevel "XR_KHR_composition_layer_equirect_SPEC_VERSION"
pattern KHR_composition_layer_equirect_SPEC_VERSION :: forall a . Integral a => a
pattern $bKHR_composition_layer_equirect_SPEC_VERSION :: a
$mKHR_composition_layer_equirect_SPEC_VERSION :: forall r a. Integral a => a -> (Void# -> r) -> (Void# -> r) -> r
KHR_composition_layer_equirect_SPEC_VERSION = 3


type KHR_COMPOSITION_LAYER_EQUIRECT_EXTENSION_NAME = "XR_KHR_composition_layer_equirect"

-- No documentation found for TopLevel "XR_KHR_COMPOSITION_LAYER_EQUIRECT_EXTENSION_NAME"
pattern KHR_COMPOSITION_LAYER_EQUIRECT_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bKHR_COMPOSITION_LAYER_EQUIRECT_EXTENSION_NAME :: a
$mKHR_COMPOSITION_LAYER_EQUIRECT_EXTENSION_NAME :: forall r a.
(Eq a, IsString a) =>
a -> (Void# -> r) -> (Void# -> r) -> r
KHR_COMPOSITION_LAYER_EQUIRECT_EXTENSION_NAME = "XR_KHR_composition_layer_equirect"