Skip to content
Open
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
4 changes: 3 additions & 1 deletion vector/changelog.md
Original file line number Diff line number Diff line change
Expand Up @@ -2,7 +2,9 @@

* [#522](https://github.com/haskell/vector/pull/522) API using Applicatives
added: `traverse` & friends.
* [#518](https://github.com/haskell/vector/pull/518) `UnboxViaStorable` added.
* `unstreamPrimM` and `unsafeUnstreamPrimM` are added to `Data.Vector.Generic`
for converting monadic streams to vectors.
* [#518](https://github.com/haskell/vector/pull/518) `UnboxViaStorable` added.
Vector constructors are reexported for `DoNotUnbox*`.
* [#531](https://github.com/haskell/vector/pull/531) `iconcatMap` added.

Expand Down
40 changes: 34 additions & 6 deletions vector/src/Data/Vector/Generic.hs
Original file line number Diff line number Diff line change
Expand Up @@ -164,7 +164,7 @@ module Data.Vector.Generic (
-- * Fusion support

-- ** Conversion to/from Bundles
stream, unstream, unstreamM, streamR, unstreamR,
stream, unstream, unstreamM, unstreamPrimM, unsafeUnstreamPrimM, streamR, unstreamR,

-- ** Recycling support
new, clone,
Expand Down Expand Up @@ -2621,23 +2621,51 @@ unstreamM s = do
xs <- MBundle.toList s
return $ unstream $ Bundle.unsafeFromList (MBundle.size s) xs


-- | Load a monadic stream bundle into a newly allocated vector. It
-- makes writes to a single buffer and copies it when finished. Note
-- for monads that encode nondeterminism result may be different
-- from `unstreamM`.
--
Copy link
Contributor

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Note for monads that encode nondeterminism result may be different from unstreamM.

Is it possible? Can the results be different? I mean, I believed that the results are always the same; I thought I just can't prove it mathematically.

Copy link
Contributor Author

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

I'm not sure myself. But they are different operationally: unstreamM uses immutable data structures and unstreamPrimM and in principle can observe mutations. ListT mutates elements in particular order so results are always same.

Perhaps some lawless variant of OmegaT built on top https://hackage-content.haskell.org/package/control-monad-omega-0.3.3/docs/Control-Monad-Omega.html will work. Or some tricks with ContT

Copy link
Contributor

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

I don't this is the case at all and IMHO unstreamPrimM is absolutely safe with unsafeFreeze instead of freeze at the end.
If this operation is unsafe for some transformer that would mean its instance for PrimMonad is incorrect.

-- @since NEXT_VERSION
unstreamPrimM :: (PrimMonad m, Vector v a) => MBundle m u a -> m (v a)
{-# INLINE_FUSED unstreamPrimM #-}
unstreamPrimM s = M.munstream s >>= unsafeFreeze
unstreamPrimM s = M.munstream s >>= freeze

-- | Load a monadic stream bundle into a newly allocated vector. This
-- function create mutable buffer, writes to it and then
-- 'unsafeFreeze's it.
--
-- This function is unsafe. For monads that encode nondeterminism
-- (e.g. @ListT@) it allows to break referential transparency. More
-- precisely if 'unsafeFreeze' is called more than once we will
-- perform writes into buffer which is considered immutable.
Comment on lines +2639 to +2642
Copy link
Contributor

@lehins lehins Sep 11, 2025

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Do you have an example of using ListT where it results in this craziness?
Honestly, even if there is one, ListT has been deprecated for a long time.
I believe that if there is a transformer that violates properties of this function, then it does not deserve an instance for PrimMonad, i.e. it is unlawful

Copy link
Contributor

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

We're talking about ListT done right; see
#416 (comment)

This ListT satisfies:

  • ListT m satisfies monad laws for every monad m
  • ListT safisfies MonadTrans laws
  • ListT m where PrimMonad m satisfies stToPrim v >>= stToPrim . f == stToPrim (v >>= f) and stToPrim (pure a) == pure a

What else would you require?

Copy link
Contributor

@lehins lehins Sep 11, 2025

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

The whole reason why PrimMonad exists is to allow mutation of arrays and other mutable structures. Therefore I would expect any monad that has an instance would also satisfy: new[Array|ByteArray..] n >>= unsafeFreeze == new[Array|ByteArray..] n >>= freeze

Copy link
Contributor

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

That is obviously satisfied by ListT m, right?

newArray n >>= unsafeFreeze
== stToPrim (newArray n) >>= stToPrim . unsafeFreeze
== stToPrim (newArray n >>= unsafeFreeze)
== stToPrim (newArray n >>= freeze)
== stToPrim (newArray n) >>= stToPrim . freeze
== newArray n >>= freeze

Well, I'm sure you're meaning something stronger, but I don't know how to formalize your idea.

Copy link
Contributor

@lehins lehins Sep 11, 2025

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

If we can't rely on a function like this to be safe:

generateArray :: PrimMonad m => Int -> (Int -> m a) -> m (Array a)
generateArray n 
  | n <= 0 = pure emptyArray
  | otherwise = do
    marr <- newArray n undefined
    let go i = when (i < n) $ f i >>= writeArray marr i >> go (i + 1)
    go 0
    unsafeFreezeArray marr

Then I am more than sure there is a lot of code that is unsafe out there!

So, if you think there is an issue here, then we need to tighten requirements on PrimMonad and what sort monads can have instances for that class.

Copy link
Contributor

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

I think we should raise a ticket on the primitive package and cross reference this conversation and get its maintainers involved in the discussion. Any volunteers?

but I'd love both unstreamPrimM and unstreamPrimMProtective.

If this issue is solved at the PrimMonad level, then there is no point in having an alternative version, because it would not even be clear what this "protective" variant would mean

Copy link
Contributor Author

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

I agree. This is not only vector's problem. I'm planning to do that tomorrow. Hopefully it would be possible to create reasonable design.

Also I wonder whether it's possible to violate referential transparency using ContT monad. It allows basically anything but I couldn't construct such example. I didn't try very hard though

Copy link
Contributor Author

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

I wonder whether it's possible to violate referential transparency using ContT monad

Answering my own question. Of course it is. Everything is possible with ContT. One just need to encode some backtracking:

import Control.DeepSeq
import Control.Monad.Trans.Cont
import Control.Monad.IO.Class
import Data.Vector.Unboxed qualified as VU
import Data.Vector.Unboxed.Mutable qualified as VUM

liftList :: Monad m => [a] -> ContT [r] m a
liftList xs = ContT $ \cont ->
  concat <$> traverse cont xs

continuedHorror :: IO [([Int], VU.Vector Int)]
continuedHorror = flip runContT (pure . pure) $ do
  mv <- VUM.generateM 2 $ \i -> liftList [i, i+5]
  v  <- VU.unsafeFreeze mv
  let !i = force $ VU.toList v
  pure (i,v)

It returns:

([0,1],[5,6])
([0,6],[5,6])
([5,1],[5,6])
([5,6],[5,6])

and of course replacing unsafeFreeze with safe variant fixes bug.

Copy link
Contributor Author

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

@lehins I created haskell/primitive#431

Since ContT is instance of PrimMonad already and allows to break referential transparency solution will probably involve subclass of PrimMonad where such use of unsafeFreeze is safe. Besides simply having way to lift ST into monad is useful too event if it can do backtracking.

Copy link
Contributor

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

@Shimuuar Very nice minimal reproducer for the problem 💪

--
-- In particular it's certainly unsafe to use this function when
-- type of monad is polymorphic but it's safe to use for monads such
-- as @IO@, @ST@, @Reader@, @Writer@, @State@.
--
-- @since NEXT_VERSION
unsafeUnstreamPrimM :: (PrimMonad m, Vector v a) => MBundle m u a -> m (v a)
{-# INLINE_FUSED unsafeUnstreamPrimM #-}
unsafeUnstreamPrimM s = M.munstream s >>= unsafeFreeze
Copy link
Contributor

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

As mentioned in my other comment I don't think there is anything unsafe about this function. I would love to be proven wrong with an example of using some known PrimMonad instance that violates the safety of this function.


-- FIXME: the next two functions are only necessary for the specialisations
unstreamPrimM_IO :: Vector v a => MBundle IO u a -> IO (v a)
{-# INLINE unstreamPrimM_IO #-}
unstreamPrimM_IO = unstreamPrimM
unstreamPrimM_IO = unsafeUnstreamPrimM

unstreamPrimM_ST :: Vector v a => MBundle (ST s) u a -> ST s (v a)
{-# INLINE unstreamPrimM_ST #-}
unstreamPrimM_ST = unstreamPrimM
unstreamPrimM_ST = unsafeUnstreamPrimM

{-# RULES

"unstreamM[IO]" unstreamM = unstreamPrimM_IO
"unstreamM[ST]" unstreamM = unstreamPrimM_ST #-}
"unstreamM[IO]" unstreamM = unstreamPrimM_IO
"unstreamM[ST]" unstreamM = unstreamPrimM_ST
"unstreamPrimM[IO]" unstreamPrimM = unstreamPrimM_IO
"unstreamPrimM[ST]" unstreamPrimM = unstreamPrimM_ST
#-}



Expand Down
Loading