Re: [Haskell-cafe] May all logos be freely used?

2009-05-27 Thread Jeff Wheeler
On Tue, 2009-05-26 at 18:36 +0200, Max Rabkin wrote:

 So at least any logos on the wiki should be usable under that license.

Furthermore, I released all my logos (the lambda/bind combination that
won) into the Public Domain. Of course, derive from them as you wish,
and there are a couple of tools around to generate various versions with
roudedness and different colors.

Jeff Wheeler

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


Re: [Haskell-cafe] Re: I love purity, but it's killing me.

2009-05-27 Thread Paul L
Let-expression in the EDSL indeed solves the sharing problem, but only
partially.
Recursion appears when you have a leaf node pointing back to the root
node or another branch and forming a cyclic graph in the data
structure. It is often desirable to recover cyclic sharing when
showing/reading/interpretating EDSL programs.

One possible solution is to further introduce a fixed point data
constructor, a Rec or even LetRec to explicitly capture cycles. But
then you still incur much overheads interpreting them, and syntax wise
it just gets more and more complicated to the point that turning the
EDSL into a DSL (or even a preprocessor with your own lexer and
parser) becomes more attractive.

Another alternative is to express the EDSL as Monad/MonadFix, or
Arrows/ArrowLoop. There are still interpretive overheads, but at the
very least they could help with the syntax.

The tagless paper is really nice, but I doubt it offers solutions to
the (cyclic) sharing problem.


On 2/13/08, Chung-chieh Shan ccs...@post.harvard.edu wrote:
 Henning Thielemann lemm...@henning-thielemann.de wrote in article
 pine.gso.4.56.0802080908310.12...@haydn.informatik.uni-halle.de in
 gmane.comp.lang.haskell.cafe:
 It seems to become a FAQ. I think all DSLs suffer from the same problems:
 sharing and recursion. I've used wrappers for CSound, SuperCollider,
 MetaPost, they all have these problems.

 What do you mean by the recursion problem?

 Sometimes (or perhaps even often), sharing in an EDSL can be expressed
 in two ways.  First, to reuse a -value- in the embedded language, you
 could introduce a let construct in the embedded language.

 let_ expr body = body expr

 Second, to reuse an -expression- in the embedded language, if your
 interpreter is compositional (here by interpreter I include a
 compiler, and by compositional I mean a fold), then you can represent
 an embedded expression simply as its interpretation.

 add x y = x + y
 let expr = add x y in add expr expr

 Jacques Carette, Oleg Kiselyov, and I have been exploring this final
 representation.  http://okmij.org/ftp/Computation/tagless-typed.html

 --
 Edit this signature at http://www.digitas.harvard.edu/cgi-bin/ken/sig
 I am a signature virus. Put me in your signature.

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



-- 
Regards,
Paul Liu

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


[Haskell-cafe] Re: Purely logical programming language

2009-05-27 Thread Sebastian Fischer


On May 27, 2009, at 1:01 AM, Ahn, Ki Yung wrote:

By the way, did Curry solved the problem of how to deal with IO and  
backtracking issues? (where and  where not should IO happen kind of  
a thing)


Curry uses the IO monad to specify where IO actions may happen. Non- 
determinism is not excluded statically from IO actions but usually  
leads to a run-time error (see Section 7.1 of [1]). For example the  
Curry systems PAKCS [2] and MCC [3] show the following behaviour (the  
infix operator (?) denotes non-deterministic choice):


  $ pakcs
  Prelude print (1?2)
  1
  2
  ERROR: non-determinism in I/O actions occurred!
  Prelude :q
  $ cyi
  Prelude print (1?2)
  Error: cannot duplicate the world
  Prelude :q

In order to use non-deterministic operations in an IO context, their  
results need to be *encapsulated*, i.e., collected in a data structure  
(e.g. a list). See [4,5] for recent research on encapsulated search.


The Curry System KiCS [6] uses encapsulated search implicitly in IO  
operations and uses the first result if there is one and only yields  
an error otherwise:


  $ kicsi
  Prelude print (1?2)
  1
  Prelude print (1=:=2)
  non-exhaustive patterns in function Prelude._case_1
  interactive: program error
  Prelude :q

Cheers,
Sebastian

[1]: http://www.informatik.uni-kiel.de/~curry/report.html
[2]: http://www.informatik.uni-kiel.de/~pakcs/
[3]: http://danae.uni-muenster.de/~lux/curry/
[4]: http://www.informatik.uni-kiel.de/~mh/papers/JFLP04_findall.html
[5]: Computing with subspaces, 
http://web.cecs.pdx.edu/~antoy/homepage/publications.html
[6]: http://www.informatik.uni-kiel.de/prog/mitarbeiter/bernd-brassel/projects/


--
Underestimating the novelty of the future is a time-honored tradition.
(D.G.)



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


Re: [Haskell-cafe] Re: I love purity, but it's killing me.

2009-05-27 Thread Paul L
BTW, I doubt the (cyclic) sharing problem relates that much to purity,
because in an impure language (or the unsafe observable sharing), you
still have to remember whether something has been traversed or not and
in the worst case accumulates everything that's been traversed so far
before releasing all of them in the end. If you remember the history
by mutating some states, e.g., using a dirty tag, you lose the ability
to do simultaneous traversals.

Adding a simple indirect reference only to the places where sharing is
needed (and thus making it explicit) could alleviate this problem. But
this solution exists in both pure and impure languages.

So let's love purity still :-)

-- 
Regards,
Paul Liu

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


[Haskell-cafe] Timing pure functions?

2009-05-27 Thread Magnus Therning
Yesterday I spent about 5 minutes trying to time a single function in
haskell (after having spent about 30 minutes on the timeit module in
Python).  I found timeit[1] on Hackage but it only times an IO
computation once, what I'd like to do is time a pure function several
times.  Timing it once was no problem, passing `return $! myPureFunc`
to `timeIt` did that[2].  My feeble attempt at collecting several
timings failed though.

  import System.CPUTime
  import qualified Codec.Binary.Base64 as B64
  import System.IO
  import qualified Data.ByteString as BS
  import Control.Monad


  timeIt times ioa = let
  timeOnce = do
  t1 - getCPUTime
  a - ioa
  t2 - getCPUTime
  let t = fromIntegral (t2-t1) * 1e-12
  return t
  in sequence $ take times $ repeat timeOnce

  main = do
  fh - openBinaryFile /dev/urandom ReadMode
  d - liftM BS.unpack $ BS.hGet fh 10
  t - timeIt 10 $ return $! B64.encode d
  print t

Running this on my machine produces the output
[2.3331e-2,0.0,0.0,0.0,0.0,0.0,0.0,0.0,0.0,0.0].  I.e. the first time
the data is encoded, but the following 9 times it's not.

I suspect that it all comes from `B64.encode d` being pure, hence the
encoding happens only once.  Now I _really_ want the encoding to
happen 10 times, is there some easy way to achieve this?

/M

[1]: http://hackage.haskell.org/cgi-bin/hackage-scripts/package/timeit
[2]:
-- 
Magnus Therning(OpenPGP: 0xAB4DFBA4)
magnus@therning.org  Jabber: magnus@therning.org
http://therning.org/magnus identi.ca|twitter: magthe
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Timing pure functions?

2009-05-27 Thread Andrew Butterfield

Magnus Therning wrote:

  timeIt times ioa = let
  timeOnce = do
  t1 - getCPUTime
  a - ioa
  t2 - getCPUTime
  let t = fromIntegral (t2-t1) * 1e-12
  return t
  in sequence $ take times $ repeat timeOnce

  main = do
  fh - openBinaryFile /dev/urandom ReadMode
  d - liftM BS.unpack $ BS.hGet fh 10
  t - timeIt 10 $ return $! B64.encode d
  print t


I suspect that it all comes from `B64.encode d` being pure, hence the
encoding happens only once.  Now I _really_ want the encoding to
happen 10 times, is there some easy way to achieve this?

  
A quick answer - not a lot of thought - pass function *and* argument 
separately into timeIt ?


 timeIt times ioaf ioaarg
    a - ioaf ioaarg

As it stands you pass the thunk (B64.encode d) in so it only gets 
evaluated once
If you pass the function and argument in then a new thunk is built each 
time around

(unless the optimiser nabbles it...)

/M

[1]: http://hackage.haskell.org/cgi-bin/hackage-scripts/package/timeit
[2]:
  



--

Andrew Butterfield Tel: +353-1-896-2517 Fax: +353-1-677-2204
Foundations and Methods Research Group Director.
School of Computer Science and Statistics,
Room F.13, O'Reilly Institute, Trinity College, University of Dublin
   http://www.cs.tcd.ie/Andrew.Butterfield/


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


Re: [Haskell-cafe] Timing pure functions?

2009-05-27 Thread Magnus Therning
On Wed, May 27, 2009 at 9:59 AM, Andrew Butterfield
andrew.butterfi...@cs.tcd.ie wrote:
 Magnus Therning wrote:

  timeIt times ioa = let
          timeOnce = do
              t1 - getCPUTime
              a - ioa
              t2 - getCPUTime
              let t = fromIntegral (t2-t1) * 1e-12
              return t
          in sequence $ take times $ repeat timeOnce

  main = do
      fh - openBinaryFile /dev/urandom ReadMode
      d - liftM BS.unpack $ BS.hGet fh 10
      t - timeIt 10 $ return $! B64.encode d
      print t


 I suspect that it all comes from `B64.encode d` being pure, hence the
 encoding happens only once.  Now I _really_ want the encoding to
 happen 10 times, is there some easy way to achieve this?



 A quick answer - not a lot of thought - pass function *and* argument
 separately into timeIt ?

  timeIt times ioaf ioaarg
        a - ioaf ioaarg

 As it stands you pass the thunk (B64.encode d) in so it only gets evaluated
 once
 If you pass the function and argument in then a new thunk is built each time
 around
 (unless the optimiser nabbles it...)

Hmm, my naive implementation of that didn't improve the situation, `t
- timeIt 10 (\ x - return $! B64.encode x) d` still results in only
one measurement /= 0.

Of course that also makes `timeIt` less general.

/M

-- 
Magnus Therning(OpenPGP: 0xAB4DFBA4)
magnus@therning.org  Jabber: magnus@therning.org
http://therning.org/magnus identi.ca|twitter: magthe
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Purely logical programming language

2009-05-27 Thread Matthias Görgens
 Mercury also has type classes and other Haskellisms, so if you're
 interested in doing Prolog the Haskell way, you should definitely
 have a look at it.

 I have to admit that I am not very familiar with Mercury. But if you are
 looking for doing Prolog the Haskell way advertiseyou can also have a
 look at Curry/advertise. Curry is a lazy functional logic programming
 language that has a Haskell like syntax (http://www.curry-language.org/).

 You forgot to mention, that you will give a talk about Curry soon, where
 Matthias might want to attend:
  http://iba-cg.de/hal4.html

Indeed.  Studying in Magdeburg, I already heard about that workshop
and considered attending, but I did not read the agenda in detail.
Now I'll definitely attend.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Timing pure functions?

2009-05-27 Thread austin s
Excerpts from Magnus Therning's message of Wed May 27 03:51:19 -0500 2009:
 Yesterday I spent about 5 minutes trying to time a single function in
 haskell (after having spent about 30 minutes on the timeit module in
 Python).  I found timeit[1] on Hackage but it only times an IO
 computation once, what I'd like to do is time a pure function several
 times.  Timing it once was no problem, passing `return $! myPureFunc`
 to `timeIt` did that[2].  My feeble attempt at collecting several
 timings failed though.
 
   import System.CPUTime
   import qualified Codec.Binary.Base64 as B64
   import System.IO
   import qualified Data.ByteString as BS
   import Control.Monad
 
 
   timeIt times ioa = let
   timeOnce = do
   t1 - getCPUTime
   a - ioa
   t2 - getCPUTime
   let t = fromIntegral (t2-t1) * 1e-12
   return t
   in sequence $ take times $ repeat timeOnce
 
   main = do
   fh - openBinaryFile /dev/urandom ReadMode
   d - liftM BS.unpack $ BS.hGet fh 10
   t - timeIt 10 $ return $! B64.encode d
   print t
 
 Running this on my machine produces the output
 [2.3331e-2,0.0,0.0,0.0,0.0,0.0,0.0,0.0,0.0,0.0].  I.e. the first time
 the data is encoded, but the following 9 times it's not.
 
 I suspect that it all comes from `B64.encode d` being pure, hence the
 encoding happens only once.  Now I _really_ want the encoding to
 happen 10 times, is there some easy way to achieve this?
 
 /M
 
 [1]: http://hackage.haskell.org/cgi-bin/hackage-scripts/package/timeit
 [2]:

Perhaps benchpress would be more to your liking:

  http://hackage.haskell.org/cgi-bin/hackage-scripts/package/benchpress

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


RE: [Haskell-cafe] The essence of my monad confusion

2009-05-27 Thread Paul Keir
Thanks for all the help. The simplified example indeed threw away too
much. There were no side effects.

Brent, of course I couldn't create your function; though I gained
through trying. I then found it useful to consider the type of:

fmap (\x - putStrLn x) getLine

which is IO (IO ()) and hence displays nothing to the screen.

Felipe, your recursive example was also compelling and concise.

Antoine, I see how the join capacity of a Monad can be useful in this
issue. I'm also reminded of what * can bring to fmap/$.

On reflection, I often trip up when learning by comparing IO to simpler
monads such as [] and Maybe. But [] and Maybe never have effects, and so
are poor foils. The ((-) t) monad is henceforth in my toolbox.

Paul


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


Re: [Haskell-cafe] I love purity, but it's killing me.

2009-05-27 Thread Sebastiaan Visser

On May 27, 2009, at 1:49 AM, Conal Elliott wrote:

Hi Tom,

I've been working on another code-generating graphics compiler,  
generating GPU code.  As always, I run into the problem of efficient  
common subexpression elimination.  In Pan, Vertigo  Pajama, I used  
lazy memoization, using stable pointers and weak references, to  
avoid the worst-case-exponential behavior you mention below.  I'm  
now using a bottom-up CSE method that's slower and more complicated  
than I'm going for.


What do you mean with `exponential behavior'? Exponential related to  
what?


For my FRP EDSL to JavaScript (toy) compiler[1] I've been implementing  
CSE as well. I traverses the expression tree recursively and creates  
an small intermediate language containing id's (pointers) to  
expressions instead of real sub-expressions.


Maybe (probably) I am very naive, but I think this trick takes time  
linear to the amount of sub-expressions in my script. When using a  
trie instead of a binary tree for the comparisons there should be no  
more character (or atomic expression) comparisons that the amount of  
characters in the script.


So the problem seems not to be CSE algorithm, but the fact that EDSL  
itself tends to blow up because it is hosted in Haskell. Like Tom's  
example:


 let d = Add c c
 e = Add d d-- e now as 16 leaf nodes.

But again, I might be missing some important point here.


What's your latest wisdom about CSE in DSELs?

Thanks,  - Conal

On Thu, Feb 7, 2008 at 11:33 PM, Tom Hawkins tomahawk...@gmail.com  
wrote:

...


--
Sebastiaan Visser

(warning: messy code)
[1] 
http://github.com/sebastiaanvisser/frp-js/blob/b4f37d3b564c4932a3019b9b580e6da9449768a8/src/Core/Compiler.hs
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Bidirectional programming in Haskell

2009-05-27 Thread Artyom Shalkhakov
Hi,

2009/5/26 Shin-Cheng Mu s...@iis.sinica.edu.tw:
 Some of the early work in the PSD project (closely related
 to the lenses) were developed in Haskell,

  http://www.iis.sinica.edu.tw/~scm/2007/inv/

 It is not in active maintenance now, but if you are interested
 in doing something with it, I'd be happy to help. :)

 Ref:

 [1] S-C. Mu, Z. Hu and M. Takeichi,
    An injective language for reversible computation.
    In Mathematics of Program Construction 2004, LNCS 3125,
    pp. 289-313, July 2004.

 [2] Z. Hu, S-C. Mu and M. Takeichi,
    A programmable editor for developing structured documents
    based on bidirectional transformations.
    In Partial Evaluation and Semantics-Based Program Manipulation,
    pp. 178-189. August 2004

