Skip to content

Commit 776e44d

Browse files
jshipdpwiz
authored andcommitted
Add unboxed vector instances for Rectangle
1 parent 2ef1b08 commit 776e44d

File tree

1 file changed

+39
-0
lines changed

1 file changed

+39
-0
lines changed

src/SDL/Video/Renderer.hs

Lines changed: 39 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -7,6 +7,7 @@
77
{-# LANGUAGE MultiParamTypeClasses #-}
88
{-# LANGUAGE OverloadedStrings #-}
99
{-# LANGUAGE PatternSynonyms #-}
10+
{-# LANGUAGE TypeFamilies #-}
1011

1112
-- | "SDL.Video.Renderer" provides a high-level interface to SDL's accelerated 2D rendering library.
1213

@@ -159,8 +160,11 @@ import SDL.Internal.Types
159160
import qualified Data.ByteString as BS
160161
import qualified Data.ByteString.Internal as BSI
161162
import qualified Data.Text.Encoding as Text
163+
import qualified Data.Vector.Generic.Base as GV
164+
import qualified Data.Vector.Generic.Mutable.Base as GMV
162165
import qualified Data.Vector.Storable as SV
163166
import qualified Data.Vector.Storable.Mutable as MSV
167+
import qualified Data.Vector.Unboxed.Base as UV
164168
import qualified SDL.Raw as Raw
165169

166170
#if !MIN_VERSION_base(4,8,0)
@@ -603,6 +607,41 @@ instance Storable a => Storable (Rectangle a) where
603607
poke (castPtr ptr) o
604608
poke (castPtr (ptr `plusPtr` sizeOf o)) s
605609

610+
newtype instance MVector s (Rectangle a) = MV_Rectangle (MVector s (Point V2 a, V2 a))
611+
newtype instance Vector (Rectangle a) = V_Rectangle (Vector (Point V2 a, V2 a))
612+
613+
instance UV.Unbox a => GMV.MVector MVector (Rectangle a) where
614+
{-# INLINE basicLength #-}
615+
{-# INLINE basicUnsafeSlice #-}
616+
{-# INLINE basicOverlaps #-}
617+
{-# INLINE basicUnsafeNew #-}
618+
{-# INLINE basicUnsafeRead #-}
619+
{-# INLINE basicUnsafeWrite #-}
620+
basicLength (MV_Rectangle v) = GMV.basicLength v
621+
basicUnsafeSlice m n (MV_Rectangle v) = MV_Rectangle (GMV.basicUnsafeSlice m n v)
622+
basicOverlaps (MV_Rectangle v) (MV_Rectangle u) = GMV.basicOverlaps v u
623+
basicUnsafeNew n = MV_Rectangle <$> GMV.basicUnsafeNew n
624+
basicUnsafeRead (MV_Rectangle v) i = uncurry Rectangle <$> GMV.basicUnsafeRead v i
625+
basicUnsafeWrite (MV_Rectangle v) i (Rectangle p e) = GMV.basicUnsafeWrite v i (p, e)
626+
#if MIN_VERSION_vector(0,11,0)
627+
{-# INLINE basicInitialize #-}
628+
basicInitialize (MV_Rectangle v) = GMV.basicInitialize v
629+
#endif
630+
631+
instance UV.Unbox a => GV.Vector Vector (Rectangle a) where
632+
{-# INLINE basicUnsafeFreeze #-}
633+
{-# INLINE basicUnsafeThaw #-}
634+
{-# INLINE basicLength #-}
635+
{-# INLINE basicUnsafeSlice #-}
636+
{-# INLINE basicUnsafeIndexM #-}
637+
basicUnsafeFreeze (MV_Rectangle v) = V_Rectangle <$> GV.basicUnsafeFreeze v
638+
basicUnsafeThaw (V_Rectangle v) = MV_Rectangle <$> GV.basicUnsafeThaw v
639+
basicLength (V_Rectangle v) = GV.basicLength v
640+
basicUnsafeSlice m n (V_Rectangle v) = V_Rectangle (GV.basicUnsafeSlice m n v)
641+
basicUnsafeIndexM (V_Rectangle v) i = uncurry Rectangle <$> GV.basicUnsafeIndexM v i
642+
643+
instance UV.Unbox a => UV.Unbox (Rectangle a)
644+
606645
data Surface = Surface (Ptr Raw.Surface) (Maybe (MSV.IOVector Word8))
607646
deriving (Typeable)
608647

0 commit comments

Comments
 (0)