GHC 6.8.1 on powerpc OS X 10.5

Chris Kuklewicz haskell at list.mightyreason.com
Thu Nov 15 18:57:44 EST 2007


Deborah Goldsmith wrote:
> I asked internally at Apple about this and got the following response:
>
>>>> obvious symptom: stage2 compiler segfaults, gdb reports:
>>>>> Program received signal SIGTRAP, Trace/breakpoint trap.
>>>>> 0x8fe0100c in __dyld__dyld_start ()
>>
>> Ignore that. `continue` to actually run the program and get to the
>> real error.
>
> Deborah
>

Ah, thanks.  It seems stage2/ghc-inplace may be a bit stripped, but
stage2/ghc-6.8.1 gives a legible backtrace:

> pamac-cek10:stage2 chrisk$ gdb ghc-6.8.1
> GNU gdb 6.3.50-20050815 (Apple version gdb-768) (Tue Oct  2 04:11:19 UTC 2007)
> Copyright 2004 Free Software Foundation, Inc.
> GDB is free software, covered by the GNU General Public License, and you are
> welcome to change it and/or distribute copies of it under certain conditions.
> Type "show copying" to see the conditions.
> There is absolutely no warranty for GDB.  Type "show warranty" for details.
> This GDB was configured as "powerpc-apple-darwin"...
> warning: Unable to read symbols for
"GNUreadline.framework/Versions/A/GNUreadline" (file not found).
>
> warning: Unable to read symbols for "GMP.framework/Versions/A/GMP" (file not
found).
> Reading symbols for shared libraries ... done
>

> (gdb) run --make /tmp/t.hs -o /tmp/t
> Starting program:
/Users/chrisk/Documents/projects/haskell/build/ghc-6.8.1/ghc-6.8.1/compiler/stage2/ghc-6.8.1
--make /tmp/t.hs -o /tmp/t
> Reading symbols for shared libraries +..+... done
>
> Program received signal EXC_BAD_ACCESS, Could not access memory.
> Reason: KERN_INVALID_ADDRESS at address: 0x4082000c
> 0x012ba9c8 in stg_ap_p_fast ()

> (gdb) bt
> #0  0x012ba9c8 in stg_ap_p_fast ()
> #1  0x010d79ec in base_GHCziIOBase_noDuplicate_info ()
> #2  0x01290e58 in schedule (initialCapability=0x41810070, task=0x38600000) at
Schedule.c:621
> #3  0x012933c8 in scheduleWaitThread (tso=0x2680000, ret=0x0, cap=0x14c4318)
at Schedule.c:2500
> #4  0x01285040 in rts_evalIO (cap=0x14c4318, p=0x13f40b4, ret=0x0) at RtsAPI.c:476
> #5  0x0129d310 in ioManagerStart () at posix/Signals.c:151
> #6  0x0128841c in hs_init (argc=0xbffff4a8, argv=0xbffff4ac) at RtsStartup.c:279
> #7  0x01288464 in startupHaskell (argc=5, argv=0xbffff594, init_root=0x113cc
<__stginit_ZCMain>) at RtsStartup.c:290
> #8  0x0127ebbc in real_main () at Main.c:57
> #9  0x0127ed1c in main (argc=5, argv=0xbffff594) at Main.c:153

A quick descent of the stack prints the single source lines:

Initial frame selected; you cannot go up.
(gdb) down
#8  0x0127ebbc in real_main () at Main.c:57
57	    startupHaskell(progargc,progargv,__stginit_ZCMain);
(gdb) down
#7  0x01288464 in startupHaskell (argc=5, argv=0xbffff594, init_root=0x113cc
<__stginit_ZCMain>) at RtsStartup.c:290
290	    hs_init(&argc, &argv);
(gdb) down
#6  0x0128841c in hs_init (argc=0xbffff4a8, argv=0xbffff4ac) at RtsStartup.c:279
279	    ioManagerStart();
(gdb) down
#5  0x0129d310 in ioManagerStart () at posix/Signals.c:151
151		rts_evalIO(cap,&base_GHCziConc_ensureIOManagerIsRunning_closure,NULL);
(gdb) down
#4  0x01285040 in rts_evalIO (cap=0x14c4318, p=0x13f40b4, ret=0x0) at RtsAPI.c:476
476	    return scheduleWaitThread(tso,ret,cap);
(gdb) down

#3  0x012933c8 in scheduleWaitThread (tso=0x2680000, ret=0x0, cap=0x14c4318) at
Schedule.c:2500
2500	    cap = schedule(cap,task);
(gdb) down

#2  0x01290e58 in schedule (initialCapability=0x41810070, task=0x38600000) at
Schedule.c:621
621		r = StgRun((StgFunPtr) stg_returnToStackTop, &cap->r);
(gdb) print r
$1 = (StgRegTable *) 0xabdffffc
(gdb) print &cap->r
$5 = (StgRegTable *) 0x7ddf7380
(gdb) print stg_returnToStackTop
$2 = {<text variable, no debug info>} 0x12b3784 <stg_returnToStackTop>
(gdb) down

#1  0x010d79ec in base_GHCziIOBase_noDuplicate_info ()
(gdb) down

#0  0x012ba9c8 in stg_ap_p_fast ()
(gdb) down
Bottom (i.e., innermost) frame selected; you cannot go down.

And disassemle the fatality

> (gdb) disassemble
> Dump of assembler code for function stg_ap_p_fast:
> 0x012ba9b0 <stg_ap_p_fast+0>:	andi.   r31,r14,3	
 And Immediate (to get the two least significant bits of r14)
> 0x012ba9b4 <stg_ap_p_fast+4>:	cmpwi   r31,1
 Equiv. to cmpi 0,0,r31,1
 Compare Immediate
> 0x012ba9b8 <stg_ap_p_fast+8>:	beq-    0x12ba9e0 <stg_ap_p_fast+48>
 Branch if equal
 (not taken, obviously, since the the next instructions are the fatal ones)
> 0x012ba9bc <stg_ap_p_fast+12>:	li      r31,-4
 Load Immediate (I believe -4 is the opposite bit pattern to 3)
> 0x012ba9c0 <stg_ap_p_fast+16>:	and     r14,r14,r31
 AND (to clear the two least significant bits of r14)
> 0x012ba9c4 <stg_ap_p_fast+20>:	lwz     r31,0(r14)
 Load Word and Zero
> 0x012ba9c8 <stg_ap_p_fast+24>:	lha     r31,-4(r31)
[ The error was for the above operation: Load Halfword Algebraic
  destination general purpose register r31
  source -4 displaced r31 ]
> 0x012ba9cc <stg_ap_p_fast+28>:	rlwinm  r31,r31,2,0,29
> 0x012ba9d0 <stg_ap_p_fast+32>:	addis   r31,r31,313
> 0x012ba9d4 <stg_ap_p_fast+36>:	lwz     r31,-28940(r31)
> 0x012ba9d8 <stg_ap_p_fast+40>:	mtctr   r31
> 0x012ba9dc <stg_ap_p_fast+44>:	bctr
> 0x012ba9e0 <stg_ap_p_fast+48>:	addi    r22,r22,0
> 0x012ba9e4 <stg_ap_p_fast+52>:	lwz     r31,-1(r14)
> 0x012ba9e8 <stg_ap_p_fast+56>:	mtctr   r31
> 0x012ba9ec <stg_ap_p_fast+60>:	bctr
> 0x012ba9f0 <stg_ap_p_fast+64>:	addi    r22,r22,-8
> 0x012ba9f4 <stg_ap_p_fast+68>:	stw     r15,4(r22)
> 0x012ba9f8 <stg_ap_p_fast+72>:	b       0x12b666c <stg_ap_p_info>
> 0x012ba9fc <stg_ap_p_fast+76>:	lwz     r31,0(r14)
> 0x012baa00 <stg_ap_p_fast+80>:	lha     r31,-10(r31)
> 0x012baa04 <stg_ap_p_fast+84>:	cmplwi  r31,0
> 0x012baa08 <stg_ap_p_fast+88>:	bgt-    0x12baa88 <stg_ap_p_fast+216>
> 0x012baa0c <stg_ap_p_fast+92>:	li      r3,0
> 0x012baa10 <stg_ap_p_fast+96>:	li      r4,2441
> 0x012baa14 <stg_ap_p_fast+100>:	bl      0x1287c80 <_assertFail>
> 0x012baa18 <stg_ap_p_fast+104>:	cmpwi   r31,1
> 0x012baa1c <stg_ap_p_fast+108>:	beq-    0x12baac8 <stg_ap_p_fast+280>
> 0x012baa20 <stg_ap_p_fast+112>:	addi    r22,r22,-8
> 0x012baa24 <stg_ap_p_fast+116>:	stw     r15,4(r22)
> 0x012baa28 <stg_ap_p_fast+120>:	cmplwi  r31,4
> 0x012baa2c <stg_ap_p_fast+124>:	blt-    0x12baa8c <stg_ap_p_fast+220>
> 0x012baa30 <stg_ap_p_fast+128>:	li      r30,16
> 0x012baa34 <stg_ap_p_fast+132>:	add     r25,r25,r30
> 0x012baa38 <stg_ap_p_fast+136>:	cmplw   r25,r26
> 0x012baa3c <stg_ap_p_fast+140>:	bgt-    0x12baa94 <stg_ap_p_fast+228>
> 0x012baa40 <stg_ap_p_fast+144>:	addi    r29,r25,4
> 0x012baa44 <stg_ap_p_fast+148>:	subf    r30,r30,r29
> 0x012baa48 <stg_ap_p_fast+152>:	lis     r29,298
> 0x012baa4c <stg_ap_p_fast+156>:	ori     r29,r29,60928
> 0x012baa50 <stg_ap_p_fast+160>:	stw     r29,0(r30)
> 0x012baa54 <stg_ap_p_fast+164>:	addi    r31,r31,-1
> 0x012baa58 <stg_ap_p_fast+168>:	sth     r31,4(r30)
> 0x012baa5c <stg_ap_p_fast+172>:	stw     r14,8(r30)
> 0x012baa60 <stg_ap_p_fast+176>:	li      r31,1
> 0x012baa64 <stg_ap_p_fast+180>:	sth     r31,6(r30)
> 0x012baa68 <stg_ap_p_fast+184>:	li      r31,0
> 0x012baa6c <stg_ap_p_fast+188>:	cmplwi  r31,1
> 0x012baa70 <stg_ap_p_fast+192>:	blt-    0x12baaa8 <stg_ap_p_fast+248>
> 0x012baa74 <stg_ap_p_fast+196>:	mr      r14,r30
> 0x012baa78 <stg_ap_p_fast+200>:	addi    r22,r22,8
> 0x012baa7c <stg_ap_p_fast+204>:	lwz     r31,0(r22)
> 0x012baa80 <stg_ap_p_fast+208>:	mtctr   r31
> 0x012baa84 <stg_ap_p_fast+212>:	bctr
> 0x012baa88 <stg_ap_p_fast+216>:	b       0x12baa18 <stg_ap_p_fast+104>
> 0x012baa8c <stg_ap_p_fast+220>:	add     r14,r14,r31
> 0x012baa90 <stg_ap_p_fast+224>:	b       0x12baa30 <stg_ap_p_fast+128>
> 0x012baa94 <stg_ap_p_fast+228>:	stw     r30,112(r27)
> 0x012baa98 <stg_ap_p_fast+232>:	lis     r31,299
> 0x012baa9c <stg_ap_p_fast+236>:	ori     r31,r31,26220
> 0x012baaa0 <stg_ap_p_fast+240>:	stw     r31,0(r22)
> 0x012baaa4 <stg_ap_p_fast+244>:	b       0x12af8ac <__stg_gc_enter_1>
> 0x012baaa8 <stg_ap_p_fast+248>:	addi    r29,r31,1
> 0x012baaac <stg_ap_p_fast+252>:	rlwinm  r29,r29,2,0,29
> 0x012baab0 <stg_ap_p_fast+256>:	lwzx    r29,r22,r29
> 0x012baab4 <stg_ap_p_fast+260>:	addi    r28,r30,12
> 0x012baab8 <stg_ap_p_fast+264>:	rlwinm  r23,r31,2,0,29
> 0x012baabc <stg_ap_p_fast+268>:	stwx    r29,r28,r23
> 0x012baac0 <stg_ap_p_fast+272>:	addi    r31,r31,1
> 0x012baac4 <stg_ap_p_fast+276>:	b       0x12baa6c <stg_ap_p_fast+188>
> 0x012baac8 <stg_ap_p_fast+280>:	addi    r22,r22,0
> 0x012baacc <stg_ap_p_fast+284>:	addi    r14,r14,1
> 0x012baad0 <stg_ap_p_fast+288>:	li      r31,-4
> 0x012baad4 <stg_ap_p_fast+292>:	and     r31,r14,r31
> 0x012baad8 <stg_ap_p_fast+296>:	lwz     r31,0(r31)
> 0x012baadc <stg_ap_p_fast+300>:	mtctr   r31
> 0x012baae0 <stg_ap_p_fast+304>:	bctr
> 0x012baae4 <stg_ap_p_fast+308>:	b       0x12baae4 <stg_ap_p_fast+308>
> End of assembler dump.

Where was the evil value in r14 filled in? I look up the stack and
disassemble, but never find the instructions which assign to r14.  The
must be in another subroutine (?).

What about printing stuff?

#2  0x01290e58 in schedule (initialCapability=0x41810070, task=0x38600000) at
Schedule.c:621
621		r = StgRun((StgFunPtr) stg_returnToStackTop, &cap->r);
(gdb) list
616		break;
617		
618	    case ThreadRunGHC:
619	    {
620		StgRegTable *r;
621		r = StgRun((StgFunPtr) stg_returnToStackTop, &cap->r);
622		cap = regTableToCapability(r);
623		ret = r->rRet;
624		break;
625	    }

#3  0x012933c8 in scheduleWaitThread (tso=0x2680000, ret=0x0, cap=0x14c4318) at
Schedule.c:2500
2500	    cap = schedule(cap,task);
(gdb) print *cap
$8 = {
  f = {
    stgGCEnter1 = 0x12af8ac <__stg_gc_enter_1>,
    stgGCFun = 0x12aff54 <__stg_gc_fun>
  },
  r = {
    rR1 = {
      w = 0,
      a = 0x0,
      c = 0,
      i8 = 0 '\0',
      f = 0,
      i = 0,
      p = 0x0,
      cl = 0x0,
      offset = 0,
      b = 0x0,
      t = 0x0
    },
    rR2 = {
      w = 0,
      a = 0x0,
      c = 0,
      i8 = 0 '\0',
      f = 0,
      i = 0,
      p = 0x0,
      cl = 0x0,
      offset = 0,
      b = 0x0,
      t = 0x0
    },
    rR3 = {
      w = 0,
      a = 0x0,
      c = 0,
      i8 = 0 '\0',
      f = 0,
      i = 0,
      p = 0x0,
      cl = 0x0,
      offset = 0,
      b = 0x0,
      t = 0x0
    },
    rR4 = {
      w = 0,
      a = 0x0,
      c = 0,
      i8 = 0 '\0',
      f = 0,
      i = 0,
      p = 0x0,
      cl = 0x0,
      offset = 0,
      b = 0x0,
      t = 0x0
    },
    rR5 = {
      w = 0,
      a = 0x0,
      c = 0,
      i8 = 0 '\0',
      f = 0,
      i = 0,
      p = 0x0,
      cl = 0x0,
      offset = 0,
      b = 0x0,
      t = 0x0
    },
    rR6 = {
      w = 0,
      a = 0x0,
      c = 0,
      i8 = 0 '\0',
      f = 0,
      i = 0,
      p = 0x0,
      cl = 0x0,
      offset = 0,
      b = 0x0,
      t = 0x0
    },
    rR7 = {
      w = 0,
      a = 0x0,
      c = 0,
      i8 = 0 '\0',
      f = 0,
      i = 0,
      p = 0x0,
      cl = 0x0,
      offset = 0,
      b = 0x0,
      t = 0x0
    },
    rR8 = {
      w = 0,
      a = 0x0,
      c = 0,
      i8 = 0 '\0',
      f = 0,
      i = 0,
      p = 0x0,
      cl = 0x0,
      offset = 0,
      b = 0x0,
      t = 0x0
    },
    rR9 = {
      w = 0,
      a = 0x0,
      c = 0,
      i8 = 0 '\0',
      f = 0,
      i = 0,
      p = 0x0,
      cl = 0x0,
      offset = 0,
      b = 0x0,
      t = 0x0
    },
    rR10 = {
      w = 0,
      a = 0x0,
      c = 0,
      i8 = 0 '\0',
      f = 0,
      i = 0,
      p = 0x0,
      cl = 0x0,
      offset = 0,
      b = 0x0,
      t = 0x0
    },
    rF1 = 0,
    rF2 = 0,
    rF3 = 0,
    rF4 = 0,
    rD1 = 0,
    rD2 = 0,
    rL1 = 0,
    rSp = 0x0,
    rSpLim = 0x0,
    rHp = 0x0,
    rHpLim = 0x0,
    rCurrentTSO = 0x2680000,
    rNursery = 0x24004d0,
    rCurrentNursery = 0x2600fe0,
    rCurrentAlloc = 0x2601000,
    rHpAlloc = 0,
    rmp_tmp_w = 0,
    rmp_tmp1 = {
      _mp_alloc = 0,
      _mp_size = 0,
      _mp_d = 0x0
    },
    rmp_tmp2 = {
      _mp_alloc = 0,
      _mp_size = 0,
      _mp_d = 0x0
    },
    rmp_result1 = {
      _mp_alloc = 0,
      _mp_size = 0,
      _mp_d = 0x0
    },
    rmp_result2 = {
      _mp_alloc = 0,
      _mp_size = 0,
      _mp_d = 0x0
    },
    rRet = 0,
    rSparks = {
      base = 0x2362000,
      lim = 0x2366000,
      hd = 0x2362000,
      tl = 0x2362000
    }
  },
  no = 0,
  running_task = 0x2400580,
  in_haskell = rtsTrue,
  run_queue_hd = 0x14076d0,
  run_queue_tl = 0x14076d0,
  suspended_ccalling_tasks = 0x0,
  mut_lists = 0x2400320,
  spare_workers = 0x0,
  lock = {
    __sig = 1297437784,
    __opaque = '\0' <repeats 16 times>, "\b", '\0' <repeats 22 times>
  },
  returning_tasks_hd = 0x0,
  returning_tasks_tl = 0x0,
  wakeup_queue_hd = 0x14076d0,
  wakeup_queue_tl = 0x14076d0,
  free_tvar_watch_queues = 0x14076c0,
  free_invariant_check_queues = 0x14076c4,
  free_trec_chunks = 0x14076c8,
  free_trec_headers = 0x14076cc,
  transaction_tokens = 0
}

(gdb) print task
$10 = (Task *) 0x2400580
(gdb) print *task
$11 = {
  id = 0xa032c074,
  cap = 0x14c4318,
  stopped = rtsFalse,
  suspended_tso = 0x0,
  tso = 0x2680000,
  stat = NoStatus,
  ret = 0x0,
  cond = {
    __sig = 1129270852,
    __opaque = '\0' <repeats 23 times>, "\002"
  },
  lock = {
    __sig = 1297437784,
    __opaque = '\0' <repeats 16 times>, "\b", '\0' <repeats 22 times>
  },
  wakeup = rtsFalse,
  elapsedtimestart = 1195167550991792,
  muttimestart = 12791,
  mut_time = 0,
  mut_etime = 0,
  gc_time = 0,
  gc_etime = 0,
  prev = 0x0,
  next = 0x0,
  return_link = 0x0,
  all_link = 0x0,
  prev_stack = 0x0
}
(gdb) print *tso
$13 = {
  header = {
    info = 0x12b3464
  },
  link = 0x14076d0,
  global_link = 0x14076d0,
  what_next = 1,
  why_blocked = 0,
  flags = 1,
  block_info = {
    closure = 0x0,
    tso = 0x0,
    fd = 0,
    target = 0
  },
  id = 1,
  saved_errno = 0,
  bound = 0x2400580,
  cap = 0x14c4318,
  trec = 0x14076cc,
  blocked_exceptions = 0x14076d0,
  stack_size = 241,
  max_stack_size = 2080753,
  sp = 0x26803ec,
  stack = 0x268003c
}
(gdb) list (with list - and list -)
2475	    Task *task;
2476	
2477	    // We already created/initialised the Task
2478	    task = cap->running_task;
2479	
2480	    // This TSO is now a bound thread; make the Task and TSO
2481	    // point to each other.
2482	    tso->bound = task;
2483	    tso->cap = cap;
2484	
2485	    task->tso = tso;
2486	    task->ret = ret;
2487	    task->stat = NoStatus;
2488	
2489	    appendToRunQueue(cap,tso);
2490	
2491	    debugTrace(DEBUG_sched, "new bound thread (%lu)", (unsigned long)tso->id);
2492	
2493	#if defined(GRAN)
2494	    /* GranSim specific init */
2495	    CurrentTSO = m->tso;                // the TSO to run
2496	    procStatus[MainProc] = Busy;        // status of main PE
2497	    CurrentProc = MainProc;             // PE to run it on
2498	#endif
2499	
2500	    cap = schedule(cap,task);
2501	
2502	    ASSERT(task->stat != NoStatus);
2503	    ASSERT_FULL_CAPABILITY_INVARIANTS(cap,task);
2504	

#4  0x01285040 in rts_evalIO (cap=0x14c4318, p=0x13f40b4, ret=0x0) at RtsAPI.c:476
476	    return scheduleWaitThread(tso,ret,cap);
(gdb) print p
$16 = (HaskellObj) 0x13f40b4
(gdb) print *p
$17 = {
  header = {
    info = 0x12b3324
  },
  payload = 0x13f40b8
}
(gdb) list
471	rts_evalIO (Capability *cap, HaskellObj p, /*out*/HaskellObj *ret)
472	{
473	    StgTSO* tso;
474	
475	    tso = createStrictIOThread(cap, RtsFlags.GcFlags.initialStkSize, p);
476	    return scheduleWaitThread(tso,ret,cap);
477	}
478	
479	/*
480	 * rts_evalStableIO() is suitable for calling from Haskell.  It

#5  0x0129d310 in ioManagerStart () at posix/Signals.c:151
151		rts_evalIO(cap,&base_GHCziConc_ensureIOManagerIsRunning_closure,NULL);
(gdb) list
146	{
147	    // Make sure the IO manager thread is running
148	    Capability *cap;
149	    if (io_manager_pipe < 0) {
150		cap = rts_lock();
151		rts_evalIO(cap,&base_GHCziConc_ensureIOManagerIsRunning_closure,NULL);
152		rts_unlock(cap);
153	    }
154	}
155	#endif


And this is the limit of what I can do with gdb for now.


More information about the Glasgow-haskell-users mailing list