RE: [Haskell-cafe] Template Haskell -- Bug?

2005-10-26 Thread Simon Peyton-Jones

| $ ghc --make THTest1.hs
| Chasing modules from: THTest1.hs
| Compiling THTest1TH( ./THTest1TH.hs, ./THTest1TH.o )
| Compiling THTest1  ( THTest1.hs, THTest1.o )
| 
| THTest1.hs:10:4: `incrSelf' is not a (visible) method of class
`IncrSelf'

I've now fixed this bug, in the HEAD.  The fix will appear in 6.4.2 (if
we release that).  

Thanks for reporting it.

Simon
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Template Haskell -- Bug?

2005-10-24 Thread Gracjan Polak

Simon Marlow wrote:

$ ghc -v
Glasgow Haskell Compiler, Version 6.4, for Haskell 98, compiled by GHC


Please try again with 6.4.1; lots of bugs were fixed.



Stupid me. I could swear I upgraded, but in fact did not.

Checked with 6.4.1, works as expected, thanks.

BTW: Does anybody have binary version of wxHaskell for windows and GHC 
6.4.1? Or is there any way of forcing GHC 6.4.1 to use hi files from ghc 
6.4?


--
Gracjan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Template Haskell -- Bug?

2005-10-21 Thread Simon Peyton-Jones
| $ ghc --make THTest1.hs
| Chasing modules from: THTest1.hs
| Compiling THTest1TH( ./THTest1TH.hs, ./THTest1TH.o )
| Compiling THTest1  ( THTest1.hs, THTest1.o )
| 
| THTest1.hs:10:4: `incrSelf' is not a (visible) method of class
`IncrSelf'

This is definitely a bug.  I'll look into it.  Thanks!

Simon
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Template Haskell -- Bug?

2005-10-21 Thread Simon Marlow
On 20 October 2005 14:03, Gracjan Polak wrote:

> $ ghc --make THTest1.hs
> Chasing modules from: THTest1.hs
> Skipping  THTest1TH( ./THTest1TH.hs, ./THTest1TH.o )
> Compiling THTest1  ( THTest1.hs, THTest1.o )
> Loading package base-1.0 ... linking ... done.
> Loading package haskell98-1.0 ... linking ... done.
> Loading package template-haskell-1.0 ... linking ... done.
> (here core dump, aka 0xc0001)
> 
> 
> 
> First of all, I do not understand the error in first compilation.
> Second, core dump is not nice :)
> 
> My config:
> 
> Windows XP Home,
> 
> $ ghc -v
> Glasgow Haskell Compiler, Version 6.4, for Haskell 98, compiled by GHC

Please try again with 6.4.1; lots of bugs were fixed.

Cheers,
Simon
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Template Haskell -- Bug?

2005-10-20 Thread Wolfgang Jeltsch
Am Donnerstag, 20. Oktober 2005 15:02 schrieb Gracjan Polak:
> Hi,
>
> Could somebody try to compile these two files *TWICE*?

Hello Gracjan,

I did so, using GHC 6.4.1 on Debian GNU/Linux, installed from the binary 
archive for generic Linux.

Upon the first run, I got the same messages, you got.  Upon the second run, I 
got the following output:

Chasing modules from: THTest1.hs
Skipping  THTest1TH( ./THTest1TH.hs, ./THTest1TH.o )
Compiling THTest1  ( THTest1.hs, THTest1.o )
Loading package base-1.0 ... linking ... done.
Loading package haskell98-1.0 ... linking ... done.
Loading package template-haskell-1.0 ... linking ... done.

THTest1.hs:1:0:
Couldn't match `Maybe (a, b)' against `(a1, b1)'
  Expected type: Maybe (a, b)
  Inferred type: (a1, b1)
In the third argument of `maybe', namely `value[a1Qx]'
In the definition of `value2[a1QD]':
value2[a1QD] = maybe Nothing (Just . snd) value[a1Qx]

THTest1.hs:1:0:
Couldn't match `Maybe (a, b)' against `(a1, b1)'
  Expected type: Maybe (a, b)
  Inferred type: (a1, b1)
In the third argument of `maybe', namely `value[a1Qx]'
In the definition of `value1[a1QC]':
value1[a1QC] = maybe Nothing (Just . fst) value[a1Qx]

> [...]

Best wishes,
Wolfgang
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Template Haskell -- Bug?

2005-10-20 Thread Gracjan Polak


Hi,

Could somebody try to compile these two files *TWICE*? GHC dumps core at 
me. I don't know if it is something about me, or something more general 
:) I'd like to know a bit more, before I bother anybody from devel team.


Log:

$ ghc --make THTest1.hs
Chasing modules from: THTest1.hs
Compiling THTest1TH( ./THTest1TH.hs, ./THTest1TH.o )
Compiling THTest1  ( THTest1.hs, THTest1.o )

THTest1.hs:10:4: `incrSelf' is not a (visible) method of class `IncrSelf'

$ ghc --make THTest1.hs
Chasing modules from: THTest1.hs
Skipping  THTest1TH( ./THTest1TH.hs, ./THTest1TH.o )
Compiling THTest1  ( THTest1.hs, THTest1.o )
Loading package base-1.0 ... linking ... done.
Loading package haskell98-1.0 ... linking ... done.
Loading package template-haskell-1.0 ... linking ... done.
(here core dump, aka 0xc0001)



First of all, I do not understand the error in first compilation. 
Second, core dump is not nice :)


My config:

Windows XP Home,

$ ghc -v
Glasgow Haskell Compiler, Version 6.4, for Haskell 98, compiled by GHC 
version 6.2.2

Using package config file: c:\ghc\ghc-6.4\package.conf
Using package config file: C:\Documents and Settings\gracjan\Application 
Data\ghc/i386-mingw32-6.4/package.conf


Default windows package as taken from www.haskell.org.

--
Gracjan


{-# OPTIONS -fglasgow-exts -fth -fallow-undecidable-instances #-}


module THTest1TH
(
  instanceIncrSelfTuple,
  IncrSelf(..)
)
where
import Control.Monad
import Data.Maybe
import Language.Haskell.TH

class IncrSelf a where
incrSelf :: a -> a

instance Num a => IncrSelf a where
incrSelf x = x + 1



sel' :: Int -> Int -> ExpQ
sel' i n = lamE [pat] rhs
where pat = tupP (map varP as)
  rhs = varE (as !! (i - 1))
  as = map mkName [ ("a__" ++ show j) | j <- [1..n] ]


instanceIncrSelfTuple :: Int -> Q [Dec]
instanceIncrSelfTuple n = do
 decs <- qOfDecs
 let listOfDecQ = map return decs
 conIncrSelf = conT ''IncrSelf
 name_a = mkName "a"
 name_b = mkName "b"
 name_c = mkName "c"
 var_a = varT name_a
 var_b = varT name_b
 var_c = varT name_c
 dec <- instanceD (sequence [appT conIncrSelf var_a,appT conIncrSelf var_b])
(appT conIncrSelf
  (appT
 (appT (tupleT 2)
   var_a
 )
 var_b
   )
 )
listOfDecQ
 return [dec]
 where qOfDecs = [d|
incrSelf value =
let
value1 = maybe Nothing (Just . fst) value
value2 = maybe Nothing (Just . snd) value
in error "adfasf" -- (incrSelf value1, incrSelf value2)
|]



{-# OPTIONS -fglasgow-exts -fth -fallow-undecidable-instances  #-}

module THTest1
where
import THTest1TH


instance IncrSelf String where
incrSelf x = x ++ "x"

$(instanceIncrSelfTuple 2)


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe