Re: Behavior of the inliner on imported class methods

2011-01-19 Thread José Pedro Magalhães
Hi Roman,

Thanks for the suggestion, but that doesn't seem to change things.


Cheers,
Pedro

2011/1/19 Roman Leshchinskiy r...@cse.unsw.edu.au

 Have you tried adding another (dummy) method to the class? GHC used to have
 problems with optimising single-method classes in the past.

 Roman


 On 18 Jan 2011, at 10:33, José Pedro Magalhães j...@cs.uu.nl wrote:

 Hello all,

 I fail to understand the behavior of the inliner in the following example:

 module M1 where

 class MyEnum a where myEnum :: [a]

 instance MyEnum () where myEnum = [()]



 module M2 where

 import M1

 f1 = map (\() - 'p') [()]
 f2 = map (\() - 'q') myEnum


 The generated core code for M2 with ghc-7.0.1 -O is:

 M2.f22 :: GHC.Types.Char
 [GblId,
  Caf=NoCafRefs,
  Str=DmdType m,
  Unf=Unf{Src=vanilla, TopLvl=True, Arity=0, Value=True,
  ConLike=True, Cheap=True, Expandable=True,
  Guidance=IF_ARGS [] 1 2}]
 M2.f22 = GHC.Types.C# 'q'

 M2.f11 :: GHC.Types.Char
 [GblId,
  Caf=NoCafRefs,
  Str=DmdType m,
  Unf=Unf{Src=vanilla, TopLvl=True, Arity=0, Value=True,
  ConLike=True, Cheap=True, Expandable=True,
  Guidance=IF_ARGS [] 1 2}]
 M2.f11 = GHC.Types.C# 'p'

 M2.f21 :: () - GHC.Types.Char
 [GblId,
  Arity=1,
  Caf=NoCafRefs,
  Unf=Unf{Src=vanilla, TopLvl=True, Arity=1, Value=True,
  ConLike=True, Cheap=True, Expandable=True,
  Guidance=ALWAYS_IF(unsat_ok=True,boring_ok=True)}]
 M2.f21 =
   \ (ds_dch :: ()) - case ds_dch of _ { () - M2.f22 }

 M2.f2 :: [GHC.Types.Char]
 [GblId,
  Str=DmdType,
  Unf=Unf{Src=vanilla, TopLvl=True, Arity=0, Value=False,
  ConLike=False, Cheap=False, Expandable=False,
  Guidance=IF_ARGS [] 3 0}]
 M2.f2 =
   GHC.Base.map
 @ () @ GHC.Types.Char M2.f21 M1.$fMyEnum()_$cmyEnum

 M2.f1 :: [GHC.Types.Char]
 [GblId,
  Caf=NoCafRefs,
  Str=DmdType,
  Unf=Unf{Src=vanilla, TopLvl=True, Arity=0, Value=True,
  ConLike=True, Cheap=True, Expandable=True,
  Guidance=IF_ARGS [] 1 3}]
 M2.f1 =
   GHC.Types.:
 @ GHC.Types.Char M2.f11 (GHC.Types.[] @ GHC.Types.Char)


 So, why does the inliner fail to get rid of the map in f2, while correctly
 ditching it in f1? Note that using two modules is essential here: if the
 instance is in M2 (and thus becoming orphan), the inliner works correctly.
 Adding INLINE/INLINABLE pragmas to myEnum doesn't improve things either. Is
 this a bug, or is there a reason for this behavior?


 Thanks,
 Pedro

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


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


backward compatibility

2011-01-19 Thread 山本和彦
Hello, 

I have been using GHC HEAD for some months and am suffering from the
breaks of backward compatibility. 

1) MANY packages cannot be complied with GHC HEAD because of lack of
FlexibleInstances and BangPatterns.

2) The network package on github cannot be compiled because the layout
handling of GHC HEAD became more severe. For instance, here is such
code from Network/Socket.hsc.

allocaBytes (2 * sizeOf (1 :: CInt)) $ \ fdArr - do
_ - throwSocketErrorIfMinus1Retry socketpair $
c_socketpair (packFamily family)
 (packSocketType stype)
 protocol fdArr

Of course, indentation is necessary before _. But this can be
compiled with GHC 7.0.1 but cannot with GHC HEAD.

I sent feedback to some maintainers of packages. Some quickly fixed it and
registered it again. But others did not respond. That is reality.

So, my question is why GHC HEAD does not maintain backward
compatibility? What are befits for giving it up?

--Kazu

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


Re: backward compatibility

2011-01-19 Thread Thomas DuBuisson
In my case I omitted BangPatterns from the pragma by accident and was
thankful for the update.

One slight benefit of the strict requirement of correct pragma is it's
easier to survey Hackage to see how features are used, their
popularity, and inform language design (ex: Garrett Morris's Haskell
Symposium paper).

Cheers,
Thomas

On Wed, Jan 19, 2011 at 6:32 PM, Kazu Yamamoto k...@iij.ad.jp wrote:
 Hello,

 I have been using GHC HEAD for some months and am suffering from the
 breaks of backward compatibility.

 1) MANY packages cannot be complied with GHC HEAD because of lack of
 FlexibleInstances and BangPatterns.

 2) The network package on github cannot be compiled because the layout
 handling of GHC HEAD became more severe. For instance, here is such
 code from Network/Socket.hsc.

    allocaBytes (2 * sizeOf (1 :: CInt)) $ \ fdArr - do
    _ - throwSocketErrorIfMinus1Retry socketpair $
                c_socketpair (packFamily family)
                             (packSocketType stype)
                             protocol fdArr

 Of course, indentation is necessary before _. But this can be
 compiled with GHC 7.0.1 but cannot with GHC HEAD.

 I sent feedback to some maintainers of packages. Some quickly fixed it and
 registered it again. But others did not respond. That is reality.

 So, my question is why GHC HEAD does not maintain backward
 compatibility? What are befits for giving it up?

 --Kazu

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


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


Re: backward compatibility

2011-01-19 Thread John Meacham
On Wed, Jan 19, 2011 at 6:32 PM, Kazu Yamamoto k...@iij.ad.jp wrote:
 Hello,

 I have been using GHC HEAD for some months and am suffering from the
 breaks of backward compatibility.

 1) MANY packages cannot be complied with GHC HEAD because of lack of
 FlexibleInstances and BangPatterns.

 2) The network package on github cannot be compiled because the layout
 handling of GHC HEAD became more severe. For instance, here is such
 code from Network/Socket.hsc.

    allocaBytes (2 * sizeOf (1 :: CInt)) $ \ fdArr - do
    _ - throwSocketErrorIfMinus1Retry socketpair $
                c_socketpair (packFamily family)
                             (packSocketType stype)
                             protocol fdArr

Allowing this was a specific feature that was included in ghc on
purpose (as well as the relaxed if/then layout rule in do statements)
So this is definitely a regression.

 John

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


Cleaning up after the Close button is pressed

2011-01-19 Thread Colin Hume

Hi everyone,

I posted previously on haskell-beginners about an issue which would have been 
better directed to this list. Since then, I have revisited the issue and am now 
even less certain of its cause.

I have to perform cleanup when my application terminates. GHC.ConsoleHandler 
handles cleanup from Ctrl-C and Ctrl-Break very nicely under Windows. My sample 
handler and main function are shown at [1].

When I press Ctrl-C and Ctrl-Break during threadDelay, messages are written to 
console_event.log as I expected. When I press the Close button during 
threadDelay, no message is written to console_event.log. Am I missing something 
fundamental about handling the Close button or installing handlers?

In case it makes a difference, I'm using GHC 6.12.3 under Windows XP.

Thanks,
Colin

[1]
module Main where

import Control.Concurrent (threadDelay)
import GHC.ConsoleHandler
import System.IO

onConsoleEventReceived :: ConsoleEvent - IO ()
onConsoleEventReceived event = withFile console_event.log AppendMode $ \ file 
- do
  hPutStrLn file $ case event of
ControlC  - Received Ctrl-C event
Break - Received Ctrl-Break event
Close - Received X button event
_ - Received other console event
  hFlush file

main :: IO ()
main = installHandler (Catch onConsoleEventReceived)  threadDelay (20*100)
  
  ___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users