Convert Data.Vector.Unboxed.Mutable.MVector to Data.Vector.Unboxed.Vector

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 -}

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...
On Sun, 6 Aug 2017 at 12:46 Cody Goodman
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.

I see the type is:
freeze :: (PrimMonad
https://hackage.haskell.org/package/primitive-0.6.2.0/docs/Control-Monad-Pri...
m, Vector
https://hackage.haskell.org/package/vector-0.12.0.1/docs/Data-Vector-Generic...
v a) => Mutable
https://hackage.haskell.org/package/vector-0.12.0.1/docs/Data-Vector-Generic...
v (PrimState
https://hackage.haskell.org/package/primitive-0.6.2.0/docs/Control-Monad-Pri...
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...
Thanks,
Cody
On Sat, Aug 5, 2017 at 9:56 PM, Amos Robinson
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
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.

Mutable is the type family from Vector to MVector. So the result type will
be an instance of Vector, but the input MVector doesn't need to be.
It's a little confusing that freeze is in Data.Unboxed.Vector, not
.Mutable:
https://hackage.haskell.org/package/vector-0.12.0.1/docs/Data-Vector-Unboxed...
On Sun, 6 Aug 2017 at 12:59 Cody Goodman
I see the type is:
freeze :: (PrimMonad https://hackage.haskell.org/package/primitive-0.6.2.0/docs/Control-Monad-Pri... m, Vector https://hackage.haskell.org/package/vector-0.12.0.1/docs/Data-Vector-Generic... v a) => Mutable https://hackage.haskell.org/package/vector-0.12.0.1/docs/Data-Vector-Generic... v (PrimState https://hackage.haskell.org/package/primitive-0.6.2.0/docs/Control-Monad-Pri... 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...
Thanks,
Cody
On Sat, Aug 5, 2017 at 9:56 PM, Amos Robinson
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...
On Sun, 6 Aug 2017 at 12:46 Cody Goodman
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.

I'm not back at a computer yet, but so I and others reading these archives
in the future know: Does that mean that freeze from
Data.Vector.Generic.freeze should work for me then?
On Sat, Aug 5, 2017 at 10:05 PM, Amos Robinson
Mutable is the type family from Vector to MVector. So the result type will be an instance of Vector, but the input MVector doesn't need to be. It's a little confusing that freeze is in Data.Unboxed.Vector, not .Mutable: https://hackage.haskell.org/package/vector-0. 12.0.1/docs/Data-Vector-Unboxed.html#v:freeze
On Sun, 6 Aug 2017 at 12:59 Cody Goodman
wrote: I see the type is:
freeze :: (PrimMonad https://hackage.haskell.org/package/primitive-0.6.2.0/docs/Control-Monad-Pri... m, Vector https://hackage.haskell.org/package/vector-0.12.0.1/docs/Data-Vector-Generic... v a) => Mutable https://hackage.haskell.org/package/vector-0.12.0.1/docs/Data-Vector-Generic... v (PrimState https://hackage.haskell.org/package/primitive-0.6.2.0/docs/Control-Monad-Pri... 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
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
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.

Yes, I believe Data.Vector.Generic.freeze will work. But I would use the
one from Data.Vector.Unboxed unless you really need the generic version.
Sometimes the extra constraints in the generic version can be a bit
cumbersome, requiring extra type annotations where the specific versions
don't.
On Sun, 6 Aug 2017 at 13:22 Cody Goodman
I'm not back at a computer yet, but so I and others reading these archives in the future know: Does that mean that freeze from Data.Vector.Generic.freeze should work for me then?
On Sat, Aug 5, 2017 at 10:05 PM, Amos Robinson
wrote: Mutable is the type family from Vector to MVector. So the result type will be an instance of Vector, but the input MVector doesn't need to be. It's a little confusing that freeze is in Data.Unboxed.Vector, not .Mutable: https://hackage.haskell.org/package/vector-0.12.0.1/docs/Data-Vector-Unboxed...
On Sun, 6 Aug 2017 at 12:59 Cody Goodman
wrote: I see the type is:
freeze :: (PrimMonad https://hackage.haskell.org/package/primitive-0.6.2.0/docs/Control-Monad-Pri... m, Vector https://hackage.haskell.org/package/vector-0.12.0.1/docs/Data-Vector-Generic... v a) => Mutable https://hackage.haskell.org/package/vector-0.12.0.1/docs/Data-Vector-Generic... v (PrimState https://hackage.haskell.org/package/primitive-0.6.2.0/docs/Control-Monad-Pri... 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...
Thanks,
Cody
On Sat, Aug 5, 2017 at 9:56 PM, Amos Robinson
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...
On Sun, 6 Aug 2017 at 12:46 Cody Goodman
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.

Thanks! I'll try it out in a bit.
On Aug 5, 2017 10:32 PM, "Amos Robinson"
Yes, I believe Data.Vector.Generic.freeze will work. But I would use the one from Data.Vector.Unboxed unless you really need the generic version. Sometimes the extra constraints in the generic version can be a bit cumbersome, requiring extra type annotations where the specific versions don't.
On Sun, 6 Aug 2017 at 13:22 Cody Goodman
wrote: I'm not back at a computer yet, but so I and others reading these archives in the future know: Does that mean that freeze from Data.Vector.Generic.freeze should work for me then?
On Sat, Aug 5, 2017 at 10:05 PM, Amos Robinson
wrote: Mutable is the type family from Vector to MVector. So the result type will be an instance of Vector, but the input MVector doesn't need to be. It's a little confusing that freeze is in Data.Unboxed.Vector, not .Mutable: https://hackage.haskell.org/package/vector-0. 12.0.1/docs/Data-Vector-Unboxed.html#v:freeze
On Sun, 6 Aug 2017 at 12:59 Cody Goodman
wrote: I see the type is:
freeze :: (PrimMonad https://hackage.haskell.org/package/primitive-0.6.2.0/docs/Control-Monad-Pri... m, Vector https://hackage.haskell.org/package/vector-0.12.0.1/docs/Data-Vector-Generic... v a) => Mutable https://hackage.haskell.org/package/vector-0.12.0.1/docs/Data-Vector-Generic... v (PrimState https://hackage.haskell.org/package/primitive-0.6.2.0/docs/Control-Monad-Pri... 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
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.

Indeed, it worked (thanks again!):
{-# 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
main :: IO ()
main = do
v :: VM.MVector RealWorld Int <- VM.new 1
VM.write v 0 (3 :: Int)
x <- VM.read v 0
v' <- V.freeze v
print $ VG.head v'
print $ VM.length v
On Sat, Aug 5, 2017 at 10:54 PM, Cody Goodman wrote: Thanks! I'll try it out in a bit. On Aug 5, 2017 10:32 PM, "Amos Robinson" Yes, I believe Data.Vector.Generic.freeze will work. But I would use the
one from Data.Vector.Unboxed unless you really need the generic version.
Sometimes the extra constraints in the generic version can be a bit
cumbersome, requiring extra type annotations where the specific versions
don't. On Sun, 6 Aug 2017 at 13:22 Cody Goodman I'm not back at a computer yet, but so I and others reading these
archives in the future know: Does that mean that freeze from
Data.Vector.Generic.freeze should work for me then? On Sat, Aug 5, 2017 at 10:05 PM, Amos Robinson Mutable is the type family from Vector to MVector. So the result type
will be an instance of Vector, but the input MVector doesn't need to be.
It's a little confusing that freeze is in Data.Unboxed.Vector, not
.Mutable: https://hackage.haskell.org/package/vector-0.12.0.
1/docs/Data-Vector-Unboxed.html#v:freeze On Sun, 6 Aug 2017 at 12:59 Cody Goodman I see the type is: freeze :: (PrimMonad
https://hackage.haskell.org/package/primitive-0.6.2.0/docs/Control-Monad-Pri...
m, Vector
https://hackage.haskell.org/package/vector-0.12.0.1/docs/Data-Vector-Generic...
v a) => Mutable
https://hackage.haskell.org/package/vector-0.12.0.1/docs/Data-Vector-Generic...
v (PrimState
https://hackage.haskell.org/package/primitive-0.6.2.0/docs/Control-Monad-Pri...
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/Dat
a-Vector-Unboxed-Mutable.html Thanks, Cody On Sat, Aug 5, 2017 at 9:56 PM, Amos Robinson 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/Dat
a-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.
participants (2)
-
Amos Robinson
-
Cody Goodman