{-# OPTIONS_GHC -fplugin Foreign.Storable.Generic.Plugin #-} {-# LANGUAGE DeriveAnyClass #-} module Render.Font.EvanwSdf.Model ( InstanceAttrs(..) ) where import RIO import Foreign.Storable.Generic (GStorable) import Geomancy (Vec4) import Vulkan.Core10 qualified as Vk import Engine.Vulkan.Format (HasVkFormat(..)) import Engine.Vulkan.Pipeline.Graphics (HasVertexInputBindings(..), instanceFormat) data InstanceAttrs = InstanceAttrs { vertRect :: Vec4 , fragRect :: Vec4 , color :: Vec4 , outlineColor :: Vec4 , samplerId :: Int32 , textureId :: Int32 , smoothing :: Float , outlineWidth :: Float } deriving (Eq, Show, Generic) -- XXX: Fine, the layout matches instance GStorable InstanceAttrs instance HasVkFormat InstanceAttrs where getVkFormat = [ Vk.FORMAT_R32G32B32A32_SFLOAT -- Quad scale+offset , Vk.FORMAT_R32G32B32A32_SFLOAT -- UV scale+offset , Vk.FORMAT_R32G32B32A32_SFLOAT -- Color , Vk.FORMAT_R32G32B32A32_SFLOAT -- Outline color , Vk.FORMAT_R32G32_SINT -- Sampler + texture IDs , Vk.FORMAT_R32G32_SFLOAT -- Smoothing + outline width ] instance HasVertexInputBindings InstanceAttrs where vertexInputBindings = [instanceFormat @InstanceAttrs]