Skip to content

Commit

Permalink
Make primitive vectors nominally roled
Browse files Browse the repository at this point in the history
Reasoning is identical to one for storable vectors. See discussion in haskell#224, and
PR haskell#235.

Fixes haskell#277
  • Loading branch information
Shimuuar committed Jun 14, 2020
1 parent 53d247b commit b35a6d3
Show file tree
Hide file tree
Showing 3 changed files with 50 additions and 3 deletions.
18 changes: 17 additions & 1 deletion Data/Vector/Primitive.hs
Original file line number Diff line number Diff line change
Expand Up @@ -137,6 +137,9 @@ module Data.Vector.Primitive (

-- ** Other vector types
G.convert,
#if __GLASGOW_HASKELL__ >= 708
unsafeCoerceVector,
#endif

-- ** Mutable vectors
freeze, thaw, copy, unsafeFreeze, unsafeThaw, unsafeCopy
Expand Down Expand Up @@ -183,11 +186,24 @@ import Data.Traversable ( Traversable )
#endif

#if __GLASGOW_HASKELL__ >= 708
import Data.Coerce
import Unsafe.Coerce
import qualified GHC.Exts as Exts
#endif

#if __GLASGOW_HASKELL__ >= 708
type role Vector representational
type role Vector nominal

-- | /O(1)/ Unsafely coerce an immutable vector from one element type to another,
-- representationally equal type. The operation just changes the type of the
-- underlying pointer and does not modify the elements.
--
-- Note that function is unsafe. @Coercible@ constraint guarantee that
-- types @a@ and @b@ are represented identically. It however cannot
-- guarantee that their respective 'Prim' instances may have different
-- representations in memory.
unsafeCoerceVector :: Coercible a b => Vector a -> Vector b
unsafeCoerceVector = unsafeCoerce
#endif

-- | Unboxed vectors of primitive types
Expand Down
30 changes: 29 additions & 1 deletion Data/Vector/Primitive/Mutable.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,9 @@
{-# LANGUAGE CPP, DeriveDataTypeable, MultiParamTypeClasses, FlexibleInstances, ScopedTypeVariables #-}

#if __GLASGOW_HASKELL__ >= 708
{-# LANGUAGE RoleAnnotations #-}
#endif

-- |
-- Module : Data.Vector.Primitive.Mutable
-- Copyright : (c) Roman Leshchinskiy 2008-2010
Expand Down Expand Up @@ -47,7 +51,12 @@ module Data.Vector.Primitive.Mutable (
nextPermutation,

-- ** Filling and copying
set, copy, move, unsafeCopy, unsafeMove
set, copy, move, unsafeCopy, unsafeMove,

-- * Unsafe conversions
#if __GLASGOW_HASKELL__ >= 708
unsafeCoerceMVector
#endif
) where

import qualified Data.Vector.Generic.Mutable as G
Expand All @@ -67,11 +76,30 @@ import Prelude hiding ( length, null, replicate, reverse, map, read,
take, drop, splitAt, init, tail )

import Data.Typeable ( Typeable )
#if __GLASGOW_HASKELL__ >= 708
import Data.Coerce
import Unsafe.Coerce
#endif

-- Data.Vector.Internal.Check is unnecessary
#define NOT_VECTOR_MODULE
#include "vector.h"

#if __GLASGOW_HASKELL__ >= 708
type role MVector nominal nominal

-- | /O(1)/ Unsafely coerce a mutable vector from one element type to another,
-- representationally equal type. The operation just changes the type of the
-- underlying pointer and does not modify the elements.
--
-- Note that function is unsafe. @Coercible@ constraint guarantee that
-- types @a@ and @b@ are represented identically. It however cannot
-- guarantee that their respective 'Prim' instances may have different
-- representations in memory.
unsafeCoerceMVector :: Coercible a b => MVector s a -> MVector s b
unsafeCoerceMVector = unsafeCoerce
#endif

-- | Mutable vectors of primitive types.
data MVector s a = MVector {-# UNPACK #-} !Int
{-# UNPACK #-} !Int
Expand Down
5 changes: 4 additions & 1 deletion changelog.md
Original file line number Diff line number Diff line change
Expand Up @@ -16,7 +16,10 @@
`type role MVector nominal representational` (previously, both arguments
were `phantom`).
* The role signature for `Data.Vector.Primitive.Vector` is now
`type role Vector representational` (previously, it was `phantom`).
`type role Vector nominal` (previously, it was `phantom`).
The role signature for `Data.Vector.Primitive.Mutable.MVector` is now
`type role MVector nominal nominal` (previously, both arguments were
`phantom`).
* The role signature for `Data.Vector.Storable.Vector` is now
`type role Vector nominal` (previous, it was `phantom`), and the signature
for `Data.Vector.Storable.Mutable.MVector` is now
Expand Down

0 comments on commit b35a6d3

Please sign in to comment.