[GHC] #14576: Internal error when compiling TH code with profiling on Windows

#14576: Internal error when compiling TH code with profiling on Windows -------------------------------------+------------------------------------- Reporter: lazac | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: GHC API | Version: 8.2.1 Keywords: | Operating System: Unknown/Multiple Architecture: x86_64 | Type of failure: Compile-time (amd64) | crash or panic Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- When using the GHC API with this minimal example, compiled with profiling enabled: {{{#!hs module Main where import GHC import GHC.Paths ( libdir ) main = runGhc (Just libdir) $ do env <- getSession dflags <- getSessionDynFlags setSessionDynFlags dflags target <- guessTarget "A.hs" Nothing setTargets [target] load LoadAllTargets }}} Invoking the main executable: {{{ testprof }}} While A.hs contains a TH splice: {{{#!hs {-# LANGUAGE TemplateHaskell #-} module A where $(return []) }}} The compiler crashes: {{{ testprof.exe: internal error: IMAGE_REL_AMD64_ADDR32[NB]: High bits are set in 10e6109d0 for .text (GHC version 8.2.1 for x86_64_unknown_mingw32) Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug This application has requested the Runtime to terminate it in an unusual way. Please contact the application's support team for more information. }}} The walkaround is to use -fexternal-interpreter, in that case, the crash does not happen. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14576 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14576: Internal error when compiling TH code with profiling on Windows -------------------------------------+------------------------------------- Reporter: lazac | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: GHC API | Version: 8.2.1 Resolution: | Keywords: Operating System: Windows | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by lazac): * os: Unknown/Multiple => Windows -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14576#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14576: Internal error when compiling TH code with profiling on Windows -------------------------------------+------------------------------------- Reporter: lazac | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: GHC API | Version: 8.2.1 Resolution: | Keywords: RemoteGHCi Operating System: Windows | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonmar): * cc: simonmar (added) * keywords: => RemoteGHCi -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14576#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14576: Internal error when compiling TH code with profiling on Windows -------------------------------------+------------------------------------- Reporter: lazac | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: GHC API | Version: 8.2.1 Resolution: | Keywords: RemoteGHCi Operating System: Windows | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by SoYman): I got a very similar error from the interpreter after doing these commands. {{{ Prelude Data.List> import qualified Data.Map.Strict as Map Prelude Data.List Map> data Dice = Dice Int Int Int Int Int Int deriving (Eq, Show) Prelude Data.List Map> Map.fromList [((0,0),(1, Dice 1 6 3 4 2 5))] ghc.exe: internal error: IMAGE_REL_AMD64_ADDR32[NB]: High bits are set in 13765d848 for .text (GHC version 8.4.3 for x86_64_unknown_mingw32) Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14576#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14576: Internal error when compiling TH code with profiling on Windows -------------------------------------+------------------------------------- Reporter: lazac | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: GHC API | Version: 8.2.1 Resolution: | Keywords: RemoteGHCi Operating System: Windows | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * cc: Phyx (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14576#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14576: Internal error when compiling TH code with profiling on Windows -------------------------------------+------------------------------------- Reporter: lazac | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: GHC API | Version: 8.2.1 Resolution: | Keywords: RemoteGHCi Operating System: Windows | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * cc: Phyx (removed) * cc: Phyx- (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14576#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC