{-# LANGUAGE MultiParamTypeClasses #-} module SDL.Data.Texture ( Renderable(..) , Texture(..) ) where import qualified SDL import Control.Monad (void) import Linear.V2 (V2(..)) import Linear.Affine (Point(..)) import Linear.V3 (V3) import Foreign.C (CDouble(..)) import Data.StateVar (StateVar) import Data.Word (Word8) -- | This class modells that something can be rendered to another -- thing. class Renderable rend tex where copyEx :: rend -- ^ rendering context -> tex -- ^ texture -> Maybe (SDL.Rectangle Int) -- ^ source rectangle -> Maybe (SDL.Rectangle Int) -- ^ destination rectangle -> Double -- ^ rotation -> Maybe (Point V2 Int) -- ^ rotation center -> V2 Bool -- ^ flipping -> IO () instance Renderable SDL.Renderer SDL.Texture where copyEx rend tex sourceRect destRect rot center flipping = void $ SDL.copyEx rend tex (fmap fromIntegral <$> sourceRect) (fmap fromIntegral <$> destRect) (CDouble rot) (fmap fromIntegral <$> center) flipping class Texture tex where textureAlphaMod :: tex -> StateVar Word8 textureColorMod :: tex -> StateVar (V3 Word8) textureBlendMode :: tex -> StateVar SDL.BlendMode instance Texture SDL.Texture where textureAlphaMod = SDL.textureAlphaMod textureColorMod = SDL.textureColorMod textureBlendMode = SDL.textureBlendMode