Newtypes in STG

Christopher Done chrisdone at gmail.com
Mon Apr 1 09:08:47 UTC 2019


On Mon, 1 Apr 2019 at 09:22, Simon Peyton Jones simonpj at microsoft.com
<http://mailto:simonpj@microsoft.com> wrote:

That does look odd. Can you explain how to reproduce this with HEAD?
That is, are we getting a newtype constructor in the argument position
of an StgApp in HEAD too?

Newtype “data constructors” are always inlined, which is why I don’t
understand what’s happening.

OK, that’s good to know. I must be missing a Core-to-Core ot Core-to-STG
transform step. I’ll try to make a single-file repro case against HEAD
and see what happens. Maybe in doing so I’ll uncover what caused this
output for me.

On Mon, 1 Apr 2019 at 09:49, Ömer Sinan Ağacan omeragacan at gmail.com
<http://mailto:omeragacan@gmail.com> wrote:
I’m a bit confused about your findings because I’m unable to reproduce
them. I
wasn’t aware that we’re generating terms for newtype constructors, and when
I
try I can see that this is really the case. For example, when I compile a
module
with just this line:

newtype MyInt = MyInt Int

in the Core or STG dumps I don’t see any terms for the MyInt constructor.

I also checked the Core for System.Timeout.timeout module, and I don’t see
any
Timeout constructor applications anywhere. I compiled with -O0 -ddump-simpl.
Here’s what I get for the fmap Timeout application in that module:

Right, I see in yours that the newtype is properly removed and mine
isn’t (via -ddump-simpl):

-- RHS size: {terms: 201, types: 218, coercions: 11, joins:
0/1}timeout :: forall a. Int -> IO a -> IO (Maybe a)
[GblId, Arity=2]timeout
  = \ (@ a_a27I4) (n_a27GX :: Int) (f_a27GY :: IO a_a27I4) ->
      case < @ Int GHC.Classes.$fOrdInt n_a27GX (GHC.Types.I# 0#) of {
        False ->
          case == @ Int GHC.Classes.$fEqInt n_a27GX (GHC.Types.I# 0#) of {
            False ->
              case rtsSupportsBoundThreads of {
                False ->
                  >>=
                    @ IO
                    GHC.Base.$fMonadIO
                    @ ThreadId
                    @ (Maybe a_a27I4)
                    myThreadId
                    (\ (pid_a27Hb :: ThreadId) ->
                       >>=
                         @ IO
                         GHC.Base.$fMonadIO
                         @ Timeout
                         @ (Maybe a_a27I4)
                         (fmap
                            @ IO
                            GHC.Base.$fFunctorIO
                            @ Unique
                            @ Timeout
                            System.Timeout.Timeout <- *NEWTYPE HERE*
                            newUnique)

So I must be missing a pass somewhere.

I’ll try to reproduce on HEAD and get back to you.

Cheers!

Chris
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-devs/attachments/20190401/d1e1fbc5/attachment.html>


More information about the ghc-devs mailing list