{-# LINE 1 "src-gen/Graphics/Vulkan/Types/Struct/LayerProperties.hsc" #-}


{-# LANGUAGE DataKinds             #-}
{-# LANGUAGE FlexibleContexts      #-}
{-# LANGUAGE FlexibleInstances     #-}
{-# LANGUAGE MagicHash             #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE PatternSynonyms       #-}
{-# LANGUAGE ScopedTypeVariables   #-}
{-# LANGUAGE Strict                #-}
{-# LANGUAGE TypeApplications      #-}
{-# LANGUAGE TypeFamilies          #-}
{-# LANGUAGE UndecidableInstances  #-}
module Graphics.Vulkan.Types.Struct.LayerProperties
       (VkLayerProperties(..)) where
import           Foreign.Storable                 (Storable (..))
import           GHC.Base                         (Addr#, ByteArray#, Proxy#,
                                                   byteArrayContents#,
                                                   plusAddr#, proxy#)
import           GHC.TypeLits                     (KnownNat, natVal') -- ' closing tick for hsc2hs
import           Graphics.Vulkan.Constants        (VK_MAX_DESCRIPTION_SIZE, pattern VK_MAX_DESCRIPTION_SIZE,
                                                   VK_MAX_EXTENSION_NAME_SIZE,
                                                   pattern VK_MAX_EXTENSION_NAME_SIZE)
import           Graphics.Vulkan.Marshal
import           Graphics.Vulkan.Marshal.Internal
import           System.IO.Unsafe                 (unsafeDupablePerformIO)

-- | > typedef struct VkLayerProperties {
--   >     char            layerName[VK_MAX_EXTENSION_NAME_SIZE];
--   >     uint32_t        specVersion;
--   >     uint32_t        implementationVersion;
--   >     char            description[VK_MAX_DESCRIPTION_SIZE];
--   > } VkLayerProperties;
--
--   <https://www.khronos.org/registry/vulkan/specs/1.1-extensions/html/vkspec.html#VkLayerProperties VkLayerProperties registry at www.khronos.org>
data VkLayerProperties = VkLayerProperties# Addr# ByteArray#

instance Eq VkLayerProperties where
        (VkLayerProperties# Addr#
a ByteArray#
_) == :: VkLayerProperties -> VkLayerProperties -> Bool
== x :: VkLayerProperties
x@(VkLayerProperties# Addr#
b ByteArray#
_)
          = Ordering
EQ Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
== Int -> Addr# -> Addr# -> Ordering
cmpBytes# (VkLayerProperties -> Int
forall a. Storable a => a -> Int
sizeOf VkLayerProperties
x) Addr#
a Addr#
b

        {-# INLINE (==) #-}

instance Ord VkLayerProperties where
        (VkLayerProperties# Addr#
a ByteArray#
_) compare :: VkLayerProperties -> VkLayerProperties -> Ordering
`compare` x :: VkLayerProperties
x@(VkLayerProperties# Addr#
b ByteArray#
_)
          = Int -> Addr# -> Addr# -> Ordering
cmpBytes# (VkLayerProperties -> Int
forall a. Storable a => a -> Int
sizeOf VkLayerProperties
x) Addr#
a Addr#
b

        {-# INLINE compare #-}

instance Storable VkLayerProperties where
        sizeOf :: VkLayerProperties -> Int
sizeOf ~VkLayerProperties
_ = (Int
520)
{-# LINE 52 "src-gen/Graphics/Vulkan/Types/Struct/LayerProperties.hsc" #-}

        {-# INLINE sizeOf #-}
        alignment :: VkLayerProperties -> Int
alignment ~VkLayerProperties
_ = Int
4
{-# LINE 55 "src-gen/Graphics/Vulkan/Types/Struct/LayerProperties.hsc" #-}

        {-# INLINE alignment #-}
        peek :: Ptr VkLayerProperties -> IO VkLayerProperties
peek = Ptr VkLayerProperties -> IO VkLayerProperties
forall a. (Storable a, VulkanMarshalPrim a) => Ptr a -> IO a
peekVkData#

        {-# INLINE peek #-}
        poke :: Ptr VkLayerProperties -> VkLayerProperties -> IO ()
poke = Ptr VkLayerProperties -> VkLayerProperties -> IO ()
forall a. (Storable a, VulkanMarshalPrim a) => Ptr a -> a -> IO ()
pokeVkData#

        {-# INLINE poke #-}

instance VulkanMarshalPrim VkLayerProperties where
        unsafeAddr :: VkLayerProperties -> Addr#
unsafeAddr (VkLayerProperties# Addr#
a ByteArray#
_) = Addr#
a

        {-# INLINE unsafeAddr #-}
        unsafeByteArray :: VkLayerProperties -> ByteArray#
unsafeByteArray (VkLayerProperties# Addr#
_ ByteArray#
b) = ByteArray#
b

        {-# INLINE unsafeByteArray #-}
        unsafeFromByteArrayOffset :: Int# -> ByteArray# -> VkLayerProperties
unsafeFromByteArrayOffset Int#
off ByteArray#
b
          = Addr# -> ByteArray# -> VkLayerProperties
VkLayerProperties# (Addr# -> Int# -> Addr#
plusAddr# (ByteArray# -> Addr#
byteArrayContents# ByteArray#
b) Int#
off) ByteArray#
b

        {-# INLINE unsafeFromByteArrayOffset #-}

instance VulkanMarshal VkLayerProperties where
        type StructFields VkLayerProperties =
             '["layerName", "specVersion", "implementationVersion", -- ' closing tick for hsc2hs
               "description"]
        type CUnionType VkLayerProperties = 'False -- ' closing tick for hsc2hs
        type ReturnedOnly VkLayerProperties = 'True -- ' closing tick for hsc2hs
        type StructExtends VkLayerProperties = '[] -- ' closing tick for hsc2hs

instance {-# OVERLAPPING #-} HasField "layerName" VkLayerProperties
         where
        type FieldType "layerName" VkLayerProperties = CChar
        type FieldOptional "layerName" VkLayerProperties = 'False -- ' closing tick for hsc2hs
        type FieldOffset "layerName" VkLayerProperties =
             (0)
{-# LINE 90 "src-gen/Graphics/Vulkan/Types/Struct/LayerProperties.hsc" #-}
        type FieldIsArray "layerName" VkLayerProperties = 'True -- ' closing tick for hsc2hs

        {-# INLINE fieldOptional #-}
        fieldOptional :: Bool
fieldOptional = Bool
False

        {-# INLINE fieldOffset #-}
        fieldOffset :: Int
fieldOffset = (Int
0)
{-# LINE 97 "src-gen/Graphics/Vulkan/Types/Struct/LayerProperties.hsc" #-}

instance {-# OVERLAPPING #-}
         (KnownNat idx, IndexInBounds "layerName" idx VkLayerProperties) =>
         CanReadFieldArray "layerName" idx VkLayerProperties
         where
        {-# SPECIALISE instance
                       CanReadFieldArray "layerName" 0 VkLayerProperties #-}

        {-# SPECIALISE instance
                       CanReadFieldArray "layerName" 1 VkLayerProperties #-}

        {-# SPECIALISE instance
                       CanReadFieldArray "layerName" 2 VkLayerProperties #-}

        {-# SPECIALISE instance
                       CanReadFieldArray "layerName" 3 VkLayerProperties #-}
        type FieldArrayLength "layerName" VkLayerProperties =
             VK_MAX_EXTENSION_NAME_SIZE

        {-# INLINE fieldArrayLength #-}
        fieldArrayLength :: Int
fieldArrayLength = Int
forall a. (Num a, Eq a) => a
VK_MAX_EXTENSION_NAME_SIZE

        {-# INLINE getFieldArray #-}
        getFieldArray :: VkLayerProperties -> FieldType "layerName" VkLayerProperties
getFieldArray = VkLayerProperties -> CChar
VkLayerProperties -> FieldType "layerName" VkLayerProperties
f
          where {-# NOINLINE f #-}
                f :: VkLayerProperties -> CChar
f VkLayerProperties
x = IO CChar -> CChar
forall a. IO a -> a
unsafeDupablePerformIO (Ptr VkLayerProperties -> Int -> IO CChar
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkLayerProperties -> Ptr VkLayerProperties
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkLayerProperties
x) Int
off)
                off :: Int
off
                  = (Int
0) Int -> Int -> Int
forall a. Num a => a -> a -> a
+
{-# LINE 125 "src-gen/Graphics/Vulkan/Types/Struct/LayerProperties.hsc" #-}
                      CChar -> Int
forall a. Storable a => a -> Int
sizeOf (CChar
forall a. HasCallStack => a
undefined :: CChar) Int -> Int -> Int
forall a. Num a => a -> a -> a
*
                        Integer -> Int
forall a. Num a => Integer -> a
fromInteger (Proxy# idx -> Integer
forall (n :: Nat). KnownNat n => Proxy# n -> Integer
natVal' (Proxy# idx
forall k (a :: k). Proxy# a
proxy# :: Proxy# idx)) -- ' closing tick for hsc2hs

        {-# INLINE readFieldArray #-}
        readFieldArray :: Ptr VkLayerProperties
-> IO (FieldType "layerName" VkLayerProperties)
readFieldArray Ptr VkLayerProperties
p
          = Ptr VkLayerProperties -> Int -> IO CChar
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkLayerProperties
p
              ((Int
0) Int -> Int -> Int
forall a. Num a => a -> a -> a
+
{-# LINE 132 "src-gen/Graphics/Vulkan/Types/Struct/LayerProperties.hsc" #-}
                 CChar -> Int
forall a. Storable a => a -> Int
sizeOf (CChar
forall a. HasCallStack => a
undefined :: CChar) Int -> Int -> Int
forall a. Num a => a -> a -> a
*
                   Integer -> Int
forall a. Num a => Integer -> a
fromInteger (Proxy# idx -> Integer
forall (n :: Nat). KnownNat n => Proxy# n -> Integer
natVal' (Proxy# idx
forall k (a :: k). Proxy# a
proxy# :: Proxy# idx))) -- ' closing tick for hsc2hs

instance {-# OVERLAPPING #-}
         (KnownNat idx, IndexInBounds "layerName" idx VkLayerProperties) =>
         CanWriteFieldArray "layerName" idx VkLayerProperties
         where
        {-# SPECIALISE instance
                       CanWriteFieldArray "layerName" 0 VkLayerProperties #-}

        {-# SPECIALISE instance
                       CanWriteFieldArray "layerName" 1 VkLayerProperties #-}

        {-# SPECIALISE instance
                       CanWriteFieldArray "layerName" 2 VkLayerProperties #-}

        {-# SPECIALISE instance
                       CanWriteFieldArray "layerName" 3 VkLayerProperties #-}

        {-# INLINE writeFieldArray #-}
        writeFieldArray :: Ptr VkLayerProperties
-> FieldType "layerName" VkLayerProperties -> IO ()
writeFieldArray Ptr VkLayerProperties
p
          = Ptr VkLayerProperties -> Int -> CChar -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkLayerProperties
p
              ((Int
0) Int -> Int -> Int
forall a. Num a => a -> a -> a
+
{-# LINE 155 "src-gen/Graphics/Vulkan/Types/Struct/LayerProperties.hsc" #-}
                 CChar -> Int
forall a. Storable a => a -> Int
sizeOf (CChar
forall a. HasCallStack => a
undefined :: CChar) Int -> Int -> Int
forall a. Num a => a -> a -> a
*
                   Integer -> Int
forall a. Num a => Integer -> a
fromInteger (Proxy# idx -> Integer
forall (n :: Nat). KnownNat n => Proxy# n -> Integer
natVal' (Proxy# idx
forall k (a :: k). Proxy# a
proxy# :: Proxy# idx))) -- ' closing tick for hsc2hs

instance {-# OVERLAPPING #-}
         HasField "specVersion" VkLayerProperties where
        type FieldType "specVersion" VkLayerProperties = Word32
        type FieldOptional "specVersion" VkLayerProperties = 'False -- ' closing tick for hsc2hs
        type FieldOffset "specVersion" VkLayerProperties =
             (256)
{-# LINE 164 "src-gen/Graphics/Vulkan/Types/Struct/LayerProperties.hsc" #-}
        type FieldIsArray "specVersion" VkLayerProperties = 'False -- ' closing tick for hsc2hs

        {-# INLINE fieldOptional #-}
        fieldOptional :: Bool
fieldOptional = Bool
False

        {-# INLINE fieldOffset #-}
        fieldOffset :: Int
fieldOffset = (Int
256)
{-# LINE 171 "src-gen/Graphics/Vulkan/Types/Struct/LayerProperties.hsc" #-}

instance {-# OVERLAPPING #-}
         CanReadField "specVersion" VkLayerProperties where
        {-# NOINLINE getField #-}
        getField :: VkLayerProperties -> FieldType "specVersion" VkLayerProperties
getField VkLayerProperties
x
          = IO Word32 -> Word32
forall a. IO a -> a
unsafeDupablePerformIO
              (Ptr VkLayerProperties -> Int -> IO Word32
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkLayerProperties -> Ptr VkLayerProperties
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkLayerProperties
x) (Int
256))
{-# LINE 178 "src-gen/Graphics/Vulkan/Types/Struct/LayerProperties.hsc" #-}

        {-# INLINE readField #-}
        readField :: Ptr VkLayerProperties
-> IO (FieldType "specVersion" VkLayerProperties)
readField Ptr VkLayerProperties
p
          = Ptr VkLayerProperties -> Int -> IO Word32
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkLayerProperties
p (Int
256)
{-# LINE 182 "src-gen/Graphics/Vulkan/Types/Struct/LayerProperties.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "specVersion" VkLayerProperties where
        {-# INLINE writeField #-}
        writeField :: Ptr VkLayerProperties
-> FieldType "specVersion" VkLayerProperties -> IO ()
writeField Ptr VkLayerProperties
p
          = Ptr VkLayerProperties -> Int -> Word32 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkLayerProperties
p (Int
256)
{-# LINE 188 "src-gen/Graphics/Vulkan/Types/Struct/LayerProperties.hsc" #-}

instance {-# OVERLAPPING #-}
         HasField "implementationVersion" VkLayerProperties where
        type FieldType "implementationVersion" VkLayerProperties = Word32
        type FieldOptional "implementationVersion" VkLayerProperties =
             'False -- ' closing tick for hsc2hs
        type FieldOffset "implementationVersion" VkLayerProperties =
             (260)
{-# LINE 196 "src-gen/Graphics/Vulkan/Types/Struct/LayerProperties.hsc" #-}
        type FieldIsArray "implementationVersion" VkLayerProperties =
             'False -- ' closing tick for hsc2hs

        {-# INLINE fieldOptional #-}
        fieldOptional :: Bool
fieldOptional = Bool
False

        {-# INLINE fieldOffset #-}
        fieldOffset :: Int
fieldOffset
          = (Int
260)
{-# LINE 205 "src-gen/Graphics/Vulkan/Types/Struct/LayerProperties.hsc" #-}

instance {-# OVERLAPPING #-}
         CanReadField "implementationVersion" VkLayerProperties where
        {-# NOINLINE getField #-}
        getField :: VkLayerProperties
-> FieldType "implementationVersion" VkLayerProperties
getField VkLayerProperties
x
          = IO Word32 -> Word32
forall a. IO a -> a
unsafeDupablePerformIO
              (Ptr VkLayerProperties -> Int -> IO Word32
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkLayerProperties -> Ptr VkLayerProperties
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkLayerProperties
x) (Int
260))
{-# LINE 212 "src-gen/Graphics/Vulkan/Types/Struct/LayerProperties.hsc" #-}

        {-# INLINE readField #-}
        readField :: Ptr VkLayerProperties
-> IO (FieldType "implementationVersion" VkLayerProperties)
readField Ptr VkLayerProperties
p
          = Ptr VkLayerProperties -> Int -> IO Word32
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkLayerProperties
p (Int
260)
{-# LINE 216 "src-gen/Graphics/Vulkan/Types/Struct/LayerProperties.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "implementationVersion" VkLayerProperties where
        {-# INLINE writeField #-}
        writeField :: Ptr VkLayerProperties
-> FieldType "implementationVersion" VkLayerProperties -> IO ()
writeField Ptr VkLayerProperties
p
          = Ptr VkLayerProperties -> Int -> Word32 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkLayerProperties
p (Int
260)
{-# LINE 222 "src-gen/Graphics/Vulkan/Types/Struct/LayerProperties.hsc" #-}

instance {-# OVERLAPPING #-}
         HasField "description" VkLayerProperties where
        type FieldType "description" VkLayerProperties = CChar
        type FieldOptional "description" VkLayerProperties = 'False -- ' closing tick for hsc2hs
        type FieldOffset "description" VkLayerProperties =
             (264)
{-# LINE 229 "src-gen/Graphics/Vulkan/Types/Struct/LayerProperties.hsc" #-}
        type FieldIsArray "description" VkLayerProperties = 'True -- ' closing tick for hsc2hs

        {-# INLINE fieldOptional #-}
        fieldOptional :: Bool
fieldOptional = Bool
False

        {-# INLINE fieldOffset #-}
        fieldOffset :: Int
fieldOffset = (Int
264)
{-# LINE 236 "src-gen/Graphics/Vulkan/Types/Struct/LayerProperties.hsc" #-}

instance {-# OVERLAPPING #-}
         (KnownNat idx,
          IndexInBounds "description" idx VkLayerProperties) =>
         CanReadFieldArray "description" idx VkLayerProperties
         where
        {-# SPECIALISE instance
                       CanReadFieldArray "description" 0 VkLayerProperties #-}

        {-# SPECIALISE instance
                       CanReadFieldArray "description" 1 VkLayerProperties #-}

        {-# SPECIALISE instance
                       CanReadFieldArray "description" 2 VkLayerProperties #-}

        {-# SPECIALISE instance
                       CanReadFieldArray "description" 3 VkLayerProperties #-}
        type FieldArrayLength "description" VkLayerProperties =
             VK_MAX_DESCRIPTION_SIZE

        {-# INLINE fieldArrayLength #-}
        fieldArrayLength :: Int
fieldArrayLength = Int
forall a. (Num a, Eq a) => a
VK_MAX_DESCRIPTION_SIZE

        {-# INLINE getFieldArray #-}
        getFieldArray :: VkLayerProperties -> FieldType "description" VkLayerProperties
getFieldArray = VkLayerProperties -> CChar
VkLayerProperties -> FieldType "description" VkLayerProperties
f
          where {-# NOINLINE f #-}
                f :: VkLayerProperties -> CChar
f VkLayerProperties
x = IO CChar -> CChar
forall a. IO a -> a
unsafeDupablePerformIO (Ptr VkLayerProperties -> Int -> IO CChar
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkLayerProperties -> Ptr VkLayerProperties
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkLayerProperties
x) Int
off)
                off :: Int
off
                  = (Int
264) Int -> Int -> Int
forall a. Num a => a -> a -> a
+
{-# LINE 265 "src-gen/Graphics/Vulkan/Types/Struct/LayerProperties.hsc" #-}
                      CChar -> Int
forall a. Storable a => a -> Int
sizeOf (CChar
forall a. HasCallStack => a
undefined :: CChar) Int -> Int -> Int
forall a. Num a => a -> a -> a
*
                        Integer -> Int
forall a. Num a => Integer -> a
fromInteger (Proxy# idx -> Integer
forall (n :: Nat). KnownNat n => Proxy# n -> Integer
natVal' (Proxy# idx
forall k (a :: k). Proxy# a
proxy# :: Proxy# idx)) -- ' closing tick for hsc2hs

        {-# INLINE readFieldArray #-}
        readFieldArray :: Ptr VkLayerProperties
-> IO (FieldType "description" VkLayerProperties)
readFieldArray Ptr VkLayerProperties
p
          = Ptr VkLayerProperties -> Int -> IO CChar
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkLayerProperties
p
              ((Int
264) Int -> Int -> Int
forall a. Num a => a -> a -> a
+
{-# LINE 272 "src-gen/Graphics/Vulkan/Types/Struct/LayerProperties.hsc" #-}
                 CChar -> Int
forall a. Storable a => a -> Int
sizeOf (CChar
forall a. HasCallStack => a
undefined :: CChar) Int -> Int -> Int
forall a. Num a => a -> a -> a
*
                   Integer -> Int
forall a. Num a => Integer -> a
fromInteger (Proxy# idx -> Integer
forall (n :: Nat). KnownNat n => Proxy# n -> Integer
natVal' (Proxy# idx
forall k (a :: k). Proxy# a
proxy# :: Proxy# idx))) -- ' closing tick for hsc2hs

instance {-# OVERLAPPING #-}
         (KnownNat idx,
          IndexInBounds "description" idx VkLayerProperties) =>
         CanWriteFieldArray "description" idx VkLayerProperties
         where
        {-# SPECIALISE instance
                       CanWriteFieldArray "description" 0 VkLayerProperties #-}

        {-# SPECIALISE instance
                       CanWriteFieldArray "description" 1 VkLayerProperties #-}

        {-# SPECIALISE instance
                       CanWriteFieldArray "description" 2 VkLayerProperties #-}

        {-# SPECIALISE instance
                       CanWriteFieldArray "description" 3 VkLayerProperties #-}

        {-# INLINE writeFieldArray #-}
        writeFieldArray :: Ptr VkLayerProperties
-> FieldType "description" VkLayerProperties -> IO ()
writeFieldArray Ptr VkLayerProperties
p
          = Ptr VkLayerProperties -> Int -> CChar -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkLayerProperties
p
              ((Int
264) Int -> Int -> Int
forall a. Num a => a -> a -> a
+
{-# LINE 296 "src-gen/Graphics/Vulkan/Types/Struct/LayerProperties.hsc" #-}
                 CChar -> Int
forall a. Storable a => a -> Int
sizeOf (CChar
forall a. HasCallStack => a
undefined :: CChar) Int -> Int -> Int
forall a. Num a => a -> a -> a
*
                   Integer -> Int
forall a. Num a => Integer -> a
fromInteger (Proxy# idx -> Integer
forall (n :: Nat). KnownNat n => Proxy# n -> Integer
natVal' (Proxy# idx
forall k (a :: k). Proxy# a
proxy# :: Proxy# idx))) -- ' closing tick for hsc2hs

instance Show VkLayerProperties where
        showsPrec :: Int -> VkLayerProperties -> ShowS
showsPrec Int
d VkLayerProperties
x
          = String -> ShowS
showString String
"VkLayerProperties {" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
              (String -> ShowS
showString String
"layerName = [" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                 Int -> [CChar] -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d
                   (let s :: Int
s = CChar -> Int
forall a. Storable a => a -> Int
sizeOf
                              (FieldType "layerName" VkLayerProperties
forall a. HasCallStack => a
undefined :: FieldType "layerName" VkLayerProperties)
                        o :: Int
o = HasField "layerName" VkLayerProperties => Int
forall (fname :: Symbol) a. HasField fname a => Int
fieldOffset @"layerName" @VkLayerProperties
                        f :: Int -> IO (FieldType "layerName" VkLayerProperties)
f Int
i
                          = Ptr VkLayerProperties -> Int -> IO CChar
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkLayerProperties -> Ptr VkLayerProperties
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkLayerProperties
x) Int
i ::
                              IO (FieldType "layerName" VkLayerProperties)
                      in
                      IO [CChar] -> [CChar]
forall a. IO a -> a
unsafeDupablePerformIO (IO [CChar] -> [CChar])
-> ([Int] -> IO [CChar]) -> [Int] -> [CChar]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> IO CChar) -> [Int] -> IO [CChar]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Int -> IO CChar
Int -> IO (FieldType "layerName" VkLayerProperties)
f ([Int] -> [CChar]) -> [Int] -> [CChar]
forall a b. (a -> b) -> a -> b
$
                        (Int -> Int) -> [Int] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map (\ Int
i -> Int
o Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
s) [Int
0 .. Int
forall a. (Num a, Eq a) => a
VK_MAX_EXTENSION_NAME_SIZE Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1])
                   ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ShowS
showChar Char
']')
                ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                String -> ShowS
showString String
", " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                  String -> ShowS
showString String
"specVersion = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                    Int -> Word32 -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkLayerProperties -> FieldType "specVersion" VkLayerProperties
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"specVersion" VkLayerProperties
x) ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                      String -> ShowS
showString String
", " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                        String -> ShowS
showString String
"implementationVersion = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                          Int -> Word32 -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkLayerProperties
-> FieldType "implementationVersion" VkLayerProperties
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"implementationVersion" VkLayerProperties
x) ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                            String -> ShowS
showString String
", " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                              (String -> ShowS
showString String
"description = [" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                                 Int -> [CChar] -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d
                                   (let s :: Int
s = CChar -> Int
forall a. Storable a => a -> Int
sizeOf
                                              (FieldType "description" VkLayerProperties
forall a. HasCallStack => a
undefined ::
                                                 FieldType "description" VkLayerProperties)
                                        o :: Int
o = HasField "description" VkLayerProperties => Int
forall (fname :: Symbol) a. HasField fname a => Int
fieldOffset @"description" @VkLayerProperties
                                        f :: Int -> IO (FieldType "description" VkLayerProperties)
f Int
i
                                          = Ptr VkLayerProperties -> Int -> IO CChar
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkLayerProperties -> Ptr VkLayerProperties
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkLayerProperties
x) Int
i ::
                                              IO (FieldType "description" VkLayerProperties)
                                      in
                                      IO [CChar] -> [CChar]
forall a. IO a -> a
unsafeDupablePerformIO (IO [CChar] -> [CChar])
-> ([Int] -> IO [CChar]) -> [Int] -> [CChar]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> IO CChar) -> [Int] -> IO [CChar]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Int -> IO CChar
Int -> IO (FieldType "description" VkLayerProperties)
f ([Int] -> [CChar]) -> [Int] -> [CChar]
forall a b. (a -> b) -> a -> b
$
                                        (Int -> Int) -> [Int] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map (\ Int
i -> Int
o Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
s) [Int
0 .. Int
forall a. (Num a, Eq a) => a
VK_MAX_DESCRIPTION_SIZE Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1])
                                   ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ShowS
showChar Char
']')
                                ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ShowS
showChar Char
'}'