RE: too liberal handling of instance imports?

2005-11-10 Thread Simon Marlow
Indeed, it is a known bug (I thought it was in SF too, but I can't find
it either).

The problem is a bit more restricted than just GHC doesn't respect the
importing structure when importing instances.  In particular, it works
properly if any of the following are true (I believe):

  - you are not using --make or GHCi
  - the instances are not in any external packages

in other words, GHC keeps a single bag of instances that it lazily
slurps from external packages when compiling with --make or GHCi.

Cheers,
Simon

On 09 November 2005 23:49, Claus Reinke wrote:

 I was pretty sure this is a well-known and long-standing bug, but I
 can't find it in the sf bug tracker, and the user guide Known bugs
 section claims in 12.1.1.5 None known, so I thought I'd ask here.
 
 The problem, as I recall it, is that ghc's import chasing collects
 instances as it follows dependencies, without respecting the
 actual import relationships between modules. For instance, the
 following compiles, but shouldn't (in my understanding, at least:-):
 
 -
 module A where
 
 f = print ((Left hi = Right) :: Either String String)
 -
 module B where
 
 import Control.Monad.Error()
 -
 module Main where
 
 import B
 import A
 
 main = f
 -
 
 Could someone please confirm that this is a bug, not a mis-
 understanding? Switching the order of imports in Main should
 not have an impact on program correctness, but it does (win xp,
 ghci 6.4.1; missing instance (Monad (Either String))). Similarly,
 after a failed load (with flipped imports) in ghci, a simple
 
 m +Control.Monad.Error
 m -Control.Monad.Error
 r
 
 should not succeed, but it does.
 
 In a larger program (think of A and B as independent sub-projects,
 from different vendors..), this is even harder to track (btw, can one
 infer the compilation order from ghc -M output? I was at a loss
 trying to find out why a certain module A was compiled at the time
 it was, for one order of imports, but not for another - when the
 compilation of A fails, the modules that caused A to be compiled
 have yet to appear in the output.. ).
 
 Cheers,
 Claus
 
 
 ___
 Glasgow-haskell-bugs mailing list
 Glasgow-haskell-bugs@haskell.org
 http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

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


RE: too liberal handling of instance imports?

2005-11-10 Thread Simon Marlow
Oops, I just found it.  It's in the user's guide, in the Bugs in GHCi
section:

http://www.haskell.org/ghc/docs/latest/html/users_guide/bugs.html#bugs-g
hci

Cheers,
Simon

On 10 November 2005 10:39, Simon Marlow wrote:

 Indeed, it is a known bug (I thought it was in SF too, but I can't
 find it either).
 
 The problem is a bit more restricted than just GHC doesn't respect
 the importing structure when importing instances.  In particular, it
 works properly if any of the following are true (I believe):
 
   - you are not using --make or GHCi
   - the instances are not in any external packages
 
 in other words, GHC keeps a single bag of instances that it lazily
 slurps from external packages when compiling with --make or GHCi.
 
 Cheers,
   Simon
 
 On 09 November 2005 23:49, Claus Reinke wrote:
 
 I was pretty sure this is a well-known and long-standing bug, but I
 can't find it in the sf bug tracker, and the user guide Known bugs
 section claims in 12.1.1.5 None known, so I thought I'd ask here.
 
 The problem, as I recall it, is that ghc's import chasing collects
 instances as it follows dependencies, without respecting the
 actual import relationships between modules. For instance, the
 following compiles, but shouldn't (in my understanding, at least:-):
 
 -
 module A where
 
 f = print ((Left hi = Right) :: Either String String)
 -
 module B where
 
 import Control.Monad.Error()
 -
 module Main where
 
 import B
 import A
 
 main = f
 -
 
 Could someone please confirm that this is a bug, not a mis-
 understanding? Switching the order of imports in Main should
 not have an impact on program correctness, but it does (win xp,
 ghci 6.4.1; missing instance (Monad (Either String))). Similarly,
 after a failed load (with flipped imports) in ghci, a simple
 
 m +Control.Monad.Error
 m -Control.Monad.Error
 r
 
 should not succeed, but it does.
 
 In a larger program (think of A and B as independent sub-projects,
 from different vendors..), this is even harder to track (btw, can one
 infer the compilation order from ghc -M output? I was at a loss
 trying to find out why a certain module A was compiled at the time
 it was, for one order of imports, but not for another - when the
 compilation of A fails, the modules that caused A to be compiled
 have yet to appear in the output.. ).
 
 Cheers,
 Claus
 
 
 ___
 Glasgow-haskell-bugs mailing list
 Glasgow-haskell-bugs@haskell.org
 http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs
 
 ___
 Glasgow-haskell-bugs mailing list
 Glasgow-haskell-bugs@haskell.org
 http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

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


Re: Bug in GHC type system

2005-11-10 Thread Christian Maeder

Hi Baltasar,

maybe it's GHC's inliner. See

http://www.haskell.org/ghc/docs/latest/html/users_guide/bugs.html#bugs-ghc

and the russel example is similar enough to yours. (I have not 
checked, though.)


I apologize, again, for the wrong spelling, It must be Russell with 
two l!


Cheers Christian

Baltasar Trancon y Widemann wrote:

Hi,

I have found a three-line program that will cause recent GHC type 
checker to diverge. The program is admittedly pathological, so here's 
the story:


As part of my PhD thesis I am investigating a backend virtual machine 
for functional programs where


  * beta reduction is explicit,
  * consequently, (-) is a free type constructor that can be mixed with
(*) and (+) in arbitrary mutual recursion.

In such a system, is possible to define a well-typed, effective Y 
combinator. Of course, the reduction strategy has to be hand-coded 
explicitly. Since the lazy strategy is not the worst choice, I tried to 
abuse the Haskell type system for an experiment:



y f = w w
  where w x = f (x x)


This is, naturally, rejected by the type checker because of recursive 
type equations of the form:



t = t - u


But one can put a datatype constructor in between:


newtype Auto a = { self :: Auto a - a }
y f = self w w
  where w = Auto (\x - f (self x x))


Sadly, I cannot load this program into GHCi or compile it with GHC. HUGS 
(as of November 2003) has no such problem, and computes the factorial 
function:



let fac f x = if x == 0 then 1 else x * f (x - 1)
 in y fac 10



Technical details:

  x86 PC with AMD Athlon XP CPU
  SuSE 9.0 Linux with kernel 2.6.10
  ghc-6.2.2

  also observed for 6.4 on a different machine

The log of `ghc -v -C Ups.hs` is attached. The compiler hangs after the


*** Simplify:


line, slowly consuming unbounded amounts of heap (presumably due to a 
divergent type unification). The last two log lines are issued only 
after a ^C signal. If 'newtype' is replaced by 'data', one more line of 
statistics



Result size = 17


is issued before the compiler hangs, too.


Greetings,

Baltasar Trancon y Widemann



module Ups where

-- y f = w w where w x = f (x x)

newtype Auto a = Auto {self :: Auto a - a}
y f = self w w
  where w = Auto (\x - f (self x x))




Glasgow Haskell Compiler, Version 6.2.2, for Haskell 98, compiled by GHC 
version 5.04.3
Using package config file: /usr/local/lib/ghc-6.2.2/package.conf

 Packages 
Package
   {name = data,
auto = False,
import_dirs = [/usr/local/lib/ghc-6.2.2/hslibs-imports/data],
source_dirs = [],
library_dirs = [/usr/local/lib/ghc-6.2.2],
hs_libraries = [HSdata],
extra_libraries = [],
include_dirs = [],
c_includes = [],
package_deps = [haskell98, lang, util],
extra_ghc_opts = [],
extra_cc_opts = [],
extra_ld_opts = [],
framework_dirs = [],
extra_frameworks = []}
Package
   {name = rts,
auto = False,
import_dirs = [],
source_dirs = [],
library_dirs = [/usr/local/lib/ghc-6.2.2],
hs_libraries = [HSrts],
extra_libraries = [m, gmp, dl],
include_dirs = [/usr/local/lib/ghc-6.2.2/include],
c_includes = [Stg.h],
package_deps = [],
extra_ghc_opts = [],
extra_cc_opts = [],
extra_ld_opts =
  [-u,
   GHCziBase_Izh_static_info,
   -u,
   GHCziBase_Czh_static_info,
   -u,
   GHCziFloat_Fzh_static_info,
   -u,
   GHCziFloat_Dzh_static_info,
   -u,
   GHCziPtr_Ptr_static_info,
   -u,
   GHCziWord_Wzh_static_info,
   -u,
   GHCziInt_I8zh_static_info,
   -u,
   GHCziInt_I16zh_static_info,
   -u,
   GHCziInt_I32zh_static_info,
   -u,
   GHCziInt_I64zh_static_info,
   -u,
   GHCziWord_W8zh_static_info,
   -u,
   GHCziWord_W16zh_static_info,
   -u,
   GHCziWord_W32zh_static_info,
   -u,
   GHCziWord_W64zh_static_info,
   -u,
   GHCziStable_StablePtr_static_info,
   -u,
   GHCziBase_Izh_con_info,
   -u,
   GHCziBase_Czh_con_info,
   -u,
   GHCziFloat_Fzh_con_info,
   -u,
   GHCziFloat_Dzh_con_info,
   -u,
   GHCziPtr_Ptr_con_info,
   -u,
   GHCziPtr_FunPtr_con_info,
   -u,
   GHCziStable_StablePtr_con_info,
   -u,
   GHCziBase_False_closure,
   -u,
   GHCziBase_True_closure,
   -u,
   GHCziPack_unpackCString_closure,
   -u,
   GHCziIOBase_stackOverflow_closure,
   -u,
   GHCziIOBase_heapOverflow_closure,
   -u,
   GHCziIOBase_NonTermination_closure,
   -u,
   GHCziIOBase_BlockedOnDeadMVar_closure,
   -u,
   GHCziIOBase_Deadlock_closure,
   -u,
   GHCziWeak_runFinalizzerBatch_closure,
   -u,
   __stginit_Prelude],
framework_dirs = [],
extra_frameworks = []}
Package
   {name = base,

[ ghc-Bugs-1353257 ] Problem with Threading under GHC

2005-11-10 Thread SourceForge.net
Bugs item #1353257, was opened at 2005-11-10 16:12
Message generated for change (Tracker Item Submitted) made by Item Submitter
You can respond by visiting: 
https://sourceforge.net/tracker/?func=detailatid=108032aid=1353257group_id=8032

Please note that this message will contain a full copy of the comment thread,
including the initial issue submission, for this request,
not just the latest update.
Category: GHCi
Group: None
Status: Open
Resolution: None
Priority: 5
Submitted By: Marco Block (schachblocki)
Assigned to: Nobody/Anonymous (nobody)
Summary: Problem with Threading under GHC

Initial Comment:
hi ghc-friends,

i try the following code, but it don't work:

import System.Process
import Control.Concurrent
import System.IO
p = threadDelay 1000
main3 = do  putStrLn test
hClose stdin
(inp, out, err, pid) - 
runInteractiveProcess Test.exe [] Nothing Nothing
p
forkIO (putStrLn = 
hGetContents out)
forkIO (putStrLn = 
hGetContents err)
p
putStrLn inp
forkIO (hPutStrLn inp in  
hClose 
inp)
p
forkIO (putStrLn = 
hGetContents out)
forkIO (putStrLn = 
hGetContents err)
putStrLn out
threadDelay 100
forkIO (hPutStrLn inp quit  
hClose 
inp)
hShow out
return ()

thanks for helping.


--

You can respond by visiting: 
https://sourceforge.net/tracker/?func=detailatid=108032aid=1353257group_id=8032
___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


[ ghc-Bugs-1353390 ] unknown exception

2005-11-10 Thread SourceForge.net
Bugs item #1353390, was opened at 2005-11-10 13:20
Message generated for change (Tracker Item Submitted) made by Item Submitter
You can respond by visiting: 
https://sourceforge.net/tracker/?func=detailatid=108032aid=1353390group_id=8032

Please note that this message will contain a full copy of the comment thread,
including the initial issue submission, for this request,
not just the latest update.
Category: Compiler
Group: 6.4.1
Status: Open
Resolution: None
Priority: 5
Submitted By: Rich (rmfought)
Assigned to: Nobody/Anonymous (nobody)
Summary: unknown exception

Initial Comment:
Compiling hsgnutls-0.2.1, get the following error:

Glasgow Haskell Compiler, Version 6.4.1, for Haskell
98, compiled by GHC version 6.4
Using package config file: /usr/lib/ghc-6.4.1/package.conf
Hsc static flags: -static
*** Chasing dependencies:
Chasing modules from: Setup.lhs
*** Literate pre-processor
/usr/lib/ghc-6.4.1/unlit -h Setup.lhs Setup.lhs
/tmp/ghc15830.lpp
Stable modules:
*** Compiling Main ( Setup.lhs, Setup.o ):
compile: input file /tmp/ghc15830.lpp
*** Checking old interface for Main:
Skipping  Main ( Setup.lhs, Setup.o )
*** Deleting temp files
Deleting: /tmp/ghc15830.s
Warning: deleting non-existent /tmp/ghc15830.s
Upsweep completely successful.
*** Deleting temp files
Deleting:
link: linkables are ...
LinkableM (Thu Nov 10 09:33:46 CST 2005) Main
   [DotO Setup.o]
Linking ...
*** Deleting temp files
Deleting: /tmp/ghc15830.lpp
ghc-6.4.1: ghc-6.4.1: panic! (the `impossible'
happened, GHC version 6.4.1):
unknown exception

This occured after I unregistered Cabal-1.0 , and
installed Cabal 1.1.1.  The compilation went fine
before this.

--

You can respond by visiting: 
https://sourceforge.net/tracker/?func=detailatid=108032aid=1353390group_id=8032
___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs