
On 2016-02-15 at 12:00:23 +0100, Yuras Shumovich wrote: [...]
- It is possible to have unlifted types about even without -XMagicHash. -XMagicHash is simply a lexer extension, nothing more. By convention, we use the # suffix with unlifted things, but there's no requirement here. Having -XMagicHash thus imply a flag about the type system is bizarre.
OK, I always forget about that. But is not it a bug already? Usually we don't allow code that uses GHC-specific extensions to compile without a language pragma. Why we don't have such pragma for levity polymorphism?
There are extensions which are only needed at the definition site. Take {-# LANGUAGE PolyKinds #-} for instance; this is enabled inside the Data.Proxy module, which defines the following type {-# LANGUAGE PolyKinds #-} module Data.Proxy where data Proxy t = Proxy Now when you query via GHCi 7.10, you get the following output
import Data.Proxy :i Proxy type role Proxy phantom data Proxy (t :: k) = Proxy -- Defined in ‘Data.Proxy’ instance forall (k :: BOX) (s :: k). Bounded (Proxy s) -- Defined in ‘Data.Proxy’ instance forall (k :: BOX) (s :: k). Enum (Proxy s) -- Defined in ‘Data.Proxy’ instance forall (k :: BOX) (s :: k). Eq (Proxy s) -- Defined in ‘Data.Proxy’ instance Monad Proxy -- Defined in ‘Data.Proxy’ instance Functor Proxy -- Defined in ‘Data.Proxy’ instance forall (k :: BOX) (s :: k). Ord (Proxy s) -- Defined in ‘Data.Proxy’ instance forall (k :: BOX) (s :: k). Read (Proxy s) -- Defined in ‘Data.Proxy’ instance forall (k :: BOX) (s :: k). Show (Proxy s) -- Defined in ‘Data.Proxy’ instance Applicative Proxy -- Defined in ‘Data.Proxy’ instance Foldable Proxy -- Defined in ‘Data.Foldable’ instance Traversable Proxy -- Defined in ‘Data.Traversable’ instance forall (k :: BOX) (s :: k). Monoid (Proxy s) -- Defined in ‘Data.Proxy’
even though you never enabled any extensions beyond what Haskell2010 provides. Do you consider this a bug as well?