Re: [Haskell-cafe] Re: classes with types which are wrapped in

2010-01-27 Thread Stephen Tetley
2010/1/27 Andrew U. Frank fr...@geoinfo.tuwien.ac.at:
{Snip]

 dotoBfield :: (b - b) - X a b c - X a b c
 dotoBfield  op x = x { bfield = op (bfield x)}

 and similar for A and C.

 is there a better idiom to achieve the same effect?
 can this be automated (for example, using generics)?


Hello Andrew

I use a family of variations on the S combinator (also known as
Starling). I wouldn't argue its a better idiom, but I find it
pleasantly regular.

Suppose I had a data type for source positions like Parsec:

 data SrcPos = SrcPos {
  src_line   :: Int,
  src_column :: Int,
  src_tab_stop   :: Int
}

Then update functions on the record follow this pattern

pstarn update-function (one-or more selection-function)


 incrCol :: SrcPos - SrcPos
 incrCol = pstar (\i s - s { src_column=i+1 }) src_column

 incrTab :: SrcPos - SrcPos
 incrTab = pstar2 (\i t s - s { src_column= (i+t) }) src_column src_tab_stop


 incrLine :: SrcPos - SrcPos
 incrLine = pstar (\i s - s { src_line =i+1, src_column=1 }) src_line


At the moment I call the function family 'pstar' for permutated
starlings, but in combinatory logic terms I don't think its strictly
true to consider them permutations so they really need a new name.
Here are the definitions, the order of arguments is changed from
starlings to allow them to be generalized to functors should I need
more generality:


 pstar :: (a - r - ans)
   - (r - a)
   - r - ans
 pstar f fa x = f (fa x) x


 pstar2:: (a - b - r - ans)
   - (r - a) - (r - b)
   - r - ans
 pstar2 f fa fb x = f (fa x) (fb x) x

 pstar3:: (a - b - c - r - ans)
   - (r - a) - (r - b) - (r - c)
   - r - ans
 pstar3 f fa fb fc x = f (fa x) (fb x) (fc x) x

 pstar4:: (a - b - c - d - r - ans)
   - (r - a) - (r - b) - (r - c) - (r - d)
   - r - ans
 pstar4 f fa fb fc fd x = f (fa x) (fb x) (fc x) (fd x) x

 pstar5:: (a - b - c - d - e - r - ans)
   - (r - a) - (r - b) - (r - c) - (r - d) - (r - e)
   - r - ans
 pstar5 f fa fb fc fd fe x = f (fa x) (fb x) (fc x) (fd x) (fe x) x


Best wishes

Stephen
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] wxHaskell - using XRC files

2010-01-27 Thread Günther Schmidt

Hi,

I'm looking for documentation on using XRC files with wxHaskell.

I finally managed to cabal-install wxHaskell last night alas sans docs.

Günther

BTW: I'm using wxFormBuilder, any other good tools out there?


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Map unionWith generalization

2010-01-27 Thread Hans Aberg
I need ideally some generalizations of unionWith and unionWithKey, for  
efficiency matters (i.e. avoiding conversions and traversing the maps  
more than once). I could use a modification of the code in Map.hs, but  
then the problem is that the module Map interface does not export the  
constructors of data Map. So suggestions are welcome.


For example, in Map String Integer (sparse representation of  
monomials) compute the minimum value of all associative pairs with the  
same key (the gcd); if only one key is present, the absent should be  
treated as having value 0. So

  unionWith min xs ys
will not work, because unionWith will always apply the identity to the  
remaining value when one key is missing, whereas it should be sent to 0.


So here, one would want:
  (a - c) - (b - c) - (a - b - c) - Map k a - Map k b - Map  
k c
where the two first functions are applied when the first or second key  
is missing.


  Hans


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] custom widgets

2010-01-27 Thread Andrew U. Frank
we used wx originally but switched to gtk. the great advantage is glade... 
which is very flexible and still you can add/change whatever you need to in gtk 
in your haskell code.

we checked porting between linux (ubuntu) and windows (xp) and encountered no 
problems.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: wxHaskell - using XRC files

2010-01-27 Thread Gour
On Wed, 27 Jan 2010 11:09:06 +0100
 Günther == Günther Schmidt gue.schm...@web.de wrote:

Günther I'm looking for documentation on using XRC files with
Günther wxHaskell.

I'd like to find it too...so, far I've found only two samples:
xrcmenu.xrc  controls.xrc.

Günther BTW: I'm using wxFormBuilder, any other good tools out there?

