module Data.Fixed.Binary.Unboxed () where
import Control.Monad
import Data.Function
import Unsafe.Coerce
import qualified Data.Vector.Generic as VG
import qualified Data.Vector.Generic.Mutable as VGM
import qualified Data.Vector.Unboxed as VU
import Data.Fixed.Binary
fixed :: a -> Fixed r a
fixed = unsafeCoerce
unFixed :: Fixed r a -> a
unFixed = unsafeCoerce
newtype instance VU.MVector s (Fixed r a) = MVFixed { unMVFixed :: VU.MVector s a }
newtype instance VU.Vector (Fixed r a) = VFixed { unVFixed :: VU.Vector a }
instance VGM.MVector VU.MVector a => VGM.MVector VU.MVector (Fixed r a) where
basicLength = VGM.basicLength . unMVFixed
basicUnsafeSlice i n = MVFixed . VGM.basicUnsafeSlice i n . unMVFixed
basicOverlaps = VGM.basicOverlaps `on` unMVFixed
basicUnsafeNew = liftM MVFixed . VGM.basicUnsafeNew
basicUnsafeReplicate n = liftM MVFixed . VGM.basicUnsafeReplicate n . unFixed
basicUnsafeRead (MVFixed mv) = liftM fixed . VGM.basicUnsafeRead mv
basicUnsafeWrite (MVFixed mv) i = VGM.basicUnsafeWrite mv i . unFixed
basicClear = VGM.basicClear . unMVFixed
basicSet (MVFixed mv) = VGM.basicSet mv . unFixed
basicUnsafeCopy = VGM.basicUnsafeCopy `on` unMVFixed
basicUnsafeGrow (MVFixed mv) = liftM MVFixed . VGM.basicUnsafeGrow mv
instance VG.Vector VU.Vector a => VG.Vector VU.Vector (Fixed r a) where
basicUnsafeFreeze = liftM VFixed . VG.basicUnsafeFreeze . unMVFixed
basicUnsafeThaw = liftM MVFixed . VG.basicUnsafeThaw . unVFixed
basicLength = VG.basicLength . unVFixed
basicUnsafeSlice i n = VFixed . VG.basicUnsafeSlice i n . unVFixed
basicUnsafeIndexM (VFixed v) = liftM fixed . VG.basicUnsafeIndexM v
basicUnsafeCopy (MVFixed mv) = VG.basicUnsafeCopy mv . unVFixed
elemseq (VFixed v) = VG.elemseq v . unFixed
instance VU.Unbox a => VU.Unbox (Fixed r a)