Re: Inferred type is less polymorphic than expected?

2005-07-29 Thread Thomas Jäger
Hi,

You're probably refering to the version where you omit the type
signatures of both 'printer' and 'printCatalog'. Here the situation is
different because the compiler needs to infer the types and not just
check. In the explicitely typed version, 'printCatalog' is used
polymorphically, i.e. the 'c' is instantiated to different types
during the recursive call. Thus the example needs polymorphic
recursion, for which type inference is known to be undecidable. It is
therefore reasonable that ghc (as well as hugs) can't compile the code
(in fact, I guess type inference will assume that both contexts are
equal).

Thomas

On 7/29/05, Benjamin Franksen <[EMAIL PROTECTED]> wrote:
> a connection to the first one? Note, I have a version of the program,
> where I only get the "Inferred type is less polymorphic than expected"
> error message and this one also disappears as soon as I use a lambda
> instead of a top-level function to initialize the record.
> 
> Ben
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Inferred type is less polymorphic than expected?

2005-07-29 Thread Benjamin Franksen
On Saturday 30 July 2005 01:46, Thomas Jäger wrote:
> This is not a bug, the restriction is actually mentioned in the
> Haskell Report, section 4.5.2. However, the restriction was recently
> lifted, so your code compiles fine with the current cvs ghc, see
>
> > http://www.haskell.org/pipermail/glasgow-haskell-users/2005-July/00
> >8786.html
>
> Thomas
>
> On 7/29/05, Benjamin Franksen <[EMAIL PROTECTED]> wrote:
> > Bug.lhs:27:0:
> > Contexts differ in length
> > When matching the contexts of the signatures for
> >   printer :: Viewer
> >   printCatalog :: forall c. (Catalog c) => View c
> > The signature contexts in a mutually recursive group should all
> > be identical

Thank you for clarifying the cause of the second error message. Is there 
a connection to the first one? Note, I have a version of the program, 
where I only get the "Inferred type is less polymorphic than expected" 
error message and this one also disappears as soon as I use a lambda 
instead of a top-level function to initialize the record.

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


Bug in placing _stub.o files with HEAD

2005-07-29 Thread Einar Karttunen
Hello

I noticed the following behaviour using GHC 6.5.20050728:
If compiling a Cabal package containing hs-source-dirs it 
places the _stub.o under dist/build//path/to/Module
when Cabal expects it in dist/build/path/to/Module. Things
appear to work without hs-source-dirs. 

For example with "hs-source-dirs: src"
Network/GnuTLS/IOWrap.hs contains foreign export declarations.
runnning Setup build creates the files:
dist/build/src/Network/GnuTLS/IOWrap_stub.o
src/Network/GnuTLS/IOWrap_stub.h
src/Network/GnuTLS/IOWrap_stub.c

But Cabal fails to include the IOWrap_stub.o as it is 
expected as dist/build/Network/GnuTLS/IOWrap_stub.o

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


Re: Inferred type is less polymorphic than expected?

2005-07-29 Thread Thomas Jäger
Hi,

This is not a bug, the restriction is actually mentioned in the
Haskell Report, section 4.5.2. However, the restriction was recently
lifted, so your code compiles fine with the current cvs ghc, see
> http://www.haskell.org/pipermail/glasgow-haskell-users/2005-July/008786.html

Thomas

On 7/29/05, Benjamin Franksen <[EMAIL PROTECTED]> wrote:
> Bug.lhs:27:0:
> Contexts differ in length
> When matching the contexts of the signatures for
>   printer :: Viewer
>   printCatalog :: forall c. (Catalog c) => View c
> The signature contexts in a mutually recursive group should all be
> identical
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Inferred type is less polymorphic than expected?

2005-07-29 Thread Benjamin Franksen
Hi,

I get an error message when I compile the following program with 
ghc-6.4:

\begin{code}
class Catalog c where
  traverse :: c -> Viewer -> IO ()

instance Catalog Int where
  traverse i v = viewShowable v i

type View a = a -> IO ()

data Viewer = Viewer {
viewShowable :: forall s. Show s => View s,
viewCatalog :: forall c. Catalog c => View c
  }

printer :: Viewer
--printer = Viewer {
--  viewCatalog = \x -> traverse x printer,
--  viewShowable = putStrLn . show }
printer = Viewer {
  viewCatalog = printCatalog,
  viewShowable = putStrLn . show }

printCatalog :: forall c. Catalog c => View c
printCatalog x = traverse x printer

data X = X {
cat :: Int
  }

instance Catalog X where
  traverse x v = do
viewCatalog v (cat x)

main = do
  let x = X { cat = 20 }
  traverse x printer
\end{code}

This is a stripped-down version of my actual code, BTW. The exact mesage 
is:

~> ghc -fallow-undecidable-instances -fglasgow-exts Bug.lhs

Bug.lhs:23:10:
Inferred type is less polymorphic than expected
  Quantified type variable `c' is mentioned in the environment:
printCatalog :: c -> IO () (bound at Bug.lhs:28:0)
In the `viewCatalog' field of a record
In the record construction: Viewer
{viewCatalog = printCatalog, 
viewShowable = putStrLn . show}
In the definition of `printer':
printer = Viewer {viewCatalog = printCatalog, viewShowable = 
putStrLn . show}

Bug.lhs:27:0:
Contexts differ in length
When matching the contexts of the signatures for
  printer :: Viewer
  printCatalog :: forall c. (Catalog c) => View c
The signature contexts in a mutually recursive group should all be 
identical

The code compiles and works fine if the definition of 'printer' is 
replaced by the out-commented version, that is, if a lambda expression 
is used that is identical to the definition of 'printCatalog'. BTW, 
this does not happen with hugs.

It looks like a bug to me, but since I use some non-standard features, 
maybe there is some subtle explanation for this behavior.

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


RE: Complexity bug in garbage collector?

2005-07-29 Thread Simon Marlow
On 29 July 2005 12:53, Josef Svenningsson wrote:

> My machine was definitely swapping when I aborted the program. Can
that
> have any effect on the timings?

yes, there's your problem.  It's still a nice regular-looking curve
though, which is mildly surprising.

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


Re: more on GHC 6.4 Debian packages

2005-07-29 Thread Ian Lynagh
On Fri, Jul 29, 2005 at 09:27:08PM +0100, Simon Marlow wrote:
> On 28 July 2005 22:42, Ian Lynagh wrote:
> 
> > However, the timeout program tickles known bugs in Linux 2.4 on hppa
> > (and possibly unknown bugs on ia64, as discussed briefly on ghc-cvs).
> 
> I'd still like to get your souped-up timeout program into CVS.  Would
> you like to post it?

Here's what I've currently got. I suspect the second forkIO should
really be forkOS, but it might not be necessary at all on non-buggy
systems (in which case the code can be simplified a bit).


Thanks
Ian

{-# OPTIONS -cpp #-}

import Control.Concurrent (forkIO, threadDelay)
import Control.Concurrent.MVar (putMVar, takeMVar, newEmptyMVar)
import Control.Exception (try)
import Data.Maybe (isNothing)
import System.Cmd (system)
import System.Environment (getArgs)
import System.Exit (exitWith, ExitCode(ExitFailure))
import System.IO (hPutStrLn, stderr)
import System.Process (waitForProcess, getProcessExitCode)
#if !defined(mingw32_HOST_OS)
import Control.Monad (when)
import System.Process.Internals (ProcessHandle(ProcessHandle))
import System.Posix.Process (forkProcess, createSession)
import System.Posix.Signals (installHandler, Handler(Catch),
 signalProcessGroup, sigINT, sigTERM, sigKILL )
#endif

main = do
  args <- getArgs
  case args of 
[secs,cmd] -> do
m <- newEmptyMVar
mp <- newEmptyMVar
#if !defined(mingw32_HOST_OS)
installHandler sigINT (Catch (putMVar m Nothing)) Nothing
#endif
forkIO (do threadDelay (read secs * 100)
   putMVar m Nothing
   )
forkIO (do try (do p <- forkProcess $ do
   createSession
   r <- system cmd
   exitWith r
   putMVar mp p
   r <- waitForProcess (ProcessHandle p)
   putMVar m (Just r))
   return ())
p <- takeMVar mp
r <- takeMVar m
case r of
  Nothing -> do
killProcess p
exitWith (ExitFailure 99)
  Just r -> do
exitWith r
_other -> do hPutStrLn stderr "timeout: bad arguments"
 exitWith (ExitFailure 1)

#if !defined(mingw32_HOST_OS)
killProcess p = do
  try (signalProcessGroup sigTERM p)
  checkReallyDead 10
  where
checkReallyDead 0 = hPutStrLn stderr "checkReallyDead: Giving up"
checkReallyDead (n+1) =
  do threadDelay (3*10) -- 3/10 sec
 m <- getProcessExitCode (ProcessHandle p)
 when (isNothing m) $ do
 try (signalProcessGroup sigKILL p)
 checkReallyDead n
#else
killProcess p = do
  terminateProcess p
  threadDelay (3*10) -- 3/10 sec
  m <- getProcessExitCode p
  when (isNothing m) $ killProcess p
#endif
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


RE: more on GHC 6.4 Debian packages

2005-07-29 Thread Simon Marlow
On 28 July 2005 22:42, Ian Lynagh wrote:

> However, the timeout program tickles known bugs in Linux 2.4 on hppa
> (and possibly unknown bugs on ia64, as discussed briefly on ghc-cvs).

I'd still like to get your souped-up timeout program into CVS.  Would
you like to post it?

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


RE: -split-objs and --make together?

2005-07-29 Thread Simon Marlow
On 29 July 2005 05:10, Dimitry Golubovsky wrote:

> Is it possible to use --make when one or more of modules involved are
> split? 

Not right now, but it's on the ToDo list.

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


Re: Complexity bug in garbage collector?

2005-07-29 Thread Josef Svenningsson
Hi,

Sorry for my late reply.

On 7/22/05, Simon Marlow <[EMAIL PROTECTED]> wrote:
> On 16 April 2005 23:19, Josef Svenningsson wrote:
> 
> > OK, I've cooked up this little program to study the behaviour a
> > little closer: \begin{code}
> > module Main where
> >
> > main = print $ strictId [1..]
> >
> > strictId list = let (c,c') = work list c'
> > in c
> >   where work [] y' = (y',[])
> >   work (x:xs) y' = (v,x:v')
> > where (v,v') = work xs y'
> > \end{code}
> >
> > This program just allocates like crazy til it dies. The funny looking
> > strictId function is just the strict identity function on lists. (Yes,
> > there are simpler ways to achieve the same thing. I just think the
> > above function is particularly sweet :-)
> >
> > I do the following:
> > $ ghc -prof -auto-all --make Main.hs
> > $ main.exe +RTS -hd -M
> >
> > The resulting graph is suspiciously similar in shape to the one of my
> > previous program. The garbage collector is still my primary suspect, I
> > simply don't know how to explain the graph otherwise.
> 
> I don't see a curve in the profile on my machine:
> 
>   http://www.haskell.org/~simonmar/main.exe.ps
> 
> This was on a Windows box, I also get the same results on a Linux
> machine.  I was only able to test with -M600m on the Windows box.  Do
> you need more to get the curve?
> 
I used -M512M so that should be fine. But I think you should wait a
little longer before you hit ^C. When I tried it just now I waited for
a minute. It produced a curve like I reported before.
But maybe this has something to do with swapping? My machine was
definitely swapping when I aborted the program. Can that have any
effect on the timings?

Cheers,

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