Re: [Haskell-cafe] Execution call graph pruning

2010-06-10 Thread C K Kashyap
Thanks Ivan.
Regards,
Kashyap

On Wed, Jun 9, 2010 at 4:40 AM, Ivan Lazar Miljenovic 
ivan.miljeno...@gmail.com wrote:

 C K Kashyap ckkash...@gmail.com writes:

  Hi,
  I have a call grah which contains information of the edges in the
 following
  format
 
  caller  callee  count   (time spent by the
  caller)
  ===
  foo  bar  10100
  xxx  yyy  2010
  zzz  yyy  1010
 
  (I used pintool pintool.org to generate this call graph)
 
  Now, the problem is that the graph is huge and it take a long to render
  using 'dot' or use any visualizing tool.
  Even if they render, it's too cluttered to be useful.
  I wanted to prune the graph in such a way that I'd have only the edges
  corresponding to the top 10% of the
  time consumers. What would be a good way to do such a thing? Has anyone
  written some utility that I could use?

 Well, graphviz [1] lets you parse Dot code, so you could then do a
 filter on it (I'm currently working on ways of letting you interact with
 the Dot code better).

 [1]: http://hackage.haskell.org/package/graphviz

 Also, to let you skip a step prof2dot [2] will create the Dot code for you.

 [2]: http://hackage.haskell.org/package/prof2dot

 --
 Ivan Lazar Miljenovic
 ivan.miljeno...@gmail.com
 IvanMiljenovic.wordpress.com




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


Re: [Haskell-cafe] A Finally Tagless Pi Calculus

2010-06-10 Thread Arnaud Bailly
Hello,
I studied (a bit) Pi-calculus and other mobile agents calculus during
my PhD, and I have always been fascinated by the beauty of this idea.
Your implementation is strikingly simple and beautiful.

I have a question though: Why is the fixpoint type

 newtype Nu f = Nu { nu :: f (Nu f) }

needed? And BTW, why generally use fixpoint on types? I read some
papers using/presenting such constructions (most notable a paper by
R.Lammel, I think, on expression trees transformation) but never quite
get it.

Thanks
Arnaud

On Wed, Jun 9, 2010 at 6:20 PM, Edward Kmett ekm...@gmail.com wrote:
 Keegan McAllister gave a very nice talk at Boston Haskell last night about
 First Class Concurrency. His slides are available online at

 http://t0rch.org/

 His final few slides covered the Pi calculus:

 http://en.wikipedia.org/wiki/Pi_calculus

 I took a few minutes over lunch to dash out a finally tagless version of the
 pi calculus interpreter presented by Keegan, since the topic of how much
 nicer it would look in HOAS came up during the meeting.

 For more information on finally tagless encodings, see:

 http://www.cs.rutgers.edu/~ccshan/tagless/jfp.pdf

 Of course, Keegan went farther and defined an encoding of the lambda
 calculus into the pi calculus, but I leave that as an exercise for the
 reader. ;)

 -Edward Kmett

 {-# LANGUAGE Rank2Types, TypeFamilies, FlexibleInstances #-}
 module Pi where

 import Control.Applicative
 import Control.Concurrent

 A finally tagless encoding of the Pi calculus. Symantics is a portmanteau of
 Syntax and Semantics.

 class Symantics p where
 type Name p :: *
 new :: (Name p - p) - p
 out :: Name p - Name p - p - p
 (|||) :: p - p - p
 inn :: Name p - (Name p - p) - p
 rep :: p - p
 nil :: p
 embed :: IO () - p

 Type level fixed points

 newtype Nu f = Nu { nu :: f (Nu f) }

 fork :: IO () - IO ()
 fork a = forkIO a  return ()

 forever :: IO a - IO a
 forever p = p  forever p

 Executable semantics

 instance Symantics (IO ()) where
 type Name (IO ()) = Nu Chan
 new f = Nu $ newChan = f
 a ||| b = forkIO a  fork b
 inn (Nu x) f = readChan x = fork . f
 out (Nu x) y b = writeChan x y  b
 rep = forever
 nil = return ()
 embed = id

 A closed pi calculus term

 newtype Pi = Pi { runPi :: forall a. Symantics a = a }

 run :: Pi - IO ()
 run (Pi a) = a

 example = Pi (new $ \z - (new $ \x - out x z nil
    ||| (inn x $ \y - out y x $ inn x $ \
 y - nil))
   ||| inn z (\v - out v v nil))

 A pretty printer for the pi calculus

 newtype Pretty = Pretty { runPretty :: [String] - Int - ShowS }

 instance Symantics Pretty where
 type Name Pretty = String
 new f = Pretty $ \(v:vs) n -
 showParen (n  10) $
 showString nu  . showString v . showString .  .
 runPretty (f v) vs 10
 out x y b = Pretty $ \vs n -
 showParen (n  10) $
 showString x . showChar '' . showString y . showString . 
 .
 runPretty b vs 10
 inn x f = Pretty $ \(v:vs) n -
 showParen (n  10) $
 showString x . showChar '(' . showString v . showString ). 
 .
 runPretty (f v) vs 10
 p ||| q = Pretty $ \vs n -
 showParen (n  4) $
 runPretty p vs 5 .
 showString  |  .
 runPretty q vs 4
 rep p = Pretty $ \vs n -
 showParen (n  10) $
 showString ! .
 runPretty p vs 10
 nil = Pretty $ \_ _ - showChar '0'
 embed io = Pretty $ \_ _ - showString {IO}

 instance Show Pi where
 showsPrec n (Pi p) = runPretty p vars n
 where
 vars = fmap return vs ++
    [i : show j | j - [1..], i - vs] where
 vs = ['a'..'z']

 Pi example
 nu a. (nu b. (ba. 0 | b(c). cb. b(d). 0) | a(b). bb. 0)

 ___
 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] Problems with threading?

2010-06-10 Thread Louis Wasserman
Yeah, Control.Parallel would be nice to have.  Heck, ideally I could get the
whole Haskell Platform, which would be a reasonable comparison to the huge
Java and C++ libraries accessible to those languages.

Out of curiosity, though, Haskell's thread-ring implementation just *tumbled
* down the rankings
http://shootout.alioth.debian.org/u64q/program.php?test=threadringlang=ghcid=3.
 Previously, it'd been doing most of its work on a single core, now it's
spread out.  Any ideas for fixin' it?  (I'm going to to try using forkOnIO.)

Louis Wasserman
wasserman.lo...@gmail.com
http://profiles.google.com/wasserman.louis


On Wed, Jun 9, 2010 at 6:18 PM, Don Stewart d...@galois.com wrote:

 igouy2:
 
  Now how do we get those regex-dna and binary-trees programs to compile?
 
  http://shootout.alioth.debian.org/u32/measurements.php?lang=ghc
 

 binary-trees:
