[GHC] #11823: Undefined stg_sel_17_upd_info symbols on OS X

GHC ghc-devs at haskell.org
Tue Apr 12 08:59:14 UTC 2016


#11823: Undefined stg_sel_17_upd_info symbols on OS X
-------------------------------------+-------------------------------------
        Reporter:  bgamari           |                Owner:
            Type:  bug               |               Status:  new
        Priority:  highest           |            Milestone:  8.0.1
       Component:  Compiler          |              Version:  8.0.1-rc3
      Resolution:                    |             Keywords:
Operating System:  MacOS X           |         Architecture:  x86_64
 Type of failure:  Building GHC      |  (amd64)
  failed                             |            Test Case:
      Blocked By:                    |             Blocking:
 Related Tickets:                    |  Differential Rev(s):
       Wiki Page:                    |
-------------------------------------+-------------------------------------

Comment (by bgamari):

 So the cause here is that we only generate special selector frames for up
 to arity 15 (see `rts/StgStdThunks.cmm`). For anything higher we are
 supposed to use the selector closure that we generate for the type in
 question. For consider the following,
 {{{#!hs
 module Test where

 data Hello = Hello { f1, f2, f3, f4
                    , f5, f6, f7, f8
                    , f9, f10, f11, f12
                    , f13, f14, f15, f16
                    , f17 :: String }

 juno :: Hello -> IO ()
 juno = putStrLn . f16

 turtle :: Hello -> IO ()
 turtle = putStrLn . f17
 }}}

 `juno` will produce code resembling,
 {{{
 Hi.turtle1_entry() {
     ...  // heap/stack check throat-clearing

     I64[Hp - 16] = stg_sel_15_noupd_info;
     P64[Hp] = R2;
     R4 = GHC.Types.True_closure+2;
     R3 = Hp - 16;
     R2 = GHC.IO.Handle.FD.stdout_closure;
     call GHC.IO.Handle.Text.hPutStr2_info(R4,
                                           R3,
                                           R2) args: 8, res: 0, upd: 8;
 }
 }}}

 Whereas `turtle` will use a helper function,
 {{{
 Hi.turtle1_entry() {
     ...  // heap/stack check throat-clearing

     I64[Hp - 16] = sat_s16u_info;
     P64[Hp] = _s16a::P64;
     _c1dl::P64 = Hp - 16;
     R4 = GHC.Types.True_closure+2;
     R3 = _c1dl::P64;
     R2 = GHC.IO.Handle.FD.stdout_closure;
     call GHC.IO.Handle.Text.hPutStr2_info(R4,
                                           R3,
                                           R2) args: 8, res: 0, upd: 8;
 }

 sat_s16u_entry() {
     ...  // heap/stack check throat-clearing

     I64[Sp - 8] = c1dp;
     R1 = P64[R1 + 16];
     Sp = Sp - 8;
     if (R1 & 7 != 0) goto c1dp; else goto c1dq;
 c1dq:
     call (I64[R1])(R1) returns to c1dp, args: 8, res: 8, upd: 8;
 c1dp:
     R1 = P64[R1 + 135] & (-8);
     Sp = Sp + 8;
     call (I64[R1])(R1) args: 8, res: 0, upd: 8;
 }
 }}}

 I haven't yet worked out where we decide which of these forms will be
 used.

--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/11823#comment:4>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list