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

{-# LINE 2 "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# a _) == x@(VkComponentMapping# b _)
          = EQ == cmpBytes# (sizeOf x) a b

        {-# INLINE (==) #-}

instance Ord VkComponentMapping where
        (VkComponentMapping# a _) `compare` x@(VkComponentMapping# b _)
          = cmpBytes# (sizeOf x) a b

        {-# INLINE compare #-}

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

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

        {-# INLINE alignment #-}
        peek = peekVkData#

        {-# INLINE peek #-}
        poke = pokeVkData#

        {-# INLINE poke #-}

instance VulkanMarshalPrim VkComponentMapping where
        unsafeAddr (VkComponentMapping# a _) = a

        {-# INLINE unsafeAddr #-}
        unsafeByteArray (VkComponentMapping# _ b) = b

        {-# INLINE unsafeByteArray #-}
        unsafeFromByteArrayOffset off b
          = VkComponentMapping# (plusAddr# (byteArrayContents# b) off) 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 = False

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

instance {-# OVERLAPPING #-} CanReadField "r" VkComponentMapping
         where
        {-# NOINLINE getField #-}
        getField x
          = unsafeDupablePerformIO
              (peekByteOff (unsafePtr x) (0))
{-# LINE 94 "src-gen/Graphics/Vulkan/Types/Struct/ComponentMapping.hsc" #-}

        {-# INLINE readField #-}
        readField p
          = peekByteOff p (0)
{-# LINE 98 "src-gen/Graphics/Vulkan/Types/Struct/ComponentMapping.hsc" #-}

instance {-# OVERLAPPING #-} CanWriteField "r" VkComponentMapping
         where
        {-# INLINE writeField #-}
        writeField p
          = pokeByteOff p (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 = False

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

instance {-# OVERLAPPING #-} CanReadField "g" VkComponentMapping
         where
        {-# NOINLINE getField #-}
        getField x
          = unsafeDupablePerformIO
              (peekByteOff (unsafePtr x) (4))
{-# LINE 124 "src-gen/Graphics/Vulkan/Types/Struct/ComponentMapping.hsc" #-}

        {-# INLINE readField #-}
        readField p
          = peekByteOff p (4)
{-# LINE 128 "src-gen/Graphics/Vulkan/Types/Struct/ComponentMapping.hsc" #-}

instance {-# OVERLAPPING #-} CanWriteField "g" VkComponentMapping
         where
        {-# INLINE writeField #-}
        writeField p
          = pokeByteOff p (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 = False

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

instance {-# OVERLAPPING #-} CanReadField "b" VkComponentMapping
         where
        {-# NOINLINE getField #-}
        getField x
          = unsafeDupablePerformIO
              (peekByteOff (unsafePtr x) (8))
{-# LINE 154 "src-gen/Graphics/Vulkan/Types/Struct/ComponentMapping.hsc" #-}

        {-# INLINE readField #-}
        readField p
          = peekByteOff p (8)
{-# LINE 158 "src-gen/Graphics/Vulkan/Types/Struct/ComponentMapping.hsc" #-}

instance {-# OVERLAPPING #-} CanWriteField "b" VkComponentMapping
         where
        {-# INLINE writeField #-}
        writeField p
          = pokeByteOff p (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 = False

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

instance {-# OVERLAPPING #-} CanReadField "a" VkComponentMapping
         where
        {-# NOINLINE getField #-}
        getField x
          = unsafeDupablePerformIO
              (peekByteOff (unsafePtr x) (12))
{-# LINE 184 "src-gen/Graphics/Vulkan/Types/Struct/ComponentMapping.hsc" #-}

        {-# INLINE readField #-}
        readField p
          = peekByteOff p (12)
{-# LINE 188 "src-gen/Graphics/Vulkan/Types/Struct/ComponentMapping.hsc" #-}

instance {-# OVERLAPPING #-} CanWriteField "a" VkComponentMapping
         where
        {-# INLINE writeField #-}
        writeField p
          = pokeByteOff p (12)
{-# LINE 194 "src-gen/Graphics/Vulkan/Types/Struct/ComponentMapping.hsc" #-}

instance Show VkComponentMapping where
        showsPrec d x
          = showString "VkComponentMapping {" .
              showString "r = " .
                showsPrec d (getField @"r" x) .
                  showString ", " .
                    showString "g = " .
                      showsPrec d (getField @"g" x) .
                        showString ", " .
                          showString "b = " .
                            showsPrec d (getField @"b" x) .
                              showString ", " .
                                showString "a = " . showsPrec d (getField @"a" x) . showChar '}'