Thanks a lot, I'm off for some reading. :)

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


RE: [Haskell-cafe] I love purity, but it's killing me.

2009-05-27 Thread Sittampalam, Ganesh
Sebastiaan Visser wrote:
 On May 27, 2009, at 1:49 AM, Conal Elliott wrote:
 Hi Tom,
 
 I've been working on another code-generating graphics compiler,
 generating GPU code.  As always, I run into the problem of efficient
 common subexpression elimination.  In Pan, Vertigo  Pajama, I used
 lazy memoization, using stable pointers and weak references, to avoid
 the worst-case-exponential behavior you mention below.  I'm now using
 a bottom-up CSE method that's slower and more complicated than I'm
 going for.
 
 What do you mean with `exponential behavior'? Exponential related to
 what? 
 
 For my FRP EDSL to JavaScript (toy) compiler[1] I've been
 implementing CSE as well. I traverses the expression tree recursively
 and creates an small intermediate language containing id's (pointers)
 to expressions instead of real sub-expressions.   
 
 Maybe (probably) I am very naive, but I think this trick takes time
 linear to the amount of sub-expressions in my script. When using a
 trie instead of a binary tree for the comparisons there should be no
 more character (or atomic expression) comparisons that the amount of
 characters in the script.
 
 So the problem seems not to be CSE algorithm, but the fact that EDSL
 itself tends to blow up because it is hosted in Haskell. Like Tom's 
 example:
 
   let d = Add c c
   e = Add d d-- e now as 16 leaf nodes.
 
 But again, I might be missing some important point here.

That's exactly right. But it's pretty inconvenient to have your
expression tree to blow up exponentially in relation to the code the
user actually wrote! You can indeed construct an intermediate language
that collapses this blowup, but the pass to create it must take
exponential time if written completely purely, since it has to visit
everything at least once.

In my experience [1], observable sharing using GHC's stable names is a
pretty effective solution to this problem.

Ganesh

[1] http://www.earth.li/~ganesh/research/paradise-icfp08/

=== 
 Please access the attached hyperlink for an important electronic 
communications disclaimer: 
 http://www.credit-suisse.com/legal/en/disclaimer_email_ib.html 
 
=== 
 
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Timing pure functions?

2009-05-27 Thread Johan Tibell
On Wed, May 27, 2009 at 12:02 PM, austin s a...@nijoruj.org wrote:

  Perhaps benchpress would be more to your liking:

  http://hackage.haskell.org/cgi-bin/hackage-scripts/package/benchpress


Note that since benchpress measures every single invocation of the provided
IO action in order to compute percentiles it's not good at measuring the
execution times of small functions as the timing overhead dominates in those
cases.

Cheers,

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


Re: [Haskell-cafe] I love purity, but it's killing me.

2009-05-27 Thread Sebastiaan Visser

On May 27, 2009, at 12:51 PM, Sittampalam, Ganesh wrote:

Sebastiaan Visser wrote:

...

But again, I might be missing some important point here.


That's exactly right. But it's pretty inconvenient to have your
expression tree to blow up exponentially in relation to the code the
user actually wrote! You can indeed construct an intermediate language
that collapses this blowup, but the pass to create it must take
exponential time if written completely purely, since it has to visit
everything at least once.

In my experience [1], observable sharing using GHC's stable names is a
pretty effective solution to this problem.

Ganesh

[1] http://www.earth.li/~ganesh/research/paradise-icfp08/



Thanks, I just pushed your paper on top of my stack.

--
Sebastiaan Visser



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


[Haskell-cafe] Bool as type class to serve EDSLs.

2009-05-27 Thread Sebastiaan Visser

Hello,

While playing with embedded domain specific languages in Haskell I  
discovered the Num type class is a really neat tool. Take this simple  
example embedded language that can embed primitives from the output  
language and can do function application.


data Expr :: * - * where
  Prim :: String - Expr a
  App  :: Expr (a - b) - Expr a - Expr b

Take these two dummy types to represent things in the output language.

data MyNum
data MyBool

Now it is very easy to create an Num instance for this language:

primPlus :: Expr (MyNum - MyNum - MyNum)
primPlus = Prim prim+

instance Num (Epxr MyNum) where
  a + b = primPlus `App` a `App` b
  fromInteger = Prim . show
  ...

Which allows you to create very beautiful expression for your language  
embedded inside Haskell. The Haskell expression `10 * 5 + 2' produces  
a nice and well typed expression in your embedded domain.


But unfortunately, not everyone in the Prelude is as tolerant as the  
Num instance. Take the Eq and the Ord type classes for example, they  
require you to deliver real Haskell `Bool's. This makes it impossible  
make your DSL an instance of these two, because there are no `Bool's  
only `Expr Bool's.


Which brings me to the point that, for the sake of embedding other  
languages, Haskell's Prelude (or an alternative) can greatly benefit  
from (at least) a Boolean type class like this:


class Boolean a where
  ifthenelse :: a - b - b - b -- Not sure about this  
representation.

  ...

And one instance:

instance Boolean (Expr MyBool) where
  ifthenelse c a b = Prim if-then-else `App` c `App` a `App` b

Now we can change (for example) the Eq type class to this:

class Eq a where
  (==) :: Boolean b = a - a - b
  (/=) :: Boolean b = a - a - b

For which we can give an implementation for our domain:

primEq :: Epxr (a - a - MyBool)
primEq = Prim ==

instance Eq (Expr a) where
  a == b = primEq `App` a `App` b

And now we get all functionality from the Prelude that is based on Eq  
(like not, , ||, etc) for free in our domain specific language! Off  
course there are many, many more examples of things from the standard  
libraries that can be generalised in order to serve reuse in EDSLs.


Anyone already working on such a generalized Prelude? I can imagine  
much more domains can benefit from this than my example above. Any  
interesting thoughts or pointers related to this subject?


Gr,

--
Sebastiaan Visser

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


Re: [Haskell-cafe] Bool as type class to serve EDSLs.

2009-05-27 Thread Edsko de Vries
+1. I agree completely, I've missed this often for exactly the same  
reasons.


Edsko

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


Re: [Haskell-cafe] Bool as type class to serve EDSLs.

2009-05-27 Thread Miguel Mitrofanov

And I would certainly celebrate when if b then x else y expression becomes polymorphic 
in b.

Edsko de Vries wrote on 27.05.2009 17:33:
+1. I agree completely, I've missed this often for exactly the same 
reasons.


Edsko

___
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] Bool as type class to serve EDSLs.

2009-05-27 Thread Jason Dusek
2009/05/27 Miguel Mitrofanov miguelim...@yandex.ru:
 And I would certainly celebrate when if b then x else y
 expression becomes polymorphic in b.

class Boolean b where
  fromBoolean :: b - Bool

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


Re: [Haskell-cafe] I love purity, but it's killing me.

2009-05-27 Thread Conal Elliott
Hi Wren,

I considered the idea of hashing, but not *perfect* hashing.  I don't know
how to hash perfectly with something like expressions, which have infinitely
many values.

Since it's stateful, that means the smart constructors may need to be in an
 appropriate monad/applicative for passing the memo table around (some hash
 functions may not need to store the table explicitly).


Hm -- stateful?  Unless I'm misunderstanding, a stateful 
monadic/applicative approach would break the simple functional interface I'm
going for.  Could well be I haven't formed a mental picture that matches
yours.

  - Conal

On Tue, May 26, 2009 at 5:23 PM, wren ng thornton w...@freegeek.org wrote:

 Conal Elliott wrote:

 Hi Tom,

 I've been working on another code-generating graphics compiler, generating
 GPU code.  As always, I run into the problem of efficient common
 subexpression elimination.  In Pan, Vertigo  Pajama, I used lazy
 memoization, using stable pointers and weak references, to avoid the
 worst-case-exponential behavior you mention below.  I'm now using a
 bottom-up CSE method that's slower and more complicated than I'm going
 for.

 What's your latest wisdom about CSE in DSELs?

 Thanks,  - Conal



 One common trick that Tom didn't seem to mention in the 2008-02-07T23:33
 post is hash cons'ing.

 Given a perfect hash function, traverse the term bottom-up storing each
 (hash,subterm) pair in a memo table and replacing the subterm by its hash.
 Once that's done, equality checks are trivial, and the memotable can be
 converted to SSA rather easily.

 This works best if you amortize the memoization by doing it with smart
 constructors, so that you don't need to worry about the exponential
 duplication of work for expressions with DAGy structure sharing in the
 Haskell. Since it's stateful, that means the smart constructors may need to
 be in an appropriate monad/applicative for passing the memo table around
 (some hash functions may not need to store the table explicitly).

 Maybe this is the too-slow too-complex solution you're using already?

 --
 Live well,
 ~wren

 ___
 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] I love purity, but it's killing me.

2009-05-27 Thread Conal Elliott

 What do you mean with `exponential behavior'? Exponential related to what?


I mean that the size of the observable tree can be exponential in the size
of the unobservable dag representation.

So the problem seems not to be CSE algorithm, but the fact that EDSL itself
 tends to blow up because it is hosted in Haskell.


In other words, the tree size blows up, and hosting in pure Haskell doesn't
allow us to examine the compact dag.

Are we on the same track now?

  - Conal

On Wed, May 27, 2009 at 3:15 AM, Sebastiaan Visser sfvis...@cs.uu.nlwrote:

 On May 27, 2009, at 1:49 AM, Conal Elliott wrote:

 Hi Tom,

 I've been working on another code-generating graphics compiler, generating
 GPU code.  As always, I run into the problem of efficient common
 subexpression elimination.  In Pan, Vertigo  Pajama, I used lazy
 memoization, using stable pointers and weak references, to avoid the
 worst-case-exponential behavior you mention below.  I'm now using a
 bottom-up CSE method that's slower and more complicated than I'm going for.


 What do you mean with `exponential behavior'? Exponential related to what?

 For my FRP EDSL to JavaScript (toy) compiler[1] I've been implementing CSE
 as well. I traverses the expression tree recursively and creates an small
 intermediate language containing id's (pointers) to expressions instead of
 real sub-expressions.

 Maybe (probably) I am very naive, but I think this trick takes time linear
 to the amount of sub-expressions in my script. When using a trie instead of
 a binary tree for the comparisons there should be no more character (or
 atomic expression) comparisons that the amount of characters in the script.

 So the problem seems not to be CSE algorithm, but the fact that EDSL itself
 tends to blow up because it is hosted in Haskell. Like Tom's example:

  let d = Add c c
  e = Add d d-- e now as 16 leaf nodes.

 But again, I might be missing some important point here.

  What's your latest wisdom about CSE in DSELs?

 Thanks,  - Conal

 On Thu, Feb 7, 2008 at 11:33 PM, Tom Hawkins tomahawk...@gmail.com
 wrote:

 ...


 --
 Sebastiaan Visser

 (warning: messy code)
 [1]
 http://github.com/sebastiaanvisser/frp-js/blob/b4f37d3b564c4932a3019b9b580e6da9449768a8/src/Core/Compiler.hs

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


Re: [Haskell-cafe] I love purity, but it's killing me.

2009-05-27 Thread Conal Elliott

 In my experience [1], observable sharing using GHC's stable names is a
 pretty effective solution to this problem.


Plus unsafePerformIO and weak references as in *Stretching the storage
manager: weak pointers and stable names in
Haskellhttp://citeseer.ist.psu.edu/peytonjones99stretching.html
*?

Lacking a more elegant alternative, that's what I'll probably do again, as
in Pan, Vertigo, and Pajama.

  - Conal

On Wed, May 27, 2009 at 3:51 AM, Sittampalam, Ganesh 
ganesh.sittampa...@credit-suisse.com wrote:

 Sebastiaan Visser wrote:
  On May 27, 2009, at 1:49 AM, Conal Elliott wrote:
  Hi Tom,
 
  I've been working on another code-generating graphics compiler,
  generating GPU code.  As always, I run into the problem of efficient
  common subexpression elimination.  In Pan, Vertigo  Pajama, I used
  lazy memoization, using stable pointers and weak references, to avoid
  the worst-case-exponential behavior you mention below.  I'm now using
  a bottom-up CSE method that's slower and more complicated than I'm
  going for.
 
  What do you mean with `exponential behavior'? Exponential related to
  what?
 
  For my FRP EDSL to JavaScript (toy) compiler[1] I've been
  implementing CSE as well. I traverses the expression tree recursively
  and creates an small intermediate language containing id's (pointers)
  to expressions instead of real sub-expressions.
 
  Maybe (probably) I am very naive, but I think this trick takes time
  linear to the amount of sub-expressions in my script. When using a
  trie instead of a binary tree for the comparisons there should be no
  more character (or atomic expression) comparisons that the amount of
  characters in the script.
 
  So the problem seems not to be CSE algorithm, but the fact that EDSL
  itself tends to blow up because it is hosted in Haskell. Like Tom's
  example:
 
let d = Add c c
e = Add d d-- e now as 16 leaf nodes.
 
  But again, I might be missing some important point here.

 That's exactly right. But it's pretty inconvenient to have your
 expression tree to blow up exponentially in relation to the code the
 user actually wrote! You can indeed construct an intermediate language
 that collapses this blowup, but the pass to create it must take
 exponential time if written completely purely, since it has to visit
 everything at least once.

 In my experience [1], observable sharing using GHC's stable names is a
 pretty effective solution to this problem.

 Ganesh

 [1] 
 http://www.earth.li/~ganesh/research/paradise-icfp08/http://www.earth.li/%7Eganesh/research/paradise-icfp08/


 ===
  Please access the attached hyperlink for an important electronic
 communications disclaimer:
  http://www.credit-suisse.com/legal/en/disclaimer_email_ib.html

  
 ===


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


Re: [Haskell-cafe] Lazy Parsing

2009-05-27 Thread Henning Thielemann
GüŸnther Schmidt schrieb:
 Hi all,
 
 is it possible to do lazy parsing with Parsec? I understand that one can
 do that with polyparse, don't know about uulib, but I happen to be
 already somewhat familiar with Parsec, so before I do switch to
 polyparse I rather make sure I actually have to.
 
 The files it has to parse is anywhere from 500 MB to 5 GB.

I don't think that it is in general possible to use the same parser for
lazy and strict parsing, just because of the handling of parser failure.
If parser failure is denoted by a Left constructor in (Either Reason
Result) then the whole parsing process must be finished, before the
parser knows whether the answer is Left or Right.
I also used polyparse for lazy parsing, but I found it unintuitive how
to make a parser lazy. I tried to do better in tagchup, where I make
explicit in the type, whether a parser can fail or not. In the first
case in cannot be lazy, in the second case it can. I also did lazy
parsing in 'midi' package and in 'spreadsheet'. I liked to factor out a
lazy parser library from them, but I failed to unify all these
applications. At least I have factored out handling of lazy failure (aka
asnychronous exceptions) in explicit-exception package.

Btw. a good place to discuss such issues is our local Haskell meeting
that takes place on 2009-06-12:
   http://iba-cg.de/hal4.html

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


Re: [Haskell-cafe] I love purity, but it's killing me.