Besides wxFormBuilder I played with DialogBlocks (eval version 'cause
it's not free).


Sincerely,
Gour

-- 

Gour  | Hlapicina, Croatia  | GPG key: F96FF5F6



signature.asc
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Map unionWith generalization

2010-01-27 Thread Jan-Willem Maessen

On Jan 27, 2010, at 5:53 AM, Hans Aberg wrote:

 I need ideally some generalizations of unionWith and unionWithKey, for 
 efficiency matters (i.e. avoiding conversions and traversing the maps more 
 than once). I could use a modification of the code in Map.hs, but then the 
 problem is that the module Map interface does not export the constructors of 
 data Map. So suggestions are welcome.
 
 For example, in Map String Integer (sparse representation of monomials) 
 compute the minimum value of all associative pairs with the same key (the 
 gcd); if only one key is present, the absent should be treated as having 
 value 0. So
  unionWith min xs ys
 will not work, because unionWith will always apply the identity to the 
 remaining value when one key is missing, whereas it should be sent to 0.
 
 So here, one would want:
  (a - c) - (b - c) - (a - b - c) - Map k a - Map k b - Map k c
 where the two first functions are applied when the first or second key is 
 missing.

Ah, the swiss army knife function on maps.  This particular formulation works 
well for the application you describe above, where you're completely traversing 
both maps.  The following really grubby variant can be used to implement 
asymptotically efficient variations of union, intersection, difference, etc., 
etc:

swissArmy ::
  (Map k a - Map k c) --- Used to process submaps unique to the left map
  (Map k b - Map k c) --- Used to process submaps unique to the right map
  (a - b - Maybe c) - -- Used to process a single common entry
  Map k a - Map k b - Map k c

Then your function appears to be:

-- helper
just2 :: (a - b - c) - a - b - Maybe c
just2 f a b = Just (f a b)

swissArmy (fmap (const 0)) (fmap (const 0)) (just2 gcd)

Here are unionWith and intersectionWith:

unionWith f = swissArmy id id (just2 f)
intersectionWith = swissArmy (const empty) (const empty) (just2 f)
differenceWith = swissArmy id (const empty) (\a b - Nothing)

When throwing together tree-like data structures, I often start by writing this 
function; it handles most of the bulk operations I might want to do as 
one-liners.  It's got a messy, ugly type signature, but it does everything you 
want as efficiently as you want.*

-Jan-Willem Maessen

* Actually, this is only true if you add the key as an argument to the third 
function, so that you can also encode unionWithKey etc!  I've skipped that here.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: wxHaskell - using XRC files

2010-01-27 Thread Günther Schmidt

Hello Gour,

creating the .xrc files with WxFormBuilder isn't the problem, I'd need 
to see the .hs files where these resources are imported and used. Do you 
happen to know where to find those too?


Günther

Am 27.01.10 13:38, schrieb Gour:

On Wed, 27 Jan 2010 11:09:06 +0100

Günther == Günther Schmidtgue.schm...@web.de  wrote:


Günther  I'm looking for documentation on using XRC files with
Günther  wxHaskell.

I'd like to find it too...so, far I've found only two samples:
xrcmenu.xrc  controls.xrc.

Günther  BTW: I'm using wxFormBuilder, any other good tools out there?

Besides wxFormBuilder I played with DialogBlocks (eval version 'cause
it's not free).


Sincerely,
Gour




___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe




___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: wxHaskell - using XRC files

2010-01-27 Thread Gour
On Wed, 27 Jan 2010 14:56:28 +0100
 Günther == Günther Schmidt gue.schm...@web.de wrote:

Günther creating the .xrc files with WxFormBuilder isn't the problem,
Günther I'd need to see the .hs files where these resources are
Günther imported and used. Do you happen to know where to find those
Günther too?

I cannot remember where did I find them, but I'm sending 'em via
email.


Sincerely,
Gour

-- 

Gour  | Hlapicina, Croatia  | GPG key: F96FF5F6



signature.asc
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Map unionWith generalization

2010-01-27 Thread Hans Aberg

On 27 Jan 2010, at 14:56, Jan-Willem Maessen wrote:


So here, one would want:
(a - c) - (b - c) - (a - b - c) - Map k a - Map k b - Map  
k c
where the two first functions are applied when the first or second  
key is missing.


Ah, the swiss army knife function on maps.  This particular  
formulation works well for the application you describe above, where  
you're completely traversing both maps.  The following really grubby  
variant can be used to implement asymptotically efficient variations  
of union, intersection, difference, etc., etc:


swissArmy ::
 (Map k a - Map k c) --- Used to process submaps unique to the  
left map
 (Map k b - Map k c) --- Used to process submaps unique to the  
right map

 (a - b - Maybe c) - -- Used to process a single common entry
 Map k a - Map k b - Map k c


I'm not sure why you want to throw in functions between maps in the  
two first arguments. Then there is no requirement that single keys are  
preserved.


But it is a good idea to have a Maybe so that one can remove keys on  
the fly.



Then your function appears to be:

-- helper
just2 :: (a - b - c) - a - b - Maybe c
just2 f a b = Just (f a b)

swissArmy (fmap (const 0)) (fmap (const 0)) (just2 gcd)

Here are unionWith and intersectionWith:

unionWith f = swissArmy id id (just2 f)
intersectionWith = swissArmy (const empty) (const empty) (just2 f)
differenceWith = swissArmy id (const empty) (\a b - Nothing)

When throwing together tree-like data structures, I often start by  
writing this function; it handles most of the bulk operations I  
might want to do as one-liners.  It's got a messy, ugly type  
signature, but it does everything you want as efficiently as you  
want.*


My guess is that is when you write things from scratch.

I wanted to add these function on top of the module Data.Map, but then  
that seems not to be possible, as the constructors are not exported. I  
could make a copy of this file, and then make my own variation.


  Hans


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Supporting GHC 6.10 and 6.12 in HDBC-postgresql Setup.hs

2010-01-27 Thread Neil Mitchell
 The other HDBC problem I have is various dependencies relying on QC1.

 The next HP will ship with QC 2.1 (in coming weeks), so it might be a
 good time for people to start migrating, since that will be the only
 version of QC on many distros.

I would strongly suggest moving to QC 2 for other reasons as well. It
does substantially better at searching the random space, to the extent
where several of my properties pass under QC 1 but fail under QC 2.
It's a much better testing tool.

Thanks, Neil
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: wxHaskell - using XRC files

2010-01-27 Thread Jeremy O'Donoghue
Hi Guenther, Gour

On Wed, 27 Jan 2010 13:38 +0100, Gour g...@gour-nitai.com wrote:
 On Wed, 27 Jan 2010 11:09:06 +0100
  Günther == Günther Schmidt gue.schm...@web.de wrote:
 
 Günther I'm looking for documentation on using XRC files with
 Günther wxHaskell.
 
 I'd like to find it too...so, far I've found only two samples:
 xrcmenu.xrc  controls.xrc.

You have found just about all there is, I'm afraid. It's on my list for
a Blog article, but as you may have realised, my list is quite long, and
the rate of service rather slow.

The basics are pretty straightforward if you have read and understood
the wxWidgets documentation on XRC.

- An XRC file needs to be loaded into a top level window.
- The objects created when the XRC file is loaded can be made available
to wxHaskell by name using the widgetRes functions (you will find most
of them in Graphics.UI.WX.Controls)

There are quite a few things to watch out for:
- XRC is incompatible with Layout (the XRC contains its own sizers, and
Layout creates sizers suitable for a given window layout)
- You must load your control as a child of the window in which you
loaded the XRC file
- If you try to fetch a control whose name doesn't exist, or if you load
a control by name as the wrong type of control, you will almost
certainly crash irrecoverably (the crash is usually in the wxWidgets
.DLL/.so/.dylib)
- It is not really possible to control an XRC-based menu very well. As
an example, I have never succeeded in disabling a menu option
- I also have not succeeded in getting XRC to work with wxHaskell custom
controls (and I've tried fairly hard). This is currently a show-stopper
for me. I very much doubt that this will ever work without putting
wxHaskell support into a GUI builder, since wxHaskell custom widgets do
not look (to C++) quite the same as C++ custom widgets.

The whole of the XRC support really needs a typesafe veneer over it (if
you search the wxhaskell-devel archives, there was a proof of concept
for doing this proposed about 8 months ago), and probably some
wxHaskell-specific work in a GUI builder.

I'll do my best to answer any specific questions you have.

Best regards
Jeremy

 Günther BTW: I'm using wxFormBuilder, any other good tools out there?
 
 Besides wxFormBuilder I played with DialogBlocks (eval version 'cause
 it's not free).
 
 
 Sincerely,
 Gour
 
 -- 
 
 Gour  | Hlapicina, Croatia  | GPG key: F96FF5F6
 
-- 
  Jeremy O'Donoghue
  jeremy.odonog...@gmail.com

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Supporting GHC 6.10 and 6.12 in HDBC-postgresql Setup.hs

2010-01-27 Thread John Goerzen
Neil Mitchell wrote:
 The other HDBC problem I have is various dependencies relying on QC1.

 The next HP will ship with QC 2.1 (in coming weeks), so it might be a
 good time for people to start migrating, since that will be the only
 version of QC on many distros.
 
 I would strongly suggest moving to QC 2 for other reasons as well. It
 does substantially better at searching the random space, to the extent
 where several of my properties pass under QC 1 but fail under QC 2.
 It's a much better testing tool.

I will be making that change once it gets into haskell-platform (and
once I have the time).

My more urgent problem, though, is maintaining Cabal compatibility with
6.10 and 6.12.

-- John

 
 Thanks, Neil
 

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] scheduling an alarm

2010-01-27 Thread Brian Denheyer
On Tue, 26 Jan 2010 22:41:44 -0800
Thomas DuBuisson thomas.dubuis...@gmail.com wrote:

 Brian Denheyer bri...@aracnet.com wrote:
 
  On Tue, 26 Jan 2010 10:54:03 -0800
  Thomas DuBuisson thomas.dubuis...@gmail.com wrote:
 
doEvent f usDelay = forkIO $
  threadDelay usDelay
  doEvent f usDelay
  f
 
  Are you sure that's right ? It seems to be a memory-gobbling
  infinite loop...
 
 
 Infinite loop?  yes, that is what you wanted.  Memory gobbling?  Why
 would you think that? Are you assuming no TCO and a full stack push
 on every function call?  Haskell compilers don't work that way.

Why would I think that ?
I think that because the following code:

import Control.Concurrent

f = putStrLn foo

doEvent f usDelay = do forkIO $ threadDelay usDelay
   doEvent f usDelay
   f

_really_ _does_ start to consume all of the memory on my system, that's
why.  I don't know why, but that's what it does on my system.  It's not
obvious to me that it should do that.  So maybe ghci is not doing TCO.

 1) There are a million ways to do this - why does one working make you
 suspicious of another?  You can always test the other - it does work
 so long as you fix the missing 'do'.

The suspicious part, that was a joke.
Having something that works is nice, making sure I understand it is
better. I haven't used the Concurrent stuff before, so I'm just
being tentative.

 
 2) It strikes me as funny you suspect the first way when there is zero
 fundamental difference between that and the way you posted except
 that: a) My version maintains the correct delay.
 b) My version forks the doEvent call and runs the action in the older
 thread while yours forks the action thread and keeps the doEvent in
 the older thread.  I suppose keeping the doEvent as the old thread is
 good so you can kill it with the original ThreadID that would be
 returned to the caller.
 

