[GHC] #14223: Casts get in the way of join points

#14223: Casts get in the way of join points -------------------------------------+------------------------------------- Reporter: nomeata | Owner: (none) Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 Keywords: JoinPoints | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- I was checking which of HLint’s rewirte rules are actually already known to the compiler in the sense that the simplifier can do them (using [ghc- proofs](http://hackage.haskell.org/package/ghc-proofs). I stumbled on this interesting case. `foldr @[] (&&) True xs` compiles down to this nice core {{{ joinrec { go [Occ=LoopBreaker] :: [Bool] -> Bool [LclId[JoinId(1)], Arity=1, Unf=Unf{Src=<vanilla>, TopLvl=False, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [30] 44 20}] go (ds :: [Bool]) = case ds of { [] -> GHC.Types.True; : y ys -> case y of { False -> GHC.Types.False; True -> jump go ys } }; } in jump go xs }}} But `and @[] xs` (which HLint suggests to use instead, and we surely want people to use!) compiles down to {{{ go [Occ=LoopBreaker] :: [Bool] -> All [LclId, Arity=1, Unf=Unf{Src=<vanilla>, TopLvl=False, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [30] 60 20}] go = \ (ds :: [Bool]) -> case ds of { [] -> GHC.Types.True `cast` (Sym Data.Monoid.N:All[0] :: Coercible Bool All); : y ys -> case y of { False -> GHC.Types.False `cast` (Nth:3 (Nth:3 ((Sym Data.Monoid.N:All[0] -> Sym Data.Monoid.N:All[0] -> <Bool>_R) ; (<All>_R -> <All>_R -> Sym Data.Monoid.N:All[0]))) :: Coercible Bool All); True -> go ys } }; } in (go xs) `cast` (Data.Monoid.N:All[0] :: Coercible All Bool) }}} If you squint and ignore all the casts, these two expressions are the same. So it would be very desirable to get a `joinrec` for `and xs` as well. Note that all “exit paths” of the return function cast from `Bool` to `All`, and the return value of the whole recursion casts back. That looks as if some smart floating of coercions could do the job. Maybe the common context transformation (https://mail.haskell.org/pipermail/ghc- devs/2013-December/003481.html)? Is this tied to GHC’s deviation of the paper to have a fixed return type for a join point? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14223 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14223: Casts get in the way of join points -------------------------------------+------------------------------------- Reporter: nomeata | Owner: (none) Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 Resolution: | Keywords: JoinPoints 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 simonpj): Hmm. IF you float the `letrec go` inside the cast you'd get {{{ (letrec go = ... in go xs) |> blah }}} Now `go` is indeed a join point, and will be turned into a join point. And then the `|> blah` continuation will move into its RHS (becuase it's a join point). So really it should work fine right now. I wonder why that does not happen? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14223#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14223: Casts get in the way of join points -------------------------------------+------------------------------------- Reporter: nomeata | Owner: (none) Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 Resolution: | Keywords: JoinPoints 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 nomeata): Oh, wait, does loopification solve this? Let’s see. We start with {{{ letrec go :: [Bool] -> All go = \ (ds :: [Bool]) -> case ds of { [] -> GHC.Types.True `cast` (… :: Coercible Bool All) : y ys -> if y then go ys else GHC.Types.False `cast` (… :: Coercible Bool All) in (go xs) `cast` (… :: Coercible All Bool) }}} and loopify: {{{ let go :: [Bool] -> All go = \ (ds :: [Bool]) -> joinrec j :: [Bool] -> All j = \ds -> case ds of { [] -> GHC.Types.True `cast` (… :: Coercible Bool All) : y ys -> if y then jump j ys else GHC.Types.False `cast` (… :: Coercible Bool All) in jump j xs in (go xs) `cast` (… :: Coercible All Bool) }}} What now? Maybe `go` will inline: {{{ ( joinrec j :: [Bool] -> All j = \ds -> case ds of { [] -> GHC.Types.True `cast` (… :: Coercible Bool All) : y ys -> if y then jump j ys else GHC.Types.False `cast` (… :: Coercible Bool All) in jump j xs ) `cast` (… :: Coercible All Bool) }}} And surely there is a “`cast`-of-`joinrec`” transformation, right? Then we’ll get {{{ joinrec j :: [Bool] -> All j = \ds -> case ds of { [] -> GHC.Types.True `cast` (… :: Coercible Bool All) `cast` (… :: Coercible All Bool) : y ys -> if y then jump j ys else GHC.Types.False `cast` (… :: Coercible Bool All) `cast` (… :: Coercible All Bool) in jump j xs }}} and we can cancel the casts and get {{{ joinrec j :: [Bool] -> All j = \ds -> case ds of { [] -> GHC.Types.True : y ys -> if y then call j ys else GHC.Types.False in jump j xs }}} and all is well. So maybe #14068 is enough. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14223#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14223: Casts get in the way of join points -------------------------------------+------------------------------------- Reporter: nomeata | Owner: (none) Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 Resolution: | Keywords: JoinPoints 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 nomeata):
IF you float the letrec `go` inside the cast you'd get
With the stand-alone example {{{ module T14223 where foo :: [Bool] -> Bool foo xs = and xs }}} the `go` becomes top-level, so maybe that’s why? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14223#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14223: Casts get in the way of join points -------------------------------------+------------------------------------- Reporter: nomeata | Owner: (none) Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 Resolution: | Keywords: JoinPoints 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 simonpj):
the go becomes top-level, so maybe that’s why?
But then it wouldn't be a join point even if there was no cast. And comment:2 seems to be about a non-top-level letrec -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14223#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14223: Casts get in the way of join points -------------------------------------+------------------------------------- Reporter: nomeata | Owner: (none) Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 Resolution: | Keywords: JoinPoints 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 nomeata): comment:2 would apply to a non-exported top-level thing just the same: Loopification works on the top level as well, and then `go` can potentially be inlined. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14223#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

Loopification works on the top level as well, and then go can
#14223: Casts get in the way of join points -------------------------------------+------------------------------------- Reporter: nomeata | Owner: (none) Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 Resolution: | Keywords: JoinPoints 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 simonpj): potentially be inlined Ok but only if it's small. Perhaps float-in should be quite aggressive and float even top-level bindings inward (albeit perhaps not through a a lambda): {{{ rec f = ..f... nonrec h = ..f.. === nonrec h = ...(letrec f = ...f... in f)... }}} That would do the job here. Then maybe the final float-out pass can be a bit mor eager about floating things to top level -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14223#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14223: Casts get in the way of join points -------------------------------------+------------------------------------- Reporter: nomeata | Owner: (none) Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 Resolution: | Keywords: JoinPoints 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 nomeata): BTW, https://ghc.haskell.org/trac/ghc/wiki/SequentCore should explain why casts are not considered tail-calls. Because they certainly look like tail-calls after type erasure… and if they were, this here would be a non- issue. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14223#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14223: Casts get in the way of join points -------------------------------------+------------------------------------- Reporter: nomeata | Owner: (none) Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 Resolution: | Keywords: JoinPoints 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 simonpj): Trouble is, the transformation that pushes continuations into join RHSs would become ill-typed. Consider {{{ case (join j x = e in case b of True -> j x |> g False -> r) of ALTS }}} Here we are allowing `j` as a join point, as proposed in comment:7. Now move that outer case inwards: {{{ join j x = case e of ALTS in case b of True -> j x False -> case r of ALTS }}} Alas, the two `(case . of ALTS)` are now scrutinising values of different types! You could say "just live with that" but I don't know what the consequences would be. Better, I think, to move the casts around somehow. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14223#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC