[GHC] #10181: Lint check: arity invariant

#10181: Lint check: arity invariant -------------------------------------+------------------------------------- Reporter: nomeata | Owner: nomeata Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Blocked By: Test Case: | Related Tickets: Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- The Arity of an ID should not exceed the arity of its type, nor the arity of its strictness signature, if it is a bottoming signatures. This should be checked by a lint check (suggested by SPJ in https://phabricator.haskell.org/D747?id=2498#inline-6058) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10181 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10181: Lint check: arity invariant -------------------------------------+------------------------------------- Reporter: nomeata | Owner: nomeata Type: task | Status: infoneeded Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by nomeata): * status: new => infoneeded Comment: GHC compiles with this lint check, but not the test suite: The invariant `idArity <= typeArity` fails to hold in the situation of #8743: {{{ T8743.hs-boot:3:10: Warning: [RHS of $fxToRowMaybe :: forall a_ani. ToRow (Maybe a_ani)] idArity 1 exceeds typeArity 0: $fxToRowMaybe }}} Here `ToRow` is a one-member class that is also imported with a self- source-import {{{ module T8743 where import {-# SOURCE #-} T8743 () class ToRow a where toRow :: a -> [()] instance ToRow (Maybe a) where toRow Nothing = [()] toRow (Just _) = [()] }}} So presumably due to the SOURCE import, `typeArity` is unable to look through the newtype `ToRow`. Maybe it is better done as a lint warning, and not a lint error? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10181#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10181: Lint check: arity invariant -------------------------------------+------------------------------------- Reporter: nomeata | Owner: nomeata Type: task | Status: infoneeded Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): This looks like a bug in the SOURCE-import mechanism to me. I think the same bug happens here: {{{ bash$ ghc -c T8743.hs-boot bash$ ghc -c T8743.hs ghc: panic! (the 'impossible' happened) (GHC version 7.8.2 for x86_64-unknown-linux): tcIfaceGlobal (local): not found: main:T8743.$fxToRowMaybe{v r2J} [(r2L, Class ‘main:T8743.ToRow{tc r2L}’), (r2M, Data constructor ‘main:T8743.D:ToRow{d r2M}’), (r2P, Identifier ‘main:T8743.D:ToRow{v r2P}’), (roB, Identifier ‘main:T8743.toRow{v roB}’), (rqT, Coercion axiom ‘main:T8743.NTCo:ToRow{tc rqT}’)] }}} Bother. Well I suppose it would be good to open a separate ticket about that. But I'll stick to my guns about `idArity <= typeArity` for now. See `Note [exprArity invariant]` in `CoreArity`. Did you find any other cases? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10181#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10181: Lint check: arity invariant -------------------------------------+------------------------------------- Reporter: nomeata | Owner: nomeata Type: task | Status: infoneeded Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): branch `wip/T10181`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10181#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

This looks like a bug in the SOURCE-import mechanism to me. […] Bother. Well I suppose it would be good to open a separate ticket about
#10181: Lint check: arity invariant -------------------------------------+------------------------------------- Reporter: nomeata | Owner: nomeata Type: task | Status: infoneeded Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by nomeata): Hi, Replying to [comment:2 simonpj]: that. I would, but I’m not able to summarize what precisely is wrong here, and how to phrase the ticket.
But I'll stick to my guns about `idArity <= typeArity` for now. See `Note [exprArity invariant]` in `CoreArity`.
Did you find any other cases?
Not yet, as I stumbled over this while building GHC. I can make it a lint warning for now and see what else comes up. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10181#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

Did you find any other cases?
Not yet, as I stumbled over this while building GHC. I can make it a
#10181: Lint check: arity invariant -------------------------------------+------------------------------------- Reporter: nomeata | Owner: nomeata Type: task | Status: infoneeded Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by nomeata): Replying to [comment:4 nomeata]: lint warning for now and see what else comes up. nevermind. That case was already in the test suite. So now, I did not find any other cases in GHC+Testsuite. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10181#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10181: Lint check: arity invariant -------------------------------------+------------------------------------- Reporter: nomeata | Owner: nomeata Type: task | Status: infoneeded Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): OK good. Well maybe add it, and mark `T8743` as expect-broken on #10182. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10181#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10181: Lint check: arity invariant -------------------------------------+------------------------------------- Reporter: nomeata | Owner: nomeata Type: task | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: Phab:751 -------------------------------------+------------------------------------- Changes (by nomeata): * status: infoneeded => patch * differential: => Phab:751 Comment: Replying to [comment:6 simonpj]:
OK good. Well maybe add it, and mark `T8743` as expect-broken on #10182.
Good idea, that validates. See Phab:D751. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10181#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10181: Lint check: arity invariant
-------------------------------------+-------------------------------------
Reporter: nomeata | Owner: nomeata
Type: task | Status: patch
Priority: normal | Milestone:
Component: Compiler | Version: 7.11
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: None/Unknown | Unknown/Multiple
Blocked By: | Test Case:
Related Tickets: | Blocking:
| Differential Revisions: Phab:751
-------------------------------------+-------------------------------------
Comment (by Joachim Breitner

#10181: Lint check: arity invariant -------------------------------------+------------------------------------- Reporter: nomeata | Owner: nomeata Type: task | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: Phab:751 -------------------------------------+------------------------------------- Changes (by nomeata): * status: patch => closed * resolution: => fixed -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10181#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10181: Lint check: arity invariant
-------------------------------------+-------------------------------------
Reporter: nomeata | Owner: nomeata
Type: task | Status: closed
Priority: normal | Milestone:
Component: Compiler | Version: 7.11
Resolution: fixed | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: None/Unknown | Unknown/Multiple
Blocked By: | Test Case:
Related Tickets: | Blocking:
| Differential Revisions: Phab:751
-------------------------------------+-------------------------------------
Comment (by Joachim Breitner

#10181: Lint check: arity invariant -------------------------------------+------------------------------------- Reporter: nomeata | Owner: Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: Phab:751 -------------------------------------+------------------------------------- Changes (by nomeata): * cc: thomie (added) * owner: nomeata => * status: closed => new * resolution: fixed => Comment: thomie notified me of a a case of this lint check firing, triggered by simply `t a = t a`. Here is what’s happening: {{{ ==================== Simplifier ==================== Max iterations = 4 SimplMode {Phase = 2 [main], inline, rules, eta-expand, case-of-case} Result size of Simplifier = {terms: 2, types: 4, coercions: 0} Rec { t [Occ=LoopBreaker] :: forall t_ans t_ant. t_ans -> t_ant [LclIdX, Arity=1, Str=DmdType] t = t end Rec } [...] ==================== Demand analysis ==================== Result size of Demand analysis = {terms: 2, types: 4, coercions: 0} Rec { t [Occ=LoopBreaker] :: forall t_ans t_ant. t_ans -> t_ant [LclIdX, Arity=1, Str=DmdType b] t = t end Rec } *** Core Linted result of Demand analysis: *** Core Lint errors : in result of Demand analysis *** T10181.hs:3:1: warning: [RHS of t :: forall t_ans t_ant. t_ans -> t_ant] idArity 1 exceeds arity imposed by the strictness signature DmdType b: t }}} So there are several possibilities: * The simplifier should not set the `idArity` of `t` if after simplification, it does not have that arity. * `idArtiy t = 1` is correct, as that is the arity provided by the programmer. In that case, the lint check is bogus. * The demand analysis should enforce the the invariant if it adds a bottoming signature. This requires some insight with someone with the big picture in mind. Simon? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10181#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10181: Lint check: arity invariant
-------------------------------------+-------------------------------------
Reporter: nomeata | Owner:
Type: task | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.11
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Revisions: Phab:751
-------------------------------------+-------------------------------------
Comment (by Thomas Miedema

#10181: Lint check: arity invariant
-------------------------------------+-------------------------------------
Reporter: nomeata | Owner:
Type: task | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.11
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Revisions: Phab:751
-------------------------------------+-------------------------------------
Comment (by Thomas Miedema

#10181: Lint check: arity invariant
-------------------------------------+-------------------------------------
Reporter: nomeata | Owner:
Type: task | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.11
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Revisions: Phab:751
-------------------------------------+-------------------------------------
Comment (by Thomas Miedema

#10181: Lint check: arity invariant -------------------------------------+------------------------------------- Reporter: nomeata | Owner: Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:751 Wiki Page: | -------------------------------------+------------------------------------- Comment (by ezyang): It seems unlikely that bullet (2) is the way to go: `idArity` is ostensibly saying something about the Core program it points to. Which causes the invariant to be violated first: the simplifier or demand analysis? I think that's the one that should be responsible for fixing the invariant. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10181#comment:15 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10181: Lint check: arity invariant -------------------------------------+------------------------------------- Reporter: nomeata | Owner: Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:751 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): The real culprit here is the eta-reduction of {{{ t = \x -> t x }}} In general `CoreUtils.tryEtaReduce` eta-reduces `\x t x` to `t` if `t` is a head-normal form, definitely not bottom. However, here `t` cheerfully says that its arity is 1, and so the eta-reduction goes ahead. But now its arity isn't 1 any more! And the eta-reduction is unsound, because {{{t `seq` True}}} will behave differently than before. One simple solution would be this: * Never eta-reduce a let right-hand side. See `SimplUtils.mkLam`, which refrains from eta-expansion of let right-hand sides. This a bit drastic because it doesn't eta-reduce the non-recursive {{{ myMap = \f x -> map f x }}} When we eta-reduce we get a trivial binding, so we can substitute, and win all round. So a better strategy would be * Never eta-reduce a let right-hand side of a recursive group. To do this, we'd have to augment `RhsCtxt` (the data constructor of `CoreUnfold.CallCtxt`) with a `RecFlag`. My bet is that this more conservative story would do little harm. More ambitiously, we should look at at recursive group of bindings as a whole. We already have special treatment for eta ''expansion'' for let(rec) rhss; see `SimplUtils.tryEtaExpandRhs`. But it is still one- binding-at-a-time, which isn't as good as it could be; see `Note [Arity analysis]` in `CoreArity`. We could instead do eta expansion and reduction for let(rec) RHSs for a group as a whole. This latter seems like the Right Thing to do. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10181#comment:16 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC