[ ghc-Bugs-746077 ] GHCi 5.02.3 dumps core

2003-05-30 Thread SourceForge.net
Bugs item #746077, was opened at 2003-05-30 16:18
Message generated for change (Tracker Item Submitted) made by Item Submitter
You can respond by visiting: 
https://sourceforge.net/tracker/?func=detail&atid=108032&aid=746077&group_id=8032

Category: Compiler
Group: 5.02
Status: Open
Resolution: None
Priority: 5
Submitted By: Nykänen, Matti (mnykanen)
Assigned to: Nobody/Anonymous (nobody)
Summary: GHCi 5.02.3 dumps core

Initial Comment:
(My e-mail is [EMAIL PROTECTED], just in
case my new SourceForge registration has problems.)

I get the following erratic behaviour - a SIGSEGV from
GHCi.
(The OS is some variant of Red Hat in use here at CS.
Dept of University of Helsinki (the birthplace of
Linux). The hardware is some generic Intel-based
desktop PC.)


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

Loading package std ... linking ... done.
Prelude> :l SegFault
Compiling SegFault ( SegFault.hs, interpreted )
Ok, modules loaded: SegFault.
SegFault> insert 1 2 None
Segmentation fault
valkokari$
---

The file I loaded is as follows (I hope the
xEmacs-generated
indentation came through):

---
module SegFault where

data Color = Red 
   | Black
 deriving Show

data Ord k => Tree k d = None 
   | Node{color::Color,
  key::k,
  item::d,
  left::(Tree k d),
  right::(Tree k d)}
 deriving Show

insert k i t = (insert2 t) {color=Black}
where insert2 None = Node{color=Red,
  key=k,
  item=i,
  left=None,
  right=None}
---

If write "where insert2 x = ..." instead, I get
something different (which may make more sense to you
than me):

---
valkokari$ ghci
   ___ ___ _
  / _ \ /\  /\/ __(_)
 / /_\// /_/ / /  | |  GHC Interactive, version
5.02.3, for Haskell 98.
/ /_\/ __  / /___| |  http://www.haskell.org/ghc/
\/\/ /_/\/|_|  Type :? for help.

Loading package std ... linking ... done.
Prelude> :l BadEta.hs
Compiling BadEta   ( BadEta.hs, interpreted )
Bad eta expand
(\ k{-aX8-} d{-aXa-} t_aXm zddOrd{-aXr-} ->
   let {
 zdmNode{-aWS-}
   = \ eta_s1e7 eta_s1e9 eta_s1eb eta_s1ed
eta_s1ef ->
   BadEta.Node{-rRX-}
 @ k{-aX8-}
 @ d{-aXa-}
 zddOrd{-aXr-}
 eta_s1e7
 eta_s1e9
 eta_s1eb
 eta_s1ed
 eta_s1ef
   } in
 \ k{-rS6-} i{-rS7-} t{-rS8-} tpl_X1J ->
   BadEta.zdwNode{-rSs-}
 @ k{-aX8-}
 @ d{-aXa-}
 k{-rS6-}
 i{-rS7-}
 (BadEta.zdwNone{-rSr-} @ k{-aX8-} @ d{-aXa-})
 (BadEta.zdwNone{-rSr-} @ k{-aX8-} @ d{-aXa-})
 tpl_X1J)
  @ k{-aX8-} @ d{-aXa-} @ t_aXm eta_s1ei eta_s1eA
eta_s1eC eta_s1eE
BadEta.Tree{-rRL-} k{-aX8-} d{-aXa-}
Ok, modules loaded: BadEta.
BadEta> insert 1 2 None
Segmentation fault
valkokari$
--

That is, then GHCi first complains about a bad eta
expansion, but nevertheless claims to have successfully
loaded the module, but still ends up crashing.



--

You can respond by visiting: 
https://sourceforge.net/tracker/?func=detail&atid=108032&aid=746077&group_id=8032
___
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


RE: Ways and Build Tags for Optimisation

2003-05-30 Thread Simon Peyton-Jones
| For some reason, even though only getCharacterName is exported, when
| optimisation is switched on, the interface file balloons a
thousandfold:
| 
| $ ls -l UnicodeNames.*hi
| -rw-r--r--1 ashley   ashley5854480 May 28 02:49
UnicodeNames.hi
| -rw-r--r--1 ashley   ashley5854497 May 28 06:56
UnicodeNames.p_hi
| -rw-r--r--1 ashley   ashley   2385 May 28 15:59
UnicodeNames.q_hi
| 
| What's the best way to stop this? Is it reasonable to simply switch
off
| profiling just for these few files?

Ashley

We'd like to understand why the file gets so much bigger. Can you send
us the smallest example you can that shows the 1000x ballooning?

Thanks

Simon


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


[ ghc-Bugs-745755 ] coreSyn/coreUtils.lhs:1188 Non-exhaustive patterns

2003-05-30 Thread SourceForge.net
Bugs item #745755, was opened at 2003-05-29 20:57
Message generated for change (Comment added) made by simonpj
You can respond by visiting: 
https://sourceforge.net/tracker/?func=detail&atid=108032&aid=745755&group_id=8032

Category: Compiler
Group: 6.0
Status: Open
Resolution: None
Priority: 5
Submitted By: Esa Pulkkinen (esapulkkinen)
Assigned to: Nobody/Anonymous (nobody)
Summary: coreSyn/coreUtils.lhs:1188 Non-exhaustive patterns

Initial Comment:
ghc-6.0: panic! (the `impossible' happened, GHC version
6.0):
coreSyn/CoreUtils.lhs:1188: Non-exhaustive
patterns in function isCrossDllArg

Options used for compiling:

ghc -syslib data -syslib text -fglasgow-exts -W
-fno-prune-tydecls -fallow-overlapping-instances
-fno-warn-unused-matches -fallow-undecidable-instances
  -o cifl --make Main.lhs

ghci handles that code fine. I didn't include the code,
since it's quite a lot of code, and from the error I'd
expect it's not that useful for finding the problem.
-- 
  Esa Pulkkinen

--

>Comment By: Simon Peyton Jones (simonpj)
Date: 2003-05-30 09:21

Message:
Logged In: YES 
user_id=50165

It would actually be easier to find this if you submitted the 
souce code, preferably cut down a bit.  Can you do that, 
please?  What's your email address?

--

You can respond by visiting: 
https://sourceforge.net/tracker/?func=detail&atid=108032&aid=745755&group_id=8032
___
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


RE: building ghc from source

2003-05-30 Thread Mike Thomas
Hi again.

| Sorry if I seem to be rejecting your offer to help.

That doesn't worry me!!

| At the 
| moment I just want 
| to get greencard, win32, x11 and hgl out the door.  I'm tired of 
| endlessly 
| tweaking makefiles...

No worries and good luck.

Cheers

Mike Thomas.


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


[ ghc-Bugs-745755 ] coreSyn/coreUtils.lhs:1188 Non-exhaustive patterns

2003-05-30 Thread SourceForge.net
Bugs item #745755, was opened at 2003-05-29 20:57
Message generated for change (Tracker Item Submitted) made by Item Submitter
You can respond by visiting: 
https://sourceforge.net/tracker/?func=detail&atid=108032&aid=745755&group_id=8032

Category: Compiler
Group: 6.0
Status: Open
Resolution: None
Priority: 5
Submitted By: Esa Pulkkinen (esapulkkinen)
Assigned to: Nobody/Anonymous (nobody)
Summary: coreSyn/coreUtils.lhs:1188 Non-exhaustive patterns

Initial Comment:
ghc-6.0: panic! (the `impossible' happened, GHC version
6.0):
coreSyn/CoreUtils.lhs:1188: Non-exhaustive
patterns in function isCrossDllArg

Options used for compiling:

ghc -syslib data -syslib text -fglasgow-exts -W
-fno-prune-tydecls -fallow-overlapping-instances
-fno-warn-unused-matches -fallow-undecidable-instances
  -o cifl --make Main.lhs

ghci handles that code fine. I didn't include the code,
since it's quite a lot of code, and from the error I'd
expect it's not that useful for finding the problem.
-- 
  Esa Pulkkinen

--

You can respond by visiting: 
https://sourceforge.net/tracker/?func=detail&atid=108032&aid=745755&group_id=8032
___
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: ANNOUNCE: GHC version 6.0

2003-05-30 Thread Ralf Hinze
> Please report bugs using our SourceForge page at
>
>   http://sourceforge.net/projects/ghc/
>
> or send them to [EMAIL PROTECTED]

Compiling 6.0 from source fails with:

../../ghc/compiler/ghc-inplace -H16m -O -Wall -fffi -Iinclude '-#include "HsOpenGL.h"' 
-cpp -I/usr/X11R6/include -DCALLCONV=ccall '-DGET_PROC_ADDRESS="glXGetProcAddressARB"' 
-package-name OpenGL -O -Rghc-timing  -package base -split-objs-c 
Graphics/Rendering/OpenGL/GL/Extensions.hs -o 
Graphics/Rendering/OpenGL/GL/Extensions.o  -ohi 
Graphics/Rendering/OpenGL/GL/Extensions.hi
Graphics/Rendering/OpenGL/GL/Extensions.hs:42: parse error on input 
`glXGetProcAddressARB'
<>
make[2]: *** [Graphics/Rendering/OpenGL/GL/Extensions.o] Fehler 1
make[1]: *** [all] Fehler 1
make[1]: Leaving directory `/var/tmp/portage/ghc-6.0/work/stage2-build/libraries'
make: *** [build] Fehler 1

Cheers, Ralf

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


Re: GHC *is* resource hungry

2003-05-30 Thread Ralf Hinze
> I bet it's massive types.  Translate the program into system F and see.
> (I remember this came up when looking at Okasaki's sequences of code
> combinators.)

Ok. I didn't use System Fomega (no compiler at hand) but GHC's
data types with locally quantified fields. Here is the original
program (I added type signatures and swapped the argument of `leaf').

> type CPS a = forall ans . (a -> ans) -> ans
> begin :: CPS (a -> a)
> begin next = next id
> leaf :: Int -> (Int -> a) -> CPS a
> leaf i k next = next (k i)
> fork :: (Int -> a) -> CPS (Int -> Int -> a)
> fork k next = next (\ t u -> k (t + u))
> end :: a -> a
> end x = x
> main = print (begin fork fork fork fork fork fork fork fork fork fork (leaf 0) (leaf 
> 0) (leaf 0) (leaf 0) (leaf 0) (leaf 0) (leaf 0) (leaf 0) (leaf 0) (leaf 0) (leaf 0) 
> end)

Still massive problems.

Now, if I turn the `type' into a `newtype' declaration and insert a few
identity functions (`CPS' and `#'), then GHC compiles the program like a charm.
The charm of the original program is, of course, gone.

> newtype CPS a = CPS (forall ans . (a -> ans) ->  ans)
> infixl 9 #
> CPS m # k = m k
> begin :: CPS (a -> a)
> begin = CPS (\ next -> next id)
> leaf :: Int -> (Int -> a) -> CPS a
> leaf i k = CPS (\ next -> next (k i))
> fork :: (Int -> a) -> CPS (Int -> Int -> a)
> fork k = CPS (\ next -> next (\ t u -> k (t + u)))
> end :: a -> a
> end x = x
> main = print (begin # fork # fork # fork # fork # fork # fork # fork # fork # fork # 
> fork # leaf 0 # leaf 0 # leaf 0 # leaf 0 # leaf 0 # leaf 0 # leaf 0 # leaf 0 # leaf 
> 0 # leaf 0 # leaf 0 # end)

Maybe this helps to identify the source of the problem.

Cheers, Ralf

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