#2633: Template Haskell and windres
-------------------------+--------------------------------------------------
Reporter: simonpj | Owner:
Type: bug | Status: new
Priority: normal | Milestone: 6.10.1
Component: Compiler | Version: 6.9
Severity: normal | Keywords:
Difficulty: Unknown | Testcase:
Architecture: Unknown | Os: Unknown
-------------------------+--------------------------------------------------
JCAB reports:
{{{
{-# LANGUAGE TemplateHaskell #-}
module MkData where
import Language.Haskell.TH
import Language.Haskell.TH.Syntax
decl name = returnQ $ [ DataD [] (mkName name) [] [RecC (mkName name) []]
[] ]
---
{-# LANGUAGE TemplateHaskell #-}
module Main where
import MkData
$(decl "KK")
main = undefined
}}}
gives the spooky error
{{{
C:\Users\JCAB\Haskell\THTest>ghc --make main.hs
[1 of 2] Compiling MkData ( MkData.hs, MkData.o )
[2 of 2] Compiling Main ( main.hs, main.o )
Loading package ghc-prim ... linking ... done.
Loading package integer ... linking ... done.
Loading package base ... linking ... done.
Loading package syb ... linking ... done.
Loading package array-0.2.0.0 ... linking ... done.
Loading package packedstring-0.1.0.1 ... linking ... done.
Loading package containers-0.2.0.0 ... linking ... done.
Loading package pretty-1.0.1.0 ... linking ... done.
Loading package template-haskell ... linking ... done.
Linking main.exe ...
C:\ghc\ghc-6.10.0.20080925\bin/windres: CreateProcess (null): Invalid
argument
}}}
Works in 6.8.3
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/2633>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs