{-# LANGUAGE AllowAmbiguousTypes #-}

module Resource.Texture
  ( Texture(..)

  , TextureError(..)
    -- * Texture types
  , Flat
  , CubeMap
  , ArrayOf
  , TextureLayers(..)

    -- * Utilities
  , debugNameCollection
  , TextureLoader

  , createImageView
  , imageCI
  , imageAllocationCI
  , stageBufferCI
  , stageAllocationCI

  , withSize2d
  , withSize3d
  ) where

import RIO

import Data.Bits ((.|.))
import Data.List qualified as List
import Geomancy (Vec2, vec2)
import GHC.Stack (withFrozenCallStack)
import GHC.TypeLits (Nat, KnownNat, natVal)
import GHC.Records (HasField(..))
import RIO.FilePath (takeBaseName)
import Vulkan.Core10 qualified as Vk
import Vulkan.NamedType ((:::))
import Vulkan.Utils.Debug qualified as Debug
import Vulkan.Zero (zero)
import VulkanMemoryAllocator qualified as VMA

import Engine.Vulkan.Types (HasVulkan(getDevice), MonadVulkan, Queues)
import Resource.Collection qualified as Collection
import Resource.Image (AllocatedImage(..))
import Resource.Image qualified as Image

data TextureError
  = LoadError Int64 Text
  | LayerError Word32 Word32
  | MipLevelsError Word32 Int
  | ArrayError Word32 Word32
  deriving (TextureError -> TextureError -> Bool
(TextureError -> TextureError -> Bool)
-> (TextureError -> TextureError -> Bool) -> Eq TextureError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TextureError -> TextureError -> Bool
== :: TextureError -> TextureError -> Bool
$c/= :: TextureError -> TextureError -> Bool
/= :: TextureError -> TextureError -> Bool
Eq, Eq TextureError
Eq TextureError
-> (TextureError -> TextureError -> Ordering)
-> (TextureError -> TextureError -> Bool)
-> (TextureError -> TextureError -> Bool)
-> (TextureError -> TextureError -> Bool)
-> (TextureError -> TextureError -> Bool)
-> (TextureError -> TextureError -> TextureError)
-> (TextureError -> TextureError -> TextureError)
-> Ord TextureError
TextureError -> TextureError -> Bool
TextureError -> TextureError -> Ordering
TextureError -> TextureError -> TextureError
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: TextureError -> TextureError -> Ordering
compare :: TextureError -> TextureError -> Ordering
$c< :: TextureError -> TextureError -> Bool
< :: TextureError -> TextureError -> Bool
$c<= :: TextureError -> TextureError -> Bool
<= :: TextureError -> TextureError -> Bool
$c> :: TextureError -> TextureError -> Bool
> :: TextureError -> TextureError -> Bool
$c>= :: TextureError -> TextureError -> Bool
>= :: TextureError -> TextureError -> Bool
$cmax :: TextureError -> TextureError -> TextureError
max :: TextureError -> TextureError -> TextureError
$cmin :: TextureError -> TextureError -> TextureError
min :: TextureError -> TextureError -> TextureError
Ord, Int -> TextureError -> ShowS
[TextureError] -> ShowS
TextureError -> String
(Int -> TextureError -> ShowS)
-> (TextureError -> String)
-> ([TextureError] -> ShowS)
-> Show TextureError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TextureError -> ShowS
showsPrec :: Int -> TextureError -> ShowS
$cshow :: TextureError -> String
show :: TextureError -> String
$cshowList :: [TextureError] -> ShowS
showList :: [TextureError] -> ShowS
Show)

instance Exception TextureError

data Texture tag = Texture
  { forall {k} (tag :: k). Texture tag -> Format
tFormat         :: Vk.Format
  , forall {k} (tag :: k). Texture tag -> Word32
tMipLevels      :: Word32
  , forall {k} (tag :: k). Texture tag -> Word32
tLayers         :: Word32 -- ^ Actual number of layers, up to @ArrayOf a@
  , forall {k} (tag :: k). Texture tag -> AllocatedImage
tAllocatedImage :: AllocatedImage
  }
  deriving (Int -> Texture tag -> ShowS
[Texture tag] -> ShowS
Texture tag -> String
(Int -> Texture tag -> ShowS)
-> (Texture tag -> String)
-> ([Texture tag] -> ShowS)
-> Show (Texture tag)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall k (tag :: k). Int -> Texture tag -> ShowS
forall k (tag :: k). [Texture tag] -> ShowS
forall k (tag :: k). Texture tag -> String
$cshowsPrec :: forall k (tag :: k). Int -> Texture tag -> ShowS
showsPrec :: Int -> Texture tag -> ShowS
$cshow :: forall k (tag :: k). Texture tag -> String
show :: Texture tag -> String
$cshowList :: forall k (tag :: k). [Texture tag] -> ShowS
showList :: [Texture tag] -> ShowS
Show)

data CubeMap
data Flat
data ArrayOf (layers :: Nat)

-- | Number of expected texture layers to load from resource.
class TextureLayers a where
  textureLayers :: Word32

instance TextureLayers CubeMap where
  textureLayers :: Word32
textureLayers = Word32
6

instance TextureLayers Flat where
  textureLayers :: Word32
textureLayers = Word32
1

instance KnownNat n => TextureLayers (ArrayOf n) where
  textureLayers :: Word32
textureLayers = Integer -> Word32
forall a. Num a => Integer -> a
fromInteger (Integer -> Word32) -> Integer -> Word32
forall a b. (a -> b) -> a -> b
$ Proxy n -> Integer
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal (forall (t :: Nat). Proxy t
forall {k} (t :: k). Proxy t
Proxy @n)

type TextureLoader m layers = Vk.Format -> Queues Vk.CommandPool -> FilePath -> m (Texture layers)

-- * Allocation wrappers

debugNameCollection
  :: ( Traversable t
     , MonadVulkan env m
     , HasLogFunc env
     , HasCallStack
     )
  => t (Texture layers)
  -> t FilePath
  -> m ()
debugNameCollection :: forall {k} (t :: * -> *) env (m :: * -> *) (layers :: k).
(Traversable t, MonadVulkan env m, HasLogFunc env, HasCallStack) =>
t (Texture layers) -> t String -> m ()
debugNameCollection t (Texture layers)
textures t String
paths = do
  Device
device <- (env -> Device) -> m Device
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks env -> Device
forall a. HasVulkan a => a -> Device
getDevice
  [((Nat, String), Texture layers)]
-> (((Nat, String), Texture layers) -> m ()) -> m ()
forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
t a -> (a -> f b) -> f ()
for_ [((Nat, String), Texture layers)]
names \((Nat
ix, String
path), Texture{AllocatedImage
$sel:tAllocatedImage:Texture :: forall {k} (tag :: k). Texture tag -> AllocatedImage
tAllocatedImage :: AllocatedImage
tAllocatedImage}) -> do
    (HasCallStack => m ()) -> m ()
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack ((HasCallStack => m ()) -> m ()) -> (HasCallStack => m ()) -> m ()
forall a b. (a -> b) -> a -> b
$
      Utf8Builder -> m ()
forall (m :: * -> *) env.
(MonadIO m, MonadReader env m, HasLogFunc env, HasCallStack) =>
Utf8Builder -> m ()
logDebug (Utf8Builder -> m ()) -> Utf8Builder -> m ()
forall a b. (a -> b) -> a -> b
$ (Nat, String) -> Utf8Builder
forall a. Show a => a -> Utf8Builder
displayShow (Nat
ix, String
path)
    Device -> Image -> ByteString -> m ()
forall a (m :: * -> *).
(HasObjectType a, MonadIO m) =>
Device -> a -> ByteString -> m ()
Debug.nameObject Device
device (AllocatedImage -> Image
Image.aiImage AllocatedImage
tAllocatedImage) (ByteString -> m ()) -> ByteString -> m ()
forall a b. (a -> b) -> a -> b
$
      String -> ByteString
forall a. IsString a => String -> a
fromString (String -> ByteString) -> String -> ByteString
forall a b. (a -> b) -> a -> b
$ forall a. Show a => a -> String
show @Natural Nat
ix String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
":" String -> ShowS
forall a. Semigroup a => a -> a -> a
<> ShowS
takeBaseName String
path
  where
    names :: [((Nat, String), Texture layers)]
names = [(Nat, String)]
-> [Texture layers] -> [((Nat, String), Texture layers)]
forall a b. [a] -> [b] -> [(a, b)]
List.zip
      (t (Nat, String) -> [(Nat, String)]
forall a. t a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList (t (Nat, String) -> [(Nat, String)])
-> t (Nat, String) -> [(Nat, String)]
forall a b. (a -> b) -> a -> b
$ t String -> t (Nat, String)
forall (t :: * -> *) ix a.
(Traversable t, Num ix) =>
t a -> t (ix, a)
Collection.enumerate t String
paths)
      (t (Texture layers) -> [Texture layers]
forall a. t a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList t (Texture layers)
textures)

-- * Implementation

createImageView
  :: (MonadIO io, HasVulkan context)
  => context
  -> Vk.Image
  -> Vk.Format
  -> "mip levels" ::: Word32
  -> "array layers" ::: Word32
  -> io Vk.ImageView
createImageView :: forall (io :: * -> *) context.
(MonadIO io, HasVulkan context) =>
context -> Image -> Format -> Word32 -> Word32 -> io ImageView
createImageView context
context Image
image Format
format Word32
mipLevels Word32
arrayLayers =
  Device
-> ImageViewCreateInfo '[]
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io ImageView
forall (a :: [*]) (io :: * -> *).
(Extendss ImageViewCreateInfo a, PokeChain a, MonadIO io) =>
Device
-> ImageViewCreateInfo a
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io ImageView
Vk.createImageView (context -> Device
forall a. HasVulkan a => a -> Device
getDevice context
context) ImageViewCreateInfo '[]
imageViewCI "allocator" ::: Maybe AllocationCallbacks
forall a. Maybe a
Nothing
  where
    imageViewCI :: ImageViewCreateInfo '[]
imageViewCI = ImageViewCreateInfo '[]
forall a. Zero a => a
zero
      { $sel:image:ImageViewCreateInfo :: Image
Vk.image            = Image
image
      , $sel:viewType:ImageViewCreateInfo :: ImageViewType
Vk.viewType         = ImageViewType
viewType
      , $sel:format:ImageViewCreateInfo :: Format
Vk.format           = Format
format
      , $sel:components:ImageViewCreateInfo :: ComponentMapping
Vk.components       = ComponentMapping
forall a. Zero a => a
zero
      , $sel:subresourceRange:ImageViewCreateInfo :: ImageSubresourceRange
Vk.subresourceRange = ImageSubresourceRange
colorRange
      }

    viewType :: ImageViewType
viewType =
      if Word32
arrayLayers Word32 -> Word32 -> Bool
forall a. Eq a => a -> a -> Bool
== Word32
6 then
        ImageViewType
Vk.IMAGE_VIEW_TYPE_CUBE
      else
        ImageViewType
Vk.IMAGE_VIEW_TYPE_2D

    colorRange :: ImageSubresourceRange
colorRange =
      ImageAspectFlags -> Word32 -> Word32 -> ImageSubresourceRange
Image.subresource ImageAspectFlags
Vk.IMAGE_ASPECT_COLOR_BIT Word32
mipLevels Word32
arrayLayers

imageCI :: Vk.Format -> Vk.Extent3D -> Word32 -> Word32 -> Vk.ImageCreateInfo '[]
imageCI :: Format -> Extent3D -> Word32 -> Word32 -> ImageCreateInfo '[]
imageCI Format
format Extent3D
extent Word32
mipLevels Word32
arrayLayers = ImageCreateInfo '[]
forall a. Zero a => a
zero
  { $sel:flags:ImageCreateInfo :: ImageCreateFlagBits
Vk.flags         = ImageCreateFlagBits
flags
  , $sel:imageType:ImageCreateInfo :: ImageType
Vk.imageType     = ImageType
Vk.IMAGE_TYPE_2D
  , $sel:format:ImageCreateInfo :: Format
Vk.format        = Format
format
  , $sel:extent:ImageCreateInfo :: Extent3D
Vk.extent        = Extent3D
extent
  , $sel:mipLevels:ImageCreateInfo :: Word32
Vk.mipLevels     = Word32
mipLevels
  , $sel:arrayLayers:ImageCreateInfo :: Word32
Vk.arrayLayers   = if Bool
isCube then Word32
6 else Word32
arrayLayers
  , $sel:tiling:ImageCreateInfo :: ImageTiling
Vk.tiling        = ImageTiling
Vk.IMAGE_TILING_OPTIMAL
  , $sel:initialLayout:ImageCreateInfo :: ImageLayout
Vk.initialLayout = ImageLayout
Vk.IMAGE_LAYOUT_UNDEFINED
  , $sel:usage:ImageCreateInfo :: ImageUsageFlags
Vk.usage         = ImageUsageFlags
usage
  , $sel:sharingMode:ImageCreateInfo :: SharingMode
Vk.sharingMode   = SharingMode
Vk.SHARING_MODE_EXCLUSIVE
  , $sel:samples:ImageCreateInfo :: SampleCountFlagBits
Vk.samples       = SampleCountFlagBits
Vk.SAMPLE_COUNT_1_BIT -- XXX: no multisampling here
  }
  where
    isCube :: Bool
isCube =
      Word32
arrayLayers Word32 -> Word32 -> Bool
forall a. Eq a => a -> a -> Bool
== Word32
6

    usage :: ImageUsageFlags
usage =
      ImageUsageFlags
Vk.IMAGE_USAGE_SAMPLED_BIT ImageUsageFlags -> ImageUsageFlags -> ImageUsageFlags
forall a. Bits a => a -> a -> a
.|.  -- Sampler
      ImageUsageFlags
Vk.IMAGE_USAGE_TRANSFER_DST_BIT -- Staging

    flags :: ImageCreateFlagBits
flags =
      if Bool
isCube then
        ImageCreateFlagBits
Vk.IMAGE_CREATE_CUBE_COMPATIBLE_BIT
      else
        ImageCreateFlagBits
forall a. Zero a => a
zero

imageAllocationCI :: VMA.AllocationCreateInfo
imageAllocationCI :: AllocationCreateInfo
imageAllocationCI = AllocationCreateInfo
forall a. Zero a => a
zero
  { $sel:usage:AllocationCreateInfo :: MemoryUsage
VMA.usage         = MemoryUsage
VMA.MEMORY_USAGE_GPU_ONLY
  , $sel:requiredFlags:AllocationCreateInfo :: MemoryPropertyFlags
VMA.requiredFlags = MemoryPropertyFlags
Vk.MEMORY_PROPERTY_DEVICE_LOCAL_BIT
  }

stageBufferCI :: Integral a => a -> Vk.BufferCreateInfo '[]
stageBufferCI :: forall a. Integral a => a -> BufferCreateInfo '[]
stageBufferCI a
pixelBytes = BufferCreateInfo '[]
forall a. Zero a => a
zero
  { $sel:size:BufferCreateInfo :: DeviceSize
Vk.size        = a -> DeviceSize
forall a b. (Integral a, Num b) => a -> b
fromIntegral a
pixelBytes
  , $sel:usage:BufferCreateInfo :: BufferUsageFlags
Vk.usage       = BufferUsageFlags
Vk.BUFFER_USAGE_TRANSFER_SRC_BIT
  , $sel:sharingMode:BufferCreateInfo :: SharingMode
Vk.sharingMode = SharingMode
Vk.SHARING_MODE_EXCLUSIVE
  }

stageAllocationCI :: VMA.AllocationCreateInfo
stageAllocationCI :: AllocationCreateInfo
stageAllocationCI = AllocationCreateInfo
forall a. Zero a => a
zero
  { $sel:flags:AllocationCreateInfo :: AllocationCreateFlags
VMA.flags         = AllocationCreateFlags
VMA.ALLOCATION_CREATE_MAPPED_BIT
  , $sel:usage:AllocationCreateInfo :: MemoryUsage
VMA.usage         = MemoryUsage
VMA.MEMORY_USAGE_CPU_TO_GPU
  , $sel:requiredFlags:AllocationCreateInfo :: MemoryPropertyFlags
VMA.requiredFlags = MemoryPropertyFlags
Vk.MEMORY_PROPERTY_HOST_VISIBLE_BIT
  }

-- * Helpers

{-# INLINE withSize2d #-}
withSize2d :: Num i => (i -> i -> a) -> Texture tag -> a
withSize2d :: forall {k} i a (tag :: k).
Num i =>
(i -> i -> a) -> Texture tag -> a
withSize2d i -> i -> a
f Texture tag
t =
  i -> i -> a
f
    (Word32 -> i
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
width)
    (Word32 -> i
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
height)
  where
    Vk.Extent3D{Word32
width :: Word32
$sel:width:Extent3D :: Extent3D -> Word32
width, Word32
height :: Word32
$sel:height:Extent3D :: Extent3D -> Word32
height} =
      AllocatedImage -> Extent3D
Image.aiExtent (Texture tag -> AllocatedImage
forall {k} (tag :: k). Texture tag -> AllocatedImage
tAllocatedImage Texture tag
t)

{-# INLINE withSize3d #-}
withSize3d :: Num i => (i -> i -> i -> a) -> Texture tag -> a
withSize3d :: forall {k} i a (tag :: k).
Num i =>
(i -> i -> i -> a) -> Texture tag -> a
withSize3d i -> i -> i -> a
f Texture tag
t =
  i -> i -> i -> a
f
    (Word32 -> i
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
width)
    (Word32 -> i
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
height)
    (Word32 -> i
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
depth)
  where
    Vk.Extent3D{Word32
$sel:width:Extent3D :: Extent3D -> Word32
width :: Word32
width, Word32
$sel:height:Extent3D :: Extent3D -> Word32
height :: Word32
height, Word32
depth :: Word32
$sel:depth:Extent3D :: Extent3D -> Word32
depth} =
      AllocatedImage -> Extent3D
Image.aiExtent (Texture tag -> AllocatedImage
forall {k} (tag :: k). Texture tag -> AllocatedImage
tAllocatedImage Texture tag
t)

instance HasField "size" (Texture tag) Vec2 where
  {-# INLINE getField #-}
  getField :: Texture tag -> Vec2
getField = (Float -> Float -> Vec2) -> Texture tag -> Vec2
forall {k} i a (tag :: k).
Num i =>
(i -> i -> a) -> Texture tag -> a
withSize2d Float -> Float -> Vec2
vec2