Thanks for the explanation, as I said I'm a little fuzzy on what
constitutes a thread, so the two versions will help.

One interesting thing I noticed in the docs (which is not important
for what I am trying to do, just interesting):

There is no guarantee that the thread will be rescheduled promptly when
the delay has expired, but the thread will never continue to run
earlier than specified. 

I expect that this means promptly in the sense of not accurately,
however I wonder what the upper bound on the (potential) delay is ?

 Some people miss the fact that threadDelay is a us value and an Int
 type - this limits the maximum delay to something like 35 minutes
 (assume a 32 bit Int) or even just 134 seconds if you go by Haskell
 98 minimum of 27 bit Ints.  Just making sure you realize this seeing
 as we are talking about delays in that order of magnitude.  I advise
 the overly-complex but functional Control-Event package if you want
 longer delays.
 

I did notice that the delay is in us.  35 minutes is plenty of time.  I
can always delay twice ;-)

Thanks for pointing me to control event, that looks useful !

Brian


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Map unionWith generalization

2010-01-27 Thread Jan-Willem Maessen

On Jan 27, 2010, at 9:42 AM, Hans Aberg wrote:

 On 27 Jan 2010, at 14:56, Jan-Willem Maessen wrote:
 
 So here, one would want:
 (a - c) - (b - c) - (a - b - c) - Map k a - Map k b - Map k c
 where the two first functions are applied when the first or second key is 
 missing.
 
 Ah, the swiss army knife function on maps.  This particular formulation 
 works well for the application you describe above, where you're completely 
 traversing both maps.  The following really grubby variant can be used to 
 implement asymptotically efficient variations of union, intersection, 
 difference, etc., etc:
 
 swissArmy ::
 (Map k a - Map k c) --- Used to process submaps unique to the left map
 (Map k b - Map k c) --- Used to process submaps unique to the right map
 (a - b - Maybe c) - -- Used to process a single common entry
 Map k a - Map k b - Map k c
 
 I'm not sure why you want to throw in functions between maps in the two first 
 arguments. Then there is no requirement that single keys are preserved.
 
 But it is a good idea to have a Maybe so that one can remove keys on the fly.

A good point.  Technically, one should delimit the scope of the first two 
arguments:

data KeyPreservingMapOperation k a b = AlwaysEmpty | Identity | MapMaybeWithKey 
(k - a - Maybe b)

perform :: KeyPreservingMapOperation a b - Map k a - Map k b
perform AlwaysEmpty = const empty
perform Identity = id
perform (MapMaybeWithKey f) = mapMaybeWithKey f

 When throwing together tree-like data structures, I often start by writing 
 this function; it handles most of the bulk operations I might want to do as 
 one-liners.  It's got a messy, ugly type signature, but it does everything 
 you want as efficiently as you want.*
 
 My guess is that is when you write things from scratch.

Yes.  On the other hand, I've repeatedly run into the same problem you're 
describing: a api that doesn't give me an efficient way to perform an operation 
I know to be very simple.  If every map provided an operation like this one, 
then I can avoid writing my own library from scratch when I need it --- 
especially when from scratch means fork the code and add what I need.

So, library implementors: think hard about your swiss army knife combinators. 
 You end up with messy functions with gigantic signatures.  On the other hand, 
you can often add a couple of judicious INLINE annotations and remove tons of 
code from the rest of your library.  Then expose them, and mark them as the 
functions of last resort that they truly are.

I bet there's even a fusion framework in here somewhere.

-Jan___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Map unionWith generalization

2010-01-27 Thread Hans Aberg

On 27 Jan 2010, at 16:33, Jan-Willem Maessen wrote:

I'm not sure why you want to throw in functions between maps in the  
two first arguments. Then there is no requirement that single keys  
are preserved.


But it is a good idea to have a Maybe so that one can remove keys  
on the fly.


A good point.  Technically, one should delimit the scope of the  
first two arguments:


data KeyPreservingMapOperation k a b = AlwaysEmpty | Identity |  
MapMaybeWithKey (k - a - Maybe b)


perform :: KeyPreservingMapOperation a b - Map k a - Map k b
perform AlwaysEmpty = const empty
perform Identity = id
perform (MapMaybeWithKey f) = mapMaybeWithKey f


