How to ensure optimization for large immutable vectors to be shared w.r.t. Referential Transparency
Viktor Dukhovni
ietf-dane at dukhovni.org
Tue Apr 6 13:51:30 UTC 2021
On Tue, Apr 06, 2021 at 07:12:51PM +0800, YueCompl via ghc-devs wrote:
> λ> import Control.Monad.ST
> λ> import qualified Data.Vector.Storable as VS
> λ>
> λ> :{
> λ|
> λ| newtype SomeVector = SomeVector (VS.Vector Int)
> λ|
> λ| isSameVector :: SomeVector -> SomeVector -> Bool
> λ| isSameVector (SomeVector !x) (SomeVector !y) = runST $ do
> λ| mx@(VS.MVector !x'offset !x'fp) <- VS.unsafeThaw x
> λ| my@(VS.MVector !y'offset !y'fp) <- VS.unsafeThaw y
> λ| _ <- VS.unsafeFreeze mx
> λ| _ <- VS.unsafeFreeze my
> λ| return $ x'offset == y'offset && x'fp == y'fp
> λ|
> λ| :}
> λ>
> λ> let !v = VS.fromList [3,2,5] in isSameVector (SomeVector v) (SomeVector v)
> False
> λ>
> λ> let !v = SomeVector (VS.fromList [3,2,5]) in isSameVector v v
> True
In GHCi, but not in compiled programs, by default the
`NoMonomorphismRestriction` extension is enabled. If I compile your
code with that restriction, I can reproduce your results (the values are
not shared).
If I either skip the extension, or add an explicit type annotation to
for the vector, then the values are shared.
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE NoMonomorphismRestriction #-}
import Control.Monad.ST
import qualified Data.Vector.Storable as VS
newtype SomeVector = SomeVector (VS.Vector Int)
isSameVector :: SomeVector -> SomeVector -> Bool
isSameVector (SomeVector !x) (SomeVector !y) = runST $ do
mx@(VS.MVector !x'offset !x'fp) <- VS.unsafeThaw x
my@(VS.MVector !y'offset !y'fp) <- VS.unsafeThaw y
_ <- VS.unsafeFreeze mx
_ <- VS.unsafeFreeze my
return $ x'offset == y'offset && x'fp == y'fp
main :: IO ()
main =
let !v = VS.fromList [0..1023] -- :: VS.Vector Int
in print $ isSameVector (SomeVector v) (SomeVector v)
Since newtypes are always strict in their argument, I don't think the
BangPattern does what you'd like it to do, it just makes "main" strict
in v. As defined with `NoMonomorphismRestriction` v is a polymorphic
function, and I guess it is specialised at the call site.
--
Viktor.
More information about the ghc-devs
mailing list