Two regressions with Template Haskell on Windows:

---
{-# LANGUAGE TemplateHaskell #-}
module MkData where

import Language.Haskell.TH
import Language.Haskell.TH.Syntax


op a b = a + b

decl = [d| func = 0 `op` 3 |]
---

  This gives a very weird error:

C:\Users\JCAB\Haskell\THTest>ghc --make main.hs
[1 of 2] Compiling MkData           ( MkData.hs, MkData.o )
attempting to use module `main:MkData' (.\MkData.hs) which is not loaded

It is related to using inline named function operators `op` in declaration quotations in the same module. If the function is defined in another module, like `const` then everything works as expected.

  The other:

---
{-# 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
---

  Also gives a spooky error message:

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

I have verified that both were working with GHC 6.8.3. Fail with the latest beta 6.10.0.20080925.

JCAB

Ian Lynagh wrote:
We are pleased to announce that the GHC 6.10.0.20080921 snapshot is a
beta release of GHC 6.10.1.

You can download snapshots from here:

    http://www.haskell.org/ghc/dist/stable/dist/

Right now we have the source bundles:

http://www.haskell.org/ghc/dist/stable/dist/ghc-6.10.0.20080921-src.tar.bz2
http://www.haskell.org/ghc/dist/stable/dist/ghc-6.10.0.20080921-src-extralibs.tar.bz2

Only the first of these is necessary. The "extralibs" package contains
various extra packages that we normally supply with GHC - unpack the
extralibs tarball on top of the source tree to add them, and they will
be included in the build automatically.

There is also currently an installer for i386/Windows, and a binary
distribution for x86_64/Linux. More may appear later.

There are a couple of known problems with the x86_64/Linux bindist:
* It uses libedit.so.0 whereas some distributions (e.g. Debian) only
  provide libedit.so.2.
* It installs utilities like unlit in the wrong place, so compiling
  literate code won't work.
If you install from source then you won't hit either of those problems.

Please test as much as possible; bugs are much cheaper if we find them
before the release!

We hope to have release candidates followed by a release in around 3
weeks time, but of course that may slip if problems are uncovered.


Thanks
Ian, on behalf of the GHC team

_______________________________________________
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

_______________________________________________
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Reply via email to