I'm thinking about
  (k - Maybe a - Maybe b - Maybe c) - Map k a - Map k b - Map k c
The first two Maybe's tell if the keys are present, the last if one  
wants it in the resulting map.


When throwing together tree-like data structures, I often start by  
writing this function; it handles most of the bulk operations I  
might want to do as one-liners.  It's got a messy, ugly type  
signature, but it does everything you want as efficiently as you  
want.*


My guess is that is when you write things from scratch.


Yes.  On the other hand, I've repeatedly run into the same problem  
you're describing: a api that doesn't give me an efficient way to  
perform an operation I know to be very simple.  If every map  
provided an operation like this one, then I can avoid writing my own  
library from scratch when I need it --- especially when from  
scratch means fork the code and add what I need.


So, library implementors: think hard about your swiss army knife  
combinators.  You end up with messy functions with gigantic  
signatures.  On the other hand, you can often add a couple of  
judicious INLINE annotations and remove tons of code from the rest  
of your library.  Then expose them, and mark them as the functions  
of last resort that they truly are.


One can transverse the product of keys. Then I'm thinking about
  (k1 - k2 - a - b - Maybe c - Maybe(k, c)) - Map k1 a - Map  
k2 b - Map k c
The first Maybe tells if the key is already present; the second if one  
wants it inserted.


The idea in both cases is to combine the modifying functions into one.  
This simplifies the interface.


  Hans


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] scheduling an alarm

2010-01-27 Thread Thomas DuBuisson
On Wed, Jan 27, 2010 at 7:31 AM, Brian Denheyer bri...@aracnet.com wrote:

 On Tue, 26 Jan 2010 22:41:44 -0800
 Thomas DuBuisson thomas.dubuis...@gmail.com wrote:

  Brian Denheyer bri...@aracnet.com wrote:
 
   On Tue, 26 Jan 2010 10:54:03 -0800
   Thomas DuBuisson thomas.dubuis...@gmail.com wrote:
  
 doEvent f usDelay = forkIO $
   threadDelay usDelay
   doEvent f usDelay
   f
  
   Are you sure that's right ? It seems to be a memory-gobbling
   infinite loop...
  
 
  Infinite loop?  yes, that is what you wanted.  Memory gobbling?  Why
  would you think that? Are you assuming no TCO and a full stack push
  on every function call?  Haskell compilers don't work that way.

 Why would I think that ?
 I think that because the following code:

 import Control.Concurrent

 f = putStrLn foo

 doEvent f usDelay = do forkIO $ threadDelay usDelay
   doEvent f usDelay
   f

 _really_ _does_ start to consume all of the memory on my system, that's
 why.  I don't know why, but that's what it does on my system.  It's not
 obvious to me that it should do that.  So maybe ghci is not doing TCO.


That would be a bug!  I'm using GHC 6.12.1 i386 and both interpreted using
GHCi CLI and compiled (even without optimization) there is no memory growth
using either of the two versions.  If you are using the latest GHC then
consider filing a report at haskell.org/ghc



 2) It strikes me as funny you suspect the first way when there is zero
  fundamental difference between that and the way you posted except
  that: a) My version maintains the correct delay.
  b) My version forks the doEvent call and runs the action in the older
  thread while yours forks the action thread and keeps the doEvent in
  the older thread.  I suppose keeping the doEvent as the old thread is
  good so you can kill it with the original ThreadID that would be
  returned to the caller.
 

 Thanks for the explanation, as I said I'm a little fuzzy on what
 constitutes a thread, so the two versions will help.


Well Concurrent Haskell has a version of green threads [1] which are
scheduled (via the GHC RTS) on some number of OS threads (typically either 1
or equal to the number of cores on the machine).  These light weight green
threads are extremely cheap to create and destroy, costing a matter of 1K
or less per thread, benchmarks can create/destory 100k threads in seconds.
forkIO creates green threads while forkOS (which you generally should
not use) creates OS threads.

One interesting thing I noticed in the docs (which is not important
 for what I am trying to do, just interesting):

 There is no guarantee that the thread will be rescheduled promptly when
 the delay has expired, but the thread will never continue to run
 earlier than specified.


Right, and this is the same as any commodity OS - you can delay for a
certain amount of time and once the delay is up you will get rescheduled but
the computer is likely busy with other processes/interrupts etc at the exact
microsecond you are done.  I think the GHC RTS schedules threads in 50us
slices by default.  Also, GHC uses (or used to use) allocation as a
scheduling point so if you have long-running tight loops that don't allocate
(and don't explicitly call 'yield') then this could be quite long. In
practice I've only once had a problem (GTK GUI didn't update during a long
computation - still not sure this was the reason).

Cheers,
Thomas

[1] http://en.wikipedia.org/wiki/Green_threads
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Non-termination of type-checking

2010-01-27 Thread Matthieu Sozeau

Dear Haskellers,

  while trying to encode a paradox recently found in Coq if one has
impredicativity and adds injectivity of type constructors [1] I
stumbled on an apparent loop in the type checker when using GADTs,
Rank2Types and EmptyDataDecls.

 {-# OPTIONS -XGADTs -XRank2Types -XEmptyDataDecls #-}

 module Impred where

The identity type

 data ID a = ID a

I is from (* - *) to *, we use a partial application of [ID] here.

 data I f where
  I1 :: I ID

The usual reification of type equality into a term.

 data Equ a b where
  Eqrefl :: Equ a a

The empty type

 data False

This uses impredicativity: Rdef embeds a (* - *) - *
object into R x :: *.

 data R x where
  Rdef :: (forall a. Equ x (I a) - a x - False) - R x

 r_eqv1 :: forall p. R (I p) - p (I p) - False
 r_eqv1 (Rdef f) pip = f Eqrefl pip

 r_eqv2 :: forall p. (p (I p) - False) - R (I p)
 r_eqv2 f = Rdef (\ eq ax -
case eq of -- Uses injectivity of type  
constructors

 Eqrefl - f ax)

 r_eqv_not_R_1 :: R (I R) - R (I R) - False
 r_eqv_not_R_1 = r_eqv1

 r_eqv_not_R_2 :: (R (I R) - False) - R (I R)
 r_eqv_not_R_2 = r_eqv2

 rir :: R (I R)
 rir = r_eqv_not_R_2 (\ rir - r_eqv_not_R_1 rir rir)

Type checking seems to loop here with ghc-6.8.3, which is a
bit strange given the simplicity of the typing problem.
Maybe it triggers a constraint with something above?

 -- Loops
 -- absurd :: False
 -- absurd = r_eqv_not_R_1 rir rir

[1] 
http://thread.gmane.org/gmane.science.mathematics.logic.coq.club/4322/focus=1405

-- Matthieu
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] ANNOUNCE: ThreadScope 0.1

2010-01-27 Thread Satnam Singh
I've just released ThreadScope version 0.1 on Hackage. Threadscope is a 
graphical utility for viewing profiling information about Haskell threads. It 
was written jointly with Simon Marlow and Donnie Jones. It uses Gtk2HS so it 
works under Windows and the L-word operating system although there seem to be 
problems making it work with OS-X (due to Gtk2Hs issues I think).

$ cabal install threadscope

You may need to do cabal update to update your packages list. On Windows 
operating systems you may need to issue the command from a shell that is 
running with administrative privileges.

Resources:

* Web page: http://research.microsoft.com/threadscope

*  Parallel Performance Tuning for 
Haskellhttp://research.microsoft.com/apps/pubs/default.aspx?id=80976 (paper 
at Haskell Symposium 2009)

Please let me know if you have any problems. Also, please do let us know about 
your experience with ThreadScope and in particular about accounts of how you 
used ThreadScope to shed light on parallel performance bugs. If I get enough 
feedback I may collate the responses into an experience report or paper for 
ICFP or the Haskell Symposium. Thank you kindly. Enjoy!

Cheers,

Satnam


Satnam Singh
Microsoft
7 JJ Thomson Avenue
Cambridge
CB3 0FB
United Kingdom

Email: satn...@microsoft.commailto:satn...@microsoft.com
UK tel: +44 1223 479905
Fax: +44 1223 479 999
UK mobile: +44 7979 648412
USA cell: 206 330 1580
USA tel: 206 219 9024
URL: http://research.microsoft.com/~satnams
Live Messenger: sat...@raintown.orgmailto:sat...@raintown.org

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Determining application directory

2010-01-27 Thread Matveev Vladimir
Hi,
I'm writing cross-platform application in Haskell which should be
running under Windows and Linux. Under Linux configuration is stored
in the /etc directory, and under Windows configuration is meant to be in
the application directory. So, is there a way to get an application
directory path under Windows? I remember that there is a way to do this
using WinAPI, but how to do this Haskell?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Determining application directory

2010-01-27 Thread Chris Eidhof
Hi Matveev,

You might be interested in the System.Directory module:

http://hackage.haskell.org/packages/archive/directory/1.0.0.3/doc/html/System-Directory.html

HTH,

-chris

On 27 jan 2010, at 18:06, Matveev Vladimir wrote:

 Hi,
 I'm writing cross-platform application in Haskell which should be
 running under Windows and Linux. Under Linux configuration is stored
 in the /etc directory, and under Windows configuration is meant to be in
 the application directory. So, is there a way to get an application
 directory path under Windows? I remember that there is a way to do this
 using WinAPI, but how to do this Haskell?
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Determining application directory

2010-01-27 Thread Rahul Kapoor
 So, is there a way to get an application
 directory path under Windows? I remember that there is a way to do this
 using WinAPI, but how to do this Haskell?

The System.Directory module has some methods to get specific
directory names in an OS agnostic manner.

The closest method that matches what you want
is getAppUserDataDirectory which uses the windows API function
SHGetFolderPath to get the folder for well known name. IIRC
Windows supports a notion of Constant special item's and if
getAppUserDataDirectory does not do what you want you can call
SHGetFolderPath using the CSIDL you are interested in.  The code
to do so should be identical to the source
for getAppUserDataDirectory

CSIDL'a are listed here [1]


Links.
[1] http://msdn.microsoft.com/en-us/library/bb762494%28VS.85%29.a
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Determining application directory

2010-01-27 Thread Thomas DuBuisson
Other responses have been great but if you are cabalizing you might also be
interested in:

http://neilmitchell.blogspot.com/2008/02/adding-data-files-using-cabal.html

Cheers,
Thomas

On Wed, Jan 27, 2010 at 9:06 AM, Matveev Vladimir dpx.infin...@gmail.comwrote:

 Hi,
 I'm writing cross-platform application in Haskell which should be
 running under Windows and Linux. Under Linux configuration is stored
 in the /etc directory, and under Windows configuration is meant to be in
 the application directory. So, is there a way to get an application
 directory path under Windows? I remember that there is a way to do this
 using WinAPI, but how to do this Haskell?
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Determining application directory

2010-01-27 Thread Vladimir Matveev
Program directory is not system directory. So it doesn't have CSIDL.
Program directory is the folder where executable file is located.
I certainly remember that there is a way to get it without, for example,
setting it in registry during install...

On Wed, Jan 27, 2010 at 12:31:19PM -0500, Rahul Kapoor wrote:
  So, is there a way to get an application
  directory path under Windows? I remember that there is a way to do this
  using WinAPI, but how to do this Haskell?
 
 The System.Directory module has some methods to get specific
 directory names in an OS agnostic manner.
 
 The closest method that matches what you want
 is getAppUserDataDirectory which uses the windows API function
 SHGetFolderPath to get the folder for well known name. IIRC
 Windows supports a notion of Constant special item's and if
 getAppUserDataDirectory does not do what you want you can call
 SHGetFolderPath using the CSIDL you are interested in.  The code
 to do so should be identical to the source
 for getAppUserDataDirectory
 
 CSIDL'a are listed here [1]
 
 
 Links.
 [1] http://msdn.microsoft.com/en-us/library/bb762494%28VS.85%29.a
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Determining application directory

2010-01-27 Thread Vladimir Matveev
Thanks, but my program will be distributed in self-made installer (on
windows), though I'm using cabal and the sources are GPL-licensed.
Just for users' convenience :)

On Wed, Jan 27, 2010 at 09:42:45AM -0800, Thomas DuBuisson wrote:
 Other responses have been great but if you are cabalizing you might also be
 interested in:
 
 http://neilmitchell.blogspot.com/2008/02/adding-data-files-using-cabal.html
 
 Cheers,
 Thomas
 
 On Wed, Jan 27, 2010 at 9:06 AM, Matveev Vladimir 
 dpx.infin...@gmail.comwrote:
 
  Hi,
  I'm writing cross-platform application in Haskell which should be
  running under Windows and Linux. Under Linux configuration is stored
  in the /etc directory, and under Windows configuration is meant to be in
  the application directory. So, is there a way to get an application
  directory path under Windows? I remember that there is a way to do this
  using WinAPI, but how to do this Haskell?
  ___
  Haskell-Cafe mailing list
  Haskell-Cafe@haskell.org
  http://www.haskell.org/mailman/listinfo/haskell-cafe
 
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Determining application directory

2010-01-27 Thread Vladimir Matveev
Oh yeah, it seems I found it. Solution is to use getModuleFileName and
getModuleHandle functions from System.Win32.DLL. Thanks for attention :)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Linguistic hair-splitting

2010-01-27 Thread Andrew Coppin

Here's one for you to ponder.

7 is a number. 7 is an integer, and integers are numbers.

7 is not a field. 7 is an element of [at least one] field, but 7 itself 
is not a field.


7 is not a group. 7 is a member of the set of integers, but the set of 
integers is not a group either. The set of integers form a group when 
taken together with the addition operator. (And, actually, forms 
another, different, group when taken with the multiplication operator.)


Now, here's the question: Is is correct to say that [3, 5, 8] is a 
monad? Is it correct to say that lists are a monad? Or would it be more 
correct to say that lists form a monad?


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Linguistic hair-splitting

2010-01-27 Thread Jochem Berndsen
Andrew Coppin wrote:
 7 is a number. 7 is an integer, and integers are numbers.
 
 7 is not a field. 7 is an element of [at least one] field, but 7 itself
 is not a field.
 
 7 is not a group. 

Why not? It might be useful to use the notation '7' for the cyclic group
with 7 elements.

 7 is a member of the set of integers, but the set of
 integers is not a group either. The set of integers form a group when
 taken together with the addition operator. (And, actually, forms
 another, different, group when taken with the multiplication operator.)

The integers endowed with the usual multiplication is not a group. (The
only invertible elements of this monoid are 1 and -1.)

 Now, here's the question: Is is correct to say that [3, 5, 8] is a
 monad? 

In what sense would this be a monad? I don't quite get your question.

Cheers, Jochem

-- 
Jochem Berndsen | joc...@functor.nl

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Linguistic hair-splitting

2010-01-27 Thread Daniel Peebles
The list type constructor ([] :: * - *) is a functor, and if you add the
implementations of join/return (or just return and bind) those together make
the monad. The value-level list [3,5,8] is just a list :)

On Wed, Jan 27, 2010 at 1:30 PM, Andrew Coppin
andrewcop...@btinternet.comwrote:

 Here's one for you to ponder.

 7 is a number. 7 is an integer, and integers are numbers.

 7 is not a field. 7 is an element of [at least one] field, but 7 itself is
 not a field.

 7 is not a group. 7 is a member of the set of integers, but the set of
 integers is not a group either. The set of integers form a group when taken
 together with the addition operator. (And, actually, forms another,
 different, group when taken with the multiplication operator.)

 Now, here's the question: Is is correct to say that [3, 5, 8] is a monad?
 Is it correct to say that lists are a monad? Or would it be more correct to
 say that lists form a monad?

 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Determining application directory

2010-01-27 Thread Holger Siegel
Am Mittwoch, den 27.01.2010, 21:19 +0300 schrieb Vladimir Matveev:
 Oh yeah, it seems I found it. Solution is to use getModuleFileName and
 getModuleHandle functions from System.Win32.DLL. Thanks for attention :)

You can also use the (portable) package 'directory' from Hackage
(http://hackage.haskell.org/package/directory).


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Linguistic hair-splitting

2010-01-27 Thread Luke Palmer
On Wed, Jan 27, 2010 at 11:39 AM, Jochem Berndsen joc...@functor.nl wrote:
 Now, here's the question: Is is correct to say that [3, 5, 8] is a
 monad?

 In what sense would this be a monad? I don't quite get your question.

I think the question is this:  if m is a monad, then what do you call
a thing of type m Int, or m Whatever.

Luke
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Linguistic hair-splitting

2010-01-27 Thread Jochem Berndsen
Luke Palmer wrote:
 On Wed, Jan 27, 2010 at 11:39 AM, Jochem Berndsen joc...@functor.nl wrote:
 Now, here's the question: Is is correct to say that [3, 5, 8] is a
 monad?
 In what sense would this be a monad? I don't quite get your question.
 
 I think the question is this:  if m is a monad, then what do you call
 a thing of type m Int, or m Whatever.

Ah yes, I see. It's probably the most common to call this a monadic
value or monadic action. As Daniel pointed out, the type constructor
itself is called a monad (e.g., Maybe).

Jochem

-- 
Jochem Berndsen | joc...@functor.nl
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Map unionWith generalization

2010-01-27 Thread Jan-Willem Maessen

On Jan 27, 2010, at 10:54 AM, Hans Aberg wrote:

 On 27 Jan 2010, at 16:33, Jan-Willem Maessen wrote:
 
 I'm not sure why you want to throw in functions between maps in the two 
 first arguments. Then there is no requirement that single keys are 
 preserved.
 
 But it is a good idea to have a Maybe so that one can remove keys on the 
 fly.
 
 A good point.  Technically, one should delimit the scope of the first two 
 arguments:
 
 data KeyPreservingMapOperation k a b = AlwaysEmpty | Identity | 
 MapMaybeWithKey (k - a - Maybe b)
 
 perform :: KeyPreservingMapOperation a b - Map k a - Map k b
 perform AlwaysEmpty = const empty
 perform Identity = id
 perform (MapMaybeWithKey f) = mapMaybeWithKey f
 
 I'm thinking about
  (k - Maybe a - Maybe b - Maybe c) - Map k a - Map k b - Map k c
 The first two Maybe's tell if the keys are present, the last if one wants it 
 in the resulting map.

That has the same behavior semantically, but it's no more efficient than 
performing a unionWith followed by a filter.  For example, consider 
implementing:

xs `intersection` singleton k v

in this way.  With the function given, the complexity is necessarily O(size 
xs): we must traverse every key/value pair in xs.  By contrast, by aggregating 
the operations on keys that exist only in a single map, we can write functions 
like intersection with the desired complexity (which is O(log (size xs)) in 
this case).

 Yes.  On the other hand, I've repeatedly run into the same problem you're 
 describing: a api that doesn't give me an efficient way to perform an 
 operation I know to be very simple.  If every map provided an operation like 
 this one, then I can avoid writing my own library from scratch when I need 
 it --- especially when from scratch means fork the code and add what I 
 need.
 
 So, library implementors: think hard about your swiss army knife 
 combinators.  You end up with messy functions with gigantic signatures.  On 
 the other hand, you can often add a couple of judicious INLINE annotations 
 and remove tons of code from the rest of your library.  Then expose them, 
 and mark them as the functions of last resort that they truly are.
 
 One can transverse the product of keys. Then I'm thinking about
  (k1 - k2 - a - b - Maybe c - Maybe(k, c)) - Map k1 a - Map k2 b - 
 Map k c
 The first Maybe tells if the key is already present; the second if one wants 
 it inserted.

Traversing cross products is a very different operation from zipping in the key 
space.  Again I wouldn't want to mistakenly substitute one for the other!  But 
in this case I think you'll find that you're already well served by the 
functions that already exist---adding this function doesn't enable you to do 
anything more efficiently (at least in a big-O sense).

 The idea in both cases is to combine the modifying functions into one. This 
 simplifies the interface.

Understood, and with a sufficiently smart compiler we might analyze the 
behavior of the function and do the right thing with the single-function 
interface in both cases.  I have yet to encounter a compiler that is both smart 
and reliable on this count.  That is why I've found it necessary to expose 
these kinds of functions.

-Jan

 
  Hans
 
 

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Map unionWith generalization

2010-01-27 Thread Hans Aberg

On 27 Jan 2010, at 21:29, Jan-Willem Maessen wrote:


I'm thinking about
(k - Maybe a - Maybe b - Maybe c) - Map k a - Map k b - Map k c
The first two Maybe's tell if the keys are present, the last if one  
wants it in the resulting map.


That has the same behavior semantically, but it's no more efficient  
than performing a unionWith followed by a filter.


It would not be the complexity, but the constant factor, by not having  
to transverse it twice. I'm not sure how it works in a functional  
language, and the trees must be rebalanced, too.



For example, consider implementing:

xs `intersection` singleton k v

in this way.  With the function given, the complexity is necessarily  
O(size xs): we must traverse every key/value pair in xs.  By  
contrast, by aggregating the operations on keys that exist only in a  
single map, we can write functions like intersection with the  
desired complexity (which is O(log (size xs)) in this case).


That is a good point.


One can transverse the product of keys. Then I'm thinking about
(k1 - k2 - a - b - Maybe c - Maybe(k, c)) - Map k1 a - Map  
k2 b - Map k c
The first Maybe tells if the key is already present; the second if  
one wants it inserted.


Traversing cross products is a very different operation from zipping  
in the key space.  Again I wouldn't want to mistakenly substitute  
one for the other!


For the first one, think of sums of sparse matrices or polynomials,  
and the second, products.


But in this case I think you'll find that you're already well served  
by the functions that already exist---adding this function doesn't  
enable you to do anything more efficiently (at least in a big-O  
sense).


Yes, I can't implements (-) directly; it must be a combination of (+)  
and negate, and the 0 must be filtered out in an extra pass. And for  
gcd of monomials, it is now a combination of lcm, (*) and (/), instead  
of a single pass. Unfortunately, these operations are used a lot, so  
getting a smaller constant factor is important.


The idea in both cases is to combine the modifying functions into  
one. This simplifies the interface.


Understood, and with a sufficiently smart compiler we might analyze  
the behavior of the function and do the right thing with the single- 
function interface in both cases.  I have yet to encounter a  
compiler that is both smart and reliable on this count.  That is why  
I've found it necessary to expose these kinds of functions.


By your example above, there may be a conflict between a general,  
simple interface, and implementing things like intersections.


  Hans


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Linguistic hair-splitting

2010-01-27 Thread Conor McBride

Hi

On 27 Jan 2010, at 20:14, Luke Palmer lrpal...@gmail.com wrote:

On Wed, Jan 27, 2010 at 11:39 AM, Jochem Berndsen  
joc...@functor.nl wrote:

Now, here's the question: Is is correct to say that [3, 5, 8] is a
monad?


In what sense would this be a monad? I don't quite get your question.


I think the question is this:  if m is a monad, then what do you call
a thing of type m Int, or m Whatever.


It has been known to call such things 'computations', as opposed to  
'values', and even to separate the categories of types and expressions  
which deliver the two.


I think that's a useful separation: I wish return (embedding values in  
computations) were silent, and thunk (embedding computations in  
values) made more noise.


Cheers

Conor



Luke
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Linguistic hair-splitting

2010-01-27 Thread Daniel Fischer
Am Mittwoch 27 Januar 2010 22:50:35 schrieb Conor McBride:

 It has been known to call such things 'computations', as opposed to
 'values', and even to separate the categories of types and expressions
 which deliver the two.

As usual, that only works part of the time. [1,4,15,3,7] is not a 
computation, it's a list of numbers. A plain and simple everyday value.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Non-termination of type-checking

2010-01-27 Thread Ryan Ingram
The compiler doesn't loop for me with GHC6.10.4; I think GADTs still
had some bugs in GHC6.8.

That said, this is pretty scary.  Here's a simplified version that
shows this paradox with just a single GADT and no other extensions.
No use of fix or recursion anywhere!

{-# LANGUAGE GADTs #-}
module Contr where

newtype I f = I (f ())
data R o a where R :: (a (I a) - o) - R o (I a)

run :: R o (I (R o)) - R o (I (R o)) - o
run x (R f) = f x
rir :: (R o) (I (R o))
rir = R (\x - run x x)

absurd :: a
absurd = run rir rir

  -- ryan

On Wed, Jan 27, 2010 at 8:27 AM, Matthieu Sozeau mat...@mattam.org wrote:
 Dear Haskellers,

  while trying to encode a paradox recently found in Coq if one has
 impredicativity and adds injectivity of type constructors [1] I
 stumbled on an apparent loop in the type checker when using GADTs,
 Rank2Types and EmptyDataDecls.

 {-# OPTIONS -XGADTs -XRank2Types -XEmptyDataDecls #-}

 module Impred where

 The identity type

 data ID a = ID a

 I is from (* - *) to *, we use a partial application of [ID] here.

 data I f where
  I1 :: I ID

 The usual reification of type equality into a term.

 data Equ a b where
  Eqrefl :: Equ a a

 The empty type

 data False

 This uses impredicativity: Rdef embeds a (* - *) - *
 object into R x :: *.

 data R x where
  Rdef :: (forall a. Equ x (I a) - a x - False) - R x

 r_eqv1 :: forall p. R (I p) - p (I p) - False
 r_eqv1 (Rdef f) pip = f Eqrefl pip

 r_eqv2 :: forall p. (p (I p) - False) - R (I p)
 r_eqv2 f = Rdef (\ eq ax -
                    case eq of -- Uses injectivity of type constructors
                     Eqrefl - f ax)

 r_eqv_not_R_1 :: R (I R) - R (I R) - False
 r_eqv_not_R_1 = r_eqv1

 r_eqv_not_R_2 :: (R (I R) - False) - R (I R)
 r_eqv_not_R_2 = r_eqv2

 rir :: R (I R)
 rir = r_eqv_not_R_2 (\ rir - r_eqv_not_R_1 rir rir)

 Type checking seems to loop here with ghc-6.8.3, which is a
 bit strange given the simplicity of the typing problem.
 Maybe it triggers a constraint with something above?

 -- Loops
 -- absurd :: False
 -- absurd = r_eqv_not_R_1 rir rir

 [1]
 http://thread.gmane.org/gmane.science.mathematics.logic.coq.club/4322/focus=1405

 -- Matthieu
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Non-termination of type-checking

2010-01-27 Thread Matthew Brecknell
Ryan Ingram wrote:
 The compiler doesn't loop for me with GHC6.10.4; I think GADTs still
 had some bugs in GHC6.8.
 
 That said, this is pretty scary.  Here's a simplified version that
 shows this paradox with just a single GADT and no other extensions.
 No use of fix or recursion anywhere!
 
 {-# LANGUAGE GADTs #-}
 module Contr where
 
 newtype I f = I (f ())
 data R o a where R :: (a (I a) - o) - R o (I a)
 
 run :: R o (I (R o)) - R o (I (R o)) - o
 run x (R f) = f x
 rir :: (R o) (I (R o))
 rir = R (\x - run x x)
 
 absurd :: a
 absurd = run rir rir

I think that's essentially the same as this:

data Fix a = Fix { unFix :: Fix a - a }

run :: Fix a - Fix a - a
run x f = unFix f x

rir :: Fix a
rir = Fix (\x - run x x)

absurd :: a
absurd = run rir rir

Non-positive recursive occurrences in type definitions provide various
ways to encode the Y-combinator in a typed lambda calculus, without the
need for any recursive let primitive. Haskell allows such non-positive
occurrences, but for strong normalisation, languages like Coq must
disallow them.

If you change data to newtype in the above, the GHC 6.10.4 compiler
(but not GHCi) will loop. I think this is just a case of the infelicity
documented here:

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

Regards,
Matthew



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Linguistic hair-splitting

2010-01-27 Thread Conor McBride





On 27 Jan 2010, at 22:02, Daniel Fischer daniel.is.fisc...@web.de  
wrote:



Am Mittwoch 27 Januar 2010 22:50:35 schrieb Conor McBride:


It has been known to call such things 'computations', as opposed to
'values', and even to separate the categories of types and  
expressions

which deliver the two.


As usual, that only works part of the time. [1,4,15,3,7] is not a
computation, it's a list of numbers. A plain and simple everyday  
value.


Yes, the separation is not clear in Haskell. (I consider this  
unfortunate.) I was thinking of Paul Levy's call-by-push-value  
calculus, where the distinction is clear, but perhaps not as fluid as  
one might like.


Int list values and nondeterministic int computations are conceptually  
different, even if they have isomorphic representations. Identifying  
their types has its downsides.


Cheers

Conor




___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANNOUNCE: ThreadScope 0.1

2010-01-27 Thread Johan Tibell
On Wed, Jan 27, 2010 at 8:51 AM, Satnam Singh satn...@microsoft.com wrote:

  I’ve just released ThreadScope version 0.1 on Hackage. Threadscope is a
 graphical utility for viewing profiling information about Haskell threads.
 It was written jointly with Simon Marlow and Donnie Jones. It uses Gtk2HS so
 it works under Windows and the L-word operating system although there seem
 to be problems making it work with OS-X (due to Gtk2Hs issues I think).

This is great news! ThreadScope was very useful when I was debugging
threading issues in the new I/O manager [1] Bryan and I have been working
on.

I managed to get it to work on OS X after building gtk2hs from source. Once
I got it to build the only problem I had is that it crashes when I try to
save to an image file.

Cheers,
Johan

1. http://github.com/tibbe/event
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Map unionWith generalization

2010-01-27 Thread Twan van Laarhoven

Hans Aberg wrote:
For example, in Map String Integer (sparse representation of monomials) 
compute the minimum value of all associative pairs with the same key 
(the gcd); if only one key is present, the absent should be treated as 
having value 0. So

  unionWith min xs ys
will not work, because unionWith will always apply the identity to the 
remaining value when one key is missing, whereas it should be sent to 0.


If missing keys represent 0, then wouldn't this work?

intersectionWith min xs ys


Twan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Linguistic hair-splitting

2010-01-27 Thread Alexander Solla

On Jan 27, 2010, at 4:57 PM, Conor McBride wrote:

Yes, the separation is not clear in Haskell. (I consider this  
unfortunate.) I was thinking of Paul Levy's call-by-push-value  
calculus, where the distinction is clear, but perhaps not as fluid  
as one might like.


What, exactly, is the supposed difference between a value and a  
computation?  Please remember that computations can and very often do  
return computations as results.  Please remember that in order for a  
function to be computed for a value, binding and computation must  
occur.  And that for every value computed, a computation must occur,  
even if it is just under identity the identity function.


Let's not forget that there's a monad for every one-argument (id est,  
monadic) function, and vice-versa.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] ghc-core 0.5 build fails

2010-01-27 Thread Brian Denheyer
Hi all,

ghc-core.hs:263:13:
Not in scope: data constructor `C.ExitException'

Looks like this comes from the base control.exception ?

When I go to the web page for control.exception, there is no
exitexception.

My reading of the hackage entry for ghc-core makes me think that I've
got the correct version of everything.

ghc is 6.10.4



Brian


Creating dist/build/ghc-core (and its parents)
Creating dist/build/ghc-core/ghc-core-tmp (and its parents)
/usr/bin/ghc -o dist/build/ghc-core/ghc-core --make -hide-all-packages
-i -idist/build/ghc-core/ghc-core-tmp -i. -idist/build/autogen
-Idist/build/autogen -Idist/build/ghc-core/ghc-core-tmp -optP-include
-optPdist/build/autogen/cabal_macros.h -odir
dist/build/ghc-core/ghc-core-tmp -hidir
dist/build/ghc-core/ghc-core-tmp -stubdir
dist/build/ghc-core/ghc-core-tmp -package base-4.1.0.0 -package
colorize-haskell-1.0.0 -package directory-1.0.0.3 -package
filepath-1.1.0.2 -package pcre-light-0.3.1 -package process-1.0.1.1 -O
-Wall -XPatternGuards ./ghc-core.hs
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ghc-core 0.5 build fails

2010-01-27 Thread Don Stewart
briand:
 Hi all,
 
 ghc-core.hs:263:13:
 Not in scope: data constructor `C.ExitException'
 
 Looks like this comes from the base control.exception ?
 
 When I go to the web page for control.exception, there is no
 exitexception.
 
 My reading of the hackage entry for ghc-core makes me think that I've
 got the correct version of everything.
 
 ghc is 6.10.4
 
 

Thanks for the report.  ghc-core 0.5.1 was released today, so cabal
update; cabal install ghc-core and you should be fine.

Cheers,
  Don
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ghc-core 0.5 build fails

2010-01-27 Thread Ivan Lazar Miljenovic
Don Stewart d...@galois.com writes:
 Thanks for the report.  ghc-core 0.5.1 was released today, so cabal
 update; cabal install ghc-core and you should be fine.

Even though I told you about this problem (your overly loose base
constraint) four months ago?

-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe