case of an empty type should have no branches

2011-10-09 Thread Roman Beslik

Hi.

Why the following code does not work?
 data Empty
 quodlibet :: Empty - a
 quodlibet x = case x of
parse error (possibly incorrect indentation)

This works in Coq, for instance. Demand for empty types is not big, but 
they are useful for generating finite types:

 Empty ≅ {}
 Maybe Empty ≅ {0}
 Maybe (Maybe Empty) ≅ {0, 1}
 Maybe (Maybe (Maybe Empty)) ≅ {0, 1, 2}
etc. Number of 'Maybe's = number of elements. I can replace @Maybe 
Empty@ with @()@, but this adds some complexity.


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


Is this a concurrency bug in base?

2011-10-09 Thread Jean-Marie Gaillourdet
Hi,

I am working on a library I'd like to release to hackage very soon, but I've 
found a problem with supporting GHC 6.12 and GHC 7.0.
Consider the following program: 

import Control.Concurrent
import Data.Typeable

main :: IO ()
main =
 do { fin1 - newEmptyMVar
; fin2 - newEmptyMVar

; forkIO $ typeRepKey (typeOf ()) = print  putMVar fin1 ()
; forkIO $ typeRepKey (typeOf ()) = print  putMVar fin2 ()

; () - takeMVar fin1
; () - takeMVar fin2
; putStrLn ---
; return ()
}

When compiled with GHC 7.0.x or GHC 6.12.x, it should print two identical 
numbers. Sometimes it does not. 
To reproduce this compile and execute as follows:

$ ghc-7.0.3 -rtsopts -threaded TypeRepKey.hs -o TypeRepKey
$ while true ; do ./TypeRepKey +RTS -N  ; done
0
0
---
0
0
---
0
0
---
0
1
---
0
0
---
…

Ideally you should get an infinite number of zeros but once in a while you have 
a single(!) one in between. The two numbers of one program run should be 
identical, but their values may be arbitrary. But it should not be possible to 
have single outliers.

This only happens when executed with more than one thread. I've also a somewhat 
larger program which seems to indicate that fromDynamic fails occasionally. I 
can post it as well if it helps. This seems to be a Heisenbug as it is 
extremely fragile, when adding a | grep 1 to the while loop it seems to 
disappears. At least on my computers. 

All this was done on several Macs running the latest OS X Lion with ghc 7.0.3 
from the binary distribution on the GHC download page. 

Actually, I am trying to find a method to use a type as key in a map which 
works before GHC 7.2. I'd be glad to get any ideas on how to achieve that, 
given that typeRepKey seems to buggy. 

 I'd be happy to get any comments on this matter. 

Regards,
  Jean



TypeRepKey.hs
Description: Binary data
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: case of an empty type should have no branches

2011-10-09 Thread Felipe Almeida Lessa
On Sun, Oct 9, 2011 at 8:26 AM, Roman Beslik ber...@ukr.net wrote:
 Why the following code does not work?
 data Empty
 quodlibet :: Empty - a
 quodlibet x = case x of
 parse error (possibly incorrect indentation)

Works for me:

  data Empty

  quodlibet :: Empty - a
  quodlibet x = case x of _ - undefined

 This works in Coq, for instance. Demand for empty types is not big, but they
 are useful for generating finite types:
 Empty ≅ {}
 Maybe Empty ≅ {0}
 Maybe (Maybe Empty) ≅ {0, 1}
 Maybe (Maybe (Maybe Empty)) ≅ {0, 1, 2}
 etc. Number of 'Maybe's = number of elements. I can replace @Maybe Empty@
 with @()@, but this adds some complexity.

I'd prefer to define something like

  data Finite = Zero | Plus Finite

Cheers, =)

-- 
Felipe.

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


Re: Is this a concurrency bug in base?

2011-10-09 Thread Jean-Marie Gaillourdet
Hi Daniel,

On 09.10.2011, at 14:45, Daniel Fischer wrote:

 On Sunday 09 October 2011, 13:52:47, Jean-Marie Gaillourdet wrote:
 This seems to be a Heisenbug as it is extremely fragile, when adding a
 | grep 1 to the while loop it seems to disappears. At least on my
 computers. 
 
 Still produces 1s here with a grep.

Well, it may have been bad luck on my site.

 
 
 All this was done on several Macs running the latest OS X Lion with ghc
 7.0.3 from the binary distribution on the GHC download page. 
 
 linux x86_64, ghc-7.0.4, 7.0.2 and 6.12.3.
 Indeed 6.12.3 goes so far to sometimes produce
 0
 0
 ---
 10
 
 ---
 0
 0
 ---
 01
 
 ---
 
 i.e. it switches threads during print.
Thanks, for reproducing it. I failed to see it on Linux so far. So I guess a 
bug report is in order? Or are bug reports to old versions not welcome? 

Jean


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


Re: Is this a concurrency bug in base?

2011-10-09 Thread Daniel Fischer
On Sunday 09 October 2011, 15:30:20, Jean-Marie Gaillourdet wrote:
 Hi Daniel,
 
 On 09.10.2011, at 14:45, Daniel Fischer wrote:
  On Sunday 09 October 2011, 13:52:47, Jean-Marie Gaillourdet wrote:
  This seems to be a Heisenbug as it is extremely fragile, when adding
  a | grep 1 to the while loop it seems to disappears. At least on
  my computers.
  
  Still produces 1s here with a grep.
 
 Well, it may have been bad luck on my site.

Or maybe Macs behave differently.

 
 Thanks, for reproducing it. I failed to see it on Linux so far. So I
 guess a bug report is in order?

I'd think so.  Although due to the changes in 7.2 there's nothing to fix 
here anymore, it might point to something still to be fixed.

 Or are bug reports to old versions not welcome?

Within reason. Reporting bugs against 5.* would be rather pointless now, 
but = 6.10 should be okay.
If the behaviour has been fixed as a by-product of some other change, at 
least a test could be made to prevent regression.
If, like here, the directly concerned code has been changed, probably 
nothing is to be done, but the bug may have been caused by something else 
which still needs to be fixed, so better report one bug too many.

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


Re: Is this a concurrency bug in base?

2011-10-09 Thread Jean-Marie Gaillourdet
Hi,

the Eq instance of TypeRep shows the same non-deterministic behavior:

import Control.Concurrent
import Control.Exception
import Control.Monad
import Data.Typeable

main :: IO ()
main =
 do { fin1 - newEmptyMVar
; fin2 - newEmptyMVar

; forkIO $ return (typeOf ()) = evaluate = putMVar fin1 
; forkIO $ return (typeOf ()) = evaluate = putMVar fin2 

; t1 - takeMVar fin1
; t2 - takeMVar fin2
; when (t1 /= t2) $
putStrLn $ typeOf  ++ show t1 ++  /= typeOf  ++ show t2
}

$ ghc-7.0.3 -threaded -rtsopts TypeRepEq.hs
snip
$ while true ; do ./TypeRepEq +RTS -N ; done
typeOf () /= typeOf ()
typeOf () /= typeOf ()
^C^C

$

On 09.10.2011, at 16:04, David Brown wrote:
 The program below will occasionally print 1 /= 0 or 0 /= 1 on
 x86_64 linux with the Debian testing 7.0.4 ghc.
 
 $ ghc bug -rtsopts -threaded
 $ while true; do ./bug +RTS -N; done
 
 module Main where
 import Control.Monad
 import Control.Concurrent
 import Data.Typeable
 main :: IO ()
 main = do
   fin1 - newEmptyMVar
   fin2 - newEmptyMVar
   forkIO $ child fin1
   forkIO $ child fin2
   a - takeMVar fin1
   b - takeMVar fin2
   when (a /= b) $
  putStrLn $ show a ++  /=  ++ show b
 child :: MVar Int - IO ()
 child var = do
   key - typeRepKey (typeOf ())
   putMVar var key

Thanks again for reproducing it.

Jean

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


Re: Is this a concurrency bug in base?

2011-10-09 Thread Jean-Marie Gaillourdet
Hi Daniel,



On 09.10.2011, at 16:24, Daniel Fischer wrote:

 On Sunday 09 October 2011, 15:30:20, Jean-Marie Gaillourdet wrote:
 Hi Daniel,
 
 On 09.10.2011, at 14:45, Daniel Fischer wrote:
 On Sunday 09 October 2011, 13:52:47, Jean-Marie Gaillourdet wrote:
 This seems to be a Heisenbug as it is extremely fragile, when adding
 a | grep 1 to the while loop it seems to disappears. At least on
 my computers.
 
 Still produces 1s here with a grep.
 
 Well, it may have been bad luck on my site.
 
 Or maybe Macs behave differently.
 
 
 Thanks, for reproducing it. I failed to see it on Linux so far. So I
 guess a bug report is in order?
 
 I'd think so.  Although due to the changes in 7.2 there's nothing to fix 
 here anymore, it might point to something still to be fixed.
 
 Or are bug reports to old versions not welcome?
 
 Within reason. Reporting bugs against 5.* would be rather pointless now, 
 but = 6.10 should be okay.
 If the behaviour has been fixed as a by-product of some other change, at 
 least a test could be made to prevent regression.
 If, like here, the directly concerned code has been changed, probably 
 nothing is to be done, but the bug may have been caused by something else 
 which still needs to be fixed, so better report one bug too many.


I've been chasing the source of the non-deterministic of my library for quite 
some time now. And at several points in time I had the impression that 
modifyMVar would not always be atomic. (Of course under the assumption that no 
other code touches the MVar). But in that case as well as in the case here it 
is only reproducible by looping the execution of the binary. Moving the loop 
into the Haskell program will show the bug in the first iteration or never.   

I will report a bug.

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


Re: Is this a concurrency bug in base?

2011-10-09 Thread Jean-Marie Gaillourdet

On 09.10.2011, at 16:40, Jean-Marie Gaillourdet wrote:

 I will report a bug.

http://hackage.haskell.org/trac/ghc/attachment/ticket/5540/

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


Re: Is this a concurrency bug in base?

2011-10-09 Thread Daniel Fischer
Jean-Marie Gaillourdet:
 the Eq instance of TypeRep shows the same non-deterministic behavior:

Of course, equality on TypeReps is implemented by comparison of the Keys.

On Sunday 09 October 2011, 16:40:13, Jean-Marie Gaillourdet wrote:
 Hi Daniel,

 I've been chasing the source of the non-deterministic of my library for
 quite some time now. And at several points in time I had the impression
 that modifyMVar would not always be atomic.

It isn't:

MVars offer more flexibility than IORefs, but less flexibility than STM. 
They are appropriate for building synchronization primitives and performing 
simple interthread communication; however they are very simple and 
susceptible to race conditions, deadlocks or uncaught exceptions. Do not 
use them if you need perform larger atomic operations such as reading from 
multiple variables: use STM instead.

In particular, the bigger functions in this module (readMVar, swapMVar, 
withMVar, modifyMVar_ and modifyMVar) are simply the composition of a 
takeMVar followed by a putMVar with exception safety. These only have 
atomicity guarantees if all other threads perform a takeMVar before a 
putMVar as well; otherwise, they may block.

But I don't think that's the problem here.

 (Of course under the
 assumption that no other code touches the MVar). But in that case as
 well as in the case here it is only reproducible by looping the
 execution of the binary. Moving the loop into the Haskell program will
 show the bug in the first iteration or never.

That's what I expect.
I think what happens is:

-- from Data.Typeable

cache = unsafePerformIO $ ...


mkTyConKey :: String - Key
mkTyConKey str 
  = unsafePerformIO $ do
let Cache {next_key = kloc, tc_tbl = tbl} = cache
mb_k - HT.lookup tbl str
case mb_k of
  Just k  - return k
  Nothing - do { k - newKey kloc ;
  HT.insert tbl str k ;
  return k }

occasionally, the second thread gets to perform the lookup before the first 
has updated the cache, so both threads create a new entry and update the 
cache.

If you loop in the Haskell programme, after the first round each thread 
definitely finds an entry for (), so the cache isn't updated anymore.

 
 I will report a bug.
 
 Jean


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


Re: Is this a concurrency bug in base?

2011-10-09 Thread Jean-Marie Gaillourdet
Hi,

