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


{-# LANGUAGE DataKinds             #-}
{-# LANGUAGE FlexibleInstances     #-}
{-# LANGUAGE MagicHash             #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE Strict                #-}
{-# LANGUAGE TypeApplications      #-}
{-# LANGUAGE TypeFamilies          #-}
module Graphics.Vulkan.Types.Struct.ComponentMapping
       (VkComponentMapping(..)) where
import           Foreign.Storable                            (Storable (..))
import           GHC.Base                                    (Addr#, ByteArray#,
                                                              byteArrayContents#,
                                                              plusAddr#)
import           Graphics.Vulkan.Marshal
import           Graphics.Vulkan.Marshal.Internal
import           Graphics.Vulkan.Types.Enum.ComponentSwizzle (VkComponentSwizzle)
import           System.IO.Unsafe                            (unsafeDupablePerformIO)

-- | > typedef struct VkComponentMapping {
--   >     VkComponentSwizzle r;
--   >     VkComponentSwizzle g;
--   >     VkComponentSwizzle b;
--   >     VkComponentSwizzle a;
--   > } VkComponentMapping;
--
--   <https://www.khronos.org/registry/vulkan/specs/1.1-extensions/html/vkspec.html#VkComponentMapping VkComponentMapping registry at www.khronos.org>
data VkComponentMapping = VkComponentMapping# Addr# ByteArray#

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

        {-# INLINE (==) #-}

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

        {-# INLINE compare #-}

instance Storable VkComponentMapping where
        sizeOf :: VkComponentMapping -> Int
sizeOf ~VkComponentMapping
_ = (Int
16)
{-# LINE 45 "src-gen/Graphics/Vulkan/Types/Struct/ComponentMapping.hsc" #-}

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

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

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

        {-# INLINE poke #-}

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

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

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

        {-# INLINE unsafeFromByteArrayOffset #-}

instance VulkanMarshal VkComponentMapping where
        type StructFields VkComponentMapping = '["r", "g", "b", "a"] -- ' closing tick for hsc2hs
        type CUnionType VkComponentMapping = 'False -- ' closing tick for hsc2hs
        type ReturnedOnly VkComponentMapping = 'False -- ' closing tick for hsc2hs
        type StructExtends VkComponentMapping = '[] -- ' closing tick for hsc2hs

instance {-# OVERLAPPING #-} HasField "r" VkComponentMapping where
        type FieldType "r" VkComponentMapping = VkComponentSwizzle
        type FieldOptional "r" VkComponentMapping = 'False -- ' closing tick for hsc2hs
        type FieldOffset "r" VkComponentMapping =
             (0)
{-# LINE 80 "src-gen/Graphics/Vulkan/Types/Struct/ComponentMapping.hsc" #-}
        type FieldIsArray "r" VkComponentMapping = 'False -- ' closing tick for hsc2hs

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

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

instance {-# OVERLAPPING #-} CanReadField "r" VkComponentMapping
         where
        {-# NOINLINE getField #-}
        getField :: VkComponentMapping -> FieldType "r" VkComponentMapping
getField VkComponentMapping
x
          = IO VkComponentSwizzle -> VkComponentSwizzle
forall a. IO a -> a
unsafeDupablePerformIO
              (Ptr VkComponentMapping -> Int -> IO VkComponentSwizzle
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkComponentMapping -> Ptr VkComponentMapping
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkComponentMapping
x) (Int
0))
{-# LINE 94 "src-gen/Graphics/Vulkan/Types/Struct/ComponentMapping.hsc" #-}

        {-# INLINE readField #-}
        readField :: Ptr VkComponentMapping -> IO (FieldType "r" VkComponentMapping)
readField Ptr VkComponentMapping
p
          = Ptr VkComponentMapping -> Int -> IO VkComponentSwizzle
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkComponentMapping
p (Int
0)
{-# LINE 98 "src-gen/Graphics/Vulkan/Types/Struct/ComponentMapping.hsc" #-}

instance {-# OVERLAPPING #-} CanWriteField "r" VkComponentMapping
         where
        {-# INLINE writeField #-}
        writeField :: Ptr VkComponentMapping -> FieldType "r" VkComponentMapping -> IO ()
writeField Ptr VkComponentMapping
p
          = Ptr VkComponentMapping -> Int -> VkComponentSwizzle -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkComponentMapping
p (Int
0)
{-# LINE 104 "src-gen/Graphics/Vulkan/Types/Struct/ComponentMapping.hsc" #-}

instance {-# OVERLAPPING #-} HasField "g" VkComponentMapping where
        type FieldType "g" VkComponentMapping = VkComponentSwizzle
        type FieldOptional "g" VkComponentMapping = 'False -- ' closing tick for hsc2hs
        type FieldOffset "g" VkComponentMapping =
             (4)
{-# LINE 110 "src-gen/Graphics/Vulkan/Types/Struct/ComponentMapping.hsc" #-}
        type FieldIsArray "g" VkComponentMapping = 'False -- ' closing tick for hsc2hs

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

        {-# INLINE fieldOffset #-}
        fieldOffset :: Int
fieldOffset = (Int
4)
{-# LINE 117 "src-gen/Graphics/Vulkan/Types/Struct/ComponentMapping.hsc" #-}

instance {-# OVERLAPPING #-} CanReadField "g" VkComponentMapping
         where
        {-# NOINLINE getField #-}
        getField :: VkComponentMapping -> FieldType "g" VkComponentMapping
getField VkComponentMapping
x
          = IO VkComponentSwizzle -> VkComponentSwizzle
forall a. IO a -> a
unsafeDupablePerformIO
              (Ptr VkComponentMapping -> Int -> IO VkComponentSwizzle
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkComponentMapping -> Ptr VkComponentMapping
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkComponentMapping
x) (Int
4))
{-# LINE 124 "src-gen/Graphics/Vulkan/Types/Struct/ComponentMapping.hsc" #-}

        {-# INLINE readField #-}
        readField :: Ptr VkComponentMapping -> IO (FieldType "g" VkComponentMapping)
readField Ptr VkComponentMapping
p
          = Ptr VkComponentMapping -> Int -> IO VkComponentSwizzle
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkComponentMapping
p (Int
4)
{-# LINE 128 "src-gen/Graphics/Vulkan/Types/Struct/ComponentMapping.hsc" #-}

instance {-# OVERLAPPING #-} CanWriteField "g" VkComponentMapping
         where
        {-# INLINE writeField #-}
        writeField :: Ptr VkComponentMapping -> FieldType "g" VkComponentMapping -> IO ()
writeField Ptr VkComponentMapping
p
          = Ptr VkComponentMapping -> Int -> VkComponentSwizzle -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkComponentMapping
p (Int
4)
{-# LINE 134 "src-gen/Graphics/Vulkan/Types/Struct/ComponentMapping.hsc" #-}

instance {-# OVERLAPPING #-} HasField "b" VkComponentMapping where
        type FieldType "b" VkComponentMapping = VkComponentSwizzle
        type FieldOptional "b" VkComponentMapping = 'False -- ' closing tick for hsc2hs
        type FieldOffset "b" VkComponentMapping =
             (8)
{-# LINE 140 "src-gen/Graphics/Vulkan/Types/Struct/ComponentMapping.hsc" #-}
        type FieldIsArray "b" VkComponentMapping = 'False -- ' closing tick for hsc2hs

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

        {-# INLINE fieldOffset #-}
        fieldOffset :: Int
fieldOffset = (Int
8)
{-# LINE 147 "src-gen/Graphics/Vulkan/Types/Struct/ComponentMapping.hsc" #-}

instance {-# OVERLAPPING #-} CanReadField "b" VkComponentMapping
         where
        {-# NOINLINE getField #-}
        getField :: VkComponentMapping -> FieldType "b" VkComponentMapping
getField VkComponentMapping
x
          = IO VkComponentSwizzle -> VkComponentSwizzle
forall a. IO a -> a
unsafeDupablePerformIO
              (Ptr VkComponentMapping -> Int -> IO VkComponentSwizzle
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkComponentMapping -> Ptr VkComponentMapping
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkComponentMapping
x) (Int
8))
{-# LINE 154 "src-gen/Graphics/Vulkan/Types/Struct/ComponentMapping.hsc" #-}

        {-# INLINE readField #-}
        readField :: Ptr VkComponentMapping -> IO (FieldType "b" VkComponentMapping)
readField Ptr VkComponentMapping
p
          = Ptr VkComponentMapping -> Int -> IO VkComponentSwizzle
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkComponentMapping
p (Int
8)
{-# LINE 158 "src-gen/Graphics/Vulkan/Types/Struct/ComponentMapping.hsc" #-}

instance {-# OVERLAPPING #-} CanWriteField "b" VkComponentMapping
         where
        {-# INLINE writeField #-}
        writeField :: Ptr VkComponentMapping -> FieldType "b" VkComponentMapping -> IO ()
writeField Ptr VkComponentMapping
p
          = Ptr VkComponentMapping -> Int -> VkComponentSwizzle -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkComponentMapping
p (Int
8)
{-# LINE 164 "src-gen/Graphics/Vulkan/Types/Struct/ComponentMapping.hsc" #-}

instance {-# OVERLAPPING #-} HasField "a" VkComponentMapping where
        type FieldType "a" VkComponentMapping = VkComponentSwizzle
        type FieldOptional "a" VkComponentMapping = 'False -- ' closing tick for hsc2hs
        type FieldOffset "a" VkComponentMapping =
             (12)
{-# LINE 170 "src-gen/Graphics/Vulkan/Types/Struct/ComponentMapping.hsc" #-}
        type FieldIsArray "a" VkComponentMapping = 'False -- ' closing tick for hsc2hs

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

        {-# INLINE fieldOffset #-}
        fieldOffset :: Int
fieldOffset = (Int
12)
{-# LINE 177 "src-gen/Graphics/Vulkan/Types/Struct/ComponentMapping.hsc" #-}

instance {-# OVERLAPPING #-} CanReadField "a" VkComponentMapping
         where
        {-# NOINLINE getField #-}
        getField :: VkComponentMapping -> FieldType "a" VkComponentMapping
getField VkComponentMapping
x
          = IO VkComponentSwizzle -> VkComponentSwizzle
forall a. IO a -> a
unsafeDupablePerformIO
              (Ptr VkComponentMapping -> Int -> IO VkComponentSwizzle
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkComponentMapping -> Ptr VkComponentMapping
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkComponentMapping
x) (Int
12))
{-# LINE 184 "src-gen/Graphics/Vulkan/Types/Struct/ComponentMapping.hsc" #-}

        {-# INLINE readField #-}
        readField :: Ptr VkComponentMapping -> IO (FieldType "a" VkComponentMapping)
readField Ptr VkComponentMapping
p
          = Ptr VkComponentMapping -> Int -> IO VkComponentSwizzle
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkComponentMapping
p (Int
12)
{-# LINE 188 "src-gen/Graphics/Vulkan/Types/Struct/ComponentMapping.hsc" #-}

instance {-# OVERLAPPING #-} CanWriteField "a" VkComponentMapping
         where
        {-# INLINE writeField #-}
        writeField :: Ptr VkComponentMapping -> FieldType "a" VkComponentMapping -> IO ()
writeField Ptr VkComponentMapping
p
          = Ptr VkComponentMapping -> Int -> VkComponentSwizzle -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkComponentMapping
p (Int
12)
{-# LINE 194 "src-gen/Graphics/Vulkan/Types/Struct/ComponentMapping.hsc" #-}

instance Show VkComponentMapping where
        showsPrec :: Int -> VkComponentMapping -> ShowS
showsPrec Int
d VkComponentMapping
x
          = String -> ShowS
showString String
"VkComponentMapping {" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
              String -> ShowS
showString String
"r = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                Int -> VkComponentSwizzle -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkComponentMapping -> FieldType "r" VkComponentMapping
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"r" VkComponentMapping
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
"g = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                      Int -> VkComponentSwizzle -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkComponentMapping -> FieldType "g" VkComponentMapping
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"g" VkComponentMapping
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
"b = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                            Int -> VkComponentSwizzle -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkComponentMapping -> FieldType "b" VkComponentMapping
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"b" VkComponentMapping
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
"a = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> VkComponentSwizzle -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkComponentMapping -> FieldType "a" VkComponentMapping
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"a" VkComponentMapping
x) ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ShowS
showChar Char
'}'