ghc-5.02.x: getTcTyVar

2001-12-27 Thread Armin Groesslinger

Hello,

when I try to compile the program below with ghc -fglasgow-exts
-fallow-undecidable-instances  ghc-5.02.1 and 5.02.2 (from today's
CVS) go into an infinite loop saying

getTcTyVar c{-r4D-}

all the time instead of complaining for the missing
instance X T c  to derive  Show S .


Regards,

Armin



module Test where

data T = T Integer

class X a b | a - b where
f :: a - b

instance X T c = Show T where
show _ = 

data S = S T deriving Show


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



typecheck/TcMonad.lhs:736: Non-exhaustive patterns in function pp_orig

2001-11-01 Thread Armin Groesslinger

Hello,

feeding the (incorrect) program given below to ghc (version 5.02 or
today's CVS version from ghc-5-02-branch ) results in

Test.hs:8:
Could not deduce (Integral (Ratio a)) from the context (Integral
a)
Probable fix:
Add (Integral (Ratio a)) to the type signature(s) for f
Or add an instance declaration for (Integral (Ratio a))
arising fromghc-5.02.1: panic! (the `impossible' happened, GHC
version 5.02.1):
typecheck/TcMonad.lhs:736: Non-exhaustive patterns in function 
pp_orig


If my quick look at TcMonad.lhs is correct, pp_orig doesn't
handle RecordUpdOrigin and DataDeclOrigin.

Regards,

Armin


module Test where

import Ratio

data Integral a = P a = P { p :: a }

f :: Integral a = P (Ratio a) - P (Ratio a)
f x = x { p = p x }

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



ghc-5.02: panic! NoCgInfo!

2001-10-16 Thread Armin Groesslinger

Hello,

when I try to compile the program below with ghc -fglasgow-exts
it says

ghc-5.02: panic! (the `impossible' happened, GHC version 5.02):
NoCgInfo!


I couldn't find a smaller example because little modifications make
the problem go away, e.g.

 - removing the type signature for `k'

 - replacing `y ([] ++ [[]] ++ [])' by `y ([] ++ [[]])'

 - changing the definition of `g' or `h', e.g.
 h ys = map (k (y [[0]])) ys


Regards,

Armin



module Test where

import List (transpose)

data X a = X a

class Y a b | a - b where
y :: a - X b

instance Y [[a]] a where
y ((x:_):_) = X x

g :: Num a = [X a] - [X a]
g xs = h xs
where
h ys = ys ++ map (k (y [[0]])) xs

k :: X a - X a - X a
k _ _ = y ([] ++ [[]] ++ [])

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



unhandled ELF relocation(RelA) type 23

2001-07-19 Thread Armin Groesslinger

Hello,

when compiling GHC 5.00.x on Solaris with gcc 2.95.x
I get this error when trying to start GHCI:

127 ghci
   ___ ___ _
  / _ \ /\  /\/ __(_)
 / /_\// /_/ / /  | |  GHC Interactive, version 5.00.2, For Haskell 98.
/ /_\\/ __  / /___| |  http://www.haskell.org/ghc/
\/\/ /_/\/|_|  Type :? for help.

Loading package std ... linking ... unhandled ELF relocation(RelA) type 23
ghc-5.00.2: fatal error: do_Elf32_Rela_relocations: unhandled ELF
relocation type



Looking at ghc/rts/Linker.c, (and finding out what type 23 is),
I applied the following patch to Linker.c, which seems to fix the
problem. I don't know much about reloction on Sparc, so I'm not
absolutely sure,  it is really correct, but I didn't experience any
problems.


Regards,

Armin


--- ghc-5.00.2/ghc/rts/Linker.c Thu Jun  7 18:36:41 2001
+++ ghc-5.00.2-p/ghc/rts/Linker.c   Thu Jul  5 16:55:00 2001
@@ -1677,6 +1677,7 @@
 w1 |= w2;
 *pP = w1;
 break;
+ case R_SPARC_UA32:
  case R_SPARC_32:
 w2 = (Elf32_Word)(S + A);
 *pP = w2;

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



ghci 5.00(.1) ignores -L ?

2001-05-25 Thread Armin Groesslinger

Hello,

I've been trying to start ghci 5.00 (Solaris) or 5.00.1 (Linux) with

  ghci -L/the/path -lglue

(where libglue.so is in /the/path), which should load (according to
Section 3.5.2 of the GHC Users Guide) libglue.so from /the/path, but
ghci says

Loading package std ... linking ... done.
Loading object (dynamic) glue ... failed (ld.so.1: /public/packages/
programming/ghc-5.00/lib/ghc-5.00/ghc-5.00: fatal: libglue.so:
open failed: No such file or directory)
ghc-5.00: user specified .o/.so/.DLL could not be loaded.


It doesn't matter whether I give  -L/the/path  or  -L/the/path/  .

It works fine with

  export LD_LIBRARY_PATH=/the/path
  ghci -lglue

and ghci says

Loading package std ... linking ... done.
Loading object (dynamic) glue ... done.
Prelude


Regards,

Armin

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



ghci-5.00: the `impossible' happened

2001-05-09 Thread Armin Groesslinger

Hello,

feeding the program

---
module Main where

import CForeign

foreign import puts puts :: CString - IO ()

main :: IO ()
main = return ()
---

to ghci-5.00 (with ghci -package lang -fglasgow-exts Main.hs
on x86/Linux) gives the following error:

Compiling Main ( Main.hs, interpreted )
ghc-5.00: panic! (the `impossible' happened, GHC version 5.00):
  bytecode generator can't handle unboxed tuples



Compiling the program with
 
  ghc -o main -package lang -fglasgow-exts Main.hs

does *not* give an error.


Regards,

Armin

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



Re[2]: [ANNOUNCE] HDoc: a javadoc for Haskell

2000-08-09 Thread Armin Groesslinger

On Tue, 08 Aug 2000 16:53:42 -0400 you wrote:

 Armin,
 
 Is HDoc also designed to work with the February 2000 version of Hugs98?
 
 Will it work under Linux and MacOS as well as under Win 32 (including Windows 2000)?
 
 --Benjamin L. Russell

HDoc should run on any version of Hugs98 as it follows the
Haskell 98 standard (except that it uses the GetOpt library,
which is available in Hugs and GHC).

At the moment, HDoc only understands "/" as separators for
directories, so it may fail under Windows (or does Windows
understand slashes, also?).

BTW, what is the path separator under MacOS ?

I'm only using Linux, so I didn't think of that problem and
cannot try what happens under other OSes and I can't
provide start scripts like hdoc.sh for Un*x   :-( 
I'll try to make a new version available tomorrow.

It is one of my aims to make HDoc run on any platform that
is supported by Hugs98 or GHC.

Armin.









[ANNOUNCE] HDoc: a javadoc for Haskell

2000-08-08 Thread Armin Groesslinger

Hello,

I have written a small program, HDoc, which can generate
HTML documents from specially annoted Haskell sources;
currently it is possible to document functions, data types,
classes and instances. The resulting documents are cross
linked and - IMHO - they look pretty nice. So, HDoc
does pretty the same job as javadoc does for Java.

Currently, _all_ the information is taken from special
comments, i.e. the Haskell code is simply ignored (I
found that it is very difficult (compared to Java) to
extract the necessary information from Haskell code.

Here's an example of what the special comments
for a function can look like (I admit, it looks a bit like
javadoc...)

{---
 @fun square :: Integer - Integer  !  Squares an integer.
 The number is multiplied by itself and the result is
  returned.

 @param x :: Integer! the number to be squared.
 @return res :: Integer ! the input number squared.
-}
square x = x * x

--

HDoc is not complete or ready for daily use; I'm looking for
some feedback/ideas etc. HDoc runs on Hugs98 and GHC 4.08
(other compilers may work, but I haven't tried).

You can get HDoc from its homepage at
http://www.fmi.uni-passau.de/~groessli/hdoc/

An example of HDoc's output (for three very simple
modules) can be viewed at
http://www.fmi.uni-passau.de/~groessli/hdoc/examples/simple/docs/


Please note again: HDoc is in a very early stage (it'll
get a re-write soon to reflect some experiences from the
first version). The main reason for announcing HDoc at this
time is that I definitely need some feedback on how useful
HDoc is or can eventually be and what concepts it should
follow etc.

So if you're interested, please give HDoc a try and send me
your ideas/suggestions/etc.

I'm looking forward to receiving your comments!


Cheers,

 Armin

 






Optimisation problem in pre-4.07-200000613 (and 4.06)

2000-06-24 Thread Armin Groesslinger

Dear GHC developers,

I think I have found an optimisation problem in GHC
pre-4.07-2613. I ran across that problem when compiling nhc98
(version 1.0pre19) without and then with -O. 

The follwoing program is a cut down version of a code excerpt from
nhc98 (taken from nhc98-1.0pre19/src/compiler98/EmitState.hs).

I tried this on
 - i386/Linux (Debian 2.2) with GHC 4.06 and pre-4.07-2613, gcc 2.95.2 
 - sparc/Solaris with GHC 4.06, gcc 2.7.2.3
The results were the same in all three configurations.


module Main where

data Label = Define String | Use String  deriving Show

testfun :: [Label] - String
testfun labs =
  let isUse (Use _) = True
  isUse  _ = False
  isDefine (Define _) = True
  isDefine  _ = False
  defines = filter isDefine labs
  uses= filter isUse labs
  externs = filter (\use- notElemBy useAfterDef use defines) uses
  notElemBy :: (a-b-Bool) - a - [b] - Bool
  notElemBy ok x = all (not . ok x)
  useAfterDef (Use sym) (Define sym') = (sym==sym')
  useAfterDef u d = error ("useAfterDef (" ++ show u ++ ") (" ++
   show d ++ ")\n")
  in
   concat (map show externs)

lablist1 = [Define "a"]

lablist2 = [Use "a",
Define "b",
Define "a"]

lablist3 = [Use "b",
Define "c",
Define "a",
Use "c",
Define "b",
Use "a"]

main :: IO ()
main = print (testfun lablist1)



The function `useAfterDef' is always called (due to the filters) as
"useAfterDef (Use _) (Define _)", so the `error ...' clause should
never be reached, right?

When I compile without -O, the program runs correctly, but with -O (or
-O2), the `... = error ...' clause is reached:


$ ghc -o main Main.hs  ./main
""

$ ghc -O -o main Main.hs  ./main

Fail: useAfterDef (Define "a") (Define "a")



With `lablist2' instead of `lablist1' the result is

Fail: useAfterDef (Define "b") (Define "b")

and with `lablist3' the program produces

Fail: useAfterDef (Define "c") (Define "c")



When I try to show the value of `uses' in the call to error, i.e.
... = error (show uses)
the problem disappers and the program runs correctly with -O.


Armin