[GHC] #7655: 7.6.2 Segmentation Fault/Bus Error in large exponentation

GHC ghc-devs at haskell.org
Sun Jul 27 21:08:46 UTC 2014


#7655: 7.6.2 Segmentation Fault/Bus Error in large exponentation
-------------------------------------+----------------------------------
              Reporter:  Doug310     |            Owner:
                  Type:  bug         |           Status:  infoneeded
              Priority:  normal      |        Milestone:  7.8.4
             Component:  GHCi        |          Version:  7.8.1-rc1
            Resolution:              |         Keywords:  exponentiation
      Operating System:  MacOS X     |     Architecture:  x86_64 (amd64)
       Type of failure:  GHCi crash  |       Difficulty:  Unknown
             Test Case:              |       Blocked By:
              Blocking:              |  Related Tickets:
Differential Revisions:              |
-------------------------------------+----------------------------------

Comment (by croyd):

 Hi, I think I ran in to this issue running the following code (fibonacci
 matrix exponentiation) in ghci. It seems to happen every single time I
 execute it inside ghci, but never when using the full compiler (ghc
 --make).

 {{{#!hs
 module Matrix where

 data Matrix = Matrix Integer Integer Integer Integer deriving (Eq, Show)

 instance Num Matrix where
         fromInteger n = Matrix n n n n
         negate = undefined
         (+) = plusMatrix
         (*) = mulMatrix
         abs (Matrix a00 a01 a10 a11) = Matrix a00' a01' a10' a11'
             where
                 a00' = abs a00
                 a01' = abs a01
                 a10' = abs a10
                 a11' = abs a11
         signum = undefined


 plusMatrix :: Matrix -> Matrix -> Matrix
 (Matrix a00 a01 a10 a11) `plusMatrix` (Matrix b00 b01 b10 b11) =
     Matrix (a00 + b00) (a01 + b01) (a10 + b10) (a11 + b11)

 mulMatrix :: Matrix -> Matrix -> Matrix
 (Matrix a00 a01 a10 a11) `mulMatrix` (Matrix b00 b01 b10 b11) =
     Matrix a00' a01' a10' a11'
            where
                a00' = a00 * b00 + a01 * b10
                a01' = a00 * b01 + a01 * b11
                a10' = a10 * b00 + a11 * b10
                a11' = a10 * b10 + a11 * b11

 fib4 :: Integer -> Integer
 fib4 0 = 0
 fib4 n = case f ^ n of
              Matrix _ fn _ _ -> fn
     where
         f = Matrix 1 1
                    1 0


 main = do
         print $ fib4 1000       -- ok
         putStrLn $ replicate 80 '-'
         print $ fib4 10000     -- ok
         putStrLn $ replicate 80 '-'
         print $ fib4 1000000 -- bus error: 10


 }}}

 crash report:
 {{{
 Process:         ghc [30070]
 Path:            /usr/local/lib/ghc-7.8.3/bin/ghc
 Identifier:      ghc
 Version:         ???
 Code Type:       X86-64 (Native)
 Parent Process:  bash [97679]
 User ID:         501

 Date/Time:       2014-07-27 15:30:12.594 -0500
 OS Version:      Mac OS X 10.8.4 (12E55)
 Report Version:  10

 Crashed Thread:  1

 Exception Type:  EXC_BAD_ACCESS (SIGBUS)
 Exception Codes: KERN_PROTECTION_FAILURE at 0x0000000115341000

 VM Regions Near 0x115341000:
     MALLOC metadata        000000011532c000-0000000115341000 [   84K]
 rw-/rwx SM=COW
 --> MALLOC guard page      0000000115341000-0000000115342000 [    4K]
 ---/rwx SM=NUL
     Stack                  0000000115342000-0000000115343000 [    4K]
 ---/rwx SM=NUL

 Thread 0:: Dispatch queue: com.apple.main-thread
 0   libsystem_kernel.dylib              0x00007fff8d3340fa __psynch_cvwait
 + 10
 1   libsystem_c.dylib                   0x00007fff8d853fe9
 _pthread_cond_wait + 869
 2   libHSrts_thr-ghc7.8.3.dylib         0x00000001152bde86 waitCondition +
 6
 3   libHSrts_thr-ghc7.8.3.dylib         0x0000000115297752 yieldCapability
 + 354
 4   libHSrts_thr-ghc7.8.3.dylib         0x00000001152a7f26 schedule + 502
 5   libHSrts_thr-ghc7.8.3.dylib         0x00000001152a7d17
 scheduleWaitThread + 167
 6   libHSrts_thr-ghc7.8.3.dylib         0x00000001152a3eea hs_main + 138
 7   ghc                                 0x000000010e8c6d73 main + 115
 8   ghc                                 0x000000010e7ddc34 start + 52

 Thread 1 Crashed:
 0   libHSinteger-gmp-0.5.1.0-ghc7.8.3.dylib     0x0000000115178811
 __gmpn_addlsh2_n + 289
 1   libHSinteger-gmp-0.5.1.0-ghc7.8.3.dylib     0x00000001151b87aa
 __gmpn_toom43_mul + 202
 2   libHSinteger-gmp-0.5.1.0-ghc7.8.3.dylib     0x0000000115196c6b
 __gmpn_mul + 1835
 3   libHSinteger-gmp-0.5.1.0-ghc7.8.3.dylib     0x000000011519d795
 __gmpn_tdiv_qr + 3221
 4   libHSinteger-gmp-0.5.1.0-ghc7.8.3.dylib     0x00000001151b4b88
 __gmpz_tdiv_qr + 408
 5   libHSinteger-gmp-0.5.1.0-ghc7.8.3.dylib     0x0000000115175b9f
 integer_cmm_quotRemIntegerzh + 207
 6   libHSbase-4.7.0.1-ghc7.8.3.dylib    0x0000000114af08f0 c6Zm_info + 56

 Thread 2:
 0   libsystem_kernel.dylib              0x00007fff8d334f96 poll + 10
 1   libHSbase-4.7.0.1-ghc7.8.3.dylib    0x0000000114be1444 cbep_info + 660
 2   ???                                 0x0000000115727e83 0 + 4654792323

 Thread 3:
 0   libsystem_kernel.dylib              0x00007fff8d334d16 kevent + 10
 1   libHSbase-4.7.0.1-ghc7.8.3.dylib    0x0000000114ba3de5 cbpC_info + 173
 2   libHSbase-4.7.0.1-ghc7.8.3.dylib    0x0000000114ba4908 cbuZ_info + 56

 Thread 4:
 0   libsystem_kernel.dylib              0x00007fff8d3340fa __psynch_cvwait
 + 10
 1   libsystem_c.dylib                   0x00007fff8d853fe9
 _pthread_cond_wait + 869
 2   libHSrts_thr-ghc7.8.3.dylib         0x00000001152bde86 waitCondition +
 6
 3   libHSrts_thr-ghc7.8.3.dylib         0x0000000115297752 yieldCapability
 + 354
 4   libHSrts_thr-ghc7.8.3.dylib         0x00000001152a7f26 schedule + 502
 5   libHSrts_thr-ghc7.8.3.dylib         0x00000001152a88bd scheduleWorker
 + 13
 6   libsystem_c.dylib                   0x00007fff8d84f7a2 _pthread_start
 + 327
 7   libsystem_c.dylib                   0x00007fff8d83c1e1 thread_start +
 13

 Thread 1 crashed with X86 Thread State (64-bit):
   rax: 0x0000000000000000  rbx: 0x000000000000045b  rcx:
 0xfffffffffffffe84  rdx: 0x00000001154a0b68
   rdi: 0x0000000115341bd0  rsi: 0x000000011549c5b8  rbp:
 0x0000000115338f40  rsp: 0x0000000115338ec8
    r8: 0x0000000000000001   r9: 0x0000000000000003  r10:
 0x0000000000000003  r11: 0x0000000000000003
   r12: 0xa37d223548939bc0  r13: 0x45cb5efb1fce45fd  r14:
 0x1ad82f94a68b146b  r15: 0xaef755979088a4bb
   rip: 0x0000000115178811  rfl: 0x0000000000010286  cr2:
 0x0000000115341000
 Logical CPU: 2

 Binary Images:
        0x10e7dc000 -        0x10e8cafff +ghc (???)
 <515FEFFC-8563-3E63-A019-2D36A4E5B376> /usr/local/lib/ghc-7.8.3/bin/ghc
        0x10e98f000 -        0x10ea80ff7
 +libHShaskeline-0.7.1.2-ghc7.8.3.dylib (0)
 <77838A66-EC3D-3443-AA05-484564631E96>
 /usr/local/lib/ghc-7.8.3/haskeline-0.7.1.2/libHShaskeline-0.7.1.2-ghc7.8.3.dylib
        0x10eb8e000 -        0x10eba8fff
 +libHSterminfo-0.4.0.0-ghc7.8.3.dylib (0)
 <F7B1336A-D768-35FB-A956-611BED7E9B16>
 /usr/local/lib/ghc-7.8.3/terminfo-0.4.0.0/libHSterminfo-0.4.0.0-ghc7.8.3.dylib
        0x10ebd8000 -        0x111533ff7 +libHSghc-7.8.3-ghc7.8.3.dylib (0)
 <7496A043-6E06-3D38-9E0C-86B2F1443163>
 /usr/local/lib/ghc-7.8.3/ghc-7.8.3/libHSghc-7.8.3-ghc7.8.3.dylib
        0x112fe9000 -        0x113037ffe
 +libHStransformers-0.3.0.0-ghc7.8.3.dylib (0) <760D119E-6E9D-3958-8EBD-
 5FD0AE08F661>
 /usr/local/lib/ghc-7.8.3/transformers-0.3.0.0/libHStransformers-0.3.0.0-ghc7.8.3.dylib
        0x1130d0000 -        0x113217ffb +libHStemplate-
 haskell-2.9.0.0-ghc7.8.3.dylib (0) <07A381B5-881A-34E7-A336-ED1E94B69C3D>
 /usr/local/lib/ghc-7.8.3/template-haskell-2.9.0.0/libHStemplate-
 haskell-2.9.0.0-ghc7.8.3.dylib
        0x1133a2000 -        0x1133b9ff8 +libHShpc-0.6.0.1-ghc7.8.3.dylib
 (0) <90B745B0-63A3-3339-8D3C-1D0864FFB3ED>
 /usr/local/lib/ghc-7.8.3/hpc-0.6.0.1/libHShpc-0.6.0.1-ghc7.8.3.dylib
        0x1133e0000 -        0x113427fff
 +libHShoopl-3.10.0.1-ghc7.8.3.dylib (0) <40C41B4C-9A7B-3179-876C-
 648C08E50D0C>
 /usr/local/lib/ghc-7.8.3/hoopl-3.10.0.1/libHShoopl-3.10.0.1-ghc7.8.3.dylib
        0x11349a000 -        0x1134abffe +libHSbin-package-
 db-0.0.0.0-ghc7.8.3.dylib (0) <3C63EAE8-C8F7-3E49-845E-51BB912CAD10>
 /usr/local/lib/ghc-7.8.3/bin-package-db-0.0.0.0/libHSbin-package-
 db-0.0.0.0-ghc7.8.3.dylib
        0x1134be000 -        0x113510ff9
 +libHSbinary-0.7.1.0-ghc7.8.3.dylib (0) <19FB0D1E-CADF-369D-AB5F-
 EFE63DB78B47>
 /usr/local/lib/ghc-7.8.3/binary-0.7.1.0/libHSbinary-0.7.1.0-ghc7.8.3.dylib
        0x11355d000 -        0x113b35ffe
 +libHSCabal-1.18.1.3-ghc7.8.3.dylib (0) <6E368272-1A7F-
 3C57-AAB0-4EBFC9AB09B2>
 /usr/local/lib/ghc-7.8.3/Cabal-1.18.1.3/libHSCabal-1.18.1.3-ghc7.8.3.dylib
        0x114104000 -        0x114113fff
 +libHSprocess-1.2.0.0-ghc7.8.3.dylib (0) <CE1B5F4C-46A2-320B-
 8CB6-2400EC97070F>
 /usr/local/lib/ghc-7.8.3/process-1.2.0.0/libHSprocess-1.2.0.0-ghc7.8.3.dylib
        0x11412a000 -        0x11413affe
 +libHSpretty-1.1.1.1-ghc7.8.3.dylib (0) <2CC28F0F-6F2F-3CEC-8A6F-
 DB9633147377>
 /usr/local/lib/ghc-7.8.3/pretty-1.1.1.1/libHSpretty-1.1.1.1-ghc7.8.3.dylib
        0x114151000 -        0x1142bcffe
 +libHScontainers-0.5.5.1-ghc7.8.3.dylib (0)
 <511470B1-0294-3F78-8BB7-CDC53E592EE1>
 /usr/local/lib/ghc-7.8.3/containers-0.5.5.1/libHScontainers-0.5.5.1-ghc7.8.3.dylib
        0x1143b1000 -        0x1143bffff
 +libHSdirectory-1.2.1.0-ghc7.8.3.dylib (0) <BBFAB672-10AD-
 326B-9080-09C1B8B04412>
 /usr/local/lib/ghc-7.8.3/directory-1.2.1.0/libHSdirectory-1.2.1.0-ghc7.8.3.dylib
        0x1143d7000 -        0x114431ff7 +libHSunix-2.7.0.1-ghc7.8.3.dylib
 (0) <82865E9A-9BBF-32B9-8A8A-31C61A1A87D7>
 /usr/local/lib/ghc-7.8.3/unix-2.7.0.1/libHSunix-2.7.0.1-ghc7.8.3.dylib
        0x1144c3000 -        0x11454cfff +libHStime-1.4.2-ghc7.8.3.dylib
 (0) <9F64C699-AEC9-372D-A926-A3D9114E5A40>
 /usr/local/lib/ghc-7.8.3/time-1.4.2/libHStime-1.4.2-ghc7.8.3.dylib
        0x1145fb000 -        0x114601ffb +libHSold-
 locale-1.0.0.6-ghc7.8.3.dylib (0) <1D324A30-3A30-3C2B-855B-BBE85CD3E46E>
 /usr/local/lib/ghc-7.8.3/old-locale-1.0.0.6/libHSold-
 locale-1.0.0.6-ghc7.8.3.dylib
        0x114611000 -        0x114621ffd
 +libHSfilepath-1.3.0.2-ghc7.8.3.dylib (0)
 <6A655401-5A48-3311-9F47-4913B98A1835>
 /usr/local/lib/ghc-7.8.3/filepath-1.3.0.2/libHSfilepath-1.3.0.2-ghc7.8.3.dylib
        0x11463e000 -        0x1146c9fff
 +libHSbytestring-0.10.4.0-ghc7.8.3.dylib (0) <37CA9ED5-C80A-3AEB-
 AE07-563EA9F8E0BC>
 /usr/local/lib/ghc-7.8.3/bytestring-0.10.4.0/libHSbytestring-0.10.4.0-ghc7.8.3.dylib
        0x11475a000 -        0x11475cff8
 +libHSdeepseq-1.3.0.2-ghc7.8.3.dylib (0) <DC275F7A-BBCD-
 319A-A454-2720B46982FD>
 /usr/local/lib/ghc-7.8.3/deepseq-1.3.0.2/libHSdeepseq-1.3.0.2-ghc7.8.3.dylib
        0x114769000 -        0x1147d4ff9 +libHSarray-0.5.0.0-ghc7.8.3.dylib
 (0) <40F4C2AD-861A-3048-AE8D-970E3D6915D3>
 /usr/local/lib/ghc-7.8.3/array-0.5.0.0/libHSarray-0.5.0.0-ghc7.8.3.dylib
        0x11483f000 -        0x114c17ff7 +libHSbase-4.7.0.1-ghc7.8.3.dylib
 (0) <363FAE50-2090-3B3F-B9CC-BAF20493C5A9>
 /usr/local/lib/ghc-7.8.3/base-4.7.0.1/libHSbase-4.7.0.1-ghc7.8.3.dylib
        0x115167000 -        0x1151d8fc7 +libHSinteger-
 gmp-0.5.1.0-ghc7.8.3.dylib (0) <1904D998-1201-3691-BFA6-0B7E8C73D9E2>
 /usr/local/lib/ghc-7.8.3/integer-gmp-0.5.1.0/libHSinteger-
 gmp-0.5.1.0-ghc7.8.3.dylib
        0x1151f7000 -        0x115240ff7 +libHSghc-
 prim-0.3.1.0-ghc7.8.3.dylib (0) <7A005B4C-2B84-3FC4-8A8E-F4384C458F17>
 /usr/local/lib/ghc-7.8.3/ghc-prim-0.3.1.0/libHSghc-
 prim-0.3.1.0-ghc7.8.3.dylib
        0x115295000 -        0x1152e5fff +libHSrts_thr-ghc7.8.3.dylib (0)
 <C4F957DB-DCE5-34D4-B4F3-495B54AB59B1> /usr/local/lib/ghc-7.8.3/rts-1.0
 /libHSrts_thr-ghc7.8.3.dylib
        0x11530d000 -        0x115310fff +libffi.dylib (7)
 <F1F11422-6371-3183-9256-5B85867D7B05>
 /usr/local/lib/ghc-7.8.3/rts-1.0/libffi.dylib
     0x7fff6e3dc000 -     0x7fff6e41093f  dyld (210.2.3)
 <A40597AA-5529-3337-8C09-D8A014EB1578> /usr/lib/dyld
     0x7fff83549000 -     0x7fff8354cff7  libdyld.dylib (210.2.3)
 <F59367C9-C110-382B-A695-9035A6DD387E> /usr/lib/system/libdyld.dylib
     0x7fff839a7000 -     0x7fff839afff7  libsystem_dnssd.dylib (379.38.1)
 <BDCB8566-0189-34C0-9634-35ABD3EFE25B>
 /usr/lib/system/libsystem_dnssd.dylib
     0x7fff83e54000 -     0x7fff83ea0ff7  libauto.dylib (185.4)
 <AD5A4CE7-CB53-313C-9FAE-673303CC2D35> /usr/lib/libauto.dylib
     0x7fff848cc000 -     0x7fff848d1fff  libcache.dylib (57) <65187C6E-
 3FBF-3EB8-A1AA-389445E2984D> /usr/lib/system/libcache.dylib
     0x7fff8519c000 -     0x7fff851a7fff  libsystem_notify.dylib (98.5)
 <C49275CC-835A-3207-AFBA-8C01374927B6>
 /usr/lib/system/libsystem_notify.dylib
     0x7fff8750c000 -     0x7fff8750dfff  libsystem_blocks.dylib (59)
 <D92DCBC3-541C-37BD-AADE-ACC75A0C59C8>
 /usr/lib/system/libsystem_blocks.dylib
     0x7fff8787a000 -     0x7fff87888fff  libcommonCrypto.dylib (60027)
 <BAAFE0C9-BB86-3CA7-88C0-E3CBA98DA06F>
 /usr/lib/system/libcommonCrypto.dylib
     0x7fff8793e000 -     0x7fff8793fff7  libremovefile.dylib (23.2)
 <6763BC8E-18B8-3AD9-8FFA-B43713A7264F> /usr/lib/system/libremovefile.dylib
     0x7fff8798b000 -     0x7fff8798cff7  libSystem.B.dylib (169.3)
 <365477AB-D641-389D-B8F4-A1FAE9657EEE> /usr/lib/libSystem.B.dylib
     0x7fff87bd0000 -     0x7fff87bd2ff7  libunc.dylib (25)
 <92805328-CD36-34FF-9436-571AB0485072> /usr/lib/system/libunc.dylib
     0x7fff88180000 -     0x7fff8818eff7  libsystem_network.dylib (77.10)
 <0D99F24E-56FE-380F-B81B-4A4C630EE587>
 /usr/lib/system/libsystem_network.dylib
     0x7fff8822b000 -     0x7fff88233fff  liblaunch.dylib (442.26.2)
 <2F71CAF8-6524-329E-AC56-C506658B4C0C> /usr/lib/system/liblaunch.dylib
     0x7fff88395000 -     0x7fff8848afff  libiconv.2.dylib (34)
 <FEE8B996-EB44-37FA-B96E-D379664DEFE1> /usr/lib/libiconv.2.dylib
     0x7fff889a9000 -     0x7fff88ac192f  libobjc.A.dylib (532.2) <90D31928
 -F48D-3E37-874F-220A51FD9E37> /usr/lib/libobjc.A.dylib
     0x7fff89440000 -     0x7fff89442fff  libquarantine.dylib (52.1)
 <143B726E-DF47-37A8-90AA-F059CFD1A2E4> /usr/lib/system/libquarantine.dylib
     0x7fff89696000 -     0x7fff896c4ff7  libsystem_m.dylib (3022.6)
 <B434BE5C-25AB-3EBD-BAA7-5304B34E3441> /usr/lib/system/libsystem_m.dylib
     0x7fff896c5000 -     0x7fff896e7ff7  libxpc.dylib (140.43)
 <70BC645B-6952-3264-930C-C835010CCEF9> /usr/lib/system/libxpc.dylib
     0x7fff8ac55000 -     0x7fff8ac5afff  libcompiler_rt.dylib (30)
 <08F8731D-5961-39F1-AD00-4590321D24A9>
 /usr/lib/system/libcompiler_rt.dylib
     0x7fff8bb78000 -     0x7fff8bb8dff7  libdispatch.dylib (228.23)
 <D26996BF-FC57-39EB-8829-F63585561E09> /usr/lib/system/libdispatch.dylib
     0x7fff8d2d2000 -     0x7fff8d321ff7  libcorecrypto.dylib (106.2)
 <CE0C29A3-C420-339B-ADAA-52F4683233CC> /usr/lib/system/libcorecrypto.dylib
     0x7fff8d322000 -     0x7fff8d33dff7  libsystem_kernel.dylib
 (2050.24.15) <A9F97289-7985-31D6-AF89-151830684461>
 /usr/lib/system/libsystem_kernel.dylib
     0x7fff8d83b000 -     0x7fff8d907ff7  libsystem_c.dylib (825.26)
 <4C9EB006-FE1F-3F8F-8074-DFD94CF2CE7B> /usr/lib/system/libsystem_c.dylib
     0x7fff8d9d9000 -     0x7fff8d9d9fff  libkeymgr.dylib (25)
 <CC9E3394-BE16-397F-926B-E579B60EE429> /usr/lib/system/libkeymgr.dylib
     0x7fff8dce2000 -     0x7fff8dce3fff  libDiagnosticMessagesClient.dylib
 (8) <8548E0DC-0D2F-30B6-B045-FE8A038E76D8>
 /usr/lib/libDiagnosticMessagesClient.dylib
     0x7fff8dd40000 -     0x7fff8dd41ff7  libsystem_sandbox.dylib (220.3)
 <B739DA63-B675-387A-AD84-412A651143C0>
 /usr/lib/system/libsystem_sandbox.dylib
     0x7fff8eb49000 -     0x7fff8eb4aff7  libdnsinfo.dylib (453.19)
 <14202FFB-C3CA-3FCC-94B0-14611BF8692D> /usr/lib/system/libdnsinfo.dylib
     0x7fff8eb4b000 -     0x7fff8eb70ff7  libc++abi.dylib (26)
 <D86169F3-9F31-377A-9AF3-DB17142052E4> /usr/lib/libc++abi.dylib
     0x7fff8ebc5000 -     0x7fff8ec2dff7  libc++.1.dylib (65.1)
 <20E31B90-19B9-3C2A-A9EB-474E08F9FE05> /usr/lib/libc++.1.dylib
     0x7fff8f14c000 -     0x7fff8f152fff  libmacho.dylib (829) <BF332AD9
 -E89F-387E-92A4-6E1AB74BD4D9> /usr/lib/system/libmacho.dylib
     0x7fff8f26d000 -     0x7fff8f2a5fff  libncurses.5.4.dylib (37.3)
 <68D5B5F5-8252-3F1E-AFF1-C6AFE145DBC1> /usr/lib/libncurses.5.4.dylib
     0x7fff8f4ef000 -     0x7fff8f4f6fff  libcopyfile.dylib (89)
 <876573D0-E907-3566-A108-577EAD1B6182> /usr/lib/system/libcopyfile.dylib
     0x7fff8f746000 -     0x7fff8f77cfff  libsystem_info.dylib (406.17)
 <4FFCA242-7F04-365F-87A6-D4EFB89503C1>
 /usr/lib/system/libsystem_info.dylib
     0x7fff8f77d000 -     0x7fff8f783ff7  libunwind.dylib (35.1) <21703D36
 -2DAB-3D8B-8442-EAAB23C060D3> /usr/lib/system/libunwind.dylib

 External Modification Summary:
   Calls made by other processes targeting this process:
     task_for_pid: 0
     thread_create: 0
     thread_set_state: 0
   Calls made by this process:
     task_for_pid: 0
     thread_create: 0
     thread_set_state: 0
   Calls made by all processes on this machine:
     task_for_pid: 11291
     thread_create: 1
     thread_set_state: 0

 VM Region Summary:
 ReadOnly portion of Libraries: Total=159.5M resident=138.3M(87%)
 swapped_out_or_unallocated=21.2M(13%)
 Writable regions: Total=52.5M written=21.6M(41%) resident=23.9M(46%)
 swapped_out=0K(0%) unallocated=28.6M(54%)

 REGION TYPE                      VIRTUAL
 ===========                      =======
 MALLOC                             18.2M
 MALLOC guard page                    16K
 STACK GUARD                        56.0M
 Stack                              10.0M
 VM_ALLOCATE                        19.0M
 __DATA                             5892K
 __LINKEDIT                         93.8M
 __TEXT                             65.7M
 shared memory                        12K
 ===========                      =======
 TOTAL                             268.5M

 }}}

 $ ghc --info
 {{{
  [("Project name","The Glorious Glasgow Haskell Compilation System")
  ,("GCC extra via C opts"," -fwrapv")
  ,("C compiler command","/usr/local/bin/gcc")
  ,("C compiler flags"," -m64 -fno-stack-protector")
  ,("C compiler link flags"," -m64")
  ,("Haskell CPP command","/usr/local/bin/gcc")
  ,("Haskell CPP flags","-E -undef -traditional ")
  ,("ld command","/usr/bin/ld")
  ,("ld flags"," -arch x86_64")
  ,("ld supports compact unwind","YES")
  ,("ld supports build-id","NO")
  ,("ld supports filelist","YES")
  ,("ld is GNU ld","NO")
  ,("ar command","/usr/bin/ar")
  ,("ar flags","clqs")
  ,("ar supports at file","NO")
  ,("touch command","touch")
  ,("dllwrap command","/bin/false")
  ,("windres command","/bin/false")
  ,("libtool command","libtool")
  ,("perl command","/usr/bin/perl")
  ,("target os","OSDarwin")
  ,("target arch","ArchX86_64")
  ,("target word size","8")
  ,("target has GNU nonexec stack","False")
  ,("target has .ident directive","True")
  ,("target has subsections via symbols","True")
  ,("Unregisterised","NO")
  ,("LLVM llc command","llc")
  ,("LLVM opt command","opt")
  ,("Project version","7.8.3")
  ,("Booter version","7.6.3")
  ,("Stage","2")
  ,("Build platform","x86_64-apple-darwin")
  ,("Host platform","x86_64-apple-darwin")
  ,("Target platform","x86_64-apple-darwin")
  ,("Have interpreter","YES")
  ,("Object splitting supported","NO")
  ,("Have native code generator","YES")
  ,("Support SMP","YES")
  ,("Tables next to code","YES")
  ,("RTS ways","l debug thr thr_debug thr_l thr_p dyn debug_dyn thr_dyn
 thr_debug_dyn l_dyn thr_l_dyn")
  ,("Support dynamic-too","YES")
  ,("Support parallel --make","YES")
  ,("Dynamic by default","NO")
  ,("GHC Dynamic","YES")
  ,("Leading underscore","YES")
  ,("Debug on","False")
  ,("LibDir","/usr/local/lib/ghc-7.8.3")
  ,("Global Package DB","/usr/local/lib/ghc-7.8.3/package.conf.d")
  ]
 }}}

 $ gcc --version
 {{{
 gcc (GCC) 4.9.0 20140302 (experimental)
 Copyright (C) 2014 Free Software Foundation, Inc.
 This is free software; see the source for copying conditions.  There is NO
 warranty; not even for MERCHANTABILITY or FITNESS FOR A PARTICULAR
 PURPOSE.
 }}}

 Please let me know if there's more I can do to help. I'd be willing to try
 and track down the issue myself, but I'm afraid I know next to nothing
 about ghc and it would probably take a lot more work helping me than it
 would to fix the issue otherwise.

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


More information about the ghc-tickets mailing list