On 09.10.2011, at 17:27, Daniel Fischer wrote:

 Jean-Marie Gaillourdet:
 the Eq instance of TypeRep shows the same non-deterministic behavior:
 
 Of course, equality on TypeReps is implemented by comparison of the Keys.
 
 On Sunday 09 October 2011, 16:40:13, Jean-Marie Gaillourdet wrote:
 Hi Daniel,
 
 I've been chasing the source of the non-deterministic of my library for
 quite some time now. And at several points in time I had the impression
 that modifyMVar would not always be atomic.
 
 It isn't:
 
 MVars offer more flexibility than IORefs, but less flexibility than STM. 
 They are appropriate for building synchronization primitives and performing 
 simple interthread communication; however they are very simple and 
 susceptible to race conditions, deadlocks or uncaught exceptions. Do not 
 use them if you need perform larger atomic operations such as reading from 
 multiple variables: use STM instead.
 
 In particular, the bigger functions in this module (readMVar, swapMVar, 
 withMVar, modifyMVar_ and modifyMVar) are simply the composition of a 
 takeMVar followed by a putMVar with exception safety. These only have 
 atomicity guarantees if all other threads perform a takeMVar before a 
 putMVar as well; otherwise, they may block.
 
 But I don't think that's the problem here.
 
 (Of course under the
 assumption that no other code touches the MVar).
This sentence referred to what you explained above. Although, my reference was 
quite cryptic.


 But in that case as
 well as in the case here it is only reproducible by looping the
 execution of the binary. Moving the loop into the Haskell program will
 show the bug in the first iteration or never.
 
 That's what I expect.
 I think what happens is:
 
 -- from Data.Typeable
 
 cache = unsafePerformIO $ ...
 
 
 mkTyConKey :: String - Key
 mkTyConKey str 
  = unsafePerformIO $ do
let Cache {next_key = kloc, tc_tbl = tbl} = cache
mb_k - HT.lookup tbl str
case mb_k of
  Just k  - return k
  Nothing - do { k - newKey kloc ;
  HT.insert tbl str k ;
  return k }
 
 occasionally, the second thread gets to perform the lookup before the first 
 has updated the cache, so both threads create a new entry and update the 
 cache.
 
 If you loop in the Haskell programme, after the first round each thread 
 definitely finds an entry for (), so the cache isn't updated anymore.

That sounds plausible. Do you see any workaround? Perhaps repeatedly evaluating 
typeOf?

Jean


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


Re: Is this a concurrency bug in base?

2011-10-09 Thread Jean-Marie Gaillourdet
Hi, 

On 09.10.2011, at 17:37, Jean-Marie Gaillourdet wrote:

 Hi,
 
 On 09.10.2011, at 17:27, Daniel Fischer wrote:
 
 That's what I expect.
 I think what happens is:
 
 -- from Data.Typeable
 
 cache = unsafePerformIO $ ...
 
 
 mkTyConKey :: String - Key
 mkTyConKey str 
 = unsafePerformIO $ do
   let Cache {next_key = kloc, tc_tbl = tbl} = cache
   mb_k - HT.lookup tbl str
   case mb_k of
 Just k  - return k
 Nothing - do { k - newKey kloc ;
 HT.insert tbl str k ;
 return k }
 
 occasionally, the second thread gets to perform the lookup before the first 
 has updated the cache, so both threads create a new entry and update the 
 cache.
 
 If you loop in the Haskell programme, after the first round each thread 
 definitely finds an entry for (), so the cache isn't updated anymore.
 
 That sounds plausible. Do you see any workaround? Perhaps repeatedly 
 evaluating typeOf?
typeOf' seems to be a working workaround: 

typeOf' val
| t1 == t2 = t1
| otherwise = typeOf' val
  where
t1 = typeOf'' val
t2 = typeOf''' val
{-# NOINLINE typeOf' #-}


typeOf'' x = typeOf x
{-# NOINLINE typeOf'' #-}
typeOf''' x = typeOf x
{-# NOINLINE typeOf''' #-}

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


Re: Is this a concurrency bug in base?

2011-10-09 Thread wagnerdm

Quoting Jean-Marie Gaillourdet j...@gaillourdet.net:

That sounds plausible. Do you see any workaround? Perhaps repeatedly  
evaluating typeOf?


If there's a concurrency bug, surely the workaround is to protect  
calls to the non-thread-safe function with a lock.


typeOfWorkaround lock v = do
() - takeMVar lock
x - evaluate (typeOf v)
putMVar lock ()
return x

~d

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


Re: case of an empty type should have no branches

2011-10-09 Thread Roman Beslik

On 09.10.11 15:45, Felipe Almeida Lessa wrote:

On Sun, Oct 9, 2011 at 8:26 AM, Roman Beslikber...@ukr.net  wrote:

Why the following code does not work?

data Empty
quodlibet :: Empty -  a
quodlibet x = case x of

parse error (possibly incorrect indentation)

Works for me:

   data Empty

   quodlibet :: Empty -  a
   quodlibet x = case x of _ -  undefined

This is a solution. Thanks.


I'd prefer to define something like

   data Finite = Zero | Plus Finite


You just defined the set of natural numbers which is infinite. ;)

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


Re: Is this a concurrency bug in base?

2011-10-09 Thread Jean-Marie Gaillourdet

On 09.10.2011, at 17:56, wagne...@seas.upenn.edu wrote:

 Quoting Jean-Marie Gaillourdet j...@gaillourdet.net:
 
 That sounds plausible. Do you see any workaround? Perhaps repeatedly 
 evaluating typeOf?
 
 If there's a concurrency bug, surely the workaround is to protect calls to 
 the non-thread-safe function with a lock.
 
typeOfWorkaround lock v = do
() - takeMVar lock
x - evaluate (typeOf v)
putMVar lock ()
return x

Yes, but this workaround is in the IO monad while mine is not.

Jean


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


Re: Is this a concurrency bug in base?

2011-10-09 Thread Daniel Fischer
On Sunday 09 October 2011, 17:51:06, Jean-Marie Gaillourdet wrote:
  That sounds plausible. Do you see any workaround? Perhaps repeatedly
  evaluating typeOf?
 
 typeOf' seems to be a working workaround: 
 
 typeOf' val
 | t1 == t2 = t1
 | otherwise = typeOf' val
   where
 t1 = typeOf'' val
 t2 = typeOf''' val
 {-# NOINLINE typeOf' #-}
 
 
 typeOf'' x = typeOf x
 {-# NOINLINE typeOf'' #-}
 typeOf''' x = typeOf x
 {-# NOINLINE typeOf''' #-}

That'll make it very improbable to get bad results, but not impossible.

Thread1: typeOf' (); typeOf'' (), lookup, not there
Thread2: typeOf' (); typeOf'' (), lookup, not there
Thread1: create and insert; typeOf''' (), entry present, use ~ Key 0
Thread2: create and insert, overwites entry with Key 0,
 new entry has Key 1; typeOf''' (), entry present, use ~ Key 1

It will probably take a long time until it bites, but when it does, it will 
hurt.
A proper fix would need a lock to ensure only one thread at a time can 
access the cache.

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


Re: Is this a concurrency bug in base?

2011-10-09 Thread Jean-Marie Gaillourdet

On 09.10.2011, at 18:13, Daniel Fischer wrote:

 On Sunday 09 October 2011, 17:51:06, Jean-Marie Gaillourdet wrote:
 That sounds plausible. Do you see any workaround? Perhaps repeatedly
 evaluating typeOf?
 
 typeOf' seems to be a working workaround: 
 
 typeOf' val
| t1 == t2 = t1
| otherwise = typeOf' val
  where
t1 = typeOf'' val
t2 = typeOf''' val
 {-# NOINLINE typeOf' #-}
 
 
 typeOf'' x = typeOf x
 {-# NOINLINE typeOf'' #-}
 typeOf''' x = typeOf x
 {-# NOINLINE typeOf''' #-}
 
 That'll make it very improbable to get bad results, but not impossible.
 
 Thread1: typeOf' (); typeOf'' (), lookup, not there
 Thread2: typeOf' (); typeOf'' (), lookup, not there
 Thread1: create and insert; typeOf''' (), entry present, use ~ Key 0
 Thread2: create and insert, overwites entry with Key 0,
 new entry has Key 1; typeOf''' (), entry present, use ~ Key 1
 
 It will probably take a long time until it bites, but when it does, it will 
 hurt.
 A proper fix would need a lock to ensure only one thread at a time can 
 access the cache.
Ok, you're right. I tried to avoid the IO monad, but there seems to be no way 
around it. 



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


log time instead of linear for case matching

2011-10-09 Thread Greg Weber
We have a couple use cases in Yesod that can potentially match many
different patterns. Routing connects the url of an http request to a Haskell
function. The current code just uses a pattern match, which scales linearly.
So if a site has a hundred different routes (urls), it could take 100
comparisons to finally match the url to a function. Michael Snoyman is
writing some code to make this issue obsolete. One of the things it does is
use a Map lookup instead of a case match.

More worrying is our system for internationalization of a website. A user is
supposed to make a sum type with every custom message as a constructor in
that sum type.

data Msg = Model
 | Year
 | Please

-- Rendering function for English.
renderEnglish Model  = Model
renderEnglish Year   = Year
renderEnglish Please = Please fill in your car's details

-- Rendering function for Swedish.
renderSwedish Model  = Modell
renderSwedish Year   = Årgång
renderSwedish Please = Vänligen fyll i uppgifterna för din bil

So if there are 100 custom messages on a site, that will setup a case match
with potentially 100 comparisons.

Note that we are using this technique for type safety- switching to a map
here would be difficult. We want to know at compile time that a translation
exists for every message.

So first of all I am wondering if a sum type comparison does in fact scale
linearly or if there are optimizations in place to make the lookup constant
or logarithmic. Second, I as wondering (for the routing case) if Haskell can
make a string case comparison logarithmic so that users can use case
comparisons instead of maps for string collections that are known at compile
time and won't change.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: log time instead of linear for case matching

2011-10-09 Thread Edward Z. Yang
Excerpts from Greg Weber's message of Sun Oct 09 12:39:03 -0400 2011:
 So first of all I am wondering if a sum type comparison does in fact scale
 linearly or if there are optimizations in place to make the lookup constant
 or logarithmic. Second, I as wondering (for the routing case) if Haskell can
 make a string case comparison logarithmic so that users can use case
 comparisons instead of maps for string collections that are known at compile
 time and won't change.

GHC will compile case-matches over large sum types into jump tables,
so the lookup becomes constant.  I don't think we have any cleverness for
strings.

Edward

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


Re: Is this a concurrency bug in base?

2011-10-09 Thread David Brown

On Sun, Oct 09, 2011 at 03:30:20PM +0200, Jean-Marie Gaillourdet wrote:

Hi Daniel,

On 09.10.2011, at 14:45, Daniel Fischer wrote:


On Sunday 09 October 2011, 13:52:47, Jean-Marie Gaillourdet wrote:

This seems to be a Heisenbug as it is extremely fragile, when adding a
| grep 1 to the while loop it seems to disappears. At least on my
computers.


Still produces 1s here with a grep.


Well, it may have been bad luck on my site.


The program below will occasionally print 1 /= 0 or 0 /= 1 on
x86_64 linux with the Debian testing 7.0.4 ghc.

$ ghc bug -rtsopts -threaded
$ while true; do ./bug +RTS -N; done


module Main where

import Control.Monad
import Control.Concurrent
import Data.Typeable

main :: IO ()
main = do
   fin1 - newEmptyMVar
   fin2 - newEmptyMVar

   forkIO $ child fin1
   forkIO $ child fin2

   a - takeMVar fin1
   b - takeMVar fin2
   when (a /= b) $
  putStrLn $ show a ++  /=  ++ show b

child :: MVar Int - IO ()
child var = do
   key - typeRepKey (typeOf ())
   putMVar var key


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


Re: Two Proposals

2011-10-09 Thread George Giorgidze
Thanks to all of you for providing feedback on my proposal and for providing 
alternatives.

In this email, I will try to collect all proposals and give pros and cons for 
each of those (although I will try to provide a good argumentation, some of 
them might be subjective).

Inspired by Simon's and Roman's suggestions I will introduce one more proposal, 
I am afraid.

Proposal (1): my original proposal

Pros:
* Simple and straightforward generalisation similar to fromInteger and 
fromString.

* Works with arithmetic sequences as well (i.e., for sequences like [1 .. 10], 
[x .. z], ['a' .. 'z']). Sequences will be desugared as defined in the Haskell 
standard and the proposed extension would just add the fromList function.

Cons:
* Performance. I share Roman's concerns. What we are overloading here is 
somewhat different from integer and string literals. Namely, what I was 
referring as list literals may feature expressions (e.g., a variable bound 
elsewhere as in f x = [x,x]) and hence may not be evaluated only once. Maybe I 
should have called it list notation and not list literals. This proposal 
would result into runtime overheads associated with conversion of lists.

* Programmers may provide partial instances failing at runtime.

(BTW. I agree that FromList is much better name than IsList).


Proposal (2) by Yitz (with improvements suggested by Gábor)
Pros:
* Allows partial instances to fail at compile time
* Allows writing of instances that convert lists at compile time

Cons:
* Consensus is emerging that people do not want to unnecessarily tie the 
lightweight extension of the list notation overloading to the heavyweight 
extension of Template Haskell.
* Not clear how to implement this and what would be the impact on quality of 
error messages.

(The first point is subjective, the second point can be addressed but at this 
stage I do not know how).


Proposal (3) by Roman: the Cons class

Pros:
* Addresses the runtime conversion issue

Cons:
* Does not support arithmetic sequences (this can be addressed, see below)


Proposal (4) by Simon: avoid classes and desugar to return and mappend
Pros:
* Addresses the runtime conversion issue
* Does not introduce new type classes (at least for the list notation)

Cons:
* Unnecessarily ties the list notation to the concept of monad.
* Does not support arithmetic sequences (this can be addressed, see below)


Proposal (5): one more proposal from me (I am afraid) addressing shortcomings 
of Proposal (3) and Proposal (4).

Here is the first attempt to generalise Proposal (4):

class Functor f = Pointed f where
  point :: a - f a

with the following (free) pointed law guaranteed by parametricity:

fmap f . point = point . f

Now the list notation can be desugared as follows:

[] = mempty
[x,y,z] = point x `mappend` point y `mappend` point z

Now this will work for any pointed function that is also a monoid (much larger 
class of structures than monads that are also monoids). However, Map and Text 
examples from my original proposal are still ruled out.

The following two classes provide as much flexibility as Proposal (1) but avoid 
going through lists at runtime.

class Singleton l where
  type Elem l
  singleton :: Elem l - l

Now the list notation can be desugarred as follows:

[] = mempty
[x,y,z] = singleton x `mappend` singleton y `mappend` singleton z

Also the following class can be used to desugar arithmetic sequences:

class Enum a = GenericEnum f a where
  genericEnumFrom:: a - f a
  genericEnumFromThen:: a - a - f a
  genericEnumFromTo  :: a - a - f a
  genericEnumFromThenTo  :: a - a - a - f a

as follows:

[ x.. ] =   genericEnumFrom x
[ x,y.. ]   =   genericEnumFromThen x y
[ x..y ]=   genericEnumFromTo x y
[ x,y..z ]  =   genericEnumFromThenTo x y z

To summarise:
* Proposal (5) is slightly more involved one compared to Proposal (1). 
* Proposal (5) avoids going through lists at runtime and is as flexible as 
Proposal (1).

For me both options are acceptable. But it seems Proposal (5) should be more 
suitable for DPH folks and other applications (other parallel arrays, e.g., GPU 
and distributed arrays) where going through lists at runtime is not an option 
for performance reasons.

OK, any thoughts on Proposal (1) vs. Proposal (5)?

Of course if no consensus is reached we should not implement any of those. 
Having said that, the reason I like this extension is that it has a potential 
to subsume and potentially displace two GHC extensions (list literal 
overloading and the DPH array notation) in future. This rarely happens these 
days :).

Cheers, George

P.S. Lennart, asked about defaulting rules and backwards compatibility. Let us 
keep this in mind and comeback to it after we decide on how to overload the 
list notation and arithmetic sequences in the first place.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org

Re: Two Proposals

2011-10-09 Thread George Giorgidze

On Oct 6, 2011, at 10:30 AM, Roman Leshchinskiy wrote:

 Manuel M T Chakravarty wrote:
 Roman Leshchinskiy:
 
 What data structures other than lists do we want to construct using list
 literals? I'm not really sure what the use cases are.
 
 Parallel arrays! (I want to get rid of our custom syntax.)
 
 Why? Don't you think it is useful to have a visual indication of which
 data structure you are using and what is going to be evaluated in
 parallel?

I am not a DPH developer :) (just an user), but I thought I would express some 
of my opinions that are related to your question.

Syntactic indications are nice. But why single out DPH arrays?

DPH arrays and associated combinators support a very important but only one 
kind of parallelism, namely nested data parallelism on shared memory multi-core 
hardware. As parallelism may turn out to be Haskell's killer application we 
will be dealing with many kinds of parallel data structure supporting different 
kinds of operations and thus having different types (e.g., GPU arrays, 
distributed arrays, flat data-parallel arrays). Having a special syntax for 
each of those would not be manageable.

 
 In any case, if we want to get rid of the parallel array syntax, we have
 to overload list literals, enumerations and list comprehensions. We have
 the generic monadic desugaring for the latter but recovering an efficient
 DPH program from that sn't trivial.

See Proposal (5) in my previous email. It suggests overloading of list literals 
and enumerations (I call those arithmetic sequences in that email) without 
going through lists at runtime. Would that work?

As for generic monad comprehension desugaring rules not being efficient enough, 
I believe it should be possible to define monad instance specific GHC rewrite 
rules that can rewrite the desugared code as needed. For example, I could 
imagine how one could rewrite monadic guards into filters, a chain of six zips 
into zip6 and things like that. I have not tried any of those though.

Cheers, George

 
 Roman
 
 
 


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


Re: Unwanted eta-expansion

2011-10-09 Thread Jan-Willem Maessen
On Sun, Oct 9, 2011 at 10:54 AM, Roman Cheplyaka r...@ro-che.info wrote:
 * Jan-Willem Maessen jmaes...@alum.mit.edu [2011-10-08 12:32:18-0400]
 It seems to be a common misconception that eta-abstracting your
 functions in this way will speed up or otherwise improve your code.

 Simon PJ has already provided a good explanation of why GHC eta
 expands.  Let me take another tack and describe why the code you wrote
 without eta expansion probably doesn't provide you with any actual
 benefit.  Roughly speaking, you're creating a chain of closures whose
 contents exactly describe the contents of your list (ie you've created
 something that's isomorphic to your original list structure), and so
 you should expect no benefit at all.

 Thanks for the analysis.

 I used myFoldl as a minimal example to ask the question.

 Here's an example of real code where this does make a difference:
 https://github.com/feuerbach/regex-applicative/tree/03ca9c852f06bf9a9d51505640b8b72f07291c7d

Ah, now things get more complicated!  :-)  I suspect here you're
actually entering the regexp closures, and compiling it down is
actually saving you a teensy bit of interpretive overhead.

 ...
 What's even more interesting (and puzzling!), if remove
 -fno-do-lambda-eta-expansion for Text/Regex/Applicative/Types.hs,
 the benchmark takes 2.82 seconds.

That *Is* odd.  The only obvious code generated here would be the
newtype instances, for which this should surely be irrelevant?  Can
someone at GHC HQ explain this one?

-Jan

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


Re: Two Proposals

2011-10-09 Thread Jan-Willem Maessen
2011/10/5 Simon Peyton-Jones simo...@microsoft.com:
 |  In the spirit of don't let the perfect be the enemy of the good
 |  though, I'm solidly in favor of the original proposal as it is.

 This is my thought too.  George is proposing to extend Haskell's existing 
 mechanism for numeric literals (namely, replace 4 by (fromInteger 
 (4::Integer))), so that it works for lists, just as Lennart did for Strings.  
 One could do more, as Yitz has suggested, but that would be an altogether 
 bigger deal, involving Template Haskell and quite a bit of new design; and if 
 done should apply uniformly to numeric and string literals too.

 So personally I favour George's general approach as a first step.  But here 
 is one thought.  In the spirit of monad comprehensions, should we not treat
        [a,b,c]
 as short for
        return a `mappend` return b `mappend` return c
 so that [a,b,c] syntax is, like [ e | x - xs ] syntax, just short for 
 monadic goop.  Then we would not need a new class at all, which would be nice.

No, you should not.  Most of the types of interest (Sets, Maps,
arrays) are not monads.  Conflating list comprehensions with monads is
a huge mistake, and this would repeat it.

-Jan

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