We need to add role annotations for 7.8

Austin Seipp austin at well-typed.com
Fri Mar 14 08:54:40 UTC 2014


*cough* I hate to be the bearer of bad news, but something went wrong
it seems in HEAD:

$ git describe
ghc-7.9-start-188-g337bac3
$ grep "^version\:" libraries/containers/containers.cabal
version: 0.5.5.0
$ ./inplace/bin/ghc-stage2 --interactive -XSafe
GHCi, version 7.9.20140313: http://www.haskell.org/ghc/  :? for help
Loading package ghc-prim ... linking ... done.
Loading package integer-gmp ... linking ... done.
Loading package base ... linking ... done.
Prelude> import Data.Coerce
Prelude Data.Coerce> import Data.Map
Prelude Data.Coerce Data.Map> import Data.Set
Prelude Data.Coerce Data.Map Data.Set> newtype Age = MkAge Int deriving Show
Prelude Data.Coerce Data.Map Data.Set> let _ = coerce :: Map Int Int
-> Map Int Age
Prelude Data.Coerce Data.Map Data.Set> let _ = coerce :: Map Int Int
-> Map Age Int

<interactive>:7:9:
    Could not coerce from ‘Map Int Int’ to ‘Map Age Int’
      because the constructors of ‘Map’ are not imported
      as required in SafeHaskell mode
      because the first type argument of ‘Map’ has role Nominal,
      but the arguments ‘Int’ and ‘Age’ differ
      arising from a use of ‘coerce’
    In the expression: coerce :: Map Int Int -> Map Age Int
    In a pattern binding: _ = coerce :: Map Int Int -> Map Age Int
Prelude Data.Coerce Data.Map Data.Set> let _ = coerce :: Set Int -> Set Age
Prelude Data.Coerce Data.Map Data.Set> :i Set
data Set a
  = containers-0.5.5.0:Data.Set.Base.Bin {-# UNPACK #-}
!containers-0.5.5.0:Data.Set.Base.Size
                                         !a
                                         !(Set a)
                                         !(Set a)
  | containers-0.5.5.0:Data.Set.Base.Tip
  -- Defined in ‘containers-0.5.5.0:Data.Set.Base’
instance Eq a => Eq (Set a)
  -- Defined in ‘containers-0.5.5.0:Data.Set.Base’
instance Ord a => Ord (Set a)
  -- Defined in ‘containers-0.5.5.0:Data.Set.Base’
instance (Read a, Ord a) => Read (Set a)
  -- Defined in ‘containers-0.5.5.0:Data.Set.Base’
instance Show a => Show (Set a)
  -- Defined in ‘containers-0.5.5.0:Data.Set.Base’
Prelude Data.Coerce Data.Map Data.Set> :i Map
type role Map nominal representational
data Map k a
  = containers-0.5.5.0:Data.Map.Base.Bin {-# UNPACK #-}
!containers-0.5.5.0:Data.Map.Base.Size
                                         !k
                                         a
                                         !(Map k a)
                                         !(Map k a)
  | containers-0.5.5.0:Data.Map.Base.Tip
  -- Defined in ‘containers-0.5.5.0:Data.Map.Base’
instance (Eq k, Eq a) => Eq (Map k a)
  -- Defined in ‘containers-0.5.5.0:Data.Map.Base’
instance Functor (Map k)
  -- Defined in ‘containers-0.5.5.0:Data.Map.Base’
instance (Ord k, Ord v) => Ord (Map k v)
  -- Defined in ‘containers-0.5.5.0:Data.Map.Base’
instance (Ord k, Read k, Read e) => Read (Map k e)
  -- Defined in ‘containers-0.5.5.0:Data.Map.Base’
instance (Show k, Show a) => Show (Map k a)
  -- Defined in ‘containers-0.5.5.0:Data.Map.Base’
Prelude Data.Coerce Data.Map Data.Set>


--------------------------------------------------------------

As you can see, Map has the proper nominal representation (:i only
shows it when it's other than strictly representational), but Set, for
some reason, does not.

I'll look into this. We should also certainly add tests to containers
(under tests-ghc/) to make sure this doesn't slip by again.

On Thu, Mar 13, 2014 at 5:03 PM, Austin Seipp <austin at well-typed.com> wrote:
> That's right. If you had another instance of Ord for a newtype with
> compare = flip compare, and were allowed to coerce the keys, you can
> break it.
>
> On Thu, Mar 13, 2014 at 5:00 PM, Andres Löh <andres at well-typed.com> wrote:
>> [Sorry for the self-reply.]
>>
>> Oh, perhaps I actually understand this:
>>
>>> Please forgive my ignorance w.r.t. roles, but why aren't all of these
>>> representational?
>>>
>>>> Map k v -- k: nominal, v: represententional
>>>> Set a -- k: nominal
>>>
>>> AFAIK both Map and Set are "normal" datatypes. Not GADTs, no type
>>> families involved. Why would anything need to be "nominal" then?
>>
>> Is this because the integrity of these types relies on the Ord
>> instance being sane, and a newtype could have a different Ord instance
>> defined?
>>
>> Cheers,
>>   Andres
>> _______________________________________________
>> Libraries mailing list
>> Libraries at haskell.org
>> http://www.haskell.org/mailman/listinfo/libraries
>>
>
>
>
> --
> Regards,
>
> Austin Seipp, Haskell Consultant
> Well-Typed LLP, http://www.well-typed.com/



-- 
Regards,

Austin Seipp, Haskell Consultant
Well-Typed LLP, http://www.well-typed.com/


More information about the Libraries mailing list