I'm trying to store a simple vector of three-dimensional points in space. To do this, I'm newtype
-ing a custom Point
and manually implement the Data.Vector.Unboxed.Vector
and Data.Vector.Unboxed.Mutable
instances for it.
However, for some reason, any attempt to use such a vector ends up in an infinite loop in basicUnsafeNew
. The following program will hang:
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeFamilies #-}
import qualified Data.Vector.Generic as G
import qualified Data.Vector.Generic.Mutable as GM
import qualified Data.Vector.Unboxed as U
import qualified Data.Vector.Unboxed.Mutable as UM
import Debug.Trace (trace)
import Linear (V3 (..))
-- ct => "coordinate type"
newtype Point ct = Point
{ coordinates :: ct
}
deriving (Show, Eq)
makePoint :: a -> a -> a -> Point (Linear.V3 a)
makePoint x y z = Point (V3 x y z)
newtype instance UM.MVector s (Point ct) = MV_Point (UM.MVector s (Point ct))
newtype instance U.Vector (Point ct) = V_Point (U.Vector (Point ct))
instance (U.Unbox ct) => GM.MVector UM.MVector (Point ct) where
{-# INLINE basicUnsafeNew #-}
basicLength (MV_Point mv) = error "basicLength"
basicUnsafeSlice i l (MV_Point mv) = error "basicUnsafeSlice"
basicOverlaps (MV_Point mv) (MV_Point mv') = error "basicOverlaps"
basicUnsafeNew l = trace "unsafe new" (MV_Point <$> GM.basicUnsafeNew l) -- <-- hangs!
basicInitialize (MV_Point mv) = error "basicInitialize"
basicUnsafeRead (MV_Point mv) i = error "basicUnsafeRead"
basicUnsafeWrite (MV_Point mv) i x = error "basicUnsafeWrite"
instance (U.Unbox ct) => G.Vector U.Vector (Point ct) where
basicUnsafeFreeze (MV_Point mv) = error "basicUnsafeFreeze"
basicUnsafeThaw (V_Point v) = error "basicUnsafeThaw"
basicLength (V_Point v) = error "basicLength"
basicUnsafeSlice i l (V_Point v) = error "basicUnsafeSlice"
basicUnsafeIndexM (V_Point v) i = error "basicUnsafeIndexM"
instance (U.Unbox ct) => U.Unbox (Point ct)
main :: IO ()
main = print $ U.length $ U.singleton $ makePoint (0.0 :: Double) 1.0 2.0
The code requires the vector
and linear
packages.
I pushed this code as MWE with stack
support here for convenience: https://github.com/jtprobst/vectortest
Simply call stack run
and observe the endless traces of "unsafe new".
I'm running with stack --version
Version 2.5.1, Git revision d6ab861544918185236cf826cb2028abb266d6d5 x86_64 hpack-0.33.0
Note that all methods except basicUnsafeNew
on the vector default to error
instead of doing anything useful. This is just to exclude the possibility of them interfering in any way. It also hangs if I use the typical default implementations for these methods (for example as described in this answer on SO, point number 2).
Any hints as to what I'm doing wrong are highly appreciated.
Well, just unroll the newtype definition:
newtype instance UM.MVector s (Point ct)
= MV_Point (UM.MVector s (Point ct))
= MV_Point (MV_Point (UM.MVector s (Point ct)))
= MV_Point (MV_Point (MV_Point (UM.MVector s (Point ct))))
= MV_Point (MV_Point (MV_Point (MV_Point (UM.MVector s (Point ct)))))
= MV_Point (MV_Point (MV_Point (MV_Point (MV_Point (UM.MVector s (Point ct))))))
= MV_Point (MV_Point (MV_Point (MV_Point (MV_Point (MV_Point (UM.MVector s (Point ct)))))))
= ...
This clearly isn't going anywhere.
You need to define it in terms of something that is already defined, not in terms of the type you're just right now defining yourself, to avoid the circular reference. The obvious candidate would be
newtype instance UM.MVector s (Point ct) = MV_Point (UM.MVector s ct)