Could not find module `Control.Parallel.Strategies':

-- cabal install parallel

 regex-dna:

 cannot satisfy -package regex-posix

-- cabal install regex-posix


 Both are in Debian.

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


Re: [Haskell-cafe] Removing alternate items from a list

2010-06-10 Thread John Lato
 From: Markus L?ll markus.l...@gmail.com

 So out of curiosity i took the definitions given in this thread, and
 tried to run timing-tests.
 Here's what I ran:
 ghc -prof -auto-all -o Test Test.h
 Test +RTS -p
 and then looked in the Test.prof file.

I think this is a poor approach for timing tests, for two reasons:

1) -O or -O2.  Reporting performance results from non-optimized builds
is often highly misleading.
2) -auto-all inhibits performance of code, sometimes significantly.

You'd be better off using a non-profiling build and criterion.  Plus
criterion does the statistics for you and warns about possibly invalid
samples.

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


Re: [Haskell-cafe] Contacting Planet Haskell

2010-06-10 Thread Yitzchak Gale
Jason Dagit wrote:
 I recently tried to send an email to the planet Haskell admins.  The webpage
 says to use pla...@community.haskell.org.  The mail was undelivered after
 several days and the daemon gave up trying to deliver it.

Which daemon gave up, ours or yours?

 My sending did overlap with the haskell.org downtown
 but I don't think that
 should have been a problem because:
 1) It looks like it retried after haskell.org was back up

Irrelevent, because

 2) I'm pretty sure community is a different host than haskell.org

Right.

 3) Shouldn't a backup mx handle this?

Hard to say, I can't tell from your sketchy description
what exactly went wrong. Please send more details
to supp...@community.haskell.org to open a ticket.

Anyway, that address is just an alias that forwards mail
to the two real email addresses of the admins. I'll send
you those off-list.

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


Re: [Haskell-cafe] A Finally Tagless Pi Calculus

2010-06-10 Thread Edward Kmett
On Thu, Jun 10, 2010 at 3:52 AM, Arnaud Bailly arnaud.oq...@gmail.comwrote:

 Hello,
 I studied (a bit) Pi-calculus and other mobile agents calculus during
 my PhD, and I have always been fascinated by the beauty of this idea.
 Your implementation is strikingly simple and beautiful.

 I have a question though: Why is the fixpoint type

  newtype Nu f = Nu { nu :: f (Nu f) }

 needed? And BTW, why generally use fixpoint on types? I read some
 papers using/presenting such constructions (most notable a paper by
 R.Lammel, I think, on expression trees transformation) but never quite
 get it.


You need the Nu type because you need channels that can only send channels
of channels of channels of channels of ...

You could equivalently use the formulation

newtype NuChan = NuChan (Chan NuChan)

but then I couldn't recycle the wrapper for other types if I wanted.

Without it the code below it would be untype because of the occurs check.

If you look in category-extras under Control.Morphism.* you'll find a lot of
other uses of the types Mu/Nu though there the type is called FixF.

-Edward Kmett


 On Wed, Jun 9, 2010 at 6:20 PM, Edward Kmett ekm...@gmail.com wrote:
  Keegan McAllister gave a very nice talk at Boston Haskell last night
 about
  First Class Concurrency. His slides are available online at
 
  http://t0rch.org/
 
  His final few slides covered the Pi calculus:
 
  http://en.wikipedia.org/wiki/Pi_calculus
 
  I took a few minutes over lunch to dash out a finally tagless version of
 the
  pi calculus interpreter presented by Keegan, since the topic of how much
  nicer it would look in HOAS came up during the meeting.
 
  For more information on finally tagless encodings, see:
 
  http://www.cs.rutgers.edu/~ccshan/tagless/jfp.pdf
 
  Of course, Keegan went farther and defined an encoding of the lambda
  calculus into the pi calculus, but I leave that as an exercise for the
  reader. ;)
 
  -Edward Kmett
 
  {-# LANGUAGE Rank2Types, TypeFamilies, FlexibleInstances #-}
  module Pi where
 
  import Control.Applicative
  import Control.Concurrent
 
  A finally tagless encoding of the Pi calculus. Symantics is a portmanteau
 of
  Syntax and Semantics.
 
  class Symantics p where
  type Name p :: *
  new :: (Name p - p) - p
  out :: Name p - Name p - p - p
  (|||) :: p - p - p
  inn :: Name p - (Name p - p) - p
  rep :: p - p
  nil :: p
  embed :: IO () - p
 
  Type level fixed points
 
  newtype Nu f = Nu { nu :: f (Nu f) }
 
  fork :: IO () - IO ()
  fork a = forkIO a  return ()
 
  forever :: IO a - IO a
  forever p = p  forever p
 
  Executable semantics
 
  instance Symantics (IO ()) where
  type Name (IO ()) = Nu Chan
  new f = Nu $ newChan = f
  a ||| b = forkIO a  fork b
  inn (Nu x) f = readChan x = fork . f
  out (Nu x) y b = writeChan x y  b
  rep = forever
  nil = return ()
  embed = id
 
  A closed pi calculus term
 
  newtype Pi = Pi { runPi :: forall a. Symantics a = a }
 
  run :: Pi - IO ()
  run (Pi a) = a
 
  example = Pi (new $ \z - (new $ \x - out x z nil
 ||| (inn x $ \y - out y x $ inn x $
 \
  y - nil))
||| inn z (\v - out v v nil))
 
  A pretty printer for the pi calculus
 
  newtype Pretty = Pretty { runPretty :: [String] - Int - ShowS }
 
  instance Symantics Pretty where
  type Name Pretty = String
  new f = Pretty $ \(v:vs) n -
  showParen (n  10) $
  showString nu  . showString v . showString .  .
  runPretty (f v) vs 10
  out x y b = Pretty $ \vs n -
  showParen (n  10) $
  showString x . showChar '' . showString y . showString .
 
  .
  runPretty b vs 10
  inn x f = Pretty $ \(v:vs) n -
  showParen (n  10) $
  showString x . showChar '(' . showString v . showString ).
 
  .
  runPretty (f v) vs 10
  p ||| q = Pretty $ \vs n -
  showParen (n  4) $
  runPretty p vs 5 .
  showString  |  .
  runPretty q vs 4
  rep p = Pretty $ \vs n -
  showParen (n  10) $
  showString ! .
  runPretty p vs 10
  nil = Pretty $ \_ _ - showChar '0'
  embed io = Pretty $ \_ _ - showString {IO}
 
  instance Show Pi where
  showsPrec n (Pi p) = runPretty p vars n
  where
  vars = fmap return vs ++
 [i : show j | j - [1..], i - vs] where
  vs = ['a'..'z']
 
  Pi example
  nu a. (nu b. (ba. 0 | b(c). cb. b(d). 0) | a(b). bb. 0)
 
  ___
  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] Using the ContT monads for early exits of IO ?

2010-06-10 Thread Günther Schmidt

Hi everyone,

I'm about to write a rather lengthy piece of IO code. Depending on the 
results of some of the IO actions I'd like the computation to stop right 
there and then.


Now I know in general how to write this but I'm wondering if this is one 
of those occasions where I should make use of the Cont monad to make an 
early exit.


Günther

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


Re: [Haskell-cafe] Removing alternate items from a list

2010-06-10 Thread Sebastiaan Visser
Or, when lists had a decent eliminator defined in the Prelude (just like maybe 
for Maybe and either for Either):

 list :: b - (a - [a] - b) - [a] - b
 list d _ [] = d 
 list _ f (x:xs) = f x xs

 fromList = list []

we could write the alternate function like this:

 alt :: [a] - [a] 
 alt = list [] $ \a - (a:)
 . list [] (const alt)


--
Sebastiaan

  
On Jun 6, 2010, at 4:46 PM, R J wrote:
 What's the cleanest definition for a function f :: [a] - [a] that takes a 
 list and returns the same list, with alternate items removed?  e.g., f [0, 1, 
 2, 3, 4, 5] = [1,3,5]?
 
 
 The New Busy is not the old busy. Search, chat and e-mail from your inbox. 
 Get started.___
 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] Removing alternate items from a list

2010-06-10 Thread Markus Läll
Yep, the test is done by a rookie. If I get more time, I'll try to
look into testing a little more, and redo the timing (if anyone
doesn't do it firs) -- using optimizations, more runs per function and
the criterion package.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Problems with threading?

2010-06-10 Thread Isaac Gouy

--- On Thu, 6/10/10, Louis Wasserman wasserman.lo...@gmail.com wrote:
 Date: Thursday, June 10, 2010, 1:32 AM

 Yeah, Control.Parallel would be nice to have.  Heck, ideally I could get  
 the whole Haskell Platform, which would be a reasonable comparison to 
 the huge Java and C++ libraries accessible to those languages.


 Out of curiosity, though, Haskell's thread-ring implementation just 
 tumbled down the rankings http://shootout.alioth.debian.org
 /u64q/program.php?test=threadringlang=ghcid=3.  Previously, it'd been  
 doing most of its work on a single core, now it's spread out.  Any ideas  
 for fixin' it?  (I'm going to to try using forkOnIO.)


There are 4 sets of rankings so -

http://shootout.alioth.debian.org/u64/program.php?test=threadringlang=ghcid=3


I have been wondering what approach is recommended when one part of a program 
would be a lot faster with -threaded but other parts of the program would be a 
lot faster without -threaded.

I can see that the C++ and Fortran and ... programmers would just wrap part of 
their program source code with a pragma.






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


Re: [Haskell-cafe] Using the ContT monads for early exits of IO ?

2010-06-10 Thread Job Vranish
Yeah I don't see why not. The ContT monad should work great.
Also, depending on what you're doing, the ErrorT monad might do what you
want as well.

- Job

2010/6/10 Günther Schmidt gue.schm...@web.de

 Hi everyone,

 I'm about to write a rather lengthy piece of IO code. Depending on the
 results of some of the IO actions I'd like the computation to stop right
 there and then.

 Now I know in general how to write this but I'm wondering if this is one of
 those occasions where I should make use of the Cont monad to make an early
 exit.

 Günther

 ___
 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] Using the ContT monads for early exits of IO ?

2010-06-10 Thread aditya siram
I have a general question about this kind of approach. Tutorials on
continuations in Haskell always come with a warning about not using it
unless you have to because it makes code unreadable and
unmaintainable. Is this true in your opinion?
-deech

On 6/10/10, Job Vranish job.vran...@gmail.com wrote:
 Yeah I don't see why not. The ContT monad should work great.
 Also, depending on what you're doing, the ErrorT monad might do what you
 want as well.

 - Job

 2010/6/10 Günther Schmidt gue.schm...@web.de

 Hi everyone,

 I'm about to write a rather lengthy piece of IO code. Depending on the
 results of some of the IO actions I'd like the computation to stop right
 there and then.

 Now I know in general how to write this but I'm wondering if this is one
 of
 those occasions where I should make use of the Cont monad to make an early
 exit.

 Günther

 ___
 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] Using the ContT monads for early exits of IO ?

2010-06-10 Thread Tim Wawrzynczak
Günther,

This is definitely one way to do it.  If you want to be able to quit the
IO action in the middle of a lengthy computation, that is one way that I,
personally, find very straightfoward.  You can find an example of this in my
Advgame package on Hackage, which uses this method to quit running the main
action (although I could have used a conditional to determine whether to
continue running the main loop, but continuations are more fun :P).

Small example:

 foo = (`runContT` id) $ do
dummy - callCC $ \exit - forever $ do
line - liftIO getLine
if line == quit then exit $ return () else ... -- do whatever
else here...


Cheers,
 - Tim

2010/6/10 Günther Schmidt gue.schm...@web.de

 Hi everyone,

 I'm about to write a rather lengthy piece of IO code. Depending on the
 results of some of the IO actions I'd like the computation to stop right
 there and then.

 Now I know in general how to write this but I'm wondering if this is one of
 those occasions where I should make use of the Cont monad to make an early
 exit.

 Günther

 ___
 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] Contacting Planet Haskell

2010-06-10 Thread Jason Dagit
On Thu, Jun 10, 2010 at 3:59 AM, Yitzchak Gale g...@sefer.org wrote:

 Jason Dagit wrote:
  I recently tried to send an email to the planet Haskell admins.  The
 webpage
  says to use pla...@community.haskell.org.  The mail was undelivered
 after
  several days and the daemon gave up trying to deliver it.

 Which daemon gave up, ours or yours?

  My sending did overlap with the haskell.org downtown
  but I don't think that
  should have been a problem because:
  1) It looks like it retried after haskell.org was back up

 Irrelevent, because

  2) I'm pretty sure community is a different host than haskell.org

 Right.

  3) Shouldn't a backup mx handle this?

 Hard to say, I can't tell from your sketchy description
 what exactly went wrong. Please send more details
 to supp...@community.haskell.org to open a ticket.

 Anyway, that address is just an alias that forwards mail
 to the two real email addresses of the admins. I'll send
 you those off-list.


Thanks.  I emailed one of the admins directly and the problem seems to be
resolved.

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


Re: [Haskell-cafe] How to Show an Operation?

2010-06-10 Thread Martin Drautzburg
On Thursday, 10. June 2010 00:08:34 Luke Palmer wrote:

 Or just:

 apply = val_of

 So, to summarize:  if you have something that isn't a function and you
 want to use it like a function, convert it to a function (using
 another function :-P).  That's all.  No syntax magic, just say what
 you're doing.

Thanks Luke

The reason I was asking is the following: suppose I have some code which uses 
some functions, and what it primarily does with those functions is CALL them 
in different orders.

Now at a later point in time I decide I need to give names to  those functions 
because at the end I need to print information about the functions which 
together solved a certain problem. Think of my problem as In which order do 
I have to call f,g,h such that (f.g.h) 42 = 42?.

I don't want to change all places where those functions are called 
into apply style. Therefore I was looking for some idiom like the python 
__call__() method, which, when present, can turn just about anything into a 
callable.

I could change the *definition* of my original functions into apply style 
and the rest of the code would not notice any difference. But that does not 
really help, because in the end I want to Show something like [g,h,f], but my 
functions would no longer carry names.

Alternatively I could associate functions with names in some association 
function, but that function simply has to know to much for my taste.

The thing is, I only need the names at the very end. Throughout the majority 
of the computation they should stay out of the way.


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


[Haskell-cafe] Haskell logo

2010-06-10 Thread Andrew Coppin
I just visited haskell.org and noticed that the old logo is back. 
Anybody know when/why this happened?


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


[Haskell-cafe] Thread scheduling

2010-06-10 Thread Andrew Coppin
Control.Concurrent provides the threadDelay function, which allows you 
to make the current thread sleep until T=now+X. However, I can't find 
any way of making the current thread sleep until T=X. In other words, I 
want to specify an absolute wakeup time, not a relative one.


What's even more frustrating is that, reading the source code, it 
appears that the internal RTS primitive *is* actually using an absolute 
time, but this isn't exposed anywhere that I can get at.


Is there any danger that this could be fixed at some point?

(I might also interject something about Data.Time, which seems to hardly 
let me do anything, but strictly that's a seperate topic...)


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


Re: [Haskell-cafe] Haskell logo

2010-06-10 Thread Roman Cheplyaka
* Andrew Coppin andrewcop...@btinternet.com [2010-06-10 18:47:23+0100]
 I just visited haskell.org and noticed that the old logo is back.
 Anybody know when/why this happened?

Result of restoring from backups?

-- 
Roman I. Cheplyaka :: http://ro-che.info/
Don't let school get in the way of your education. - Mark Twain
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How to Show an Operation?

2010-06-10 Thread Chris BROWN
Hi Martin,

Can you not just use trace?

http://cvs.haskell.org/Hugs/pages/libraries/base/Debug-Trace.html

f x = trace in f  x

g x = trace in g x


That should show the order of evaluation.
Chris.


On 10 Jun 2010, at 18:44, Martin Drautzburg wrote:

 On Thursday, 10. June 2010 00:08:34 Luke Palmer wrote:
 
 Or just:
 
 apply = val_of
 
 So, to summarize:  if you have something that isn't a function and you
 want to use it like a function, convert it to a function (using
 another function :-P).  That's all.  No syntax magic, just say what
 you're doing.
 
 Thanks Luke
 
 The reason I was asking is the following: suppose I have some code which uses 
 some functions, and what it primarily does with those functions is CALL them 
 in different orders.
 
 Now at a later point in time I decide I need to give names to  those 
 functions 
 because at the end I need to print information about the functions which 
 together solved a certain problem. Think of my problem as In which order do 
 I have to call f,g,h such that (f.g.h) 42 = 42?.
 
 I don't want to change all places where those functions are called 
 into apply style. Therefore I was looking for some idiom like the python 
 __call__() method, which, when present, can turn just about anything into a 
 callable.
 
 I could change the *definition* of my original functions into apply style 
 and the rest of the code would not notice any difference. But that does not 
 really help, because in the end I want to Show something like [g,h,f], but my 
 functions would no longer carry names.
 
 Alternatively I could associate functions with names in some association 
 function, but that function simply has to know to much for my taste.
 
 The thing is, I only need the names at the very end. Throughout the majority 
 of the computation they should stay out of the way.
 
 
 -- 
 Martin
 ___
 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] Using the ContT monads for early exits of IO ?

2010-06-10 Thread Lennart Augustsson
I would not use the continuation monad just for early exit.  Sounds
like the error monad to me.

2010/6/10 Günther Schmidt gue.schm...@web.de:
 Hi everyone,

 I'm about to write a rather lengthy piece of IO code. Depending on the
 results of some of the IO actions I'd like the computation to stop right
 there and then.

 Now I know in general how to write this but I'm wondering if this is one of
 those occasions where I should make use of the Cont monad to make an early
 exit.

 Günther

 ___
 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] Problems with threading?

2010-06-10 Thread Louis Wasserman


 There are 4 sets of rankings so -


 http://shootout.alioth.debian.org/u64/program.php?test=threadringlang=ghcid=3


Yes, but Haskell used to be doing much better specifically on the u64q,
which was why I was surprised.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Problems with threading?

2010-06-10 Thread Isaac Gouy

--- On Thu, 6/10/10, Louis Wasserman wasserman.lo...@gmail.com wrote:

 Date: Thursday, June 10, 2010, 11:25 AM

  There are 4 sets of rankings so -
  http://shootout.alioth.debian.org/u64/program.php?test=threadringlang=ghcid=3

 Yes, but Haskell used to be doing much better specifically on the u64q,
 which was why I was surprised.

I tend not to believe used to be doing much better comments until I'm shown 
the numbers ;-)




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


Re: [Haskell-cafe] Problems with threading?

2010-06-10 Thread Don Stewart
wasserman.louis:
 
 There are 4 sets of rankings so -
 
 
 http://shootout.alioth.debian.org/u64/program.php?test=threadringlang=ghc;
 id=3
 
 
 Yes, but Haskell used to be doing much better specifically on the u64q, which
 was why I was surprised.

Oh, indeed,

http://shootout.alioth.debian.org/u64q/performance.php?test=threadring

Something broke.

Simon Marlow described how best to parallelize this problem extensively
in:

http://www.haskell.org/~simonmar/bib/multicore-ghc-09_abstract.html

So I'd suggest doing what he says.

In particular, use thread pinning to improve locality.

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


Re: [Haskell-cafe] Problems with threading?

2010-06-10 Thread Isaac Gouy


--- On Thu, 6/10/10, Don Stewart d...@galois.com wrote:

 From: Don Stewart d...@galois.com
 Subject: Re: [Haskell-cafe] Problems with threading?
 To: Louis Wasserman wasserman.lo...@gmail.com
 Cc: igo...@yahoo.com, Haskell Café List haskell-cafe@haskell.org
 Date: Thursday, June 10, 2010, 11:36 AM
 wasserman.louis:
  
      There are 4 sets of rankings
 so -
  
      http://shootout.alioth.debian.org/u64/program.php?test=threadring〈=ghc;
      id=3
  
  
  Yes, but Haskell used to be doing much better
 specifically on the u64q, which
  was why I was surprised.
 
 Oh, indeed,
 
     http://shootout.alioth.debian.org/u64q/performance.php?test=threadring
 
 Something broke.
 
 Simon Marlow described how best to parallelize this problem
 extensively
 in:
 
     http://www.haskell.org/~simonmar/bib/multicore-ghc-09_abstract.html
 
 So I'd suggest doing what he says.
 
 In particular, use thread pinning to improve locality.


-qw -qm ?

How's that going to work out when applied to the other Haskell programs?


 

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


Re: [Haskell-cafe] Re: GATD and pattern matching

2010-06-10 Thread Dupont Corentin
On Thu, Jun 10, 2010 at 11:14 PM, Daniel Fischer
daniel.is.fisc...@web.dewrote:

 On Thursday 10 June 2010 22:01:38, Dupont Corentin wrote:
  Hello Maciej,
  i tried this out, but it didn't worked.
 
  Daniel,
 
  I added a (Show a) constraint to Equal:
   data Obs a where
   Player :: Obs Integer
   Turn :: Obs Integer
   Official :: Obs Bool
   Equ :: (Show a, Eq a) = Obs a - Obs a - Obs Bool
 
  --woops!!
 
   Plus :: (Num a) = Obs a - Obs a - Obs a
   Time :: (Num a) = Obs a - Obs a - Obs a
   Minus :: (Num a) = Obs a - Obs a - Obs a
   Konst :: a - Obs a
   And :: Obs Bool - Obs Bool - Obs Bool
   Or :: Obs Bool - Obs Bool - Obs Bool
 
  It works for the Show instance, but not Eq.
  By the way, shouldn't the Show constraint be on the instance and not on
  the datatype declaration?

 Can't be here, because of
   Equ :: Obs a - Obs a - Obs Bool

 You forget the parameter a, and you can't recover it in the instance
 declaration. So you have to provide the Show instance for a on
 construction, i.e. put the constraint on the data constructor.


Anyway, is my Obs construction revelant at all? What i want to do is to
provide an EDSL to the user to test things about the state of the game (for
the Nomic game i'm making). Obs will be then embedded in another EDSL to
construct Nomic's rules.



  I'd prefer to keep the datatype as generic as possible...
 
  There is really no way to make my Obs datatype an instance of Eq and
  Show??

 Show can work (should with the constraint on Equ), Eq is hairy.

 instance Show t = Show (Obs t) where
 show (Equ a b) = show a ++  `Equal`  ++ show b
show (Plus a b) = ...
show (Konst x) = Konst  ++ show x
...

 For an Eq instance, you have the problem that

 Equ (Konst True) (Konst False)
 and
 Equ Player Turn

 both have the type Obs Bool, but have been constructed from different
 types, so you can't compare (Konst True) and Player.
 I don't see a nice way to work around that.


These is a dirty way: compare the string representation of the rules. They
should be unique.

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


Re: [Haskell-cafe] Using the ContT monads for early exits of IO ?

2010-06-10 Thread Christopher Done
2010/6/10 Günther Schmidt gue.schm...@web.de:
 Hi everyone,

 I'm about to write a rather lengthy piece of IO code. Depending on the
 results of some of the IO actions I'd like the computation to stop right
 there and then.

What's wrong with a mere if/else condition?

foo = do
  bar
  x - mu
  case x of
Bar - return ()
Mu - do y - zot
 case y of
   Zot - return ()
   Foo - gud

foo = do
 bar
 x - mu
 y - bar
 when (pred x y) $ do
zot x

Continuations are risky for causing confusion of readers (and the
author herself), do you definitely need this?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] QuickCheck 2

2010-06-10 Thread wren ng thornton
Since GHC 6.12 ships with QC2 it looks like it's finally time to get 
around to converting some old testing scripts. Unfortunately, one of the 
things I couldn't figure out last time I looked (and hence why I haven't 
switched) is how to reconfigure the configuration parameters to the 
driver function. Is there a porting guide anywhere, or how else can I 
adjust the configuration parameters (in particular, the configMaxTest 
and configMaxFail parameters)?


--
Live well,
~wren

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


Re: [Haskell-cafe] Re: How to Show an Operation?

2010-06-10 Thread Daniel Fischer
On Thursday 10 June 2010 23:38:15, Martin Drautzburg wrote:
 On Thursday, 10. June 2010 22:10:08 Maciej Piechotka wrote:

 Wow!

 this is somewhat above my level. I guess I need to go back to the books.
 I'll document my ignorance nontheless.

  data Named a = Named String a
 
  instance Functor Named where
  f `fmap` (Named s v) = Named s (f v)

 okay so far

  instance Applicative Named where
  pure x = Named  x
  (Named s f) * (Named t v) = Named (s ++ ( ++ t ++ )) (f v)

 Applicative. Need to study that
 Control.Applicative   (*) :: Applicative f = f (a - b) - f a - f b

 So in our case the Applicative is a Named.

Here, we define (*) for the type

(*) :: (Named (a - b)) - (Named a) - (Named b)

(redundant parentheses against ambiguity errors).

A 'Named' thing is a thing together with a name.
So how do we apply a function with a name to an argument with a name?
What we get is a value with a name. The value is of course the function 
applied to the argument ignoring names. The name of the result is the 
textual representation of the function application, e.g.

Named sin sin * Named pi pi ~ Named sin(pi) 1.2246063538223773e-16

(*) is application of named functions to named values, or 'lifting 
function application to named things'.

 When I apply a Named to a
 function, then I get a function between the corresponding Named types.
 When I pass it an Int-Char function, I get a Named Int - Named Char
 function.

 But here it is applied to another Named ... is that the (a-b)?
 Puzzeled.

  instance Eq a = Eq (Named a) where
  (Named _ x) == (Named _ y) = x == y
 
  instance Show (Named a) where
  show (Named s _) = s

 Understood.

  namedPure :: Show a = a - Named a
  namedPure x = Named (show x) x

 When I can show something I can always name it so its name is what
 'show' would return. Okay I guess I got it. This turns a showable into
 a Named.

  test :: Num a
   = (a - a) - (a - a) - (a - a) - [String]
  test f g h = do
  [f', g', h'] - permutations [Named f f, Named g g, Named h
  h]

 According to Hoogle permutations should be in Data.List. Mine (GHCI
 6.8.2) does not seem to have it. Seems to have something to do with

Upgrade. We're at 6.12 now!
Lots of improvements.
permutations was added in 6.10, IIRC.

 base, whatever that is.

  guard $ namedPure 42 == f' * g' * h' * namedPure 42

 Ah, the 42 needs namedPure.

Simplest way, it could be
Named answer to Life, the Universe and Everything 42

 Again this * operator...
 I believe the whole thing is using a List Monad.

  return $ show f' ++  .  ++ show g' ++  .  ++ show h'

 I wonder if the thing returns just one string or a list of strings. I

A list, one string for every permutation satisfying the condition.

 guess return cannot return anything more unwrapped than a List, so it
 must be a List. But does it contain just the first match or all of them?
 All of them! And how many brackets are around them?


do x - list
   guard (condition x)
   return (f x)

is syntactic sugar for

concat (map (\x - if condition x then [f x] else []) list)

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


Re: [Haskell-cafe] QuickCheck 2

2010-06-10 Thread wren ng thornton

wren ng thornton wrote:
Since GHC 6.12 ships with QC2 it looks like it's finally time to get 
around to converting some old testing scripts. Unfortunately, one of the 
things I couldn't figure out last time I looked (and hence why I haven't 
switched) is how to reconfigure the configuration parameters to the 
driver function. Is there a porting guide anywhere, or how else can I 
adjust the configuration parameters (in particular, the configMaxTest 
and configMaxFail parameters)?


Ah, nevermind. I found what they renamed things to

--
Live well,
~wren
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Using the ContT monads for early exits of IO ?

2010-06-10 Thread Tim Wawrzynczak
Actually, on second thought, Lennart is probably right.  Continuations are
probably overkill for this situation.
Since not wanting to continue is probably an 'erroneous condition,' you may
as well use Error.

Cheers,
 - Tim

2010/6/10 Lennart Augustsson lenn...@augustsson.net

 I would not use the continuation monad just for early exit.  Sounds
 like the error monad to me.

 2010/6/10 Günther Schmidt gue.schm...@web.de:
  Hi everyone,
 
  I'm about to write a rather lengthy piece of IO code. Depending on the
  results of some of the IO actions I'd like the computation to stop right
  there and then.
 
  Now I know in general how to write this but I'm wondering if this is one
 of
  those occasions where I should make use of the Cont monad to make an
 early
  exit.
 
  Günther
 
  ___
  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 mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] QuickCheck 2

2010-06-10 Thread Ivan Lazar Miljenovic
wren ng thornton w...@freegeek.org writes:

 Since GHC 6.12 ships with QC2 it looks like it's finally time to get
 around to converting some old testing scripts.

Well, the Haskell Platform does, not GHC...

 Unfortunately, one of the things I couldn't figure out last time I
 looked (and hence why I haven't switched) is how to reconfigure the
 configuration parameters to the driver function.  Is there a porting
 guide anywhere, or how else can I adjust the configuration parameters
 (in particular, the configMaxTest and configMaxFail parameters)?

I'm not sure what you mean by driver function, but there is
quickCheckWith:
http://hackage.haskell.org/packages/archive/QuickCheck/2.1.0.3/doc/html/Test-QuickCheck.html#v%3AquickCheckWith
(and also quickCheckWithResult) which let you customise the number of
tests you want, etc.  Is that what you were after?

-- 
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


Re: [Haskell-cafe] Re: GATD and pattern matching

2010-06-10 Thread Dupont Corentin
Hello Maciej,
i tried this out, but it didn't worked.

Daniel,
I added a (Show a) constraint to Equal:

 data Obs a where
 Player :: Obs Integer
 Turn :: Obs Integer
 Official :: Obs Bool
 Equ :: (Show a, Eq a) = Obs a - Obs a - Obs Bool
--woops!!
 Plus :: (Num a) = Obs a - Obs a - Obs a
 Time :: (Num a) = Obs a - Obs a - Obs a
 Minus :: (Num a) = Obs a - Obs a - Obs a
 Konst :: a - Obs a
 And :: Obs Bool - Obs Bool - Obs Bool
 Or :: Obs Bool - Obs Bool - Obs Bool


It works for the Show instance, but not Eq.
By the way, shouldn't the Show constraint be on the instance and not on the
datatype declaration?
I'd prefer to keep the datatype as generic as possible...

There is really no way to make my Obs datatype an instance of Eq and Show??

I searched around a way to add type information on the pattern match like:

 instance Show t = Show (Obs t) where
 show (Equal (a::Obs t) (b::Obs t)) = (show a) ++  Equal  ++ (show b)
 show (Plus a b) = (show a) ++  Plus  ++ (show b)


But it doesn't work.

thanks for your help,
Corentin



On Thu, Jun 10, 2010 at 2:47 AM, Maciej Piechotka uzytkown...@gmail.comwrote:

 On Wed, 2010-06-09 at 22:28 +0200, Dupont Corentin wrote:
  Thanks for your response.
 
  How would you do it? I design this GATD for a game i'm making:
 
   data Obs a where
   Player :: Obs Integer
   Turn :: Obs Integer
   Official :: Obs Bool
   Equ :: Obs a - Obs a - Obs Bool   --woops!!
   Plus :: (Num a) = Obs a - Obs a - Obs a
   Time :: (Num a) = Obs a - Obs a - Obs a
   Minus :: (Num a) = Obs a - Obs a - Obs a
   Konst :: a - Obs a

 Actually woops is here. Make it for example

Const :: (Show a, Eq a, ...) = a - Obs a

   And :: Obs Bool - Obs Bool - Obs Bool
   Or :: Obs Bool - Obs Bool - Obs Bool
 
  For example I can design an Observable like that:
 
  myObs = Player `Equ` (Konst 1) `And` Official
 
  These Observables will then be processed during gameplay.
 
  I would like to be able to do in ghci:
 
   show myObs
  Player `Equ` (Konst 1) `And` Official
 
  and:
myObs == myObs
  True
 

 Regards


 ___
 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] Problems with threading?

2010-06-10 Thread Isaac Gouy


--- On Thu, 6/10/10, Don Stewart d...@galois.com wrote:

 From: Don Stewart d...@galois.com
 Subject: Re: [Haskell-cafe] Problems with threading?
 To: Isaac Gouy igo...@yahoo.com
 Cc: Louis Wasserman wasserman.lo...@gmail.com, Haskell Café List 
 haskell-cafe@haskell.org
 Date: Thursday, June 10, 2010, 12:54 PM
 igouy2:
   Simon Marlow described how best to parallelize
 this problem
   extensively
   in:
   
       http://www.haskell.org/~simonmar/bib/multicore-ghc-09_abstract.html
   
   So I'd suggest doing what he says.
   
   In particular, use thread pinning to improve
 locality.
  
  -qw -qm ?
  
  How's that going to work out when applied to the other
 Haskell programs?
  
 
 I'm sure it does bad things to them. 


Yep, earlier in the week I measured the programs using +RTS -N4 -qw -qm which 
is why I wonder how you would approach programs that have a mix of performance 
characteristics? Maybe there aren't large Haskell programs like that?




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


Re: [Haskell-cafe] Re: Using the ContT monads for early exits of IO ?

2010-06-10 Thread Job Vranish
Yeah, I might actually prefer calling it EitherT instead of ErrorT. It
doesn't have to be used for error, it's just what it is most often used for.

- Job

On Thu, Jun 10, 2010 at 3:57 PM, Maciej Piechotka uzytkown...@gmail.comwrote:

 On Thu, 2010-06-10 at 14:09 -0500, Tim Wawrzynczak wrote:
  Actually, on second thought, Lennart is probably right.  Continuations
  are probably overkill for this situation.
  Since not wanting to continue is probably an 'erroneous condition,'
  you may as well use Error.
 
  Cheers,
   - Tim
 

 Technically it can be a success. For example if we get a list of
 HostInfo for given hostname we want to connect once instead of many
 times. Also the first time might not succeed (it is  entry in IPv4
 network).

 Error monad seems not to be a semantic solution as we exit on success
 not failure.

 Regards



 ___
 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] Re: Using the ContT monads for early exits of IO ?

2010-06-10 Thread Ben Millwood
On Thu, Jun 10, 2010 at 8:57 PM, Maciej Piechotka uzytkown...@gmail.com wrote:

 Error monad seems not to be a semantic solution as we exit on success
 not failure.


Which is really why the Either monad should not necessarily have Error
associations :)
If you forget about the fail method, the Monad (Either e) instance
doesn't need the e to be an error type.

Alternatively, if even Error is more information than you need, you
could use MaybeT:

http://hackage.haskell.org/package/MaybeT

which allows you to just stop. Given you're using it with IO it'd be
easy to write a result to an IORef before terminating the computation,
so it's of equivalent power, if slightly less convenient.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Problems with threading?

2010-06-10 Thread Don Stewart
igouy2:
In particular, use thread pinning to improve
  locality.
   
   -qw -qm ?
   
   How's that going to work out when applied to the other
  Haskell programs?
   
  
  I'm sure it does bad things to them. 
 
 
 Yep, earlier in the week I measured the programs using +RTS -N4 -qw
 -qm which is why I wonder how you would approach programs that have a
 mix of performance characteristics? Maybe there aren't large Haskell
 programs like that?

Partioning different parallel components of the application has been
studied in large scale systems. I'm not aware of work done on this in
Haskell yet.

If different phases of a algorithm need to use more or less parallelism,
that's certainly a lot easier (mixtures of forkOnIO and (forkIO or
par)). 

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


Re: [Haskell-cafe] QuickCheck 2

2010-06-10 Thread wren ng thornton

Ivan Lazar Miljenovic wrote:

wren ng thornton w...@freegeek.org writes:


Since GHC 6.12 ships with QC2 it looks like it's finally time to get
around to converting some old testing scripts.


Well, the Haskell Platform does, not GHC...


Fair enough (it was one of the two :)



Unfortunately, one of the things I couldn't figure out last time I
looked (and hence why I haven't switched) is how to reconfigure the
configuration parameters to the driver function.  Is there a porting
guide anywhere, or how else can I adjust the configuration parameters
(in particular, the configMaxTest and configMaxFail parameters)?


I'm not sure what you mean by driver function, but there is
quickCheckWith:
http://hackage.haskell.org/packages/archive/QuickCheck/2.1.0.3/doc/html/Test-QuickCheck.html#v%3AquickCheckWith
(and also quickCheckWithResult) which let you customise the number of
tests you want, etc.  Is that what you were after?


Yeah, that's the one.

--
Live well,
~wren
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: GATD and pattern matching

2010-06-10 Thread Daniel Fischer
On Thursday 10 June 2010 22:01:38, Dupont Corentin wrote:
 Hello Maciej,
 i tried this out, but it didn't worked.

 Daniel,

 I added a (Show a) constraint to Equal:
  data Obs a where
  Player :: Obs Integer
  Turn :: Obs Integer
  Official :: Obs Bool
  Equ :: (Show a, Eq a) = Obs a - Obs a - Obs Bool

 --woops!!

  Plus :: (Num a) = Obs a - Obs a - Obs a
  Time :: (Num a) = Obs a - Obs a - Obs a
  Minus :: (Num a) = Obs a - Obs a - Obs a
  Konst :: a - Obs a
  And :: Obs Bool - Obs Bool - Obs Bool
  Or :: Obs Bool - Obs Bool - Obs Bool

 It works for the Show instance, but not Eq.
 By the way, shouldn't the Show constraint be on the instance and not on
 the datatype declaration?

Can't be here, because of 
  Equ :: Obs a - Obs a - Obs Bool

You forget the parameter a, and you can't recover it in the instance 
declaration. So you have to provide the Show instance for a on 
construction, i.e. put the constraint on the data constructor.

 I'd prefer to keep the datatype as generic as possible...

 There is really no way to make my Obs datatype an instance of Eq and
 Show??

Show can work (should with the constraint on Equ), Eq is hairy.

instance Show t = Show (Obs t) where
show (Equ a b) = show a ++  `Equal`  ++ show b
show (Plus a b) = ...
show (Konst x) = Konst  ++ show x
...

For an Eq instance, you have the problem that

Equ (Konst True) (Konst False)
and
Equ Player Turn

both have the type Obs Bool, but have been constructed from different 
types, so you can't compare (Konst True) and Player.
I don't see a nice way to work around that.


 I searched around a way to add type information on the pattern match 
like:
  instance Show t = Show (Obs t) where
  show (Equal (a::Obs t) (b::Obs t)) = (show a) ++  Equal  ++
  (show b) show (Plus a b) = (show a) ++  Plus  ++ (show b)

 But it doesn't work.

 thanks for your help,
 Corentin

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


Re: [Haskell-cafe] Using the ContT monads for early exits of IO ?

2010-06-10 Thread Günther Schmidt

Hi Christopher,

there is nothing wrong with ifs as such except the won't actually exit a 
long piece of code, the computation will continue, just in a useless way.


Primarily for every if I need two forks, so at every if the branches 
double.


I have written the previous code with ifs and it's quite spaghetti-ish 
and I hope that using callCC here helps to avoid it.


Of course there is no guarantee that it actually will. ;)

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


[Haskell-cafe] Re: How to Show an Operation?

2010-06-10 Thread Maciej Piechotka
On Thu, 2010-06-10 at 19:44 +0200, Martin Drautzburg wrote:
 On Thursday, 10. June 2010 00:08:34 Luke Palmer wrote:
 
  Or just:
 
  apply = val_of
 
  So, to summarize:  if you have something that isn't a function and you
  want to use it like a function, convert it to a function (using
  another function :-P).  That's all.  No syntax magic, just say what
  you're doing.
 
 Thanks Luke
 
 The reason I was asking is the following: suppose I have some code which uses 
 some functions, and what it primarily does with those functions is CALL them 
 in different orders.
 
 Now at a later point in time I decide I need to give names to  those 
 functions 
 because at the end I need to print information about the functions which 
 together solved a certain problem. Think of my problem as In which order do 
 I have to call f,g,h such that (f.g.h) 42 = 42?.
 
 I don't want to change all places where those functions are called 
 into apply style. Therefore I was looking for some idiom like the python 
 __call__() method, which, when present, can turn just about anything into a 
 callable.
 
 I could change the *definition* of my original functions into apply style 
 and the rest of the code would not notice any difference. But that does not 
 really help, because in the end I want to Show something like [g,h,f], but my 
 functions would no longer carry names.
 
 Alternatively I could associate functions with names in some association 
 function, but that function simply has to know to much for my taste.
 
 The thing is, I only need the names at the very end. Throughout the majority 
 of the computation they should stay out of the way.
 
 

data Named a = Named String a

instance Functor Named where
f `fmap` (Named s v) = Named s (f v)

instance Applicative Named where
pure x = Named  x
(Named s f) * (Named t v) = Named (s ++ ( ++ t ++ )) (f v)

instance Eq a = Eq (Named a) where
(Named _ x) == (Named _ y) = x == y

instance Show (Named a) where
show (Named s _) = s

namedPure :: Show a = a - Named a
namedPure x = Named (show x) x

test :: Num a
 = (a - a) - (a - a) - (a - a) - [String]
test f g h = do
[f', g', h'] - permutations [Named f f, Named g g, Named h h]
guard $ namedPure 42 == f' * g' * h' * namedPure 42
return $ show f' ++  .  ++ show g' ++  .  ++ show h'

(code is not tested but it should work)

Regards


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Problems with threading?

2010-06-10 Thread Don Stewart
igouy2:
  Simon Marlow described how best to parallelize this problem
  extensively
  in:
  
      http://www.haskell.org/~simonmar/bib/multicore-ghc-09_abstract.html
  
  So I'd suggest doing what he says.
  
  In particular, use thread pinning to improve locality.
 
 -qw -qm ?
 
 How's that going to work out when applied to the other Haskell programs?
 

I'm sure it does bad things to them. 

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


[Haskell-cafe] Re: Using the ContT monads for early exits of IO ?

2010-06-10 Thread Maciej Piechotka
On Thu, 2010-06-10 at 14:09 -0500, Tim Wawrzynczak wrote:
 Actually, on second thought, Lennart is probably right.  Continuations
 are probably overkill for this situation.
 Since not wanting to continue is probably an 'erroneous condition,'
 you may as well use Error.
 
 Cheers,
  - Tim
 

Technically it can be a success. For example if we get a list of
HostInfo for given hostname we want to connect once instead of many
times. Also the first time might not succeed (it is  entry in IPv4
network).

Error monad seems not to be a semantic solution as we exit on success
not failure.

Regards




signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Using the ContT monads for early exits of IO ?

2010-06-10 Thread Yitzchak Gale
Lennart Augustsson wrote:
 I would not use the continuation monad just for early exit.  Sounds
 like the error monad to me.

I.e., the Either/ErrorT monad. But the mtl/transformers packages
have an orphan instance for Either that requires the
exit type to be an instance of the Error class. If that
doesn't work in your case, use the Exit monad:

http://www.haskell.org/haskellwiki/New_monads/MonadExit

Or use the Maybe monad written additively, i.e. mplus
in place of  (more or less).

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


Re: [Haskell-cafe] Re: How to Show an Operation?

2010-06-10 Thread Martin Drautzburg
On Thursday, 10. June 2010 22:10:08 Maciej Piechotka wrote:

Wow!

this is somewhat above my level. I guess I need to go back to the books. I'll 
document my ignorance nontheless.

 data Named a = Named String a

 instance Functor Named where
 f `fmap` (Named s v) = Named s (f v)

okay so far

 instance Applicative Named where
 pure x = Named  x
 (Named s f) * (Named t v) = Named (s ++ ( ++ t ++ )) (f v)

Applicative. Need to study that
Control.Applicative (*) :: Applicative f = f (a - b) - f a - f b

So in our case the Applicative is a Named. When I apply a Named to a 
function, then I get a function between the corresponding Named types. When I 
pass it an Int-Char function, I get a Named Int - Named Char function.

But here it is applied to another Named ... is that the (a-b)? Puzzeled.

 instance Eq a = Eq (Named a) where
 (Named _ x) == (Named _ y) = x == y

 instance Show (Named a) where
 show (Named s _) = s


Understood.

 namedPure :: Show a = a - Named a
 namedPure x = Named (show x) x

When I can show something I can always name it so its name is what 'show' 
would return. Okay I guess I got it. This turns a showable into a Named.


 test :: Num a
  = (a - a) - (a - a) - (a - a) - [String]
 test f g h = do
 [f', g', h'] - permutations [Named f f, Named g g, Named h h]

According to Hoogle permutations should be in Data.List. Mine (GHCI 6.8.2) 
does not seem to have it. Seems to have something to do with base, whatever 
that is.

 guard $ namedPure 42 == f' * g' * h' * namedPure 42

Ah, the 42 needs namedPure.
Again this * operator... 
I believe the whole thing is using a List Monad. 

 return $ show f' ++  .  ++ show g' ++  .  ++ show h'

I wonder if the thing returns just one string or a list of strings. I 
guess return cannot return anything more unwrapped than a List, so it must 
be a List. But does it contain just the first match or all of them? All of 
them! And how many brackets are around them?

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


Re: [Haskell-cafe] Re: GATD and pattern matching

2010-06-10 Thread Felipe Lessa
On Thu, Jun 10, 2010 at 11:14:42PM +0200, Daniel Fischer wrote:
 Show can work (should with the constraint on Equ), Eq is hairy.

 instance Show t = Show (Obs t) where
 show (Equ a b) = show a ++  `Equal`  ++ show b
 show (Plus a b) = ...
 show (Konst x) = Konst  ++ show x
 ...

 For an Eq instance, you have the problem that

 Equ (Konst True) (Konst False)
 and
 Equ Player Turn

 both have the type Obs Bool, but have been constructed from different
 types, so you can't compare (Konst True) and Player.
 I don't see a nice way to work around that.

I didn't test, but something like this could work:

  Equ :: (Show a, Eq a, Typeable a) = Obs a - Obs a - Obs Bool

  (Equ a b) == (Equ c d) = eqTypeable (a,b) (c,d)

  eqTypeable :: (Typeable a, Eq a, Typeable b, Eq b) = a - b - Bool
  eqTypeable x y = case cast y of
 Just y' - x == y'
 Nothing - False

Maybe not ;).

Cheers,

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


Re: [Haskell-cafe] Re: Using the ContT monads for early exits of IO ?

2010-06-10 Thread Tim Wawrzynczak
Or what about a specialized Escape Continuation monad?  (Perhaps there is
one on hackage, not sure).

Something that allows you to set up an continuation (for escape) purposes,
but does not allow you
to capture any more continuations after that, and call that escape cont w/in
itself, supplying a return value.

i.e.

 run = do
result - createEscape $ \escape -
lengthyComputation1
inp - askToContinue
if (not (continue inp))
  then escape They quit
  else lengthyComputation2
return result

Just thinking off the top of my head :).

However, if there are going to be multiple 'lengthy computations' then
perhaps
MaybeT or EitherT would be better, b/c they allow the propagation of failure
across multiple actions, instead of cascading off to the right of the screen
w/ 'if's or 'case's.

Cheers,
 - Tim

On Thu, Jun 10, 2010 at 3:21 PM, Ben Millwood hask...@benmachine.co.ukwrote:

 On Thu, Jun 10, 2010 at 8:57 PM, Maciej Piechotka uzytkown...@gmail.com
 wrote:
 
  Error monad seems not to be a semantic solution as we exit on success
  not failure.
 

 Which is really why the Either monad should not necessarily have Error
 associations :)
 If you forget about the fail method, the Monad (Either e) instance
 doesn't need the e to be an error type.

 Alternatively, if even Error is more information than you need, you
 could use MaybeT:

 http://hackage.haskell.org/package/MaybeT

 which allows you to just stop. Given you're using it with IO it'd be
 easy to write a result to an IORef before terminating the computation,
 so it's of equivalent power, if slightly less convenient.
 ___
 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] ANN: bytestring-trie 0.2.2 (major bugfix)

2010-06-10 Thread wren ng thornton


-- bytestring-trie 0.2.2 (major bugfix)


Another release for efficient finite maps from (byte)strings to values. 
This version corrects a major bug affecting all users who merge tries.




-- Changes (since 0.1.4)


* Corrected a major bug in mergeBy which caused conflicting values to be 
merged in the wrong order. Since this is a core function, all other 
merging-based functions are affected as well (e.g., unionR, unionL,...). 
The bug was filed by Gregory Crosswhite (thanks!).


* added Data.Trie.Convenience.fromListWith --- A variant of 'fromListR' 
that takes a function for combining values on conflict.


* generalized the type of toListBy

* removed KeyString and KeyElem aliases

* documentation tweaks



-- Future work


* Worked on explicit definitions for foldl and foldr, as opposed to the 
default definitions given by Foldable using Endo. The suggested 
definitions are around 3x faster than the old definitions, however the 
order of folding is different than foldrWithKey (which seems to have the 
correct order). These definitions are not currently being used, but 
perhaps the future will see faster folding functions for Tries.




-- Links


Homepage:
http://code.haskell.org/~wren/

Hackage:
http://hackage.haskell.org/package/bytestring-trie

Darcs:
http://community.haskell.org/~wren/bytestring-trie/

Haddock (Darcs version):

http://community.haskell.org/~wren/bytestring-trie/dist/doc/html/bytestring-trie/

--
Live well,
~wren
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Using the ContT monads for early exits of IO ?

2010-06-10 Thread Derek Elkins
Or... one could just use the exceptions that are already built into
the IO monad...

2010/6/10 Yitzchak Gale g...@sefer.org:
 Lennart Augustsson wrote:
 I would not use the continuation monad just for early exit.  Sounds
 like the error monad to me.

 I.e., the Either/ErrorT monad. But the mtl/transformers packages
 have an orphan instance for Either that requires the
 exit type to be an instance of the Error class. If that
 doesn't work in your case, use the Exit monad:

 http://www.haskell.org/haskellwiki/New_monads/MonadExit

 Or use the Maybe monad written additively, i.e. mplus
 in place of  (more or less).

 Regards,
 Yitz
 ___
 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] Using the ContT monads for early exits of IO ?

2010-06-10 Thread Jason Dagit
On Thu, Jun 10, 2010 at 8:45 PM, Derek Elkins derek.a.elk...@gmail.comwrote:

 Or... one could just use the exceptions that are already built into
 the IO monad...


It feels to me like this discussion has a lot of speculation in it.  I would
like to see concrete examples of the code and the suggested improvements.


 2010/6/10 Yitzchak Gale g...@sefer.org:
  Lennart Augustsson wrote:
  I would not use the continuation monad just for early exit.  Sounds
  like the error monad to me.
 
  I.e., the Either/ErrorT monad. But the mtl/transformers packages
  have an orphan instance for Either that requires the
  exit type to be an instance of the Error class. If that
  doesn't work in your case, use the Exit monad:
 
  http://www.haskell.org/haskellwiki/New_monads/MonadExit
 
  Or use the Maybe monad written additively, i.e. mplus
  in place of  (more or less).
 
  Regards,
  Yitz
  ___
  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 mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: How to Show an Operation?

2010-06-10 Thread Brandon S. Allbery KF8NH

On Jun 10, 2010, at 17:38 , Martin Drautzburg wrote:

instance Applicative Named where
   pure x = Named  x
   (Named s f) * (Named t v) = Named (s ++ ( ++ t ++ )) (f v)


Applicative. Need to study that


The above is just the Functor, rephrased in Applicative style.  * is  
exactly fmap.  Likewise, Monad has a function liftM which is exactly  
fmap.  (For historical reasons, these are not related the way they  
should be:  all Monads should be Applicatives, all Applicatives should  
be Functors, and all Functors should be instances of an even more  
primitive class Pointed.)


According to Hoogle permutations should be in Data.List. Mine (GHCI  
6.8.2)
does not seem to have it. Seems to have something to do with base,  
whatever

that is.


Things have gradually been moving out of base; you probably need to  
install containers from Hackage.


--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allb...@kf8nh.com
system administrator [openafs,heimdal,too many hats] allb...@ece.cmu.edu
electrical and computer engineering, carnegie mellon universityKF8NH




PGP.sig
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Thread scheduling

2010-06-10 Thread Luke Palmer
On Thu, Jun 10, 2010 at 11:50 AM, Andrew Coppin
andrewcop...@btinternet.com wrote:
 Control.Concurrent provides the threadDelay function, which allows you to
 make the current thread sleep until T=now+X. However, I can't find any way
 of making the current thread sleep until T=X. In other words, I want to
 specify an absolute wakeup time, not a relative one.

Modulo a small epsilon between the two actions, can't you just get the
current time and subtract it from the target time?  threadDelay is
allowed to delay for too long anyway, so doing it this way does not
lose you any correctness.

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


Re: [Haskell-cafe] Thread scheduling

2010-06-10 Thread Luke Palmer
Say, using System.Time.getClockTime.

Luke

On Thu, Jun 10, 2010 at 11:31 PM, Luke Palmer lrpal...@gmail.com wrote:
 On Thu, Jun 10, 2010 at 11:50 AM, Andrew Coppin
 andrewcop...@btinternet.com wrote:
 Control.Concurrent provides the threadDelay function, which allows you to
 make the current thread sleep until T=now+X. However, I can't find any way
 of making the current thread sleep until T=X. In other words, I want to
 specify an absolute wakeup time, not a relative one.

 Modulo a small epsilon between the two actions, can't you just get the
 current time and subtract it from the target time?  threadDelay is
 allowed to delay for too long anyway, so doing it this way does not
 lose you any correctness.

 Luke

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


Re: [Haskell-cafe] Re: How to Show an Operation?

2010-06-10 Thread Luke Palmer
On Thu, Jun 10, 2010 at 10:43 PM, Brandon S. Allbery KF8NH
allb...@ece.cmu.edu wrote:
 On Jun 10, 2010, at 17:38 , Martin Drautzburg wrote:

 instance Applicative Named where
   pure x = Named  x
   (Named s f) * (Named t v) = Named (s ++ ( ++ t ++ )) (f v)

 Applicative. Need to study that

 The above is just the Functor, rephrased in Applicative style.  * is
 exactly fmap.  Likewise, Monad has a function liftM which is exactly fmap.
  (For historical reasons, these are not related the way they should be:  all
 Monads should be Applicatives, all Applicatives should be Functors, and all
 Functors should be instances of an even more primitive class Pointed.)

(*) :: Applicative f = f (a - b) - f a - f b
($) :: Functor f = (a - b) - f a - f b

($) is fmap, not (*).  (*) is available for monads as Control.Monad.ap.

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


Re: [Haskell-cafe] Re: How to Show an Operation?

2010-06-10 Thread Martin Drautzburg
On Friday, 11. June 2010 00:12:03 Daniel Fischer wrote:

Thanks Daniel. 

 Upgrade. We're at 6.12 now!

Did that. Everything is available now.

I am still having trouble with the test function. First it seems I need 
braces, so I can mix == and *.
test :: Num a
 = (a - a) - (a - a) - (a - a) - [String]
test f g h = do
[f', g', h'] - permutations [Named f f, Named g g, Named h h]
guard $ namedPure 42 == (f' * g' * h' * namedPure 42)
return $ show f' ++  .  ++ show g' ++  .  ++ show h'

But this leads to

Occurs check: cannot construct the infinite type:
  a = (a - a) - a1 - t
When generalising the type(s) for `test'

This error message is still the maximum penalty for me (along with Corba 
marshall exception in J2EE and Missing right parenthesis in Oracle SQL)

Then generally speaking, I have the feeling that this code does not 
allow namifying existing code either. In this respect it does not seem to 
do better than the apply method pattern discussed earlier in this thread.

The problem it solves is very simple and therefore using (*) and namedPure 
isn't much of a drawback. But if I had tons of code to namify I would still 
have to do significant changes to it, right?





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