
On Sun, Jan 20, 2013 at 8:13 PM, wren ng thornton
I care. So far I've gotten around some of the problems by defining rewrite rules which take (fmap NT), (fmap unNT), etc into unsafeCoerce. I haven't run into the eta problems that I'm aware of, but the non-constant-time maps are something that shows up quite a lot.
1. As far as I can tell, the (fmap NT) rewrite rule won't ever fire. At least, I haven't figured out a way to do it, because newtype constructors (though not selectors) get turned into unsafeCoerces too early, before any rewrite rules have a change to fire. See http://hackage.haskell.org/trac/ghc/ticket/7398. 2. This might not be relevant in your case, but this rule isn't safe in general -- you can derive unsafeCoerce from it using an invalid Functor instance. For example: {-# LANGUAGE TypeFamilies #-} import Unsafe.Coerce newtype Id a = MkId { unId :: a } {-# RULES "fmap unId" fmap unId = unsafeCoerce #-} data family Foo x y a data instance Foo x y (Id a) = FooI x data instance Foo x y Bool = FooB { unB :: y } instance Functor (Foo x y) where fmap = undefined coerce :: a -> b coerce = unB . fmap unId . FooI Even without extensions, this would let you break invariants in types like Data.Set by defining an invalid Functor instance. This is a bigger deal than it might seem, given SafeHaskell -- you can't export this sort of rule from a Trustworthy library. Shachaf