Re: Bugs with GADTs in GHC6.4.1

2005-12-12 Thread Andres Loeh
 The attached script induces panic in GHC6.4.1: ghc-6.4.1: panic! (the 
 `impossible' happened, GHC version 6.4.1): applyTypeToArgs f{v a1Eg} 
 x{v a1Ei}.

I think this is related to a known bug, because the same workaround
helps -- annotate the f and x arguments in the last line of your
program with dummy type variables, and the program will be accepted:

 zap :: Vector n (a - b) - Vector n a - Vector n b
 zap fs xs = unfoldv f (len fs) (VP (fs, xs)) where
   f :: VectorPair (a-b) a (S n) - (b, VectorPair (a-b) a n)
   f (VP (VCons (f :: foo) fs, VCons (x :: bar) xs)) = (f x, VP (fs, xs))

Cheers,
  Andres
___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: bug in GADT typechecking

2005-11-28 Thread Andres Loeh
  {-# OPTIONS_GHC -fglasgow-exts #-}
  module Main where
  
  data Foo a b where
  Foo :: Int - Foo a b
  
  data Patch a b where
  PP :: Foo a b - Patch a b
  Lis :: PL a b - Patch a b
  
  data PL a b where
  U :: Patch a b - PL a b
  Nil :: PL x x
  (:-) :: PL c d - PL d e - PL c e
  
  data Pair alpha omega where
  (:.) :: Patch a i - Patch i o - Pair a o
  
  foo :: Pair a b - Maybe (Pair a b)
  foo (Lis (U x :- y) :. Lis Nil) = Just (PP x :. Lis y)
 
   
 
 Oddly enough, the code *does* typecheck if we change the above line to
 
 foo (Lis (U a :- b) :. Lis Nil) = Just (Lis (U a) :. Lis b)
 
 which differs only in here   

Looks to me as if ghc is right to complain. PP takes a Foo, but U takes
a Patch. Therefore the x that's matched on the lhs is a Patch, not a Foo.

 test.lhs:27:44:
 Couldn't match `Foo a b' against `Patch a1 d'
   Expected type: Foo a b
   Inferred type: Patch a1 d
 In the first argument of `PP', namely `x'
 In the first argument of `(:.)', namely `PP x'

 Glasgow Haskell Compiler, Version 6.4, for Haskell 98, compiled by GHC 
 version 6.4

FWIW, same error with ghc-6.5 from a few weeks ago.

Cheers,
  Andres
___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: problems building ghc 6.4.1_pre using 6.4 with multiplecabalversions installed

2005-09-13 Thread Andres Loeh
 Just glancing over the patch, I can't immediately see how it works.  GHC
 6.4 gives priority to package modules over modules on the local search
 path, so Distribution.* will be taken from the installed Cabal package.
 However, when linking GHC you are ommitting -package Cabal, so I'd
 expect a link error.
 
 Hmm, I guess I should try this and figure out what's happening.

The idea is that no installed Cabal version will be used. I think the
ghc distribution should just always build its own Cabal during stage1.
That's what the patch tries to achieve, and afaics, it works. However,
Duncan didn't give you the full story with the patch. We also do the
following:

echo GHC+=-ignore-package Cabal  mk/build.mk
echo HC+=-ignore-package Cabal  mk/build.mk

This was the only way I could find to make sure that a preinstalled
Cabal is ignored whenever the preinstalled ghc is called, but not once
the in-place ghc is available.

Cheers,
  Andres
___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


small error in building.xml

2005-08-05 Thread Andres Loeh
A recent change to the stable branch seems to have introduced a slight
error in docs/building/building.xml.

In line 3822, a /screen tag is missing.

The version that has this bug is 1.13.2.11.

Cheers,
  Andres
___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: exposed package exposes dependent packages

2005-04-06 Thread Andres Loeh
  Our example was compiling happy. happy does not import anything from
  cabal-0.5 and yet it was hit by this problem. Unless we consider 'part
  of the program' to be all modules in all exposed packages (and all
  modules in 'efectively exposed' packages like util via the cabal-0.5
  dep).
 
 You're asking GHC to decide which modules the program depends on, in
 order to figure out which packages are part of the program, rather than
 just starting from the list of exposed packages.
 
 Hmm, that might be possible... we could eagerly report module clashes in
 the exposed packages, but only report module clashes in the hidden
 packages when we know which ones are required.

This sounds like a good compromise to me. It would allow to have
some packages exposed which are not particularly well-behaved (i.e.,
pollute the name space), but you pay the price only when you're
actually using the package. 

The current situation is unfortunately very fragile. An exposed 
package that is accidentally added to the system can break the 
compilation of completely unrelated programs.

It'd be great if you could make this change in ghc.

Cheers,
  Andres
___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: HOpenGL buglet

2004-08-23 Thread Andres Loeh
Sven's fix that Simon M. mentioned will appear in 6.2.2 is included in
the Gentoo ebuild ghc-6.2.1-r1.ebuild .

If it still doesn't work with that version, please report it as a
Gentoo bug on bugs.gentoo.org.

Cheers,
  Andres

___
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


bug during documentation generation?

2003-12-18 Thread Andres Loeh
Shouldn't the attached patch be applied to the file package.mk
in the GHC 6.2 build system?

Explanation:
I think that for the generation of the documentation the new
ghc should be used, not the old one. I got the following error
while compiling GHC 6.2 with OpenGL support, using the binary
distribution of 6.2 for Linux, which seems to not support OpenGL.


==fptools== make html - --no-print-directory -r;
 in /var/tmp/portage/ghc-6.2/work/ghc-6.2/libraries/GLUT

/opt/ghc/bin/ghc -H16m -O -Wall -fffi -Iinclude '-#include HsGLUT.h' -cpp -DCA
LLCONV=ccall -package-name GLUT -O -Rghc-timing  -package base  -package OpenGL
-split-objs-D__HADDOCK__ -E -cpp Graphics/UI/GLUT.hs -o Graphics/UI/GLUT.hs.
tmp  sed -e 's/^#.*//' Graphics/UI/GLUT.hs.tmp Graphics/UI/GLUT.raw-hs
ghc-6.2: unknown package name: OpenGL
ghc: 2877832 bytes, 2 GCs, 51232/51232 avg/max bytes residency (1 samples), 5M
 in use, 0.00 INIT (0.00 elapsed), 0.00 MUT (0.02 elapsed), 0.01 GC (0.01 elapse
d) :ghc
make[2]: *** [Graphics/UI/GLUT.raw-hs] Error 1
make[1]: *** [html] Error 1
make: *** [html] Error 1

Best,
  Andres
diff -Naur ghc-6.2.orig/mk/package.mk ghc-6.2/mk/package.mk
--- ghc-6.2.orig/mk/package.mk  2003-12-17 16:26:11.0 +0100
+++ ghc-6.2/mk/package.mk   2003-12-17 16:27:21.0 +0100
@@ -237,10 +237,10 @@
 CLEAN_FILES += $(PACKAGE).haddock
 
 %.raw-hs : %.lhs
-   $(GHC) $(HC_OPTS) -D__HADDOCK__ -E -cpp $ -o $.tmp  sed -e 's/^#.*//' 
$.tmp $@
+   $(HC) $(HC_OPTS) -D__HADDOCK__ -E -cpp $ -o $.tmp  sed -e 's/^#.*//' 
$.tmp $@
 
 %.raw-hs : %.hs
-   $(GHC) $(HC_OPTS) -D__HADDOCK__ -E -cpp $ -o $.tmp  sed -e 's/^#.*//' 
$.tmp $@
+   $(HC) $(HC_OPTS) -D__HADDOCK__ -E -cpp $ -o $.tmp  sed -e 's/^#.*//' 
$.tmp $@
 
 install-docs :: $(HTML_DOC)
@$(INSTALL_DIR) $(datadir)/html/libraries/$(PACKAGE)
___
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


problem compiling OpenGL/.../Extensions.hs with GHC version 6.0

2003-06-02 Thread Andres Loeh
Hi.

The problem that Ralf Hinze reported with compiling GHC version 6.0
seems to be caused by the following:

The problematic line in the source file where the parse error is reported
reads (this is OpenGL/Graphics/Rendering/OpenGL/GL/Extensions.hs):

foreign import CALLCONV unsafe GET_PROC_ADDRESS glXGetProcAddressARB ::
   CString - IO (FunPtr a)

The CPP var GET_PROC_ADDRESS is set in the Makefile in OpenGL in the line:

SRC_HC_OPTS += -DCALLCONV=ccall '-DGET_PROC_ADDRESS=glXGetProcAddressARB'

The problem (that can be witnessed by calling ghc with the option -v) is
that in calling the C preprocessor, the double quotes around the value
of GET_PROC_ADDRESS, which are syntactically necessary, are no longer 
present. The problem can be fixed by quoting the double quotes once more,
i.e. by saying

SRC_HC_OPTS += -DCALLCONV=ccall '-DGET_PROC_ADDRESS=\glXGetProcAddressARB\'

However, this is a change in behaviour compared to earlier versions of
ghc that seems undesireable to me ...

One more thing: during compilation, ghc-inplace is called with the option
-Rghc-timing. I do not see it report timing-related messages, though.

Best,
  Andres

-- 

Andres Loeh, Universiteit Utrecht

mailto:[EMAIL PROTECTED] mailto:[EMAIL PROTECTED]
http://www.andres-loeh.de
___
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


linker error

2003-01-30 Thread Andres Loeh
Hi there,

while compiling the latest Generic Haskell version I got the following
linker error:

UHA_Parser.o(.text+0x117f13): In function `r18Ks_entry':
: undefined reference to `DataziTuple_Z94T_con_info'
collect2: ld returned 1 exit status


The file UHA_Parser.hs is a generated parser for the language, using
Ralf Hinze's frown parser generator.

When I first saw the error, I expected that too large tuples might be
used in that file (motivated by the undefined reference containing the
work Tuple and the number 94, which is higher than the GHC maximum
as declared in the User's guide), but browsing through the file it
does not seem to make much use of tuples at all.

In the meantime I found out that using -O2 to compile UHA_Parser
will circumvent the bug, so it is not really a problem.

The bug occurs with both yesterday's CVS 5.05 version and 5.04. 

I can try to produce a better bug description by cutting down the size
of the involved files at least a little bit, but I thought that maybe
you already know where to look ...

Best,
  Andres
___
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs