[GHC] #8540: Template Haskell handling bug in ghc-7.7.20131115 under windows
GHC
ghc-devs at haskell.org
Tue Nov 19 05:05:38 UTC 2013
#8540: Template Haskell handling bug in ghc-7.7.20131115 under windows
----------------------------+----------------------------------
Reporter: awson | Owner:
Type: bug | Status: new
Priority: high | Milestone:
Component: Compiler | Version: 7.7
Keywords: | Operating System: Windows
Architecture: x86 | Type of failure: Runtime crash
Difficulty: Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: |
----------------------------+----------------------------------
Compiling this:
{{{
{-# LANGUAGE TemplateHaskell #-}
module Foo where
import Data.Aeson
import Data.Aeson.TH
data Test = Test
$(deriveFromJSON defaultOptions ''Test)
}}}
ghc-7.7.20131115 crashes with
{{{
Foo.hs:10:3:
Can't find interface-file declaration for variable
Data.Aeson.TH.parseTypeMismatch'
Probable cause: bug in .hi-boot file, or inconsistent .hi file
Use -ddump-if-trace to get an idea of which file caused the error
In the expression:
Data.Aeson.TH.parseTypeMismatch'
"Test"
"Foo.Test"
"an empty Array"
("Array of length " ++ ((show . Data.Vector.length) arr_a3BM))
In a case alternative:
Array arr_a3BM
| Data.Vector.null arr_a3BM -> Control.Applicative.pure Test
| otherwise
-> Data.Aeson.TH.parseTypeMismatch'
"Test"
"Foo.Test"
"an empty Array"
("Array of length " ++ ((show . Data.Vector.length)
arr_a3BM))
In the expression:
case value_a3BL of {
Array arr_a3BM
| Data.Vector.null arr_a3BM -> Control.Applicative.pure Test
| otherwise
-> Data.Aeson.TH.parseTypeMismatch'
"Test"
"Foo.Test"
"an empty Array"
("Array of length " ++ ((show . Data.Vector.length)
arr_a3BM))
other_a3BN
-> Data.Aeson.TH.parseTypeMismatch'
"Test" "Foo.Test" "Array" (Data.Aeson.TH.valueConName
other_a3BN) }
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/8540>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list