2009-05-27 Thread Conal Elliott
I just remembered: Andy Gill has a new paper Type Directed Observable
Sharing (http://www.ittc.ku.edu/~andygill/paper.php?label=DSLExtract09)
that looks very relevant.

Abstract:

Haskell is a great language for writing and supporting embedded Domain
 Specific Languages (DSLs). Some form of observable sharing is often a
 critical capability for allowing so-called deep DSLs to be compiled and
 processed. In this paper, we describe and explore uses of an IO function for
 reification which allows direct observation of sharing.




On Tue, May 26, 2009 at 4:49 PM, Conal Elliott co...@conal.net wrote:

 Hi Tom,

 I've been working on another code-generating graphics compiler, generating
 GPU code.  As always, I run into the problem of efficient common
 subexpression elimination.  In Pan, Vertigo  Pajama, I used lazy
 memoization, using stable pointers and weak references, to avoid the
 worst-case-exponential behavior you mention below.  I'm now using a
 bottom-up CSE method that's slower and more complicated than I'm going for.

 What's your latest wisdom about CSE in DSELs?

 Thanks,  - Conal


 On Thu, Feb 7, 2008 at 11:33 PM, Tom Hawkins tomahawk...@gmail.comwrote:

 I've been programming with Haskell for a few years and love it.  One
 of my favorite applications of Haskell is using for domain specific
 languages.  However, after designing a handful of DSLs, I continue to
 hit what appears to be a fundamental hurdle -- or at least I have yet
 to find an adequate solution.

 My DSLs invariably define a datatype to capture expressions; something
 like this:

 data Expression
  = Add Expression Expression
  | Sub Expression Expression
  | Variable String
  | Constant Int
  deriving Eq

 Using the datatype Expression, it is easy to mass a collections of
 functions to help assemble complex expressions, which leads to very
 concise programs in the DSL.

 The problem comes when I want to generate efficient code from an
 Expression (ie. to C or some other target language).  The method I use
 invovles converting the tree of subexpressions into an acyclic graphic
 to eliminate common subexpressions.  The nodes are then topologically
 ordered and assigned an instruction, or statement for each node.  For
 example:

 let a = Add (Constant 10) (Variable i1)
b = Sub (Variable i2) (Constant 2)
c = Add a b

 would compile to a C program that may look like this:

  a = 10 + i1;
  b = i2 - 2;
  c = a + b;

 The process of converting an expression tree to a graph uses either Eq
 or Ord (either derived or a custom instance) to search and build a set
 of unique nodes to be ordered for execution.  In this case a, then
 b, then c.  The problem is expressions often have shared,
 equivalent subnodes, which dramatically grows the size of the tree.
 For example:

 let d = Add c c
e = Add d d-- e now as 16 leaf nodes.

 As these trees grow in size, the equality comparison in graph
 construction quickly becomes the bottleneck for DSL compilation.
 What's worse, the phase transition from tractable to intractable is
 very sharp.  In one of my DSL programs, I made a seemingly small
 change, and compilation time went from milliseconds to
 not-in-a-million-years.

 Prior to Haskell, I wrote a few DSLs in OCaml.  I didn't have this
 problem in OCaml because each let expression was mutable, and I
 could use the physical equality operator to perform fast comparisons.
 Unfortunately, I have grown to love Haskell's type system and its lack
 of side effects, and could never go back.

 Is there anything that can be done to dramatically speed up
 comparisons, or is there a better approach I can take to extract
 common subexpressions?  I should point out I have an opportunity to
 get Haskell on a real industrial application.  But if I can't solve
 this problem, I may have to resort to far less eloquent languages.
 :-(

 Thanks for any and all help.

 -Tom
 ___
 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] Facebook puzzles allow for GHC solutions

2009-05-27 Thread David Leimbach
Interesting:
http://www.facebook.com/careers/puzzles.php

So they use Haskell at Facebook?

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


Re: [Haskell-cafe] Timing pure functions?

2009-05-27 Thread wren ng thornton

Johan Tibell wrote:

austin s wrote:
  Perhaps benchpress would be more to your liking:

  http://hackage.haskell.org/cgi-bin/hackage-scripts/package/benchpress

Note that since benchpress measures every single invocation of the provided
IO action in order to compute percentiles it's not good at measuring the
execution times of small functions as the timing overhead dominates in those
cases.



For small functions, microbench is another good option:

  http://hackage.haskell.org/cgi-bin/hackage-scripts/package/microbench


When comparing functions with large multiplicative discrepancies in 
runtime, it can give erroneous answers due to Int overflow. Modifying it 
to use Integers instead fixes the bug a some overhead cost. (Perhaps 
both versions could be offered by the package?)


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


[Haskell-cafe] Stack overflow

2009-05-27 Thread Krzysztof Skrzętnicki
Hello Cafe

I'm currently writing an app with heavy use of message passing. To see
which messages takes most of the bandwidth I wrote the following code:

--
data Counter = CNT !Int !Int !Int !Int

cntMsg (CNT a b c d) (MoveOther _ _) = (CNT a+1 b c d)
cntMsg (CNT a b c d) (MoveSelf _) = (CNT a b+1 c d)
cntMsg (CNT a b c d) (NilMsg) = (CNT a b c+1 d)
cntMsg (CNT a b c d) (RoundEnd) = (CNT a b c d+1)

emptyCnt = CNT 0 0 0 0
showCnt (CNT a b c d) = printf CNT MoveOther=%d MoveSelf=%d NilMsg=%d
RoundEnd=%d a b c d
--

The code for modifying the counter:
(\ msg - atomicModifyIORef ioref (\ cnt - (cntMsg cnt msg,(

Running it without increased stack blows it. With 200M stack I get
after a second or so:

CNT MoveOther=2125764 MoveSelf=0 NilMsg=0 RoundEnd=2916

The datatype itself is strict. So where is the thunk actually accumulating?

Best regards

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


Re: [Haskell-cafe] Facebook puzzles allow for GHC solutions

2009-05-27 Thread Mattias Bengtsson
On Wed, 2009-05-27 at 08:20 -0700, David Leimbach wrote:
 Interesting:
 
 
 http://www.facebook.com/careers/puzzles.php
 
 
 So they use Haskell at Facebook?


They could very well be having ghc installed on their puzzle test
server without using it elsewhere.
They got my attention though. Perhaps i should solve some puzzles
instead of studying for my exam!

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


RE: [Haskell-cafe] I love purity, but it's killing me.

2009-05-27 Thread Sittampalam, Ganesh
Yes, though we don't bother with weak pointers as we only keep the
stable names map around for the duration of CSE so there's no ongoing
memory leak issue.
 


From: haskell-cafe-boun...@haskell.org
[mailto:haskell-cafe-boun...@haskell.org] On Behalf Of Conal Elliott
Sent: 27 May 2009 16:14
To: Sittampalam, Ganesh
Cc: Haskell Cafe
Subject: Re: [Haskell-cafe] I love purity, but it's killing me.



In my experience [1], observable sharing using GHC's stable
names is a pretty effective solution to this problem.


Plus unsafePerformIO and weak references as in Stretching the storage
manager: weak pointers and stable names in Haskell
http://citeseer.ist.psu.edu/peytonjones99stretching.html ?

Lacking a more elegant alternative, that's what I'll probably do again,
as in Pan, Vertigo, and Pajama.

  - Conal


On Wed, May 27, 2009 at 3:51 AM, Sittampalam, Ganesh
ganesh.sittampa...@credit-suisse.com wrote:


Sebastiaan Visser wrote:
 On May 27, 2009, at 1:49 AM, Conal Elliott wrote:
 Hi Tom,

 I've been working on another code-generating graphics
compiler,
 generating GPU code.  As always, I run into the problem of
efficient
 common subexpression elimination.  In Pan, Vertigo  Pajama,
I used
 lazy memoization, using stable pointers and weak references,
to avoid
 the worst-case-exponential behavior you mention below.  I'm
now using
 a bottom-up CSE method that's slower and more complicated
than I'm
 going for.

 What do you mean with `exponential behavior'? Exponential
related to
 what?

 For my FRP EDSL to JavaScript (toy) compiler[1] I've been
 implementing CSE as well. I traverses the expression tree
recursively
 and creates an small intermediate language containing id's
(pointers)
 to expressions instead of real sub-expressions.

 Maybe (probably) I am very naive, but I think this trick takes
time
 linear to the amount of sub-expressions in my script. When
using a
 trie instead of a binary tree for the comparisons there should
be no
 more character (or atomic expression) comparisons that the
amount of
 characters in the script.

 So the problem seems not to be CSE algorithm, but the fact
that EDSL
 itself tends to blow up because it is hosted in Haskell. Like
Tom's
 example:

   let d = Add c c
   e = Add d d-- e now as 16 leaf nodes.

 But again, I might be missing some important point here.


That's exactly right. But it's pretty inconvenient to have your
expression tree to blow up exponentially in relation to the code
the
user actually wrote! You can indeed construct an intermediate
language
that collapses this blowup, but the pass to create it must take
exponential time if written completely purely, since it has to
visit
everything at least once.

In my experience [1], observable sharing using GHC's stable
names is a
pretty effective solution to this problem.

Ganesh

[1] http://www.earth.li/~ganesh/research/paradise-icfp08/
http://www.earth.li/%7Eganesh/research/paradise-icfp08/ 



===
 Please access the attached hyperlink for an important
electronic communications disclaimer:
 http://www.credit-suisse.com/legal/en/disclaimer_email_ib.html


===





=== 
 Please access the attached hyperlink for an important electronic 
communications disclaimer: 
 http://www.credit-suisse.com/legal/en/disclaimer_email_ib.html 
 
=== 
 
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Beginner SOS

2009-05-27 Thread Manu Gupta
Dear anyone,I wish to learn HASKELL. However my institution does not teach
it so plus I don't have a clue how to get around with it. Everything seems
so unconventional and out of place

Can you help me out in getting good tutorials that will help me to learn
HASKELL by myself so that I can pursue it as a serious programming languages

Till now I have referred Haskell wiki and have tried everywhere but does not
seem to learn it

PLZ, PLZ HELP ME OUT

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


Re: [Haskell-cafe] Beginner SOS

2009-05-27 Thread Cristiano Paris
On Wed, May 27, 2009 at 7:14 PM, Manu Gupta manugu...@gmail.com wrote:
 Dear anyone,
 I wish to learn HASKELL.

That's good for you.

 However my institution does not teach it so plus
 I don't have a clue how to get around with it. Everything seems so
 unconventional and out of place

I know that feeling...

 Can you help me out in getting good tutorials that will help me to learn
 HASKELL by myself so that I can pursue it as a serious programming languages
 Till now I have referred Haskell wiki and have tried everywhere but does not
 seem to learn it

You're lucky since Real World Haskell is out today. Go get your
printed copy, it's well worth to have it under your pillow. If you
want, you can even read it online (google) but I advise to buy it
anyhow.

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


Re: [Haskell-cafe] Beginner SOS

2009-05-27 Thread Max Rabkin
Hi Manu

Depending on your style, you might prefer Real World Haskell
(available online or in print) or Learn You A Haskell
(http://learnyouahaskell.com/).

Of course, there are others, but my personal preference is for LYAH.

--Max

On Wed, May 27, 2009 at 7:14 PM, Manu Gupta manugu...@gmail.com wrote:
 Dear anyone,
 I wish to learn HASKELL. However my institution does not teach it so plus
 I don't have a clue how to get around with it. Everything seems so
 unconventional and out of place
 Can you help me out in getting good tutorials that will help me to learn
 HASKELL by myself so that I can pursue it as a serious programming languages
 Till now I have referred Haskell wiki and have tried everywhere but does not
 seem to learn it
 PLZ, PLZ HELP ME OUT

 --
 Regards
 MANU


 ___
 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] Facebook puzzles allow for GHC solutions

2009-05-27 Thread David Leimbach
On Wed, May 27, 2009 at 9:34 AM, Mattias Bengtsson 
moonl...@dtek.chalmers.se wrote:

 On Wed, 2009-05-27 at 08:20 -0700, David Leimbach wrote:
  Interesting:
 
 
  http://www.facebook.com/careers/puzzles.php
 
 
  So they use Haskell at Facebook?


 They could very well be having ghc installed on their puzzle test
 server without using it elsewhere.
 They got my attention though. Perhaps i should solve some puzzles
 instead of studying for my exam!


Yes, but people who solve those puzzles go into their hiring processes. :-)
 They at least have the proper respect for a nice list of languages there.

Dave



 ___
 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] Beginner SOS

2009-05-27 Thread Thomas DuBuisson
Manu,
Did you skip over the dozens of links at haskell.org answering exactly
these questions?  There are links to some great tutorials [1] and IRC
information where you can get real-time help [2].  Also there are some
good books [3].

I think most recent learners learned from YAHT [4], Gentle
Introduction [5], and LYAH [6].  I personall read [3]  [4] and
eventually discovered [7], which is well written but last I checked
isn't nearly a complete tutorial.

Thomas

On Wed, May 27, 2009 at 10:35 AM, Max Rabkin max.rab...@gmail.com wrote:
 Hi Manu

 Depending on your style, you might prefer Real World Haskell
 (available online or in print) or Learn You A Haskell
 (http://learnyouahaskell.com/).

 Of course, there are others, but my personal preference is for LYAH.

 --Max

 On Wed, May 27, 2009 at 7:14 PM, Manu Gupta manugu...@gmail.com wrote:
 Dear anyone,
 I wish to learn HASKELL. However my institution does not teach it so plus
 I don't have a clue how to get around with it. Everything seems so
 unconventional and out of place
 Can you help me out in getting good tutorials that will help me to learn
 HASKELL by myself so that I can pursue it as a serious programming languages
 Till now I have referred Haskell wiki and have tried everywhere but does not
 seem to learn it
 PLZ, PLZ HELP ME OUT

 --
 Regards
 MANU


 ___
 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] Facebook puzzles allow for GHC solutions

2009-05-27 Thread Rick R
They are the creators of Thrift which they created for internal use and then
published/open-sourced.. It is a multi-language RPC API/Service. When it
went public, one of the languages interfaces they provided was Haskell. So
yes. They use Haskell somewhere inside Facebook.


On Wed, May 27, 2009 at 11:20 AM, David Leimbach leim...@gmail.com wrote:

 Interesting:
 http://www.facebook.com/careers/puzzles.php

 So they use Haskell at Facebook?

 Dave

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




-- 
The greatest obstacle to discovering the shape of the earth, the
continents, and the oceans was not ignorance but the illusion of knowledge.

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


Re: [Haskell-cafe] Beginner SOS

2009-05-27 Thread Daniel Fischer
Am Mittwoch 27 Mai 2009 19:14:15 schrieb Manu Gupta:
 Dear anyone,I wish to learn HASKELL.

Good :)

 However my institution does not teach it

Bad :(

 so plus I don't have a clue how to get around with it. Everything seems
 so unconventional and out of place

 Can you help me out in getting good tutorials that will help me to learn
 HASKELL by myself so that I can pursue it as a serious programming
 languages

For self-study, I would recommend having at least one textbook available, you 
can find a 
list at http://www.haskell.org/haskellwiki/Books
I found Simon Thompson's Craft of Functional Programming an excellent guide 
into the 
language when I first met Haskell, I'm sure other books will be too.

Apart from a real paper book, I can recommend reading the wikibook at
http://en.wikibooks.org/wiki/Haskell
it's continually work in progress, so much of it is not yet polished, but it 
contains a 
huge amount of cool and useful information.

More tutorials (of different quality) can be found at 
http://www.haskell.org/haskellwiki/Tutorials
, look at some and read those which give the best impression.

And for the questions you will certainly have at some time, there are almost 
always a lot 
of friendly and helpful people on the haskell irc-channel, reading the 
beginn...@haskell.org mailing list (lower traffic than haskell-cafe, so your 
questions 
will be in less danger of being inundated by other messages) and haskell-cafe.


 Till now I have referred Haskell wiki and have tried everywhere but does
 not seem to learn it

 PLZ, PLZ HELP ME OUT

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


[Haskell-cafe] Updating HsJudy to work with the latest Judy

2009-05-27 Thread Robin Green
I would like to use the HsJudy bindings to the Judy high-performance
trie library (on hackage), but unfortunately they have bitrotted. I can
have a go at mending them but I have no experience with FFI. Any tips?

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


[Haskell-cafe] We tried this functional, higher-order stuff with LISP and look what happened...

2009-05-27 Thread Jason Dusek
  What can we say to that? I'm well practiced in handling those
  who reject types outright (Python programmers), those who
  reject what is too different (C programmers), those who can
  not live without objects (Java programmers), those who insist
  we must move everything to message passing (Erlang
  programmers). It's not too often that I meet an embittered
  LISP programmer -- one who's well acquainted with a bold and
  well-supported community of functional programmers whose
  shooting star soon descended to dig a smoking hole in the
  ground.

  Who's to say Haskell (and the more typeful languages in
  general) do not find themselves in the same situation in just
  a few years' time? Is avoiding success at all costs really
  enough?

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


Re: [Haskell-cafe] I love purity, but it's killing me.

2009-05-27 Thread wren ng thornton

Conal Elliott wrote:

Hi Wren,

I considered the idea of hashing, but not *perfect* hashing.  I don't know
how to hash perfectly with something like expressions, which have infinitely
many values.


An imperfect hash can work. You'll need a memo table with a source of 
unique symbols (e.g. storing the next unused integer) in order to, 
effectively, make the hash function perfect[1]. If you have a source 
of unique symbols then you can also use a trie, Data.Map, or similar in 
lieu of a hash map.


In a language with pointers (or stable names), the pointer is often used 
as the hash in conjunction with using the memo table as an intern 
table for smart constructors. Thus, client code can never observe that 
structurally equal expressions could have different hashes.


[1]
hash :: HashState m = Expr - m Hash
hash e = case lookupHS e of
 Just h  - return h
 Nothing - do h - nextH
   insertHS e h
   return h


 Since it's stateful, that means the smart constructors may need to be in an
 appropriate monad/applicative for passing the memo table around (some hash
 functions may not need to store the table explicitly).

Hm -- stateful?  Unless I'm misunderstanding, a stateful 
monadic/applicative approach would break the simple functional interface I'm
going for.  Could well be I haven't formed a mental picture that matches
yours.


Er, it's only stateful for the versions above that use pointers or a 
source of unique symbols (since they need to maintain a memo table). If 
you can come up with a perfect hash function[2], then there's no need to 
create/store the memo table at all, since it can be reconstructed on the 
fly. Since perfect hashing often isn't feasible, the stateful 
approximations to a perfect hash function are generally used. Sorry if I 
was unclear.


If you don't mind unsafePerformIO (or similar hacks) then you can hide 
the state from the type system by using the same table for the whole 
program. Generally for hash cons'ing you want your tables to be as large 
as they can be (to maximize sharing) so this shouldn't be problematic. 
However, for languages with scoping it can be beneficial to use separate 
tables to recognize when expressions need to be recomputed; so the 
global store might want to be something like a stack of memo tables with 
fall-through lookup.


I believe Applicative is powerful enough to capture the sort of state 
passing needed since the client code can't ever make decisions based on 
the state. So with smart constructors (to package up the * etc) I'd 
think you should be able to have an EDSL that looks nice, just with a 
more complicated type. Perhaps the issues are with mixing pure Haskell 
functions into the EDSL?


...

The real trick behind hash cons'ing is everywhere substituting the 
hash in for the sub-expression, effectively flattening all expressions 
into a single ply. Thus, expression constructors cons the hashes 
rather than cons'ing expressions. It's similar in spirit to trie'ing, 
but from the bottom up in the same way that dynamic programming is done.


The reason for wanting to do the hashing in smart constructors, as 
opposed to at the end, is to maximize the benefit of dynamic 
programming. If all client-visible expressions are represented by 
hashes, then any structure sharing in the Haskell layer is sharing the 
hash representation, thus you don't need to traverse the shared 
substructure multiple times. (If you hand construct equal expressions 
without sharing, then you'll have to traverse each expression to prove 
that they're equal, but you can use that proof (the hashes) 
thenceforth). For host languages with destructive updates (like 
Smalltalk's become), you can rewrite the subterms as you traverse 
them, so doing it at the end isn't too bad.


If you only expose smart constructors then your Expr type can recurse 
as whatever Hash type. If you do the hashing at the end, then you'll 
need to define a catamorphism on Expr.


...

This is probably similar to what you're doing in Pan, Vertigo, and 
Pajama (I haven't read it). The general technique is elegant in its 
simplicity, and it's not uncommon. Though, like most dynamic programming 
tricks, it seems not to be as widely known as I would assume, so I 
thought I'd mention it in case you've missed it.




[2] Into any domain of terms that can quickly answer (==), namely flat 
terms like Integer. Using a bounded type like Int can give better 
performance guarantees, but there's only so many of them.


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


Re: [Haskell-cafe] Stack overflow

2009-05-27 Thread Bertram Felgenhauer
Krzysztof Skrzętnicki wrote:
 The code for modifying the counter:
 (\ msg - atomicModifyIORef ioref (\ cnt - (cntMsg cnt msg,(

atomicModifyIORef does not force the new value of the IORef.
If the previous contents of the IORef is x, the new contents
will be a thunk,

   (\ cnt - (cntMsg cnt msg,())) x

You can try forcing the new value, say by adding

readIORef ioref = (return $!)

after the atomicModifyIORef.

 The datatype itself is strict. So where is the thunk actually accumulating?

In the IORef.

HTH,

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


Re: [Haskell-cafe] Updating HsJudy to work with the latest Judy

2009-05-27 Thread Bryan O'Sullivan
On Wed, May 27, 2009 at 11:02 AM, Robin Green gree...@greenrd.org wrote:

 I would like to use the HsJudy bindings to the Judy high-performance
 trie library (on hackage), but unfortunately they have bitrotted. I can
 have a go at mending them but I have no experience with FFI. Any tips?


Just dive in. The FFI is extremely easy to use.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Facebook puzzles allow for GHC solutions

2009-05-27 Thread Bulat Ziganshin
Hello David,

Wednesday, May 27, 2009, 7:20:33 PM, you wrote:

 Interesting:
 http://www.facebook.com/careers/puzzles.php

 So they use Haskell at Facebook?

actually, of 5 compiled languages there, 3 are FP, and only 2
remaining are the most popular languages on planet - C++ and Java

so this list shows their huge respect to FP

-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re: [Haskell-cafe] Stack overflow

2009-05-27 Thread Bertram Felgenhauer
I wrote:
 Krzysztof Skrzętnicki wrote:
 The code for modifying the counter:
 (\ msg - atomicModifyIORef ioref (\ cnt - (cntMsg cnt msg,(

 atomicModifyIORef does not force the new value of the IORef.
 If the previous contents of the IORef is x, the new contents
 will be a thunk,

   (\ cnt - (cntMsg cnt msg,())) x

Sorry, it's slightly worse than that. The contents becomes

sel_0 (\ cnt - (cntMsg cnt msg, ())) x

where sel_0 is basically an RTS internal version of fst.

Instead of reading the new value of the IORef, you could also force the
old one:

atomicModifyIORef ioref (\ cnt - (cntMsg cnt msg, msg)) = (return $!)

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


Re: [Haskell-cafe] Stack overflow

2009-05-27 Thread Krzysztof Skrzętnicki
2009/5/27 Bertram Felgenhauer bertram.felgenha...@googlemail.com:
 I wrote:
 Krzysztof Skrzętnicki wrote:
 The code for modifying the counter:
 (\ msg - atomicModifyIORef ioref (\ cnt - (cntMsg cnt msg,(

 atomicModifyIORef does not force the new value of the IORef.
 If the previous contents of the IORef is x, the new contents
 will be a thunk,

   (\ cnt - (cntMsg cnt msg,())) x

 Sorry, it's slightly worse than that. The contents becomes

    sel_0 (\ cnt - (cntMsg cnt msg, ())) x

 where sel_0 is basically an RTS internal version of fst.

 Instead of reading the new value of the IORef, you could also force the
 old one:

    atomicModifyIORef ioref (\ cnt - (cntMsg cnt msg, msg)) = (return $!)


Thanks for the tip, although it seems tricky to get it right. I wonder
why there is no strict version of atomicModifyIORef?
Dually there might be a strict version of IORef datatype.

Best regards

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


RE: [Haskell-cafe] Template Haskell very wordy w/r/t Decs and Types

2009-05-27 Thread Simon Peyton-Jones
Folks

Quite a few people have asked for splices in Template Haskell *types*, and I 
have finally gotten around to implementing them.  So now you can write things 
like

instance Binary $(blah blah) where ...
or  f :: $(wubble bubble) - Int

as requested, for example, in the message below.  Give it a whirl.  You need 
the HEAD; in a day or two you should find binary snapshots if you don't want to 
build from source.

Simon

PS: Note that you (still) cannot write a splice in a *binding* position. Thus 
you can't write
f $(blah blah) = e
or
data T $(blah blah) = MkT Int

I don't intend to change this; see the commentary at 
http://hackage.haskell.org/trac/ghc/ticket/1476

| -Original Message-
| From: haskell-cafe-boun...@haskell.org 
[mailto:haskell-cafe-boun...@haskell.org] On
| Behalf Of Ross Mellgren
| Sent: 25 January 2009 19:55
| To: Haskell Cafe
| Subject: [Haskell-cafe] Template Haskell very wordy w/r/t Decs and Types
|
| Hi all,
|
| I'm writing a small module that exposes a template haskell splice that
| takes a (very simplified) C struct definition and builds:
|
|   - A data type definition,
|   - an instance for Data.Binary.Binary,
|   - and optionally a pretty print function for it
|
| However, it seems to do this I have to write a bunch of really ugly
| code that builds up the TH data structures by hand because quoting
| only works with splices for expressions, or so it seems.
|
| For example, to generate the binary instance I have this code:
|
| import qualified Language.Haskell.TH as TH
|
| -- tyname is the name of the data type I've already created, as a
| TH.Name
| -- tempnames is a list of temporary variable names that are used in
| lambda patterns
| -- fields is a list of tuples describing each field
| -- makeGetExp recursively builds a monadic computation consisting
| mostly of Binary.getWord32be = \ tempvar - ...
|
|  binaryInstDec - liftM (TH.InstanceD [] (TH.AppT (TH.ConT $
| TH.mkName Data.Binary.Binary) (TH.ConT tyname)))
| [d| get = $(makeGetExp (reverse $ zip
| fields tempnames) returnExp)
| put = undefined |]
|
| I'd really rather write:
|
|  binaryInstDec - [d|
|  instance Binary.Binary $(tyname) where
|  get = $(makeGetExp (reverse $ zip fields tempnames)
| returnExp)
|  put = undefined |]
|
| But GHC gives me a syntax error on the tyname splice. The docs seem to
| indicate this is the way it is -- that splices in type locations is
| plain not implemented.
|
| My question is whether or not this is just the way it is, and people
| writing TH declaration splices tend to have to start manually
| assembling a bunch of it, or is there some trick I've missed? Perhaps
| even better are there some tricks that people tend to use to make this
| less painful?
|
| I did try using some of the lowercased monadic constructors in
| Language.Haskell.TH.Lib but I didn't seem to get anything more succint
| out of it.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Strange type error with associated type synonyms

2009-05-27 Thread Simon Peyton-Jones
Claus made a suggestion about type error messages:

| Apart from bracketing fully applied type synonyms, the error message
| could be improved by providing the missing bit of information about
| 'Memo':
|
| D:\home\Haskell\tmp\desktop\types.hs:11:11:
| Couldn't match expected type `Memo d1'
|against inferred type `Memo d'
| (type Memo d :: * - *)
| In the second argument of `(.)', namely `appl'
| In the expression: abst . appl
| In the definition of `f': f = abst . appl

I've implemented this idea; note the NB line below:

NoMatchErr.hs:20:11:
Couldn't match expected type `Memo d'
   against inferred type `Memo d1'
  NB: `Memo' is a (non-injective) type function
In the second argument of `(.)', namely `appl'
In the expression: abst . appl
In the definition of `f': f = abst . appl

(Rather than give its kind, I thought it was better to focus on the reason for 
the mis-match, namely the non-injectivity.)

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


Re: [Haskell-cafe] trying to understand space leaks....

2009-05-27 Thread Daryoush Mehrtash
So long as the [s] is a fixed list (say [1,2,3,4]) there is no space
leak.My understanding was that the space leak only happens if there is
computation involved in building the list of s.  Am I correct?

If so, I still don't have any feeling for what needs to be saved on the heap
to be able to back track on computation that needs and  IO computation
data.What would be approximate  space that an IO (Char) computation
take  on the heap, is it few bytes, 100, 1k,  ?

Daryoush


On Tue, May 26, 2009 at 6:11 PM, Ryan Ingram ryani.s...@gmail.com wrote:

 On Tue, May 26, 2009 at 5:03 PM, Daryoush Mehrtash dmehrt...@gmail.com
 wrote:
  newtype Parser s a = P( [s] - Maybe (a, [s]))
 (fixed typo)

  instance MonadPlus  Parser where
P a mplus P b = P (\s - case a s of
  Just (x, s') - Just (x, s')
  Nothing - b s)

  a)what exactly gets saved on the heap between the mplus calls?

 Two things:

 (1) Values in the input stream that a parses before failing.
 Beforehand, it might just be a thunk that generates the list lazily in
 some fashion.

 (2) The state of the closure b; if parser a fails, we need to be
 able to run b; that could use an arbitrary amount of space depending
 on what data it keeps alive.

  b)I am assuming the computation to get the next character for parsing to
 be
  an IO Char type computation,  in that case, what would be the size of
 the
  heap buffer that is kept around in case the computation result needs to
 be
  reused?

 Nope, no IO involved; just look at the types:

 P :: ([s] - Maybe (a,[s])) - Parser s a

 (Parser s a) is just a function that takes a list of s, and possibly
 returns a value of type a and another list [s] (of the remaining
 tokens, one hopes)

 It's up to the caller of the parsing function to provide the token
 stream [s] somehow.

  c) Assuming Pa in the above code reads n tokens from the input stream
 then
  fails, how does the run time returns the same token to the P b?

 It just passes the same stream to both.  No mutability means no danger :)

  -- ryan

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


Re: [Haskell-cafe] Template Haskell very wordy w/r/t Decs and Types

2009-05-27 Thread Miguel Mitrofanov


On 27 May 2009, at 23:38, Simon Peyton-Jones wrote:


Folks

Quite a few people have asked for splices in Template Haskell  
*types*, and I have finally gotten around to implementing them.  So  
now you can write things like


   instance Binary $(blah blah) where ...
or  f :: $(wubble bubble) - Int


Great! Just what I was looking for a couple of days ago.

PS: Note that you (still) cannot write a splice in a *binding*  
position.


I think, I can live without it.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Strange type error with associated type synonyms

2009-05-27 Thread Sittampalam, Ganesh
Simon Peyton-Jones wrote:

 NoMatchErr.hs:20:11:
 Couldn't match expected type `Memo d'
against inferred type `Memo d1'
   NB: `Memo' is a (non-injective) type function
 In the second argument of `(.)', namely `appl'
 In the expression: abst . appl
 In the definition of `f': f = abst . appl
 
 (Rather than give its kind, I thought it was better to focus on the
 reason for the mis-match, namely the non-injectivity.) 

I'd suggest is a type function and thus may not be injective or
similar, otherwise people will think that type functions which are
injective according to the instances they've defined would be ok.

Cheers,

Ganesh

=== 
 Please access the attached hyperlink for an important electronic 
communications disclaimer: 
 http://www.credit-suisse.com/legal/en/disclaimer_email_ib.html 
 
=== 
 
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re[2]: [Haskell-cafe] Strange type error with associated type synonyms

2009-05-27 Thread Bulat Ziganshin
Hello Simon,

Wednesday, May 27, 2009, 11:42:22 PM, you wrote:

while we are here - i always had problems understanding what is
inferred and what is expected type. may be problem is just that i'm
not native speaker

are other, especially beginners, had the same problem?

 Claus made a suggestion about type error messages:

 | Apart from bracketing fully applied type synonyms, the error message
 | could be improved by providing the missing bit of information about
 | 'Memo':
 |
 | D:\home\Haskell\tmp\desktop\types.hs:11:11:
 | Couldn't match expected type `Memo d1'
 |against inferred type `Memo d'
 | (type Memo d :: * - *)
 | In the second argument of `(.)', namely `appl'
 | In the expression: abst . appl
 | In the definition of `f': f = abst . appl

 I've implemented this idea; note the NB line below:

 NoMatchErr.hs:20:11:
 Couldn't match expected type `Memo d'
against inferred type `Memo d1'
   NB: `Memo' is a (non-injective) type function
 In the second argument of `(.)', namely `appl'
 In the expression: abst . appl
 In the definition of `f': f = abst . appl

 (Rather than give its kind, I thought it was better to focus on the
 reason for the mis-match, namely the non-injectivity.)

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



-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re: [Haskell-cafe] About the lazy pattern

2009-05-27 Thread Bulat Ziganshin
Hello 张旭,

Wednesday, May 27, 2009, 11:51:34 PM, you wrote:

 Hi, I am really new to haskell. I am reading A gentle instruction
 to haskell now. And I just cannot understand the chapter below. Is
 there anybody who can gives me some hints about why the pattern
 matching for client is so early?

because it assumes that there are may be *multiple* lines defining
client and therefore to start executing right part of equation it
should ensure that left side is correct. with lazy patterns, you
effectively disable multi-equation definitions:

length ~(x:xs) = 1+length xs
length [] = 0  -- this line never used!

lazy patter is exactly equivalent to using one variable and `let` to
further parse data:

length xxs = let x:xs=xxs in 1+length xs


 How does the pattern matching works here?
  Thank you so much for answering my questions!
  ?
  Sincerely, 
  nemo
  
 4.4??Lazy Patterns
  There is one other kind of pattern allowed in Haskell. It is
 called a lazy pattern, and has the form ~pat. Lazy patterns are
 irrefutable: matching a value v against ~pat always succeeds,
 regardless of pat. Operationally speaking, if an identifier in pat
 is later used on the right-hand-side, it will be bound to that
 portion of the value that would result if v were to successfully match pat, 
 and _|_ otherwise.
 Lazy patterns are useful in contexts where infinite data structures
 are being defined recursively. For example, infinite lists are an
 excellent vehicle for writing simulation programs, and in this
 context the infinite lists are often called streams. Consider the
 simple case of simulating the interactions between a server process
 server and a client process client, where client sends a sequence of
 requests to server, and server replies to each request with some
 kind of response. This situation is shown pictorially in Figure 2.
 (Note that client also takes an initial message as argument.)  
   
 Figure 2
 Using streams to simulate the message sequences, the Haskell code
 corresponding to this diagram is: 

 reqs?=?client?init?resps
 resps=?server?reqs

 These recursive equations are a direct lexical transliteration of the diagram.
 Let us further assume that the structure of the server and client look 
 something like this:

 client?init?(resp:resps)?=?init?:?client?(next?resp)?resps
 server??(req:reqs)???=?process?req?:?server?reqs

 where we assume that next is a function that, given a response from
 the server, determines the next request, and process is a function
 that processes a request from the client, returning an appropriate response.
 Unfortunately, this program has a serious problem: it will not
 produce any output! The problem is that client, as used in the
 recursive setting of reqs and resps, attempts a match on the
 response list before it has submitted its first request! In other
 words, the pattern matching is being done too early. One way to
 fix this is to redefine client as follows: 

 client?init?resps?=?init?:?client?(next?(head?resps))?(tail resps)

 Although workable, this solution does not read as well as that
 given earlier. A better solution is to use a lazy pattern: 

 client?init?~(resp:resps)?=?init?:?client?(next?resp)?resps

 Because lazy pat  terns are irrefutable, the match will immediately
 succeed, allowing the initial request to be submitted, in turn
 allowing the first response to be generated; the engine is now
 primed, and the recursion takes care of the rest.
  ?


 使用新一代 Windows Live Messenger 轻松交流和共享! 立刻下载!
   


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re: Re[2]: [Haskell-cafe] Strange type error with associated type synonyms

2009-05-27 Thread Max Rabkin
On Wed, May 27, 2009 at 9:59 PM, Bulat Ziganshin
bulat.zigans...@gmail.com wrote:
 Hello Simon,

 Wednesday, May 27, 2009, 11:42:22 PM, you wrote:

 while we are here - i always had problems understanding what is
 inferred and what is expected type. may be problem is just that i'm
 not native speaker

 are other, especially beginners, had the same problem?

The inferred type of e is the type that the compiler thinks e has. The
expected type is the type it *should* have, given its context.

Consider:

f :: Int - Int

then the expression (f True) has a type error:

Couldn't match expected type `Int' against inferred type `Bool'
In the first argument of `f', namely `True'

GHC is saying the first argument of f *should* be an Int, but it seems
to be a Bool.

As to whether it's confusing, I sometimes have to read these messages
a few times (sometimes it's unclear which expression is being referred
to, or why GHC thinks that the expression has a certain type), but the
words themselves are clear in their meaning to me.

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


Re: [Haskell-cafe] We tried this functional, higher-order stuff with LISP and look what happened...

2009-05-27 Thread Tord Romstad
Hi all,

Time to delurk. I'm a Lisper and mathematician who has been reading
this group for about a year, but I haven't posted until now.

On Wed, May 27, 2009 at 8:31 PM, Jason Dusek jason.du...@gmail.com wrote:
  What can we say to that? I'm well practiced in handling those
  who reject types outright (Python programmers), those who
  reject what is too different (C programmers), those who can
  not live without objects (Java programmers), those who insist
  we must move everything to message passing (Erlang
  programmers). It's not too often that I meet an embittered
  LISP programmer -- one who's well acquainted with a bold and
  well-supported community of functional programmers whose
  shooting star soon descended to dig a smoking hole in the
  ground.

I think you rarely meet embittered Lisp programmers simply because we
Lispers are rarely embittered, but are still Lisping happily, and don't
feel that the picture of a shooting start descending to dig a smoking
hole in the ground is an accurate representation of reality.  :-)

  Who's to say Haskell (and the more typeful languages in
  general) do not find themselves in the same situation in just
  a few years' time? Is avoiding success at all costs really
  enough?

That's funny, because from my perspective the situation looks
diametrically opposite. Haskell is an awesome language, and I
would love to use it, but the community seems so small, and I've never
seen a Haskell job. Lisp, on the other hand, has a thriving community,
several high-quality implementations for all major platforms, and
pays my bills.

My impression has always been that Haskell, unlike Lisp, is little
more than a marginal research language which is only used in
academia and by a few enthusiastic hobbyists. Am I just hanging
around with the wrong people? I hope I am: I would love to have
a Haskell job some day.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re[4]: [Haskell-cafe] Strange type error with associated type synonyms

2009-05-27 Thread Bulat Ziganshin
Hello Max,

Thursday, May 28, 2009, 12:14:50 AM, you wrote:

 As to whether it's confusing, I sometimes have to read these messages
 a few times (sometimes it's unclear which expression is being referred
 to, or why GHC thinks that the expression has a certain type), but the
 words themselves are clear in their meaning to me.

can you recall early times of your work with GHC? i think that these
words are non-obvious for novices. finally it becomes part of your instincts
as anything else often used. but it can be learning barrier. overall,
hard-to-understand error messages was elected as one of 3 most
important GHC problems in the survey conducted several years ago

-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re: [Haskell-cafe] Updating HsJudy to work with the latest Judy

2009-05-27 Thread Don Stewart
bos:
 On Wed, May 27, 2009 at 11:02 AM, Robin Green gree...@greenrd.org wrote:
 
 I would like to use the HsJudy bindings to the Judy high-performance
 trie library (on hackage), but unfortunately they have bitrotted. I can
 have a go at mending them but I have no experience with FFI. Any tips?
 
 
 Just dive in. The FFI is extremely easy to use.


I tweaked them recently for a benchmark, and it took about 5 minutes to
get working. I'll dig up the patches tonight.

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


[Haskell-cafe] platform/cabal problems

2009-05-27 Thread Johannes Waldmann
Hi all.

I've written some Haskell program,
and I wanted to give it to a friend, in source form,
so he can run and modify it, and learn some Haskell
while doing so. I was using some cabalized extra packages
but hey, this looks like the typical use case for the haskell-platform.
So: I told him to install the newest stable ghc
and the current platform release and this happens:

la:/home/b/appl.linux/haskell-platform-2009.2.0# ./configure
...
checking for hsc2hs... /usr/local/bin/hsc2hs
checking version of ghc... 6.10.3
checking version of ghc-pkg matches... yes
checking ghc actually works... yes
checking the ghc core packages are all installed... no
configure: error: The core package editline-0.2.1.0 is missing.
  It should have been distributed with 6.10.2
  

Well, editline is available from hackage,
but to access it, one needs cabal,
which is included in the platform,
which cannot be built, because, see above.

Yes, I know a handfull of workarounds - but they all
require some previous knowledge, experience, and/or extra time.
Really, if the platform fails in this very simple setting
(a fresh install with current stable releases)
then it is not much help in advertising Haskell.

What's the particular reason for the failure?
editline was distributed with ghc-6.10.2, but not with 6.10.3?
I wouldn't expect an incompatible change
when (only) the patchlevel is bumped.

The platform web site should probably replace
works with ghc-6.10.x by works with ghc-6.10.2 only.

Best regards, Johannes.




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


Re: Re[4]: [Haskell-cafe] Strange type error with associated type synonyms

2009-05-27 Thread Max Rabkin
On Wed, May 27, 2009 at 10:28 PM, Bulat Ziganshin
bulat.zigans...@gmail.com wrote:
 can you recall early times of your work with GHC? i think that these
 words are non-obvious for novices. finally it becomes part of your instincts
 as anything else often used. but it can be learning barrier. overall,
 hard-to-understand error messages was elected as one of 3 most
 important GHC problems in the survey conducted several years ago

I don't remember having any trouble, but that was a few years ago, and
type errors are confusing generally. I think that the main difficulty
with type errors is not the error *messages*, but I'm sure there is
room for improvement.

Do you have any ideas?

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


[Haskell-cafe] Who takes care of Haskell mailing lists?

2009-05-27 Thread Maurício
Hi,

I would like to create a mailing list for Portuguese speaking
Haskell programmers. I tried checking haskell.org mailing lists
page, but the only contact e-mail I see is 'mail...@haskell.org',
and a message sent to that address is replied with an automatic
message saying I'm not authorized to use it.

Is there someone I could contact about that?

Thanks,
Maurício

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


Re: [Haskell-cafe] Introducing Instances in GHC point releases

2009-05-27 Thread Henning Thielemann


On Sun, 24 May 2009, Ketil Malde wrote:


Duncan Coutts duncan.cou...@worc.ox.ac.uk writes:


The PVP says:



 1. If any entity was removed, or the types of any entities
or the definitions of datatypes or classes were changed,
or instances were added or removed, then the new A.B
must be greater than the previous A.B.


When I read this point the first time, I was fine with this convention. 
But the more hassle I had with orphan instances I came to the conclusion 
that they are bad enough that they should be treated like unqualified 
anonymous imports. I mean, version policy warrants that I can import a 
module of any package version of type A.B.* when I use exclusively 
qualified imports or explicit unqualified imports. Instances are always 
imported whenever you touch a module, you cannot exclude them. Thus they 
behave like anonymous imports - you cannot control what exactly is 
imported. Version policy does not support anonymous unqualified imports 
because it does not make any warranties if you import this way.


What about orphan instances? If a module misses an instance that belongs 
to one of its types or its classes then it may be added by any other 
module in any other package. If that is done then those orphan instances 
are likely to clash sooner or later. The version policy should warrant 
that within the A.B.* version range I'm safe to import a module the 
qualified or explicitly unqualified way. But since orphan instances can 
get in the way, we don't have this warranty! Say I import packages 
foo-1.2.3 and bar-4.5.6, where foo exports orphan instance C T and bar 
does not import such an instance. I see that it works and think this will 
continue to work as long as I restrict to foo =1.2.3  1.3 and bar = 
4.5.6  4.6. Now, the new version bar-4.5.7 starts to import package 
hmpf-8.9.0, which provides another orphan instance C T. It is allowed to 
depend on new packages in such a version bump, right? Now, my package can 
no longer be compiled, because 'bar' re-exports the orphan instance from 
'hmpf'.


My proposal is thus: Discourage orphan instances! If you encounter that an 
instance is missing and it is a canonical one, it should be added to the 
package that defines the type or the class. If there are several choices 
for the implementation then the package where the instance would belong to 
should document that. Then programmers should find a consensus which of 
the choices they prefer. If you cannot wait for an official adaption of 
the required instance, then you must work with newtype wrappers.


There are cases where you must define an orphan instance. Then this should 
instance should go into a new package by consensus between the maintainer 
of the class and the maintainer of the type.


However, when orphan instances are banned, then it would also be no 
problem to add instances to their home modules within the A.B.* range. So 
I vote for allowing this, too.

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


Re[6]: [Haskell-cafe] Strange type error with associated type synonyms

2009-05-27 Thread Bulat Ziganshin
Hello Max,

Thursday, May 28, 2009, 12:49:20 AM, you wrote:

 I don't remember having any trouble, but that was a few years ago, and
 type errors are confusing generally. I think that the main difficulty
 with type errors is not the error *messages*, but I'm sure there is
 room for improvement.

 Do you have any ideas?

i mean just changing the words to make obvious what type was got in
what way. and check it on beginners who don't yet read your
explanations, for example teachers may test it on their students

my English is limited... for example, it may be like this:

read x

Error: type of x is Integer
 while type of read argument should be String


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


[Haskell-cafe] Type class context propagation investigation

2009-05-27 Thread Paul Keir
Hi,

How does the context of a class instance declaration affect its subclasses?

The Num class instance outlined below has its requirement for Eq and Show 
satisfied on the preceding lines, and the code will compile. But if I, say, add 
an (Eq a) constraint to the Eq instance, in preparation for a simple (==) 
definition, I find that the Num instance declaration is left lacking. If I add 
the same (Eq a) constraint now to Num, calm is restored.

data Foo a = F a

instance Eq (Foo a) where
 (==) = undefined

instance Show (Foo a) where
 show = undefined

instance Num (Foo a)
 (+) = undefined
 ... etc.

The thing that confuses me with this is that it seems like Num knows that an 
(Eq a) context has been applied, and so what it sees as a problem, is somehow 
also the solution. Any advice/rules of thumb? Does this situation occur 
elsewhere? How do these constraints propagate?

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


Re: [Haskell-cafe] Design in Haskell?

2009-05-27 Thread Henning Thielemann
Dan schrieb:
 Hi,
 
 When I was learning to program in imperative languages like Java, there
 were plenty of resources to learn from about how to design large
 programs.   Ideas like the GoF Design Patterns gave useful models that
 one could then scale up.

You will also find remarks on good practice in
   http://www.haskell.org/haskellwiki/Category:Style

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


Re: [Haskell-cafe] Beginner SOS

2009-05-27 Thread Brent Yorgey
On Wed, May 27, 2009 at 10:39:20AM -0700, Thomas DuBuisson wrote:
 Manu,
 Did you skip over the dozens of links at haskell.org answering exactly
 these questions?  There are links to some great tutorials [1] and IRC
 information where you can get real-time help [2].  Also there are some
 good books [3].
 
 I think most recent learners learned from YAHT [4], Gentle
 Introduction [5], and LYAH [6].  I personall read [3]  [4] and
 eventually discovered [7], which is well written but last I checked
 isn't nearly a complete tutorial.
 
 Thomas

Did you forget the actual URLs?

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


Re: [Haskell-cafe] Facebook puzzles allow for GHC solutions

2009-05-27 Thread Gaius Hammond


On 27 May 2009, at 19:45, Bulat Ziganshin wrote:


actually, of 5 compiled languages there, 3 are FP, and only 2
remaining are the most popular languages on planet - C++ and Java

so this list shows their huge respect to FP




It is well known that Facebook are heavy Erlang users.


http://www.facebook.com/note.php?note_id=51412338919


They haven't made public AFAIK what they're using Haskell for.


Cheers,



G


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


Re: [Haskell-cafe] Lazy Parsing

2009-05-27 Thread Henning Thielemann


On Wed, 27 May 2009, Gü?nther Schmidt wrote:

is it possible to do lazy parsing with Parsec? I understand that one can do 
that with polyparse, don't know about uulib, but I happen to be already 
somewhat familiar with Parsec, so before I do switch to polyparse I rather 
make sure I actually have to.


Also see
  http://www.haskell.org/haskellwiki/Maintaining_laziness___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] cabal option to specify the ghc version?

2009-05-27 Thread Johannes Waldmann
Hi. How can I tell cabal (= the executable from cabal-install)
to use a specific ghc version (and not the one that's
currently linked to ghc)? - Thanks, J.W.



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


[Haskell-cafe] Error message reform (was: Strange type error with associated type synonyms)

2009-05-27 Thread Max Rabkin
On Wed, May 27, 2009 at 11:05 PM, Bulat Ziganshin
bulat.zigans...@gmail.com wrote:
 i mean just changing the words to make obvious what type was got in
 what way. and check it on beginners who don't yet read your
 explanations, for example teachers may test it on their students

 my English is limited... for example, it may be like this:

 read x

 Error: type of x is Integer
  while type of read argument should be String

For me, this word order is an improvement, but it doesn't help to
leave out the words expected and inferred. To me, those words add
explanation. Of course they don't help if you don't know what they
mean. I think they add something because they explains where the types
came from.

When I get type errors, I often think why do you say True has type
Bool (of course in most cases it is not so transparent). Although the
compiler doesn't say *why* it inferred that type, at least it says it
did infer it.

I prefer this wording:

The inferred type of `True' is `Bool',
while the type of the first argument of `f' should be `Int'.
In the expression: f True

I prefer all three to Hugs's

ERROR - Type error in application
*** Expression : f True
*** Term   : True
*** Type   : Bool
*** Does not match : Int

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


[Haskell-cafe] Re: Strange type error with associated type synonyms

2009-05-27 Thread Achim Schneider
Bulat Ziganshin bulat.zigans...@gmail.com wrote:

 while we are here - i always had problems understanding what is
 inferred and what is expected type. may be problem is just that i'm
 not native speaker

The shape of the brick you are trying to push through a hole is
analysed (inferred) by the universe from the brick's overall
properties, while the hole certainly can be said to expect a certain
shape of block.

The actual universe might very well do pixel-based collision, not
something as elaborate as what I described, though. YMMV.

-- 
(c) this sig last receiving data processing entity. Inspect headers
for copyright history. All rights reserved. Copying, hiring, renting,
performance and/or quoting of this signature prohibited.


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


Re: [Haskell-cafe] cabal option to specify the ghc version?

2009-05-27 Thread David Menendez
On Wed, May 27, 2009 at 5:25 PM, Johannes Waldmann
waldm...@imn.htwk-leipzig.de wrote:
 Hi. How can I tell cabal (= the executable from cabal-install)
 to use a specific ghc version (and not the one that's
 currently linked to ghc)? - Thanks, J.W.

According to 
http://haskell.org/haskellwiki/Cabal/How_to_install_a_Cabal_package,
you would use the --with-compiler option.

-- 
Dave Menendez d...@zednenem.com
http://www.eyrie.org/~zednenem/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Strange type error with associated type synonyms

2009-05-27 Thread Achim Schneider
Bulat Ziganshin bulat.zigans...@gmail.com wrote:

 Error: type of x is Integer
  while type of read argument should be String
 
The problem with this is that the compiler can't know whether or not
the type of arguments to read should be a String, as someone could
have messed up read's signature. Granted, you have to have a knack for
semantic bickering to not just glance over the imprecision. 


-- 
(c) this sig last receiving data processing entity. Inspect headers
for copyright history. All rights reserved. Copying, hiring, renting,
performance and/or quoting of this signature prohibited.


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


[Haskell-cafe] Re: Error message reform (was: Strange type error with associated type synonyms)

2009-05-27 Thread Bulat Ziganshin
Hello Max,

Thursday, May 28, 2009, 1:30:28 AM, you wrote:

 I prefer this wording:

 The inferred type of `True' is `Bool',
 while the type of the first argument of `f' should be `Int'.
 In the expression: f True

yes, it's also self-explanatory


 I prefer all three to Hugs's

 ERROR - Type error in application
 *** Expression : f True
 *** Term   : True
 *** Type   : Bool
 *** Does not match : Int

for me, it was better than ghc errmsg. main thing is that i don't feel
automatically what is expected and what is inferred. here Hugs says
that True is Bool and the remaining is Int, so i feel the situation

overall, this expected/inferred words are probably go directly from
compiler algorithms. it looks natural for compiler developer - saying
that some term has different types evaluated by two different compiler
parts. but for me as a user it's natural to think in terms of function
having parameter of some type and term having another type, so i need
to fix the call giving it the right parameter:

 The type of the first argument of `f' should be `Int',
 while the inferred type of `True' is `Bool'.
 In the expression: f True


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re: [Haskell-cafe] Re: Strange type error with associated type synonyms

2009-05-27 Thread Bulat Ziganshin
Hello Achim,

Thursday, May 28, 2009, 1:34:55 AM, you wrote:

 Error: type of x is Integer
  while type of read argument should be String
 
 The problem with this is that the compiler can't know whether or not
 the type of arguments to read should be a String, as someone could
 have messed up read's signature.

i don't understood what you mean, can you give an example?

 Granted, you have to have a knack for
 semantic bickering to not just glance over the imprecision. 

yes, that's the part of problem - haskell is high-order language and
in general we have complex term applied to another complex term. but
in practice most times these terms are simple

at least, something like Type of this term SHOULD BE Bool, while
actually it's Int looks more understandable for me than
expected/inferred pair



-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re: [Haskell-cafe] Re: Error message reform (was: Strange type error with associated type synonyms)

2009-05-27 Thread Jeff Wheeler
On Thu, 2009-05-28 at 01:45 +0400, Bulat Ziganshin wrote:

 for me, it was better than ghc errmsg. main thing is that i don't feel
 automatically what is expected and what is inferred. here Hugs says
 that True is Bool and the remaining is Int, so i feel the situation

I absolutely agree about expected/inferred. I always forget which is
which, because I can figure both could apply to each.

Say, in this simple example:

 Prelude let f = (+5)
 Prelude f abc
 
 interactive:1:2:
 Couldn't match expected type `Integer'
against inferred type `[Char]'
 In the first argument of `f', namely `abc'
 In the expression: f abc
 In the definition of `it': it = f abc

Does expected mean that, based on the type signature, it should be an
Integer, or based on the argument that I provided, it should be a
String? The same goes for the inferred type: it knows what the type of
the literal argument (String), so I would assume the inferred type was
the type in the function's signature. Unfortunately, my reasoning in
both cases can go the wrong way . . .

Better language may be much more helpful, although I'm not sure what may
be easier to interpret.

Jeff Wheeler

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


Re[6]: [Haskell-cafe] Strange type error with associated type synonyms

2009-05-27 Thread Henning Thielemann


On Thu, 28 May 2009, Bulat Ziganshin wrote:


read x

Error: type of x is Integer
while type of read argument should be String


I also have my problems with inferred/expected and find your suggested 
message easier to understand in this case. But can it be generalized? I 
think that inferred and expected are quite arbitrary terms for the 
user, since he does not know, what GHC first believed to know for sure.


Prelude let a = 'a'; b = b in a==b

interactive:1:27:
Couldn't match expected type `Char' against inferred type `[Char]'


Is the type of 'a' wrong or that of 'b'? The compiler cannot know. It can 
only state that the types mismatch. The order in which it infers is not 
obvious for the user.

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


Re: [Haskell-cafe] cabal option to specify the ghc version?

2009-05-27 Thread Henning Thielemann


On Wed, 27 May 2009, Johannes Waldmann wrote:


Hi. How can I tell cabal (= the executable from cabal-install)
to use a specific ghc version (and not the one that's
currently linked to ghc)? - Thanks, J.W.


cabal install --with-compiler=/usr/local/lib/ghc-6.4.2/whatknowi
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Beginner SOS

2009-05-27 Thread Thomas DuBuisson
  There are links to some great tutorials [1] and IRC
 information where you can get real-time help [2].  Also there are some
 good books [3].

 I think most recent learners learned from YAHT [4], Gentle
 Introduction [5], and LYAH [6].  I personall read [3]  [4] and
 eventually discovered [7], which is well written but last I checked
 isn't nearly a complete tutorial.

 Thomas

 Did you forget the actual URLs?

Arrghhh,
Indeed - that's what I get for copy/pasting between boxes.

[1] http://haskell.org/haskellwiki/Tutorials
[2] http://haskell.org/haskellwiki/IRC_channel
[3] look for 'Real World Haskell' and 'The Craft of Functional Programming'
[4] http://darcs.haskell.org/yaht/yaht.pdf
[5] http://www.haskell.org/tutorial/
[6] http://learnyouahaskell.com/
[7] http://en.wikibooks.org/wiki/Haskell
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] trying to understand space leaks....

2009-05-27 Thread Ryan Ingram
There's still the space used by the closure b.

An example:

expensiveParser :: Parser Char ExpensiveStructure

simple :: Parser Char Int

withExpensive :: ExpensiveStructure - Parser Char Int
withExpensive _ = mzero  -- actually always fails, not using its argument.

example = do
e - expensiveParser
simple `mplus` withExpensive e

The expensive structure constructed by expensiveParser needs to be
kept in memory throughout the entire parsing of simple, even though
withExpensive doesn't actually use it and would immediately fail.  A
smarter parser could realize that e couldn't actually ever be used and
allow the GC to free it much more quickly.

This example can be made arbitrarily more complicated; withExpensive
could run different things based on the value of e that could be
determined to fail quickly, simple might actually do a lot of work,
etc.  But during the mplus in the monadic parser, we can't free e.

  -- ryan

On Wed, May 27, 2009 at 12:49 PM, Daryoush Mehrtash dmehrt...@gmail.com wrote:
 So long as the [s] is a fixed list (say [1,2,3,4]) there is no space
 leak.    My understanding was that the space leak only happens if there is
 computation involved in building the list of s.  Am I correct?

 If so, I still don't have any feeling for what needs to be saved on the heap
 to be able to back track on computation that needs and  IO computation
 data.    What would be approximate  space that an IO (Char) computation
 take  on the heap, is it few bytes, 100, 1k,  ?

 Daryoush


 On Tue, May 26, 2009 at 6:11 PM, Ryan Ingram ryani.s...@gmail.com wrote:

 On Tue, May 26, 2009 at 5:03 PM, Daryoush Mehrtash dmehrt...@gmail.com
 wrote:
  newtype Parser s a = P( [s] - Maybe (a, [s]))
 (fixed typo)

  instance MonadPlus  Parser where
    P a mplus P b = P (\s - case a s of
      Just (x, s') - Just (x, s')
      Nothing - b s)

  a)what exactly gets saved on the heap between the mplus calls?

 Two things:

 (1) Values in the input stream that a parses before failing.
 Beforehand, it might just be a thunk that generates the list lazily in
 some fashion.

 (2) The state of the closure b; if parser a fails, we need to be
 able to run b; that could use an arbitrary amount of space depending
 on what data it keeps alive.

  b)I am assuming the computation to get the next character for parsing to
  be
  an IO Char type computation,  in that case, what would be the size of
  the
  heap buffer that is kept around in case the computation result needs to
  be
  reused?

 Nope, no IO involved; just look at the types:

 P :: ([s] - Maybe (a,[s])) - Parser s a

 (Parser s a) is just a function that takes a list of s, and possibly
 returns a value of type a and another list [s] (of the remaining
 tokens, one hopes)

 It's up to the caller of the parsing function to provide the token
 stream [s] somehow.

  c) Assuming Pa in the above code reads n tokens from the input stream
  then
  fails, how does the run time returns the same token to the P b?

 It just passes the same stream to both.  No mutability means no danger :)

  -- ryan



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


Re: [Haskell-cafe] Re: Error message reform (was: Strange type error with associated type synonyms)

2009-05-27 Thread Max Rabkin
On Thu, May 28, 2009 at 12:03 AM, Jeff Wheeler j...@nokrev.com wrote:
 I absolutely agree about expected/inferred. I always forget which is
 which, because I can figure both could apply to each.

That's actually true for me too. When you say it like that, I remember
times when I've had the same confusion.

 Better language may be much more helpful, although I'm not sure what may
 be easier to interpret.

I think one big improvement (demonstrated in Bulat's proposal) is to
put the two types near where those types come from. GHC gives you the
two types, and then the context in which they arose. Hugs gives the
context and then two types, but doesn't say which type is which.

So we say: you have here `True', it is a `Bool'. But the first
argument of `f' should be an `Int'.

Thus it's clearly indicated where the two types came from.

My preference is still to include the words expected and inferred
which indicate (to me) that *either* could be wrong. And they don't
seem to me to be compiler writers' jargon. They're both ordinary (if
not everyday) English words. But definitely we should use language
which more clearly indicates which is which.

I'll pay more attention to error messages in the future.

GHC devs: would patches for error message language be considered?

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


Re[7]: [Haskell-cafe] Strange type error with associated type synonyms

2009-05-27 Thread Bulat Ziganshin
Hello Henning,

Thursday, May 28, 2009, 2:06:36 AM, you wrote:

Prelude let a = 'a'; b = b in a==b

 interactive:1:27:
  Couldn't match expected type `Char' against inferred type `[Char]'
  

 Is the type of 'a' wrong or that of 'b'?

it is not important, well, at least we can live with it. Compiler
should say:

First argument of == should be of type String
while a is of type Char

and then it's user's problem to decide whether he need to fix call or
argument. only some interactive IDE may allow user to select term to
fix and then give him message tuned to this exact term


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re[2]: [Haskell-cafe] Re: Error message reform (was: Strange type error with associated type synonyms)

2009-05-27 Thread Bulat Ziganshin
Hello Jeff,

Thursday, May 28, 2009, 2:03:30 AM, you wrote:

 I absolutely agree about expected/inferred. I always forget which is
 which, because I can figure both could apply to each.

thank you, it's what i meant! compiler infers types of both caller and
its argument and then expect to see types inferred. these two words are
actually describe two stages of process, not two opposite processes!


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re[2]: [Haskell-cafe] Re: Error message reform (was: Strange type error with associated type synonyms)

2009-05-27 Thread Bulat Ziganshin
Hello Max,

Thursday, May 28, 2009, 2:14:19 AM, you wrote:

 I absolutely agree about expected/inferred. I always forget which is
 which, because I can figure both could apply to each.

 That's actually true for me too. When you say it like that, I remember
 times when I've had the same confusion.

it's why i asked beginners. it seems that we all go through times
when ghc errmsgs looks cryptic but then we start to live with it and
forget the first period

actually, i don't have much problems with errrmsgs now, but trying to
grok how i interpret them i've found that i mainly use *position*
part of message, it's enough for me most times :)


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re: [Haskell-cafe] Re: Error message reform

2009-05-27 Thread Henning Thielemann
Bulat Ziganshin schrieb:

 actually, i don't have much problems with errrmsgs now, but trying to
 grok how i interpret them i've found that i mainly use *position*
 part of message, it's enough for me most times :)

I have heard the statement users are only interested in the error
position in a talk 2007 in RISC in Hagenberg. But I still try to
understand error messages.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re[2]: [Haskell-cafe] Re: Error message reform

2009-05-27 Thread Bulat Ziganshin
Hello Henning,

Thursday, May 28, 2009, 2:30:18 AM, you wrote:

 Bulat Ziganshin schrieb:

 actually, i don't have much problems with errrmsgs now, but trying to
 grok how i interpret them i've found that i mainly use *position*
 part of message, it's enough for me most times :)

 I have heard the statement users are only interested in the error
 position in a talk 2007 in RISC in Hagenberg. But I still try to
 understand error messages.

i'm not uninterested. it's just faster for me to find message looking
at the code rather than to decipher errmsg

so while beginners crying at cryptic errmsgs, advanced beginners like
me don't waste time trying to decrypt them :)

but don't take it too seriously - for this particular message problem
is only those inferred/expected interpretation, types by itself are
helpful


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re: [Haskell-cafe] About the lazy pattern

2009-05-27 Thread Ryan Ingram
Hi nemo.  I had a lot of trouble with that section of the tutorial as
well, and I believe that once you get it, a lot of Haskell becomes a
lot simpler.

The way I eventually figured it out is using this idealized execution
model for Haskell: you just work by rewriting the left side of a
function to its right side.  The only question is figuring out *which*
function to rewrite!

Here's a simpler example:

 f 0 = 0
 f x = x+1

 g (x:xs) = error urk
 g [] = 2
 const a b = a

 ex1 = const (f 1) (g [2,3])
 ex2 = f (const (g []) (g [1,2]))

Lets say you wanted to know the value of ex1; you just use rewriting

ex1
-- rewrite using ex1
= const (f 1) (g [2,3])
-- rewrite using const
= f 1
-- rewrite using f (second pattern)
= 1+1
-- rewrite using +
= 2

But lets say we picked a different order to rewrite...

ex1
-- rewrite using ex1
= const (f 1) (g [2,3])
-- rewrite using g
= const (f 1) (error urk)
-- rewrite using error
computation stops

Of course this is bad, and it was obviously wrong to evaluate g first
(because const is lazy).  So one heuristic we always use is rewrite
the leftmost application first which avoids this problem.  But lets
try that rule on ex2!

ex2
-- rewrite using ex2
= f (const (g []) (g [1,2]))
-- rewrite using f
= ?

Unfortunately, now we don't know which pattern to match!  So we have
to pick a different thing to rewrite.  The next rule is that, if the
thing you want to rewrite has a pattern match, look at the argument
for the patterns being matched and rewrite them instead, using the
same leftmost first rule:

f (const (g []) (g [1,2]))
-- trying to pattern match f's first argument
-- rewrite using const
= f (g [])
-- still pattern matching
-- rewrite using g
= f 2
-- now we can match
-- rewrite using f (second pattern)
= 2+1
-- rewrite using +
= 3

So, back to the original question (I'm rewriting the arguments to
client and server for clarity)

 reqs = client init resps
 resps = server reqs
 client v (rsp:rsps) = v : client (next rsp) rsps
 server (rq:rqs) = process rq : server rqs

Lets say we are trying to figure out the value of resps, to print
all the responses to the screen:

resps
-- rewrite using resps
= server reqs
-- pattern match in server
-- rewrite reqs
= server (client init resps)
-- pattern match in server
-- pattern match also in client
-- rewrite using resps
= server (client init (server reqs))
-- pattern match in server, client, then server
-- rewrite using reqs
= server (client init (server (client init resps)))

You see that we are in a loop now; we are stuck trying to pattern
match and we will never make any progress!

The lazy pattern says trust me, this pattern will match, you can
call me on it later if it doesn't!

 reqs = client init resps
 resps = server reqs
 client v (rsp:rsps) = v : client (next rsp) rsps
 server (rq:rqs) = process rq : server rqs

resps
-- rewrite resps
= server reqs
-- server wants to pattern match, rewrite reqs
= server (client init resps)
-- Now, the lazy pattern match says this will match, wait until later
-- rewrite using client!
= let (rsp:rsps) = resps
   in server (init : client (next rq) rqs)
-- rewrite using server
= let (rsp:rsps) = resps
   in process init : server (client (next rq) rqs)

We now have a list node, so we can print the first element and
continue (which requires us to know the code for process and next,
but you get the idea, I hope!)

Now of course, you can lie to the pattern matcher:

 next x = x + 1
 init = 5

client init []
-- rewrite using client
= let (rsp0:rsps0) = []
   in init : client (next rsp0) rsps0
-- rewrite using init
= let (rsp0:rsps0) = []
   in 5 : client (next rsp0) rsps0

-- print 5 and continue to evaluate...
   let (rsp0:rsps0) = []
   in client (next rsp0) rsps0
-- rewrite using client
= let
(rsp0:rsps0) = []
(rsp1:rsps1) = rsps0
   in (next rsp0) : client (next rsp1) rsps1
-- rewrite using next
= let
(rsp0:rsps0) = []
(rsp1:rsps1) = rsps0
   in rsp0+1 : client (next rsp1) rsps1
-- + wants to pattern match on its first argument
-- rewrite using rsp0
computation stops, pattern match failure, (rsp0:rsps0) does not match []

For this reason, many people (myself included) consider it bad style
to use lazy/irrefutable pattern matches on data types with more than
one constructure.  But they are very handy on types with a single
constructor, like pairs:

 weird ~(x,y) = (1,x)
 crazy = weird crazy

crazy
-- rewrite crazy
= weird crazy
-- rewrite weird
= let (x0,y0) = crazy
   in (1, x0)
-- We really want to know what x0 is now.
-- But it is the result of a pattern match inside a let; so we need to evaluate
-- the right hand side of the binding to see if the patterns match.
-- So, rewrite crazy to attempt to pattern match...
= let (x0, y0) = weird crazy
   in (1, x0)
-- Then, rewrite weird
= let
(x1, y1) = crazy
(x0, y0) = (1, x1)
   in (1, x0)
-- rewrite x0
= let
(x1, y1) = crazy
(x0, y0) = (1, x1)
   in (1, 1)
-- garbage collect
= (1,1)

I hope this helps!

  -- ryan



Re: [Haskell-cafe] Template Haskell very wordy w/r/t Decs and Types

2009-05-27 Thread Matt Morrow
Spectacular!

How difficult would it be to implement splicing in decls? I'm interested in
having a go at it, and it seems like a perfect time since I can cheat off
the fresh diff. In particular I'd love to be able to do stuff like this
(without the current vicious hackery i'm using) (and granted, where i'm
splicing is somewhat willy-nilly, but some approximation of this):

-

{-# LANGUAGE TemplateHaskell, QuasiQuotes #-}
module DecTest where
import HsDec
import Data.List
import DecTestBoot
import Language.Haskell.TH.Lib
import Language.Haskell.TH.Syntax
import Language.Haskell.Meta.Utils

bootQ :: Q [Dec]
bootQ = bootQFunct
  primQStruct

primQStruct = (''[]
  ,(conT ''[] `appT`)
  ,[|[]|]
  ,[|null|]
  ,[|undefined|]
  ,[|union|]
  ,[|undefined|]
  ,[|undefined|])

bootQFunct
  (primN  :: Name
  ,primQ  :: TypeQ
  - TypeQ  -- exists q. forall a. a - q a
  ,emptyQ :: ExpQ   -- Q a
  ,isEmptyQ   :: ExpQ   -- q a - Bool
  ,insertQ:: ExpQ   -- Int - a - q a - q a
  ,mergeQ :: ExpQ   -- q a - q a - q a
  ,findMinQ   :: ExpQ   -- q a - Maybe (Int, a)
  ,deleteMinQ :: ExpQ)  -- q a - q a

  = do  n - newName a
let primT = varT primN
a = varT n

[$dec|
  data BootQ $(a)
= Nil
| Node {-# UNPACK #-} !Int $(a) ($(primT) (BootQ $(a)))
deriving(Eq,Ord)

  empty :: BootQ $(a)
  isEmpty   :: BootQ $(a) - Bool
  insert:: Int - $(a) - BootQ $(a) - BootQ $(a)
  merge :: BootQ $(a) - BootQ $(a) - BootQ $(a)
  findMin   :: BootQ $(a) - Maybe (Int, $(a))
  deleteMin :: BootQ $(a) - BootQ $(a)

  empty = Nil
  isEmpty Nil = True
  isEmpty   _ = False
  findMin  Nil = Nothing
  findMin (Node n x _) = Just (n, x)
  insert n x q = merge (Node n x $(emptyQ)) q
  merge (Node n1 x1 q1)
(Node n2 x2 q2)
| n1 = n2  = Node n1 x1 ($(insertQ) n2 (Node n2 x2 q2) q1)
| otherwise = Node n2 x2 ($(insertQ) n1 (Node n1 x1 q1) q2)
  merge Nil q  = q
  merge q  Nil = q
  deleteMin  Nil = Nil
  deleteMin (Node _ _ q)
= case $(findMinQ) q of
Nothing - Nil
Just (_, Node m y q1)
  - let q2 = $(deleteMinQ) q
  in Node m y ($(mergeQ) q1 q2)
|]

{-
-- FORGOT TO PUT AN (Eq a) CXT, but oh well
ghci ppDoc `fmap` bootQ
data BootQ a_0_0 = Nil | Node !Int a_0_0 ([] (BootQ a_0_0))
deriving (Eq, Ord)
empty :: forall a_0_1 . BootQ a_0_1
isEmpty :: forall a_0_2 . BootQ a_0_2 - Bool
insert :: forall a_0_3 . Int - a_0_3 - BootQ a_0_3 - BootQ a_0_3
merge :: forall a_0_4 . BootQ a_0_4 - BootQ a_0_4 - BootQ a_0_4
findMin :: forall a_0_5 . BootQ a_0_5 - Maybe ((Int, a_0_5))
deleteMin :: forall a_0_6 . BootQ a_0_6 - BootQ a_0_6
empty = Nil
isEmpty (Nil) = True
isEmpty _ = False
findMin (Nil) = Nothing
findMin (Node n_7 x_8 _) = Just (n_7, x_8)
insert n_9 x_10 q_11 = merge (Node n_9 x_10 []) q_11
merge (Node n1_12 x1_13 q1_14) (Node n2_15
 x2_16
 q2_17) | n1_12 = n2_15 = Node n1_12
x1_13 (undefined n2_15 (Node n2_15 x2_16 q2_17) q1_14)
| otherwise = Node n2_15 x2_16
(undefined n1_12 (Node n1_12 x1_13 q1_14) q2_17)
merge (Nil) q_18 = q_18
merge q_19 (Nil) = q_19
deleteMin (Nil) = Nil
deleteMin (Node _ _ q_20) = case undefined q_20 of
Nothing - Nil
Just (_, Node m_21 y_22 q1_23) - let q2_24
= undefined q_20
   in Node
m_21 y_22 (union q1_23 q2_24)
ghci
-}

-

Thanks,
Matt



On Wed, May 27, 2009 at 2:38 PM, Simon Peyton-Jones
simo...@microsoft.comwrote:

 Folks

 Quite a few people have asked for splices in Template Haskell *types*, and
 I have finally gotten around to implementing them.  So now you can write
 things like

instance Binary $(blah blah) where ...
 or  f :: $(wubble bubble) - Int

 as requested, for example, in the message below.  Give it a whirl.  You
 need the HEAD; in a day or two you should find binary snapshots if you don't
 want to build from source.

Simon

 PS: Note that you (still) cannot write a splice in a *binding* position.
 Thus you can't write
f $(blah blah) = e
 or
data T $(blah blah) = MkT Int

 I don't intend to change this; see the commentary at
 http://hackage.haskell.org/trac/ghc/ticket/1476

 | -Original Message-
 | From: haskell-cafe-boun...@haskell.org [mailto:
 haskell-cafe-boun...@haskell.org] On
 | Behalf Of Ross Mellgren
 | 

Re: [Haskell-cafe] platform/cabal problems

2009-05-27 Thread Duncan Coutts
On Wed, 2009-05-27 at 22:43 +0200, Johannes Waldmann wrote:
 Hi all.
 
 I've written some Haskell program,
 and I wanted to give it to a friend, in source form,
 so he can run and modify it, and learn some Haskell
 while doing so. I was using some cabalized extra packages
 but hey, this looks like the typical use case for the haskell-platform.
 So: I told him to install the newest stable ghc
 and the current platform release and this happens:
 
 la:/home/b/appl.linux/haskell-platform-2009.2.0# ./configure
 ...
 checking for hsc2hs... /usr/local/bin/hsc2hs
 checking version of ghc... 6.10.3
 checking version of ghc-pkg matches... yes
 checking ghc actually works... yes
 checking the ghc core packages are all installed... no
 configure: error: The core package editline-0.2.1.0 is missing.
   It should have been distributed with 6.10.2
   

When we released 2009.2.0, ghc-6.10.3 had not been released yet. I had
hoped that the source based installer would work with 6.10.3, but we
forgot that 6.10.3 was removing a package that had shipped with 6.10.2,
hence the error you see.

You can hack the list of expected packages or use
--enable-unsupported-ghc-version or wait 'til the release next week of
2009.2.0.1 which will use ghc 6.10.3.

 What's the particular reason for the failure?
 editline was distributed with ghc-6.10.2, but not with 6.10.3?
 I wouldn't expect an incompatible change
 when (only) the patchlevel is bumped.

It's a bit unfortunate. The way we're coping with it in 2009.2.0.1 is
that we supply editline.

 The platform web site should probably replace
 works with ghc-6.10.x by works with ghc-6.10.2 only.

Yes.

Duncan

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


Re: [Haskell-cafe] Type class context propagation investigation

2009-05-27 Thread Ryan Ingram
Think of classes like data declarations; an instance with no context
is a constant, and one with context is a function.  Here's a simple
translation of your code into data; this is very similar to the
implementation used by GHC for typeclasses:

 data EqDict a = EqDict { eq :: a - a - Bool }
 data ShowDict a = ShowDict { show :: a - String }
 data NumDict a = NumDict { num_eq :: EqDict a, num_show :: ShowDict a, plus 
 :: a - a - a }

The goal of the compiler is to turn your instance declarations into
these structures automatically.  Here's a translation of your original
instance:

 eq_foo :: EqDict (Foo a)
 eq_foo = EqDict { eq = undefined }

 show_foo :: ShowDict (Foo a)
 show_foo = ShowDict { show = undefined }

 num_foo :: NumDict (Foo a)
 num_foo = NumDict { num_eq = eq_foo, num_show = show_foo, plus = undefined }

Now if you add a constraint on the Eq instance, this means that eq
from eq_foo might refer to eq in the dictionary for a.  How do we
get that dictionary?  We just pass it as an argument!

 eq_foo :: EqDict a - EqDict (Foo a)
 eq_foo eq_a = EqDict { eq = undefined }

However, you don't have a similar constraint on the Num instance:

 num_foo :: NumDict (Foo a)
 num_foo = NumDict { num_eq = eq_foo something, num_show = show_foo, plus = 
 undefined }

The compiler wants to fill in something, but it can't; it doesn't
have a dictionary of the type EqDict a.  So it tells you so, saying
that Eq a is missing!

Once you add the (Eq a) constraint to the Num instance, it works:

 num_foo :: EqDict a - NumDict (Foo a)
 num_foo eq_a = NumDict { num_eq = eq_foo eq_a, num_show = show_foo, plus = 
 undefined }

You can also add a (Num a) constraint instead, and the compiler can
use it to get the Eq instance out:

 num_foo :: NumDict a - NumDict (Foo a)
 num_foo num_a = NumDict { num_eq = eq_foo (num_eq num_a), num_show = 
 show_foo, plus = undefined }

Of course, I'm glossing over the interesting details of the search,
but the basic idea is to attempt to fill in the blanks in these
definitions.

  -- ryan

On Wed, May 27, 2009 at 2:10 PM, Paul Keir pk...@dcs.gla.ac.uk wrote:
 Hi,

 How does the context of a class instance declaration affect its subclasses?

 The Num class instance outlined below has its requirement for Eq and Show
 satisfied on the preceding lines, and the code will compile. But if I, say,
 add an (Eq a) constraint to the Eq instance, in preparation for a simple
 (==) definition, I find that the Num instance declaration is left lacking.
 If I add the same (Eq a) constraint now to Num, calm is restored.

 data Foo a = F a

 instance Eq (Foo a) where
  (==) = undefined

 instance Show (Foo a) where
  show = undefined

 instance Num (Foo a)
  (+) = undefined
  ... etc.

 The thing that confuses me with this is that it seems like Num knows that
 an (Eq a) context has been applied, and so what it sees as a problem, is
 somehow also the solution. Any advice/rules of thumb? Does this situation
 occur elsewhere? How do these constraints propagate?

 Thanks,
 Paul

 ___
 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] What's the problem with iota's type signature?

2009-05-27 Thread michael rice
Still exploring monads. I don't understand why the type signature for double is 
OK, but not the one for iota.

Michael

=

--double :: (Int a) = a - Maybe b
--double x = Just (x + x)

iota :: (Int a) = a - [b]
iota  n = [1..n]

--usage: [3,4,5] = iota
--should produce [1,2,3,1,2,3,4,1,2,3,4,5]


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


Re: [Haskell-cafe] What's the problem with iota's type signature?

2009-05-27 Thread Lionel Barret de Nazaris

On 28/05/2009 04:33, michael rice wrote:
Still exploring monads. I don't understand why the type signature for 
double is OK, but not the one for iota.


Michael

=

--double :: (Int a) = a - Maybe b
--double x = Just (x + x)

iota :: (Int a) = a - [b]
iota  n = [1..n]

--usage: [3,4,5] = iota
--should produce [1,2,3,1,2,3,4,1,2,3,4,5]



iota is executed within the monad and as such must respect its law ?




___
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] What's the problem with iota's type signature?

2009-05-27 Thread David Leimbach
On Wed, May 27, 2009 at 7:33 PM, michael rice nowg...@yahoo.com wrote:

 Still exploring monads. I don't understand why the type signature for
 double is OK, but not the one for iota.

 Michael

 =

 --double :: (Int a) = a - Maybe b
 --double x = Just (x + x)

 iota :: (Int a) = a - [b]
 iota  n = [1..n]


Int is not a class, and you are using it as such?





 --usage: [3,4,5] = iota
 --should produce [1,2,3,1,2,3,4,1,2,3,4,5]

 ___
 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] Stack overflow

2009-05-27 Thread Tim Docker
 Thanks for the tip, although it seems tricky to get it right. I wonder
 why there is no strict version of atomicModifyIORef?
 Dually there might be a strict version of IORef datatype.

Alternatively, you could use STM, where you can write your own atomic
update function, which has the strictness you need (untested):

import Control.Concurrent.STM

strictUpdate :: (a-a) - TVar a - STM ()
strictUpdate f v = do
x - readTVar v
let x1 = f x
x1 `seq` writeTVar v x1

g :: (Int-Int) - TVar Int - IO ()
g f v = atomically (strictUpdate f v)


Tim

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


Re: [Haskell-cafe] What's the problem with iota's type signature?

2009-05-27 Thread Lee Duhem
On Thu, May 28, 2009 at 10:33 AM, michael rice nowg...@yahoo.com wrote:
 Still exploring monads. I don't understand why the type signature for double
 is OK, but not the one for iota.

 Michael

 =

 --double :: (Int a) = a - Maybe b
 --double x = Just (x + x)

Prelude let double x = Just $ x + x
Prelude Just 2 = double
Just 4

You can define double as
double x = return $ x + x

Prelude let double x = return $ x + x
Prelude Just 2 = double
Just 4


 iota :: (Int a) = a - [b]
 iota  n = [1..n]

 --usage: [3,4,5] = iota
 --should produce [1,2,3,1,2,3,4,1,2,3,4,5]

I did.
Prelude let iota n = [1..n]
Prelude [3,4,5] = iota
[1,2,3,1,2,3,4,1,2,3,4,5]

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


Re: Re[2]: [Haskell-cafe] Re: Error message reform (was: Strange type error with associated type synonyms)

2009-05-27 Thread Alexander Dunlap
On Wed, May 27, 2009 at 3:24 PM, Bulat Ziganshin
bulat.zigans...@gmail.com wrote:
 Hello Max,

 Thursday, May 28, 2009, 2:14:19 AM, you wrote:

 I absolutely agree about expected/inferred. I always forget which is
 which, because I can figure both could apply to each.

 That's actually true for me too. When you say it like that, I remember
 times when I've had the same confusion.

 it's why i asked beginners. it seems that we all go through times
 when ghc errmsgs looks cryptic but then we start to live with it and
 forget the first period

 actually, i don't have much problems with errrmsgs now, but trying to
 grok how i interpret them i've found that i mainly use *position*
 part of message, it's enough for me most times :)


 --
 Best regards,
  Bulat                            mailto:bulat.zigans...@gmail.com


Hi,

I like the expected/inferred vocabulary. Maybe it comes from being a
native English speaker, but to me, it says this is what we expected
to get, but instead (through type inference), we got this type for
this term.

Of course, I've also been reading GHC error messages for a while, so
I've gotten used to understanding what they mean. When I was new, I
had more of a problem...but I'm not sure you can really eliminate
that. Everything takes practice. :)

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


Re: [Haskell-cafe] the problem of design by negation

2009-05-27 Thread David Fox
What I do like about this so-called negative approach is that it
represents a part of a program's documentation that is usually omitted.  You
can look at the code and see exactly how and (to a certain extent) why the
program does what it does, but what you can't see is all the things it
doesn't do, and the reasons it doesn't do them.  This can be extremely
important to know when you are thinking about modifying a program.  The
change you are considering may have already been tried and rejected, but
unless these sorts of negative decisions are documented in the software you
may end up spinning your wheels.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] We tried this functional, higher-order stuff with LISP and look what happened...

2009-05-27 Thread Jason Dusek
2009/05/27 Tord Romstad tord.roms...@gmail.com:
 I think you rarely meet embittered Lisp programmers simply
 because we Lispers are rarely embittered...

  I have a very small sample size :)

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


Re: [Haskell-cafe] Data.Binary and little endian encoding

2009-05-27 Thread David Leimbach
Sorry took so long to get back... Thank you for the response.  Been really
busy lately :-)

On Sat, May 16, 2009 at 3:46 AM, Khudyakov Alexey alexey.sklad...@gmail.com
 wrote:

 On Friday 15 May 2009 06:52:29 David Leimbach wrote:
  I actually need little endian encoding... wondering if anyone else hit
 this
  with Data.Binary. (because I'm working with Bell Lab's 9P protocol which
  does encode things on the network in little-endian order).
  Anyone got some tricks for this?
 
  Dave

 You could just define data type and Binary instance for 9P messages.
 Something
 like this:

 P9Message = Tversion { tag :: Word16, msize :: Word32, version :: String }
| ...

 instance Binary P9Message where
  put (Tverstion  t m v) =  putWord16le t   putWord32le m  put v
  -- and so on...

  get = do
length - getWord32le
id - getWord16le
case is of
  p9TMessage - do ...

 There are a lot of boilerplate code thought...


Thank you, this still looks like a useful way to proceed, combined with the
BinaryLE approach perhaps, to avoid a lot of boilerplate.




 BTW could you say what do you want to do with 9P? I tried to play with it
 using libixp library but without any success. It was mainly to understand
 how
 does it works and how can it be used.


From a services point of view, 9P gives you a way to host them, and even
devices, on a network share that can be mounted into the filesystem's
namespace.  The net result is you've plugged into the standard unix
utilities that do open, read, write etc, and can do a lot of interesting
things with mere shell scripts.

Operating systems that can be clients of a 9P service include Linux,
Inferno, Plan 9, and anything else that runs FUSE 9P (several BSDs).

From a client perspective, having a 9P implementation gives you a more
fine-grained programatic interface to accessing other 9P services.

There are also a lot of 9P implementations in many languages that you can
interoperate with:

http://9p.cat-v.org/implementations






 ___
 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] Type class context propagation investigation

2009-05-27 Thread wren ng thornton

Ryan Ingram wrote:

Think of classes like data declarations; an instance with no context
is a constant, and one with context is a function.  Here's a simple
translation of your code into data; this is very similar to the
implementation used by GHC for typeclasses:

 data EqDict a = EqDict { eq :: a - a - Bool }
 data ShowDict a = ShowDict { show :: a - String }
 data NumDict a = NumDict { num_eq :: EqDict a, num_show :: ShowDict a, plus :: a 
- a - a }

The goal of the compiler is to turn your instance declarations into
these structures automatically.


Another way of explaining this, if you're a Curry--Howard fan, is that 
the compiler is looking for a proof that the type belongs to the class, 
where = is logical implication. This is very similar to how Prolog 
searches for proofs, if you're familiar with logic programming.


Classes declare the existence of logical predicates, along with the form 
of what a proof of the predicate looks like. Instances declare a 
particular proof (or family of proofs if there are free type variables).



Thus, the Num class is declared as,

class (Eq a, Show a) = Num a where ...

which says: for any type |a|, we can prove |Num a| if (and only if) we 
can prove |Eq a| and |Show a|, and can provide definitions for all the 
functions in the class using only the assumptions that |Eq a|, |Show a|, 
and |Num a|.



When you declare,

instance Eq b = Eq (Foo b) where ...

you're providing a proof of |Eq b = Eq (Foo b)|. That is, you can 
provide a conditional proof of |Eq (Foo b)|, given the assumption that 
you have a proof of |Eq b|.


Notice how the context for instances is subtly different from the 
context for classes. For instances you're saying that this particular 
proof happens to make certain assumptions; for classes you're saying 
that all proofs require these assumptions are valid (that is, providing 
the functions isn't enough to prove membership in the class).



Later on you declare,

instance Num (Foo b) where ...

but remember that this proof must have the same form as is declared by 
the class definition. This means that you must have proofs of |Eq (Foo 
b)| and |Show (Foo b)|. Unfortunately, you don't actually have a proof 
of |Eq (Foo b)|, you only have a proof of |Eq b = Eq (Foo b)|. In order 
to use that proof you must add the |Eq b| assumption to this proof as well:


instance Eq b = Num (Foo b) where ...

When the compiler is complaining about the original one, what it's 
telling you is that the |Num (Foo b)| proof can never exist because you 
can never provide it with a proof of |Eq (Foo b)| in order to fulfill 
its requirements.


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


Re: Re[2]: [Haskell-cafe] Re: Error message reform (was: Strange type error with associated type synonyms)

2009-05-27 Thread John Dorsey
 I like the expected/inferred vocabulary. Maybe it comes from being a
 native English speaker, but to me, it says this is what we expected
 to get, but instead (through type inference), we got this type for
 this term.

As another native English speaker, I found expected/inferred very
intuitive when I was new to GHC, and to Haskell.  I even think that
expected/inferred helped me form my intuition about Haskell's type
inference.

There was one hang-up; it wasn't at all clear which referred to the term,
and which referred to the context.  (Really both types are inferred.) This
stopped bothering me when I decided it didn't matter which was which, and I
could generally find the problem pretty quickly just knowing the location
and the types involved.

Of course, I can see how the messages are probably much less useful to
non-native speakers, and that's quite important.  Something along the lines
of inferred type droozle for term, but expected type snidgit in
context.

John

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


Re: [Haskell-cafe] trying to understand space leaks....

2009-05-27 Thread Daryoush Mehrtash
I (think)  I understand the problem.  What I don't have any intuition about
is how much  space would Expensive Structure take if it was basically an
IO Char computation fed into a simple function (say checks for char being
equal to a).   Is there any way to guess, know the size of the buffer that
is kept in the heap?

thanks,

Daryoush
On Wed, May 27, 2009 at 3:12 PM, Ryan Ingram ryani.s...@gmail.com wrote:

 There's still the space used by the closure b.

 An example:

 expensiveParser :: Parser Char ExpensiveStructure

 simple :: Parser Char Int

 withExpensive :: ExpensiveStructure - Parser Char Int
 withExpensive _ = mzero  -- actually always fails, not using its argument.

 example = do
e - expensiveParser
simple `mplus` withExpensive e

 The expensive structure constructed by expensiveParser needs to be
 kept in memory throughout the entire parsing of simple, even though
 withExpensive doesn't actually use it and would immediately fail.  A
 smarter parser could realize that e couldn't actually ever be used and
 allow the GC to free it much more quickly.

 This example can be made arbitrarily more complicated; withExpensive
 could run different things based on the value of e that could be
 determined to fail quickly, simple might actually do a lot of work,
 etc.  But during the mplus in the monadic parser, we can't free e.

  -- ryan

 On Wed, May 27, 2009 at 12:49 PM, Daryoush Mehrtash dmehrt...@gmail.com
 wrote:
  So long as the [s] is a fixed list (say [1,2,3,4]) there is no space
  leak.My understanding was that the space leak only happens if there
 is
  computation involved in building the list of s.  Am I correct?
 
  If so, I still don't have any feeling for what needs to be saved on the
 heap
  to be able to back track on computation that needs and  IO computation
  data.What would be approximate  space that an IO (Char) computation
  take  on the heap, is it few bytes, 100, 1k,  ?
 
  Daryoush
 
 
  On Tue, May 26, 2009 at 6:11 PM, Ryan Ingram ryani.s...@gmail.com
 wrote:
 
  On Tue, May 26, 2009 at 5:03 PM, Daryoush Mehrtash dmehrt...@gmail.com
 
  wrote:
   newtype Parser s a = P( [s] - Maybe (a, [s]))
  (fixed typo)
 
   instance MonadPlus  Parser where
 P a mplus P b = P (\s - case a s of
   Just (x, s') - Just (x, s')
   Nothing - b s)
 
   a)what exactly gets saved on the heap between the mplus calls?
 
  Two things:
 
  (1) Values in the input stream that a parses before failing.
  Beforehand, it might just be a thunk that generates the list lazily in
  some fashion.
 
  (2) The state of the closure b; if parser a fails, we need to be
  able to run b; that could use an arbitrary amount of space depending
  on what data it keeps alive.
 
   b)I am assuming the computation to get the next character for parsing
 to
   be
   an IO Char type computation,  in that case, what would be the size
 of
   the
   heap buffer that is kept around in case the computation result needs
 to
   be
   reused?
 
  Nope, no IO involved; just look at the types:
 
  P :: ([s] - Maybe (a,[s])) - Parser s a
 
  (Parser s a) is just a function that takes a list of s, and possibly
  returns a value of type a and another list [s] (of the remaining
  tokens, one hopes)
 
  It's up to the caller of the parsing function to provide the token
  stream [s] somehow.
 
   c) Assuming Pa in the above code reads n tokens from the input stream
   then
   fails, how does the run time returns the same token to the P b?
 
  It just passes the same stream to both.  No mutability means no danger
 :)
 
   -- ryan
 
 
 

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


Re: Re[2]: [Haskell-cafe] Re: Error message reform (was: Strange type error with associated type synonyms)

2009-05-27 Thread Jeff Wheeler
On Wed, 2009-05-27 at 23:59 -0400, John Dorsey wrote:


 There was one hang-up; it wasn't at all clear which referred to the term,
 and which referred to the context.  (Really both types are inferred.) This
 stopped bothering me when I decided it didn't matter which was which, and I
 could generally find the problem pretty quickly just knowing the location
 and the types involved.
 
 Of course, I can see how the messages are probably much less useful to
 non-native speakers, and that's quite important.  Something along the lines
 of inferred type droozle for term, but expected type snidgit in
 context.

As a native English speaker myself, I've also found it awkward because
both types are inferred, I suppose.

The alternate format you've suggested would make it much more clear, in
my opinion, and I strongly feel that the current version should be
replaced with yours.

Jeff Wheeler

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


  1   2   >