-dinline-check for symbolic names?

I'm trying to figure out why this function from ConCat.AltCat is not getting inlined: (&&&) :: forall k a c d. (MProductCat k, Ok3 k a c d) => (a `k` c) -> (a `k` d) -> (a `k` Prod k c d) f &&& g = (f *** g) . dup <+ okProd @k @a @a <+ okProd @k @c @d {-# INLINE (&&&) #-} So I put {-# OPTIONS_GHC -dinline-check ConCat.AltCat.&&& #-} in the importing module. Alas, I'm getting no output on &&&. I can get output from lots of other functions - I'm guessing it might be because of the name. Could somebody help me enable the inline check? Would be much appreciated! -- Regards, Mike

I’m not sure about the pragma debugging, but are you using it in point free
style? Cause I’m that case it may not be inclined because it’s not being
fully applied on the left hand side?
On Wed, Aug 4, 2021 at 11:36 AM Michael Sperber
I'm trying to figure out why this function from ConCat.AltCat is not getting inlined:
(&&&) :: forall k a c d. (MProductCat k, Ok3 k a c d) => (a `k` c) -> (a `k` d) -> (a `k` Prod k c d) f &&& g = (f *** g) . dup <+ okProd @k @a @a <+ okProd @k @c @d {-# INLINE (&&&) #-}
So I put
{-# OPTIONS_GHC -dinline-check ConCat.AltCat.&&& #-}
in the importing module. Alas, I'm getting no output on &&&. I can get output from lots of other functions - I'm guessing it might be because of the name.
Could somebody help me enable the inline check? Would be much appreciated!
-- Regards, Mike
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users

On Wed, Aug 04 2021, Carter Schonwald
I’m not sure about the pragma debugging, but are you using it in point free style? Cause I’m that case it may not be inclined because it’s not being fully applied on the left hand side?
Good point, but I checked, and it's fully applied. :-( I should also note that, with the inline check, I've also tried: {-# OPTIONS_GHC -dinline-check &&& #-} {-# OPTIONS_GHC -dinline-check (&&&) #-} ... to no avail. -- Regards, Mike

On Fri, Aug 06 2021, Michael Sperber
On Wed, Aug 04 2021, Carter Schonwald
wrote: I’m not sure about the pragma debugging, but are you using it in point free style? Cause I’m that case it may not be inclined because it’s not being fully applied on the left hand side?
Good point, but I checked, and it's fully applied. :-(
Another note: Once I change the INLINE to INLINE [0], everything works: (&&&) gets inlined, and -dinline-check works. Explanation welcome ... -- Regards, Mike

It's hard to tell what is happening without a repro case. Can you share one?
You suggested that it might have something to do with using an operator. Does the same thing happen if you replace the operator with an alpha-numeric name?
Simon
| -----Original Message-----
| From: Glasgow-haskell-users

On Tue, Aug 10 2021, Simon Peyton Jones
It's hard to tell what is happening without a repro case. Can you share one?
Haven't been able to do that with <10MB of output, I'm afraid ...
You suggested that it might have something to do with using an operator. Does the same thing happen if you replace the operator with an alpha-numeric name?
I've now concluded several things are coming together. As things started working with INLINE [0] instead of INLINE, it's not the symbolic name. First, reading the ghc source code suggests I can only have one -ddinline-check. Correct? Also, I'm guessing that the inlining I didn't see reported by -dinline-check happened inside the simplifier pass inserted by the ConCat plugin. (And hence INLINE [0] moved it out of that pass.) Is it possible that the flag isn't getting propagated there? (Sorry for being vague - if you don't know offhand, it's not worth digging without more info from me.) -- Regards, Mike

| First, reading the ghc source code suggests I can only have one -ddinline-
| check. Correct?
Yes. The last one wins. This should be in the user manual. Would anyone like to offer a PR?
| Also, I'm guessing that the inlining I didn't see reported by -dinline-check
| happened inside the simplifier pass inserted by the ConCat plugin. (And
| hence INLINE [0] moved it out of that pass.) Is it possible that the flag
| isn't getting propagated there?
I don't see how that could happen, but I only have a vague idea of what is going on.
Simon
| -----Original Message-----
| From: Michael Sperber
participants (3)
-
Carter Schonwald
-
Michael Sperber
-
Simon Peyton Jones