[GHC] #9190: Iface type variable out of scope: s

#9190: Iface type variable out of scope: s ------------------------------------+------------------------------------- Reporter: nomeata | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.9 Keywords: | Operating System: Unknown/Multiple Architecture: Unknown/Multiple | Type of failure: None/Unknown Difficulty: Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | ------------------------------------+------------------------------------- I just tried to install criterion with the current GHC HEAD, and `statistics` failed with this message: {{{ /home/jojo/.cabal/lib/x86_64-linux-ghc-7.9.20140609/math- functions-0.1.5.2/Numeric/Sum.hi Declaration for R:MVectorsKBNSum: Iface type variable out of scope: s Cannot continue after interface file error }}} I tried to reproduce this with smaller code than `statistics`, but could not trigger it. The interface dump gives me: {{{ 661d69e55c1491128ac1ed3c03f864e2 axiom TFCo:R:MVectorsKB2Sum:: Data.Vector.Unboxed.Base.MVector s0 Numeric.Sum.KB2Sum = Numeric.Sum.R:MVectorsKB2Sum s0 a69bb56c3760003bcb7d99cd40c3d843 axiom TFCo:R:MVectorsKBNSum:: Data.Vector.Unboxed.Base.MVector s0 Numeric.Sum.KBNSum = Numeric.Sum.R:MVectorsKBNSum s0 }}} – not sure if there is a `forall` missing or note. Note that these data types are generated using template haskell [http://hdiff.luite.com/cgit /math- functions/tree/Numeric/Sum.hs?id=06b09eb4f110f99fb51a9ec0ec598fba54ac0986#n123 source]. In order to reproduce this, run someting like `cabal install --with-compiler=.../inplace/bin/ghc-stage2 --ghc- option=-XTypeFamilies .` in `statistics-0.11.0.3` with the attached patch applied. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9190 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9190: Iface type variable out of scope: s -------------------------------------+------------------------------------ Reporter: nomeata | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.9 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Comment (by nomeata): I managed to extract a smaller example exhibiting the problem: {{{ module T9190 (pfxSumR) where import Numeric.Sum import qualified Data.Vector.Generic as G import qualified Data.Vector.Unboxed as U pfxSumR :: U.Vector Double -> U.Vector Double pfxSumR = G.map kbn . G.scanr (flip add) zero }}} The problem only occurs with `-O`, and would not occur with {{{ -- No error with: -- pfxSumR :: U.Vector KBNSum -> U.Vector Double -- pfxSumR = G.map kbn . G.scanr (flip add) zero }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9190#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9190: Iface type variable out of scope: s -------------------------------------+------------------------------------ Reporter: nomeata | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.9 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Description changed by nomeata: Old description:
I just tried to install criterion with the current GHC HEAD, and `statistics` failed with this message:
{{{ /home/jojo/.cabal/lib/x86_64-linux-ghc-7.9.20140609/math- functions-0.1.5.2/Numeric/Sum.hi Declaration for R:MVectorsKBNSum: Iface type variable out of scope: s Cannot continue after interface file error }}}
I tried to reproduce this with smaller code than `statistics`, but could not trigger it.
The interface dump gives me: {{{ 661d69e55c1491128ac1ed3c03f864e2 axiom TFCo:R:MVectorsKB2Sum:: Data.Vector.Unboxed.Base.MVector s0 Numeric.Sum.KB2Sum = Numeric.Sum.R:MVectorsKB2Sum s0 a69bb56c3760003bcb7d99cd40c3d843 axiom TFCo:R:MVectorsKBNSum:: Data.Vector.Unboxed.Base.MVector s0 Numeric.Sum.KBNSum = Numeric.Sum.R:MVectorsKBNSum s0 }}} – not sure if there is a `forall` missing or note. Note that these data types are generated using template haskell [http://hdiff.luite.com/cgit /math- functions/tree/Numeric/Sum.hs?id=06b09eb4f110f99fb51a9ec0ec598fba54ac0986#n123 source].
In order to reproduce this, run someting like `cabal install --with-compiler=.../inplace/bin/ghc-stage2 --ghc- option=-XTypeFamilies .` in `statistics-0.11.0.3` with the attached patch applied.
New description: I just tried to install criterion with the current GHC HEAD, and `statistics` failed with this message: {{{ /home/jojo/.cabal/lib/x86_64-linux-ghc-7.9.20140609/math- functions-0.1.5.2/Numeric/Sum.hi Declaration for R:MVectorsKBNSum: Iface type variable out of scope: s Cannot continue after interface file error }}} I tried to reproduce this with smaller code than `statistics`, but could not trigger it. The interface dump gives me: {{{ 661d69e55c1491128ac1ed3c03f864e2 axiom TFCo:R:MVectorsKB2Sum:: Data.Vector.Unboxed.Base.MVector s0 Numeric.Sum.KB2Sum = Numeric.Sum.R:MVectorsKB2Sum s0 a69bb56c3760003bcb7d99cd40c3d843 axiom TFCo:R:MVectorsKBNSum:: Data.Vector.Unboxed.Base.MVector s0 Numeric.Sum.KBNSum = Numeric.Sum.R:MVectorsKBNSum s0 }}} – not sure if there is a `forall` missing or not. Note that these data types are generated using template haskell [http://hdiff.luite.com/cgit /math- functions/tree/Numeric/Sum.hs?id=06b09eb4f110f99fb51a9ec0ec598fba54ac0986#n123 source]. In order to reproduce this, run someting like `cabal install --with-compiler=.../inplace/bin/ghc-stage2 --ghc- option=-XTypeFamilies .` in `statistics-0.11.0.3` with the attached patch applied. -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9190#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9190: Iface type variable out of scope: s -------------------------------------+------------------------------------ Reporter: nomeata | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.9 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Comment (by nomeata): The interface of `Numeric.Sum`, when printed with GHC 7.6.3, looks like this {{{ axiom TFCo:R:MVectorsKBNSum [(s0, *)] :: Data.Vector.Unboxed.Base.MVector s0 Numeric.Sum.KBNSum ~# Numeric.Sum.R:MVectorsKBNSum s0 }}} Does `[(s0,*)]` indicate the type variables this axiom is abstracted over? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9190#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9190: Iface type variable out of scope: s -------------------------------------+------------------------------------ Reporter: nomeata | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.9 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Old description:
I just tried to install criterion with the current GHC HEAD, and `statistics` failed with this message:
{{{ /home/jojo/.cabal/lib/x86_64-linux-ghc-7.9.20140609/math- functions-0.1.5.2/Numeric/Sum.hi Declaration for R:MVectorsKBNSum: Iface type variable out of scope: s Cannot continue after interface file error }}}
I tried to reproduce this with smaller code than `statistics`, but could not trigger it.
The interface dump gives me: {{{ 661d69e55c1491128ac1ed3c03f864e2 axiom TFCo:R:MVectorsKB2Sum:: Data.Vector.Unboxed.Base.MVector s0 Numeric.Sum.KB2Sum = Numeric.Sum.R:MVectorsKB2Sum s0 a69bb56c3760003bcb7d99cd40c3d843 axiom TFCo:R:MVectorsKBNSum:: Data.Vector.Unboxed.Base.MVector s0 Numeric.Sum.KBNSum = Numeric.Sum.R:MVectorsKBNSum s0 }}} – not sure if there is a `forall` missing or not. Note that these data types are generated using template haskell [http://hdiff.luite.com/cgit /math- functions/tree/Numeric/Sum.hs?id=06b09eb4f110f99fb51a9ec0ec598fba54ac0986#n123 source].
In order to reproduce this, run someting like `cabal install --with-compiler=.../inplace/bin/ghc-stage2 --ghc- option=-XTypeFamilies .` in `statistics-0.11.0.3` with the attached patch applied.
New description: I just tried to install criterion with the current GHC HEAD, and `statistics` failed with this message: {{{ /home/jojo/.cabal/lib/x86_64-linux-ghc-7.9.20140609/math- functions-0.1.5.2/Numeric/Sum.hi Declaration for R:MVectorsKBNSum: Iface type variable out of scope: s Cannot continue after interface file error }}} I tried to reproduce this with smaller code than `statistics`, but could not trigger it. The interface dump gives me: {{{ 661d69e55c1491128ac1ed3c03f864e2 axiom TFCo:R:MVectorsKB2Sum:: Data.Vector.Unboxed.Base.MVector s0 Numeric.Sum.KB2Sum = Numeric.Sum.R:MVectorsKB2Sum s0 a69bb56c3760003bcb7d99cd40c3d843 axiom TFCo:R:MVectorsKBNSum:: Data.Vector.Unboxed.Base.MVector s0 Numeric.Sum.KBNSum = Numeric.Sum.R:MVectorsKBNSum s0 }}} – not sure if there is a `forall` missing or note. Note that these data types are generated using template haskell [http://hdiff.luite.com/cgit /math- functions/tree/Numeric/Sum.hs?id=06b09eb4f110f99fb51a9ec0ec598fba54ac0986#n123 source]. In order to reproduce this, run someting like `cabal install --with-compiler=.../inplace/bin/ghc-stage2 --ghc- option=-XTypeFamilies .` in `statistics-0.11.0.3` with the attached patch applied. -- Comment (by simonpj): I tried reproducing this, but the `cabal install` process fell over much earlier in `mwc-random`: {{{ System\Random\MWC\Distributions.hs:83:5: Illegal equational constraint PrimState m ~ PrimState m (Use GADTs or TypeFamilies to permit this) When checking that `normalTail' has the inferred type `forall (m1 :: * -> *). (PrimMonad m1, PrimState m1 ~ PrimState m) => Bool -> m1 Double' In an equation for `standard': standard gen = loop where .... }}} This is more fallout from #8883. (The inferred type also looks ambiguous, but it isn't because the type variable `m` is free in the environment.) Very similar errors show up in `vector-algorithms`. Both are solved by `-XMonoLocalBinds`. I'm not sure why this didn't happen to you. Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9190#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9190: Iface type variable out of scope: s -------------------------------------+------------------------------------ Reporter: nomeata | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.9 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Comment (by nomeata): You can work around this with passing `--ghc-option=-XTypeFamilies` to `cabal`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9190#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9190: Iface type variable out of scope: s -------------------------------------+------------------------------------ Reporter: nomeata | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.9 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Changes (by jstolarek): * cc: jan.stolarek@… (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9190#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9190: Iface type variable out of scope: s -------------------------------------+------------------------------------ Reporter: nomeata | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.9 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Comment (by nomeata): If the above interface output is indeed a symptom of something being wrong, then this module (extracted from math-functions) suffices to reproduce it (still needs vector-th-unbox, slowly working towards less dependencies). I cannot trigger the the actual error with that, though. {{{ {-# LANGUAGE MultiParamTypeClasses, TemplateHaskell, TypeFamilies #-} module T9190a where import Data.Vector.Unboxed.Deriving (derivingUnbox) data KBNSum = KBNSum Double Double derivingUnbox "KBNSum" [t| KBNSum -> (Double, Double) |] [| \ (KBNSum a b) -> (a, b) |] [| \ (a, b) -> KBNSum a b |] }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9190#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9190: Iface type variable out of scope: s -------------------------------------+------------------------------------ Reporter: nomeata | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.9 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Comment (by nomeata): And finally, the last dependency not in GHC reduced to this module {{{ {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TypeFamilies #-} module T9190b (derivingUnbox) where import Control.Applicative import Data.Vector.Unboxed.Base (MVector (..)) import Language.Haskell.TH derivingUnbox :: String -> TypeQ -> DecsQ derivingUnbox name argsQ = do let mvName = mkName $ "MV_" ++ name args <- argsQ (_, typ, rep) <- case args of ForallT _ cxts (ArrowT `AppT` typ `AppT` rep) -> return (cxts, typ, rep) ArrowT `AppT` typ `AppT` rep -> return ([], typ, rep) _ -> fail "Expecting a type of the form: cxts => typ -> rep" s <- VarT <$> newName "s" let newtypeMVector = NewtypeInstD [] ''MVector [s, typ] (NormalC mvName [(NotStrict, ConT ''MVector `AppT` s `AppT` rep)]) [] return [ newtypeMVector] }}} to be used with {{{ {-# LANGUAGE MultiParamTypeClasses, TemplateHaskell, TypeFamilies #-} module T9190a where import T9190b data KBNSum = KBNSum Double Double derivingUnbox "KBNSum" [t| KBNSum -> (Double, Double) |] }}} There we see a new variable `s` being introduced and put in the type of the newtype declaration. Is it TH’s responsibility to abstract over `s` here, or GHCs -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9190#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9190: Iface type variable out of scope: s -------------------------------------+------------------------------------ Reporter: nomeata | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.9 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Comment (by nomeata): Further reduced the problem: {{{ {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TypeFamilies #-} module T9190b where import Language.Haskell.TH data family Family a b foo :: DecsQ foo = do s <- VarT `fmap` newName "s" return [ NewtypeInstD [] ''Family [s, ConT ''Double] (NormalC (mkName "Foo") [(NotStrict, TupleT 0) ]) [] ] }}} and {{{ {-# LANGUAGE TypeFamilies, TemplateHaskell #-} module T9190a where import T9190b foo }}} yields {{{ b179ce4def4d6d8b892ce82aab2d2a37 newtype instance T9190b.Family s GHC.Types.Double = Foo () RecFlag: Recursive b179ce4def4d6d8b892ce82aab2d2a37 axiom TFCo:R:FamilysDouble:: T9190b.Family s0 GHC.Types.Double = T9190a.R:FamilysDouble s0 family instance T9190b.Family [.], [GHC.Types.Double] = T9190a.TFCo:R:FamilysDouble }}} I’m off traveling to OPSLL, but I hope that this makes it easier for someone else to pick up the issue. (But maybe I’m completely off the track here, and the interface is actually fine – I just discovered that with `-fprint-explicit-foralls` this reads {{{ b179ce4def4d6d8b892ce82aab2d2a37 axiom TFCo:R:FamilysDouble:: forall s0. T9190b.Family s0 GHC.Types.Double = T9190a.R:FamilysDouble s0 }}} and this hiding of `forall` is new in 7.8 or 7.9 compared to 7.6, which had printed the `s0` directly. :-( ) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9190#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9190: Iface type variable out of scope: s
-------------------------------------+------------------------------------
Reporter: nomeata | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.9
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture: Unknown/Multiple
Type of failure: None/Unknown | Difficulty: Unknown
Test Case: | Blocked By:
Blocking: | Related Tickets:
-------------------------------------+------------------------------------
Comment (by Simon Peyton Jones

#9190: Iface type variable out of scope: s -------------------------------------+------------------------------------ Reporter: nomeata | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.9 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Comment (by simonpj): PS: this doesn't affect the GHC 7.8 branch. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9190#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9190: Iface type variable out of scope: s -------------------------------------+------------------------------------ Reporter: nomeata | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.9 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Changes (by simonpj): * status: new => closed * resolution: => fixed Comment: It's quite awkward to reproduce this problem in a small test cases (the smaller cases from comment 8 onwards were actually red herrings), and the bug was an egregious one now fixed, so I'm just going to close this without a regression test. Thank you for reporting it. Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9190#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC