module Graphics.LambdaCube.HardwareVertexBuffer where

import Data.IntMap
import Data.Word
import Foreign.C.Types
import Foreign.Storable

import Graphics.LambdaCube.HardwareBuffer

class HardwareBuffer a => HardwareVertexBuffer a where
    getVertexSize  :: a -> Int -- ^ Gets the size in bytes of a single vertex in this buffer
    getNumVertices :: a -> Int -- ^ Get the number of vertices in this buffer

-- | Vertex element semantics, used to identify the meaning of vertex buffer contents
data VertexElementSemantic
    = VES_POSITION              -- ^ Position, 3 reals per vertex
    | VES_BLEND_WEIGHTS         -- ^ Blending weights
    | VES_BLEND_INDICES         -- ^ Blending indices
    | VES_NORMAL                -- ^ Normal, 3 reals per vertex
    | VES_DIFFUSE               -- ^ Diffuse colours
    | VES_SPECULAR              -- ^ Specular colours
    | VES_TEXTURE_COORDINATES   -- ^ Texture coordinates
    | VES_BINORMAL              -- ^ Binormal (Y axis if normal is Z)
    | VES_TANGENT               -- ^ Tangent (X axis if normal is Z)
    deriving (Enum,Eq,Ord,Show)


-- | Vertex element type, used to identify the base types of the vertex contents
data VertexElementType
    = VET_FLOAT1
    | VET_FLOAT2
    | VET_FLOAT3
    | VET_FLOAT4
    | VET_SHORT1
    | VET_SHORT2
    | VET_SHORT3
    | VET_SHORT4
    | VET_UBYTE4
    | VET_COLOUR_ARGB -- ^ D3D style compact colour
    | VET_COLOUR_ABGR -- ^ GL style compact colour
    deriving (Eq,Ord,Show)

data VertexElement
    = VertexElement
    { veSource      :: Int                      -- ^ The source vertex buffer, as bound to an index using VertexBufferBinding
    , veOffset      :: Int                      -- ^ The offset in the buffer that this element starts at
    , veType        :: VertexElementType        -- ^ The type of element
    , veSemantic    :: VertexElementSemantic    -- ^ The meaning of the element
    , veIndex       :: Int                      -- ^ Index of the item, only applicable for some elements like texture coords
    }
    deriving (Eq,Ord,Show)

-- | Utility method for helping to calculate offsets
getTypeSize :: VertexElementType -> Int
getTypeSize etype = case etype of
    VET_COLOUR_ABGR   ->     sizeOf (undefined::Word32) -- sizeof(RGBA);
    VET_COLOUR_ARGB   ->     sizeOf (undefined::Word32) -- sizeof(RGBA);
    VET_FLOAT1        ->     sizeOf (undefined::CFloat) -- sizeof(float);
    VET_FLOAT2        -> 2 * sizeOf (undefined::CFloat) -- sizeof(float)*2;
    VET_FLOAT3        -> 3 * sizeOf (undefined::CFloat) -- sizeof(float)*3;
    VET_FLOAT4        -> 4 * sizeOf (undefined::CFloat) -- sizeof(float)*4;
    VET_SHORT1        ->     sizeOf (undefined::CShort) -- sizeof(short);
    VET_SHORT2        -> 2 * sizeOf (undefined::CShort) -- sizeof(short)*2;
    VET_SHORT3        -> 3 * sizeOf (undefined::CShort) -- sizeof(short)*3;
    VET_SHORT4        -> 4 * sizeOf (undefined::CShort) -- sizeof(short)*4;
    VET_UBYTE4        -> 4 * sizeOf (undefined::CUChar) -- sizeof(unsigned char)*4;

-- | Utility method which returns the count of values in a given type
getTypeCount :: VertexElementType -> Int
getTypeCount etype = case etype of
    VET_COLOUR_ABGR   -> 4
    VET_COLOUR_ARGB   -> 4
    VET_FLOAT1        -> 1
    VET_FLOAT2        -> 2
    VET_FLOAT3        -> 3
    VET_FLOAT4        -> 4
    VET_SHORT1        -> 1
    VET_SHORT2        -> 2
    VET_SHORT3        -> 3
    VET_SHORT4        -> 4
    VET_UBYTE4        -> 4

-- | Simple converter function which will turn a single-value type into a multi-value type based on a parameter.
multiplyTypeCount :: VertexElementType -> Int -> VertexElementType
multiplyTypeCount baseType count = case baseType of
    VET_FLOAT1 -> case count of
      1 -> VET_FLOAT1
      2 -> VET_FLOAT2
      3 -> VET_FLOAT3
      4 -> VET_FLOAT4
      _ -> error $ "multiplyTypeCount: Invalid VET_FLOAT type " ++ show count
    VET_SHORT1 -> case count of
      1 -> VET_SHORT1
      2 -> VET_SHORT2
      3 -> VET_SHORT3
      4 -> VET_SHORT4
      _ -> error $ "multiplyTypeCount: Invalid VET_FLOAT type " ++ show count
    _ -> error $ "multiplyTypeCount: Invalid base type " ++ show baseType

-- | Simple converter function which will convert a type into its
-- single-value equivalent to make switches on type easier.
getBaseType :: VertexElementType -> VertexElementType
getBaseType multiType = case multiType of
    VET_FLOAT1 -> VET_FLOAT1
    VET_FLOAT2 -> VET_FLOAT1
    VET_FLOAT3 -> VET_FLOAT1
    VET_FLOAT4 -> VET_FLOAT1
    VET_SHORT1 -> VET_SHORT1
    VET_SHORT2 -> VET_SHORT1
    VET_SHORT3 -> VET_SHORT1
    VET_SHORT4 -> VET_SHORT1
    mt         -> mt

data VertexDeclaration
    = VertexDeclaration
    { vdElementList :: [VertexElement] -- ^ The list of vertex elements that makes up this declaration
    }
    deriving (Eq,Ord,Show)

data HardwareVertexBuffer vb => VertexBufferBinding vb
    = VertexBufferBinding
    { vbbBindingMap :: IntMap vb
    }
    deriving (Eq,Ord)