
#15633: Type-checker plugins aren't loaded in GHCi 8.6.1 -------------------------------------+------------------------------------- Reporter: phadej | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.6.1-beta1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by darchon): To elaborate further Loading: {{{ {-# LANGUAGE DataKinds, TypeOperators #-} module Test where import Data.Proxy import GHC.TypeLits p1 :: Proxy a -> Proxy b -> Proxy (a + b) -> Proxy (b + a) p1 _ _ = id }}} without the normalisation plugin gives: {{{ $ ghci Test.hs GHCi, version 8.6.0.20180907: http://www.haskell.org/ghc/ :? for help Loaded package environment from /home/christiaan/devel/clash-compiler /clash-prelude/.ghc.environment.x86_64-linux-8.6.0.20180907 [1 of 1] Compiling Test ( Test.hs, interpreted ) Test.hs:8:10: error: • Couldn't match type ‘a + b’ with ‘b + a’ Expected type: Proxy (a + b) -> Proxy (b + a) Actual type: Proxy (b + a) -> Proxy (b + a) NB: ‘+’ is a non-injective type family • In the expression: id In an equation for ‘p1’: p1 _ _ = id • Relevant bindings include p1 :: Proxy a -> Proxy b -> Proxy (a + b) -> Proxy (b + a) (bound at Test.hs:8:1) | 8 | p1 _ _ = id | ^^ Failed, no modules loaded. }}} and of course with the normalisation plugin gives: {{{ $ ghci -fplugin=GHC.TypeLits.Normalise Test.hs GHCi, version 8.6.0.20180907: http://www.haskell.org/ghc/ :? for help Loaded package environment from /home/christiaan/devel/clash-compiler /clash-prelude/.ghc.environment.x86_64-linux-8.6.0.20180907 [1 of 1] Compiling Test ( Test.hs, interpreted ) Ok, one module loaded. *Test> }}} However, the following session in GHCi doesn't seem to work: {{{ $ ghci -fplugin=GHC.TypeLits.Normalise -XDataKinds -XTypeOperators GHCi, version 8.6.0.20180907: http://www.haskell.org/ghc/ :? for help Loaded package environment from /home/christiaan/devel/clash-compiler /clash-prelude/.ghc.environment.x86_64-linux-8.6.0.20180907 Prelude> import Data.Proxy Prelude Data.Proxy> import GHC.TypeLits Prelude Data.Proxy GHC.TypeLits> :{ Prelude Data.Proxy GHC.TypeLits| p1 :: Proxy a -> Proxy b -> Proxy (a + b) -> Proxy (b + a) Prelude Data.Proxy GHC.TypeLits| p1 _ _ = id Prelude Data.Proxy GHC.TypeLits| :} <interactive>:5:10: error: • Couldn't match type ‘a + b’ with ‘b + a’ Expected type: Proxy (a + b) -> Proxy (b + a) Actual type: Proxy (b + a) -> Proxy (b + a) NB: ‘+’ is a non-injective type family • In the expression: id In an equation for ‘p1’: p1 _ _ = id • Relevant bindings include p1 :: Proxy a -> Proxy b -> Proxy (a + b) -> Proxy (b + a) (bound at <interactive>:5:1) Prelude Data.Proxy GHC.TypeLits> }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15633#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler