System.Posix.Signals weirdness

2011-02-06 Thread Matthias Kilian
Hi,

I'd expect the following program (compiled with ghc and without any
specieal flags) to produce

Just (Exited ExitSuccess)
True

but it produces

Just (Exited ExitSuccess)
False

on Debian Lenny (ghc-6.8), OpenBSD-current (ghc-6.12.3), OpenBSD-current
(ghc=7.0 from the 7.0 branch).

module Main where

import Data.IORef
import System.Posix.Process
import System.Posix.Signals
import System.Posix.Unistd

main = do
caughtCHLD - newIORef False
installHandler sigCHLD (Catch $ writeIORef caughtCHLD True) 
Nothing
pid - forkProcess $ sleep 2  return ()
s - sleep 8
getProcessStatus False False pid = print
readIORef caughtCHLD = print

The sigCHLD handler is never called in this program. Is this expected
behaviour? If so, why?

Ciao,
Kili

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


Re: Question about Haskell AST

2011-02-06 Thread Tim Chevalier
On Mon, Jan 10, 2011 at 9:21 AM, Jane Ren j2...@ucsd.edu wrote:
 Hi,

 I need to be able to take a piece of Haskell source code and get an 
 simplified, typed, intermediate representation of the AST, which means I need 
 to use compiler/coreSyn/CoreSyn.lhs

 So I'm first trying to get the desguaredModule of the source code with
        ...
        modSum - getModSummary $ mkModuleName ...
        p - parseModule modSum
        t - typecheckModule p
        d - desugarModule t

 Now I'm really stuck on figuring out how to connect the variable d of type 
 desugaredModule to compiler/coreSyn/CoreSyn.lhs to get Expr patterns like 
 App, Let, Case, etc.

 Also, is it correct to get the deguaredModule first?  At least CoreSyn.lhs 
 seems to suggest this.


Sorry for the very late reply, but have you considered using External Core?
http://www.haskell.org/ghc/docs/7.0.1/html/users_guide/ext-core.html
http://hackage.haskell.org/package/extcore

IMO, it's less pain than linking with the GHC library unless your
application really needs to get transformed Core back into the GHC
back-end.

Cheers,
Tim

-- 
Tim Chevalier * http://cs.pdx.edu/~tjc/ * Often in error, never in doubt
an intelligent person fights for lost causes,realizing that others
are merely effects -- E.E. Cummings

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


a compiled program is slower than byte code

2011-02-06 Thread 山本和彦
Hello, 

If I compile the attach code with GHC of the newest ghc-7.0 darcs
branch, the compiled program is much slower than byte code. This
phenomenon does not exist in GHC 6.12.3.

6.12.3  runghc   -- 6.23s user 0.59s system 98% cpu 6.912 total
ghc  -- 5.72s user 0.70s system 99% cpu 6.422 total
ghc -O   -- 5.70s user 0.67s system 99% cpu 6.376 total
ghc -O2  -- 5.69s user 0.67s system 99% cpu 6.373 total

ghc-7.0 runghc   -- 6.43s user 0.10s system 99% cpu 6.593 total
ghc  -- 9.20s user 0.09s system 99% cpu 9.302 total
ghc -O   -- 9.20s user 0.09s system 99% cpu 9.298 total
ghc -O2  -- 9.38s user 0.09s system 99% cpu 9.478 total

Is this a bug?

My environment is Mac which runs Snow Leopard.

--Kazu


import System.IO

n :: Int
n = 1

main :: IO ()
main = withFile /dev/null WriteMode $ \h -
hPutStr h . foldr1 (++) . replicate n . replicate n $ 'a'


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


Dictionaries and full laziness transformation

2011-02-06 Thread Akio Takano
Hi,

I'm using GHC 7.0.1. I found that recursive overloaded functions tend
to leak memory when compiled with full-laziness optimization on. Here
is a simple case.

-- TestSub.hs
{-# LANGUAGE BangPatterns #-}
module TestSub where

{-# NOINLINE factorial #-}
factorial :: (Num a) = a - a - a
factorial !n !acc = if n == 0 then acc else factorial (n - 1) (acc * n)

-- main.hs
import TestSub

factorial1 :: Int - Int - Int
factorial1 = factorial

main = do
n - readLn
print $ factorial1 n 1

main

This program should run in constant space, and compiled with -O0 or
-O2 -fno-full-laziness, it does. However with -O2, it takes a linear
amount of memory. The core for factorial looks like this:

TestSub.factorial =
  \ (@ a_ajm) ($dNum_slz :: GHC.Num.Num a_ajm) -
let {
  a_slA :: GHC.Classes.Eq a_ajm
  [LclId]
  a_slA = GHC.Num.$p1Num @ a_ajm $dNum_slz } in
let {
  lvl2_slC :: a_ajm - a_ajm - a_ajm
  [LclId]
  lvl2_slC = TestSub.factorial @ a_ajm $dNum_slz } in
...

The problem is that lvl2_slC closure is created whenever factorial is
applied to a Num dictionary, and kept alive until that application is
GCed. In this program it never happens, because an application to the
Num Int dictionary is referred to by the factorial1 CAF, and it
recursively keeps the whole chain of closures alive.

I know that full laziness transformation *sometimes* causes a space
leak, but this looks like a bad result to me, because:

- It looks like there is no point building a lot of equivalent
closures, instead of one.
- A lot of code can suffer from this behavior, because overloaded
recursive functions are fairly common.
  For example, unfoldConvStream function from the latest iteratee
package suffers from this problem, if I understand correctly.

Does anyone have an idea on whether this can be fixed in GHC, or how
to work around this problem?

Regards,

Takano Akio

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