[GHC] #10539: ghc internal error compiling simple template haskell + lens program
GHC
ghc-devs at haskell.org
Wed Jun 17 16:29:30 UTC 2015
#10539: ghc internal error compiling simple template haskell + lens program
-------------------------------------+-------------------------------------
Reporter: andrew.wja | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.10.1
Keywords: lens | Operating System: Linux
template-haskell | Type of failure: Compile-time
Architecture: x86_64 | crash
(amd64) | Blocked By:
Test Case: | Related Tickets:
Blocking: |
Differential Revisions: |
-------------------------------------+-------------------------------------
The following happens when compiling a piece of Haskell code with GHC
7.10.1 (code at the bottom of this report). Compilation is successful with
GHC 7.8.4 -- both using lens-4.11, which makes this seem like a TH issue.
{{{#!sh
Building language-arithmetic-0.1.0.0...
Preprocessing library language-arithmetic-0.1.0.0...
[1 of 2] Compiling Language.Arithmetic.Syntax (
src/Language/Arithmetic/Syntax.hs, dist/build/Language/Arithmetic/Syntax.o
)
ghc: internal error: stg_ap_v_ret
(GHC version 7.10.1 for x86_64_unknown_linux)
Please report this as a GHC bug:
http://www.haskell.org/ghc/reportabug
Aborted (core dumped)
}}}
{{{#!hs
module Language.Arithmetic.Syntax where
import Control.Applicative hiding (Const)
import Control.Lens hiding (Const)
import Control.Lens.Plated
import Prelude hiding (const)
import Data.Data
data Arith a b c = Plus { _left :: (Arith a b c), _right :: (Arith a b
c) }
| Minus { _left :: (Arith a b c), _right :: (Arith a b
c) }
| Times { _left :: (Arith a b c), _right :: (Arith a b
c) }
| Divide { _left :: (Arith a b c), _right :: (Arith a b
c) }
| Modulo { _left :: (Arith a b c), _right :: (Arith a b
c) }
| Parens { _subexp :: (Arith a b c) }
| FunCall{ _name :: String, _subexp :: (Arith a b c) }
| Const { _const :: a}
| Var { _var :: b }
| Embed { _embed :: c }
deriving (Show, Eq, Ord, Data, Typeable)
makeLenses ''Arith
instance Plated (Arith a b c) where
plate = uniplate
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/10539>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list