
On Tue, Apr 06, 2021 at 09:51:30AM -0400, Viktor Dukhovni wrote:
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.
The below variant makes the issue even more clear for me: {-# 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 -- makev :: VS.Vector Int makev = VS.fromList [0..1023] main :: IO () main = let v = makev in print $ v `seq` isSameVector (SomeVector v) (SomeVector v) With `NoMonomorphismRestriction` it fails to compile: /tmp/vec.hs:22:17: error: • Ambiguous type variable ‘a0’ arising from a use of ‘v’ prevents the constraint ‘(VS.Storable a0)’ from being solved. Probable fix: use a type annotation to specify what ‘a0’ should be. These potential instances exist: instance VS.Storable () -- Defined in ‘Foreign.Storable’ instance VS.Storable Bool -- Defined in ‘Foreign.Storable’ instance VS.Storable Char -- Defined in ‘Foreign.Storable’ ...plus four others ...plus 13 instances involving out-of-scope types (use -fprint-potential-instances to see them all) • In the first argument of ‘seq’, namely ‘v’ In the second argument of ‘($)’, namely ‘v `seq` isSameVector (SomeVector v) (SomeVector v)’ In the expression: print $ v `seq` isSameVector (SomeVector v) (SomeVector v) | 22 | in print $ v `seq` isSameVector (SomeVector v) (SomeVector v) | ^ With the default `MonomorphismRestriction`, it compiles and reports that the vectors are shared. -- Viktor.