[Haskell-cafe] Convert Data.Vector.Unboxed.Mutable.MVector to Data.Vector.Unboxed.Vector

Cody Goodman codygman.consulting at gmail.com
Sun Aug 6 02:45:04 UTC 2017


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
-}
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20170805/0a7001d5/attachment.html>


More information about the Haskell-Cafe mailing list