I see the type is:

freeze :: (PrimMonad m, Vector v a) => Mutable v (PrimState m) a -> m (v a)


So there is a Vector constrant that MVector will not have. Does the Mutable type family get around this somehow?


There doesn't seem to be a freeze function specifically for Data.Vector.Unboxed.Mutable.MVector listed at: https://hackage.haskell.org/package/vector-0.12.0.1/docs/Data-Vector-Unboxed-Mutable.html

Thanks,

Cody


On Sat, Aug 5, 2017 at 9:56 PM, Amos Robinson <amos.robinson@gmail.com> wrote:
I think you want "Data.Vector.Generic.freeze", or unsafeFreeze if you are sure you won't modify the mutable vector after making it immutable.
https://hackage.haskell.org/package/vector-0.12.0.1/docs/Data-Vector-Generic.html#v:freeze

On Sun, 6 Aug 2017 at 12:46 Cody Goodman <codygman.consulting@gmail.com> wrote:
I want to do this so I can use the Data.Vector.Unboxed.Generic functions requiring the Vector constraint, namely the maxIndex function. Implementing maxIndex for Data.Vector.Unboxed.Mutable.MVector would be useful as well, but I'm even more confused at how to do that or where to begin.

Here is some stubbed out code demonstrating this.

{-# Language ScopedTypeVariables #-}
module Main where

import Control.Monad.Primitive
import qualified Data.Vector.Unboxed
import qualified Data.Vector.Generic as VG
import qualified Data.Vector.Unboxed.Mutable as VM
import qualified Data.Vector.Unboxed as V

toImmutable :: VM.MVector RealWorld Int -> V.Vector Int
toImmutable = undefined

main :: IO ()
main = do
  v :: VM.MVector RealWorld Int <- VM.new 1
  VM.write v 0 (3 :: Int)
  x <- VM.read v 0
  -- y <- VG.head . toImmutable $ v
  -- print y
  print $ VM.length v

{-
Thanks,


Cody
-}
_______________________________________________
Haskell-Cafe mailing list
To (un)subscribe, modify options or view archives go to:
http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
Only members subscribed via the mailman list are allowed to post.