Re: [Haskell-cafe] memoization

2013-07-24 Thread Andreas Abel

Sorry I screwed up.  The following is indeed memoizing:

fib5 :: Int - Integer
fib5 = \ x - fibs !! x
   where fibs = map fib [0 ..]
 fib 0 = 0
 fib 1 = 1
 fib n = fib5 (n-2) + fib5 (n-1)

Here, the eta-expansion does not matter.  But as you say, memoized_fib 
below is not memoizing, since x is in scope in the where clauses, even 
though they do not mention it.  Thus, for each x we get new 
definitions of fibs and fib.  Yet, this is only true for -O0.


For -O1 and greater, ghc seems to see that x is not mentioned in the 
where clauses and apparently lifts them out.  Thus, for -O1.. 
memoized_fib is also memoizing.  (I ran it, this time ;-) !)


Cheers,
Andreas

On 22.07.13 11:43 PM, Tom Ellis wrote:

On Mon, Jul 22, 2013 at 04:16:19PM +0200, Andreas Abel wrote:

In general, I would not trust such compiler magic, but just let-bind
anything I want memoized myself:

memoized_fib :: Int - Integer
memoized_fib x = fibs !! x
 where fibs  = map fib [0..]   -- lazily computed infinite list
   fib 0 = 0
   fib 1 = 1
   fib n = memoized_fib (n-2) + memoized_fib (n-1)

The eta-expansions do not matter.


I meant to write

  Then, eta-expansions do not matter.

(In general, they do matter.)


But this is *not* memoized (run it and see!).  The eta-expansions do
indeed matter (although I don't think they are truly eta-expasions because
of the desugaring of the where to a let).

What matters is not the let binding, but where the let binding occurs in
relation to the lambda.  There's no compiler magic here, just operational
semantics.

Tom

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



--
Andreas AbelDu bist der geliebte Mensch.

Theoretical Computer Science, University of Munich
Oettingenstr. 67, D-80538 Munich, GERMANY

andreas.a...@ifi.lmu.de
http://www2.tcs.ifi.lmu.de/~abel/

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


Re: [Haskell-cafe] Proposal: Non-recursive let

2013-07-24 Thread Andreas Abel

On 23.07.13 4:34 AM, Richard A. O'Keefe wrote:


On 22/07/2013, at 8:14 PM, Andreas Abel wrote:


Just today, my student asked me why the following program does nothing:


Did you ask your student why their code should not be torn into pieces,
burned to ashes, and incorporated into a pot for radioactive waste?

All those occurrences of unsafePerformIO!


No, here they are intended, to simulate something like uniqueness types 
in Clean, which incidentially has been mentioned on this thread before.


The loop has nothing to do with unsafePerformIO, but stems from 
Haskell's idiosyncratic recursive let, which is a trap for all that come 
from another functional language.


--
Andreas AbelDu bist der geliebte Mensch.

Theoretical Computer Science, University of Munich
Oettingenstr. 67, D-80538 Munich, GERMANY

andreas.a...@ifi.lmu.de
http://www2.tcs.ifi.lmu.de/~abel/

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


Re: [Haskell-cafe] Proposal: Non-recursive let

2013-07-24 Thread Andreas Abel
Sure.  I have not looked a concrete strictness analyses, but I expect 
they would treat Conat differently than Integer.  In particular,


  x   does *not* appear strictly in  S x

if S is a lazy constructor.

On 22.07.13 4:54 PM, Edward Kmett wrote:

let x = x +1

is perfectly cromulent when x is sufficiently lazy, e.g. in the one point 
compactification of the naturals:

data Conat = S Conat | Z

There it represents infinity with proper sharing.

-Edward

On Jul 22, 2013, at 10:24 AM, Andreas Abel andreas.a...@ifi.lmu.de wrote:


On 22.07.2013 10:50, MigMit wrote:


On Jul 22, 2013, at 12:27 PM, Andreas Abel andreas.a...@ifi.lmu.de
wrote:


On 20.07.13 9:36 PM, Evan Laforge wrote:

However, I'm also not agitating for a non-recursive let, I think
that ship has sailed.  Besides, if it were added people would
start wondering about non-recursive where, and it would introduce
an exception to haskell's pretty consistently order-independent
declaration style.


For functions, recursive-by-default let makes sense.  But for
*values*, intended recursion is rather the exception.  It is useful
for infinite lists and the like.  For values of atomic type like
Int or Bool, recursive let is a bug.


It seems hard to distinguish between them. What about values that
contain functions, like data T = T Int (Int - Int)? What about
polymorphic values, that could be functions and could be not?


I agree.  It cannot be implemented like that.  A thing that could be 
implemented is that

  let x = e

is an error if x appears strictly in e.  In practice, this could catch some 
unintended cases of recursion like

  let x = x +1

, but not all of them.

Cheers,
Andreas

--
Andreas AbelDu bist der geliebte Mensch.

Theoretical Computer Science, University of Munich
Oettingenstr. 67, D-80538 Munich, GERMANY

andreas.a...@ifi.lmu.de
http://www2.tcs.ifi.lmu.de/~abel/

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




--
Andreas AbelDu bist der geliebte Mensch.

Theoretical Computer Science, University of Munich
Oettingenstr. 67, D-80538 Munich, GERMANY

andreas.a...@ifi.lmu.de
http://www2.tcs.ifi.lmu.de/~abel/

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


Re: [Haskell-cafe] How can I use ghci more wisely?

2013-07-24 Thread Michael Sloan
This portion of haskell-mode (haskell-interactive-mode-eval-pretty) is what
the UI for something like this could look like:

https://www.youtube.com/watch?v=pu9AGSOySlE

This isn't an answer to your question, though, because expanding subparts
of the output doesn't drive evaluation.  It would be very cool, and quite
possible, to have a variant of the Show typeclass that had output with such
structured laziness.

Another non-answer is to take a look at using vaccum[0] and
vaccum-graphviz[1] together, to get an idea of the heap structure of
unforced values.  I've made a gist demonstrating how to use these to
visualize the heap without forcing values[2].  This doesn't show any
concrete values (as that would require some serious voodoo), but does show
how the heap changes due to thunks being forced.

-Michael

[0] http://hackage.haskell.org/package/vacuum
[1] http://hackage.haskell.org/package/vacuum-graphviz
[2] https://gist.github.com/mgsloan/6068915


On Tue, Jul 23, 2013 at 7:30 PM, yi lu zhiwudazhanjiang...@gmail.comwrote:

 I am wondering how can I ask ghci to show an infinite list wisely.
 When I type

 *fst ([1..],[1..10])*

 The result is what as you may guess

 *1,2,3,4,...*(continues to show, cut now)

 How could I may ghci show

 *[1..]*

 this wise way not the long long long list itself?

 Yi

 ___
 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] memoization

2013-07-24 Thread Tom Ellis
On Wed, Jul 24, 2013 at 10:06:59AM +0200, Andreas Abel wrote:
 For -O1 and greater, ghc seems to see that x is not mentioned in the
 where clauses and apparently lifts them out.  Thus, for -O1..
 memoized_fib is also memoizing.  (I ran it, this time ;-) !)

Right, I believe this is the full laziness transformation I mentioned
before

http://foldoc.org/full+laziness 
 

 
http://www.haskell.org/pipermail/haskell-cafe/2013-February/105201.html

Tom

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


Re: [Haskell-cafe] How can I use ghci more wisely?

2013-07-24 Thread Joachim Breitner
Hi,

Am Mittwoch, den 24.07.2013, 01:41 -0700 schrieb Michael Sloan:
 Another non-answer is to take a look at using vaccum[0] and
 vaccum-graphviz[1] together, to get an idea of the heap structure of
 unforced values.  I've made a gist demonstrating how to use these to
 visualize the heap without forcing values[2].  This doesn't show any
 concrete values (as that would require some serious voodoo), but does
 show how the heap changes due to thunks being forced.

if you want to stay in GHCi with it you can use ghc-heapview instead of
vacuum:

Prelude :script /home/jojo/.cabal/share/ghc-heap-view-0.5.1/ghci 
Prelude let x = [1..]
Prelude take 20 x
[1,2,3,4,5,6,7,8,9,10,11,12,13,14,15,16,17,18,19,20]
Prelude :printHeap x
Prelude :printHeap x
let x1 = S# 20
in S# 1 : S# 2 : S# 3 : S# 4 : S# 5 : S# 6 : S# 7 : S# 8 : S# 9 : S# 10 : S# 11 
: S# 12 : S# 13 : S# 14 : S# 15 : S# 16 : S# 17 : S# 18 : S# 19 : x1 : _thunk 
x1 (S# 1)

For this kind of infinite values you don’t see its finite, but for
others you do:

Prelude let inf = let x = ha ++ x in x
Prelude take 20 inf
hahahahahahahahahaha
Prelude :printHeap inf
let x1 = C# 'h' : C# 'a' : x1
in x1

Greetings,
Joachim



-- 
Joachim “nomeata” Breitner
  m...@joachim-breitner.de • http://www.joachim-breitner.de/
  Jabber: nome...@joachim-breitner.de  • GPG-Key: 0x4743206C
  Debian Developer: nome...@debian.org


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


Re: [Haskell-cafe] How can I use ghci more wisely?

2013-07-24 Thread Jun Inoue
The data-pprint package's pprint function might give you a quick fix.
For example:

Prelude :m Data.PPrint
Prelude Data.PPrint pprint [1..]
[1, 2, 3, 4, 5, 6, 7, 8, 9, 10, 11, 12, 13, 14, 15, 16, 17, 18, 19,
 20, 21, 22, 23, 24, 25, 26, 27, 28, 29, 30, 31, 32, 33, 34, 35, 36,
 37, 38, 39, 40, 41, 42, 43, 44, 45, 46, 47, 48, 49, 50, 51, 52, 53,
 54, 55, 56, 57, 58, 59, 60, 61, 62, 63, 64, 65, 66, 67, 68, 69, 70,
 71, 72, 73, 74, 75, 76, 77, 78, 79, 80, 81, 82, 83, 84, 85, 86, 87,
 88, 89, 90, 91, 92, 93, 94, 95, 96, 97, 98, 99, 100, 101, 102, 103,
 104, 105, 106, 107, 108, 109, 110, 111, 112, 113, 114, 115, 116,
 117, 118, 119, 120, 121, 122, 123, 124, 125, 126, 127, 128, 129,
 130, 131, 132, 133, 134, 135, …, ……]
Prelude Data.PPrint let long_computation = long_computation
Prelude Data.PPrint pprint [1, long_computation, 3]
[1, ⊥₁, 3]
  ⊥₁: timeout at 0%

It's a bit of a hassle to have to type pprint all the time though,
and it doesn't give you a way to show the data without printing to the
terminal in the IO monad.

On Wed, Jul 24, 2013 at 4:30 AM, yi lu zhiwudazhanjiang...@gmail.com wrote:
 I am wondering how can I ask ghci to show an infinite list wisely.
 When I type

 fst ([1..],[1..10])

 The result is what as you may guess

 1,2,3,4,...(continues to show, cut now)

 How could I may ghci show

 [1..]

 this wise way not the long long long list itself?

 Yi

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




-- 
Jun Inoue

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


[Haskell-cafe] Parsec question

2013-07-24 Thread C K Kashyap
Dear Cafe,

I am trying to implement[1] parsec in go using the Monadic Parser
Combinators paper [2] . I've been able to implement plus bind and
many
While doing the implementation - I looked at bind closely

bind :: Parser a - (a - Parser b) - Parser b
p `bind` f = \inp - concat [f v inp' | (v,inp') - p inp]

I wondered if the result needs the complete list - wouldn't just the first
successful value suffice?
Perhaps -
p `bind` f = \inp - take 1 $ concat [f v inp' | (v,inp') - p inp]

Will this miss out matches?


Regards,
Kashyap

[1] https://github.com/ckkashyap/parsec/blob/master/parsec.go
[2] Monadic Parser Combinators: Graham Hutton, Erik Meijer
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Parsec question

2013-07-24 Thread Roman Cheplyaka
Think about this: if you always take only the first element, why do you
need lists at all?

Roman

* C K Kashyap ckkash...@gmail.com [2013-07-24 19:56:29+0530]
 Dear Cafe,
 
 I am trying to implement[1] parsec in go using the Monadic Parser
 Combinators paper [2] . I've been able to implement plus bind and
 many
 While doing the implementation - I looked at bind closely
 
 bind :: Parser a - (a - Parser b) - Parser b
 p `bind` f = \inp - concat [f v inp' | (v,inp') - p inp]
 
 I wondered if the result needs the complete list - wouldn't just the first
 successful value suffice?
 Perhaps -
 p `bind` f = \inp - take 1 $ concat [f v inp' | (v,inp') - p inp]
 
 Will this miss out matches?
 
 
 Regards,
 Kashyap
 
 [1] https://github.com/ckkashyap/parsec/blob/master/parsec.go
 [2] Monadic Parser Combinators: Graham Hutton, Erik Meijer

 ___
 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] Expression problem in the database?

2013-07-24 Thread Felipe Almeida Lessa
On Mon, Jul 22, 2013 at 4:00 PM, Manuel Gómez tar...@gmail.com wrote:
 *   I could sacrifice relational integrity and store the expression
 serialized, perhaps as an AST represented in JSON or somesuch —
 although the rest of the data model is a rather traditional,
 normalized relational schema, so this is undesirable in my situation
 if only for consistency.

A hybrid solution could be storing the expression as a string on an
entity's field *and* creating a new entity for each foreign reference.
 In order words, instead of storing the whole AST in the database,
store it as a list on the database and the whole thing again in a
field.

-- 
Felipe.

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


Re: [Haskell-cafe] Parsec question

2013-07-24 Thread Kashyap CK
There is reference in the paper that empty list indicates failure...so
could we just use it like Maybe? I'd like it very much if I could get
an example of a missed match by not using the complete match.

regards,
Kashyap

Sent from my Windows Phone
From: Roman Cheplyaka
Sent: 24/07/2013 8:19 PM
To: C K Kashyap
Cc: Haskell Cafe
Subject: Re: [Haskell-cafe] Parsec question
Think about this: if you always take only the first element, why do you
need lists at all?

Roman

* C K Kashyap ckkash...@gmail.com [2013-07-24 19:56:29+0530]
 Dear Cafe,

 I am trying to implement[1] parsec in go using the Monadic Parser
 Combinators paper [2] . I've been able to implement plus bind and
 many
 While doing the implementation - I looked at bind closely

 bind :: Parser a - (a - Parser b) - Parser b
 p `bind` f = \inp - concat [f v inp' | (v,inp') - p inp]

 I wondered if the result needs the complete list - wouldn't just the first
 successful value suffice?
 Perhaps -
 p `bind` f = \inp - take 1 $ concat [f v inp' | (v,inp') - p inp]

 Will this miss out matches?


 Regards,
 Kashyap

 [1] https://github.com/ckkashyap/parsec/blob/master/parsec.go
 [2] Monadic Parser Combinators: Graham Hutton, Erik Meijer

 ___
 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] Proposal: Non-recursive let

2013-07-24 Thread Edward Kmett
You only have a Num constraint when type checking that code:

(+) :: Num a = a - a - a

For better or worse, you don't get strictness in the type signatures in
Haskell.

We do not separate codata from data here.

Without knowing about the particular instance of Num and even the direction
of recursion on (+) there is no information for such a strictness analyzer
to work with.

many :: Alternative m = m a - m [a]
many p = ps where
  ps = (:) $ p * ps
   | pure []

is another perfectly cromulent example of value recursion, and one that
is far nearer and dearer to my heart and is similarly opaque to any such
analysis.

-Edward



On Wed, Jul 24, 2013 at 4:14 AM, Andreas Abel andreas.a...@ifi.lmu.dewrote:

 Sure.  I have not looked a concrete strictness analyses, but I expect they
 would treat Conat differently than Integer.  In particular,

   x   does *not* appear strictly in  S x

 if S is a lazy constructor.


 On 22.07.13 4:54 PM, Edward Kmett wrote:

 let x = x +1

 is perfectly cromulent when x is sufficiently lazy, e.g. in the one point
 compactification of the naturals:

 data Conat = S Conat | Z

 There it represents infinity with proper sharing.

 -Edward

 On Jul 22, 2013, at 10:24 AM, Andreas Abel andreas.a...@ifi.lmu.de
 wrote:

  On 22.07.2013 10:50, MigMit wrote:


 On Jul 22, 2013, at 12:27 PM, Andreas Abel andreas.a...@ifi.lmu.de
 wrote:

  On 20.07.13 9:36 PM, Evan Laforge wrote:

 However, I'm also not agitating for a non-recursive let, I think
 that ship has sailed.  Besides, if it were added people would
 start wondering about non-recursive where, and it would introduce
 an exception to haskell's pretty consistently order-independent
 declaration style.


 For functions, recursive-by-default let makes sense.  But for
 *values*, intended recursion is rather the exception.  It is useful
 for infinite lists and the like.  For values of atomic type like
 Int or Bool, recursive let is a bug.


 It seems hard to distinguish between them. What about values that
 contain functions, like data T = T Int (Int - Int)? What about
 polymorphic values, that could be functions and could be not?


 I agree.  It cannot be implemented like that.  A thing that could be
 implemented is that

   let x = e

 is an error if x appears strictly in e.  In practice, this could catch
 some unintended cases of recursion like

   let x = x +1

 , but not all of them.

 Cheers,
 Andreas

 --
 Andreas AbelDu bist der geliebte Mensch.

 Theoretical Computer Science, University of Munich
 Oettingenstr. 67, D-80538 Munich, GERMANY

 andreas.a...@ifi.lmu.de
 http://www2.tcs.ifi.lmu.de/~**abel/ http://www2.tcs.ifi.lmu.de/~abel/

 __**_
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/**mailman/listinfo/haskell-cafehttp://www.haskell.org/mailman/listinfo/haskell-cafe



 --
 Andreas AbelDu bist der geliebte Mensch.

 Theoretical Computer Science, University of Munich
 Oettingenstr. 67, D-80538 Munich, GERMANY

 andreas.a...@ifi.lmu.de
 http://www2.tcs.ifi.lmu.de/~**abel/ http://www2.tcs.ifi.lmu.de/~abel/

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


Re: [Haskell-cafe] Parsec question

2013-07-24 Thread Kyle Miller
Because of laziness, you do in a sense only take the first successful
value.  When I've made parser combinators for Python before, I've used
either generators or exceptions to get lazy evaluation, since computing the
whole list of possibilities for each bind would ruin the running time of
the algorithm (or make it never terminate).  From your go code, it looks
like you're evaluating the entire list.

The bind you give looks like it's for a backtracking parser.  For
non-backtracking, though, I believe it would be possible to use Maybe.
 Parsec has a different bind operator which only lets backtracking happen
when you explicitly allow it with 'try'.

Assuming you're wanting a full backtracking parser, here's a counterexample
for the take 1:

needsList = do
  v - many (char 'a')
  a - return v  -- just to make sure the take 1 bind happens at least
once before the next step
  guard $ length a == 3
  return a

If my input string is , then many (char 'a') will produce matches of
'', 'a', 'aa', 'aaa', and '', but the bind will probably force the
incorrect one of these before it reaches the guard.

I can't guarantee this is any good, and I haven't looked at it in a while,
but at [1] I have an example of using exceptions to get a parsec-like
backtracking-when-explicitly-allowed parser.  I was planning on writing an
article about how to do this technique, but I never got around to it.

Kyle

[1] https://github.com/kmill/metaview/blob/master/src/mparserlib/parser.py


On Wed, Jul 24, 2013 at 10:26 AM, C K Kashyap ckkash...@gmail.com wrote:

 Dear Cafe,

 I am trying to implement[1] parsec in go using the Monadic Parser
 Combinators paper [2] . I've been able to implement plus bind and
 many
 While doing the implementation - I looked at bind closely

 bind :: Parser a - (a - Parser b) - Parser b
 p `bind` f = \inp - concat [f v inp' | (v,inp') - p inp]

 I wondered if the result needs the complete list - wouldn't just the first
 successful value suffice?
 Perhaps -
 p `bind` f = \inp - take 1 $ concat [f v inp' | (v,inp') - p inp]

 Will this miss out matches?


 Regards,
 Kashyap

 [1] https://github.com/ckkashyap/parsec/blob/master/parsec.go
 [2] Monadic Parser Combinators: Graham Hutton, Erik Meijer

 ___
 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] How can I use ghci more wisely?

2013-07-24 Thread David McBride
You might like to know about this option for ghci -interactive-print

I tested it with data-pprint though and it didn't work because it
returns an IO Doc instead of IO () (I assume).  But if you wrote a
function that used that, returned the right type, cabal installed it
and put it in your .ghci, you would have your pprinting by default
whenever you use ghci.

On Wed, Jul 24, 2013 at 7:33 AM, Jun Inoue jun.lam...@gmail.com wrote:
 The data-pprint package's pprint function might give you a quick fix.
 For example:

 Prelude :m Data.PPrint
 Prelude Data.PPrint pprint [1..]
 [1, 2, 3, 4, 5, 6, 7, 8, 9, 10, 11, 12, 13, 14, 15, 16, 17, 18, 19,
  20, 21, 22, 23, 24, 25, 26, 27, 28, 29, 30, 31, 32, 33, 34, 35, 36,
  37, 38, 39, 40, 41, 42, 43, 44, 45, 46, 47, 48, 49, 50, 51, 52, 53,
  54, 55, 56, 57, 58, 59, 60, 61, 62, 63, 64, 65, 66, 67, 68, 69, 70,
  71, 72, 73, 74, 75, 76, 77, 78, 79, 80, 81, 82, 83, 84, 85, 86, 87,
  88, 89, 90, 91, 92, 93, 94, 95, 96, 97, 98, 99, 100, 101, 102, 103,
  104, 105, 106, 107, 108, 109, 110, 111, 112, 113, 114, 115, 116,
  117, 118, 119, 120, 121, 122, 123, 124, 125, 126, 127, 128, 129,
  130, 131, 132, 133, 134, 135, …, ……]
 Prelude Data.PPrint let long_computation = long_computation
 Prelude Data.PPrint pprint [1, long_computation, 3]
 [1, ⊥₁, 3]
   ⊥₁: timeout at 0%

 It's a bit of a hassle to have to type pprint all the time though,
 and it doesn't give you a way to show the data without printing to the
 terminal in the IO monad.

 On Wed, Jul 24, 2013 at 4:30 AM, yi lu zhiwudazhanjiang...@gmail.com wrote:
 I am wondering how can I ask ghci to show an infinite list wisely.
 When I type

 fst ([1..],[1..10])

 The result is what as you may guess

 1,2,3,4,...(continues to show, cut now)

 How could I may ghci show

 [1..]

 this wise way not the long long long list itself?

 Yi

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




 --
 Jun Inoue

 ___
 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] Parsec question

2013-07-24 Thread Roman Cheplyaka
To construct such an example, you have to ask yourself: when can we get a
list of more than one element?

Consider this:

  a = char 'a'

  ((a  a) | a)  a

Suppose that our input is aa. The result of ((a  a) | a) would be
the list

  [('a', ), ('a', a)]

If you proceed with the first element of the list, the overall parse
will fail. It can only succeed if you then try the second element.

By the way, you shouldn't confuse Parsec (the library) with the general
concept of parser combinators or the implementation from the paper you
reference. The above parse would fail in Parsec as well, despite the
fact that Parsec allows backtracking.

Roman

* Kashyap CK ckkash...@gmail.com [2013-07-24 08:38:53-0700]
 There is reference in the paper that empty list indicates failure...so
 could we just use it like Maybe? I'd like it very much if I could get
 an example of a missed match by not using the complete match.
 
 regards,
 Kashyap
 
 Sent from my Windows Phone
 From: Roman Cheplyaka
 Sent: 24/07/2013 8:19 PM
 To: C K Kashyap
 Cc: Haskell Cafe
 Subject: Re: [Haskell-cafe] Parsec question
 Think about this: if you always take only the first element, why do you
 need lists at all?
 
 Roman
 
 * C K Kashyap ckkash...@gmail.com [2013-07-24 19:56:29+0530]
  Dear Cafe,
 
  I am trying to implement[1] parsec in go using the Monadic Parser
  Combinators paper [2] . I've been able to implement plus bind and
  many
  While doing the implementation - I looked at bind closely
 
  bind :: Parser a - (a - Parser b) - Parser b
  p `bind` f = \inp - concat [f v inp' | (v,inp') - p inp]
 
  I wondered if the result needs the complete list - wouldn't just the first
  successful value suffice?
  Perhaps -
  p `bind` f = \inp - take 1 $ concat [f v inp' | (v,inp') - p inp]
 
  Will this miss out matches?
 
 
  Regards,
  Kashyap
 
  [1] https://github.com/ckkashyap/parsec/blob/master/parsec.go
  [2] Monadic Parser Combinators: Graham Hutton, Erik Meijer
 
  ___
  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] How can I use ghci more wisely?

2013-07-24 Thread Jun Inoue
Thanks for the tip, David, I didn't know about that flag!  Looks
really handy for playing with EDSLs, which is usually better off
displayed through Doc, but the default Show instance is indispensable
when I find a bug in the conversion to the Doc.

Unfortunately, though, I'd be reluctant to make data-pprint the
universal default as it is now.  I forgot to mention this in my
previous post, but data-pprint doesn't let you customize the output
per-datatype.  It just works generically over Data.Data instances and
the format is fixed to be the same as default Show instances (except
for lists, which are special-cased internally).  So as annoying as the
explicit pprint is, I see it as a necessary evil.  Perhaps I can
generalize its interface and send a patch.  I have some ideas but
never got around to trying them.


On Wed, Jul 24, 2013 at 10:16 PM, David McBride toa...@gmail.com wrote:
 You might like to know about this option for ghci -interactive-print

 I tested it with data-pprint though and it didn't work because it
 returns an IO Doc instead of IO () (I assume).  But if you wrote a
 function that used that, returned the right type, cabal installed it
 and put it in your .ghci, you would have your pprinting by default
 whenever you use ghci.

 On Wed, Jul 24, 2013 at 7:33 AM, Jun Inoue jun.lam...@gmail.com wrote:
 The data-pprint package's pprint function might give you a quick fix.
 For example:

 Prelude :m Data.PPrint
 Prelude Data.PPrint pprint [1..]
 [1, 2, 3, 4, 5, 6, 7, 8, 9, 10, 11, 12, 13, 14, 15, 16, 17, 18, 19,
  20, 21, 22, 23, 24, 25, 26, 27, 28, 29, 30, 31, 32, 33, 34, 35, 36,
  37, 38, 39, 40, 41, 42, 43, 44, 45, 46, 47, 48, 49, 50, 51, 52, 53,
  54, 55, 56, 57, 58, 59, 60, 61, 62, 63, 64, 65, 66, 67, 68, 69, 70,
  71, 72, 73, 74, 75, 76, 77, 78, 79, 80, 81, 82, 83, 84, 85, 86, 87,
  88, 89, 90, 91, 92, 93, 94, 95, 96, 97, 98, 99, 100, 101, 102, 103,
  104, 105, 106, 107, 108, 109, 110, 111, 112, 113, 114, 115, 116,
  117, 118, 119, 120, 121, 122, 123, 124, 125, 126, 127, 128, 129,
  130, 131, 132, 133, 134, 135, …, ……]
 Prelude Data.PPrint let long_computation = long_computation
 Prelude Data.PPrint pprint [1, long_computation, 3]
 [1, ⊥₁, 3]
   ⊥₁: timeout at 0%

 It's a bit of a hassle to have to type pprint all the time though,
 and it doesn't give you a way to show the data without printing to the
 terminal in the IO monad.

 On Wed, Jul 24, 2013 at 4:30 AM, yi lu zhiwudazhanjiang...@gmail.com wrote:
 I am wondering how can I ask ghci to show an infinite list wisely.
 When I type

 fst ([1..],[1..10])

 The result is what as you may guess

 1,2,3,4,...(continues to show, cut now)

 How could I may ghci show

 [1..]

 this wise way not the long long long list itself?

 Yi

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




 --
 Jun Inoue

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



-- 
Jun Inoue

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


[Haskell-cafe] haskell-gtk entry question

2013-07-24 Thread briand
Hello all,

This should be simple, and I thought it had it working, but I've broken it and 
can't figure out why.

What I want is to invoke the callback whenever the user activates and entry in 
a dialogbox, so I did both this :

  Gtk.on entry Gtk.entryActivate (boxHandler entry)

(I believe this supercedes the previous method which was onEntryActivate)

and this

  Gtk.on entry Gtk.entryPreeditChanged (boxHandler entry)


however neither method will invoke the callback.  The program compiles and 
works just fine, it's just that the callback never runs.

Thank you,

Brian


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


Re: [Haskell-cafe] Parsec question

2013-07-24 Thread C K Kashyap
Thanks Kyle,

My initial implementation was evaluating the whole list - the current one
though just returns the first successful result. Anyway, I think I need the
backtracking - I would want the aaa as the result :)

I will now explore using go-routines to implement laziness.

Thank you so much for your input.

Regards,
Kashyap




On Thu, Jul 25, 2013 at 1:44 AM, Kyle Miller kmill31...@gmail.com wrote:

 Because of laziness, you do in a sense only take the first successful
 value.  When I've made parser combinators for Python before, I've used
 either generators or exceptions to get lazy evaluation, since computing the
 whole list of possibilities for each bind would ruin the running time of
 the algorithm (or make it never terminate).  From your go code, it looks
 like you're evaluating the entire list.

 The bind you give looks like it's for a backtracking parser.  For
 non-backtracking, though, I believe it would be possible to use Maybe.
  Parsec has a different bind operator which only lets backtracking happen
 when you explicitly allow it with 'try'.

 Assuming you're wanting a full backtracking parser, here's a
 counterexample for the take 1:

 needsList = do
   v - many (char 'a')
   a - return v  -- just to make sure the take 1 bind happens at least
 once before the next step
   guard $ length a == 3
   return a

 If my input string is , then many (char 'a') will produce matches of
 '', 'a', 'aa', 'aaa', and '', but the bind will probably force the
 incorrect one of these before it reaches the guard.

 I can't guarantee this is any good, and I haven't looked at it in a while,
 but at [1] I have an example of using exceptions to get a parsec-like
 backtracking-when-explicitly-allowed parser.  I was planning on writing an
 article about how to do this technique, but I never got around to it.

 Kyle

 [1] https://github.com/kmill/metaview/blob/master/src/mparserlib/parser.py


 On Wed, Jul 24, 2013 at 10:26 AM, C K Kashyap ckkash...@gmail.com wrote:

 Dear Cafe,

 I am trying to implement[1] parsec in go using the Monadic Parser
 Combinators paper [2] . I've been able to implement plus bind and
 many
 While doing the implementation - I looked at bind closely

 bind :: Parser a - (a - Parser b) - Parser b
 p `bind` f = \inp - concat [f v inp' | (v,inp') - p inp]

 I wondered if the result needs the complete list - wouldn't just the
 first successful value suffice?
 Perhaps -
 p `bind` f = \inp - take 1 $ concat [f v inp' | (v,inp') - p inp]

 Will this miss out matches?


 Regards,
 Kashyap

 [1] https://github.com/ckkashyap/parsec/blob/master/parsec.go
 [2] Monadic Parser Combinators: Graham Hutton, Erik Meijer

 ___
 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] Parsec question

2013-07-24 Thread C K Kashyap
Thanks Roman .. I'll try and implement laziness to retain the whole list.
Regards,
Kashyap


On Thu, Jul 25, 2013 at 3:41 AM, Roman Cheplyaka r...@ro-che.info wrote:

 To construct such an example, you have to ask yourself: when can we get a
 list of more than one element?

 Consider this:

   a = char 'a'

   ((a  a) | a)  a

 Suppose that our input is aa. The result of ((a  a) | a) would be
 the list

   [('a', ), ('a', a)]

 If you proceed with the first element of the list, the overall parse
 will fail. It can only succeed if you then try the second element.

 By the way, you shouldn't confuse Parsec (the library) with the general
 concept of parser combinators or the implementation from the paper you
 reference. The above parse would fail in Parsec as well, despite the
 fact that Parsec allows backtracking.

 Roman

 * Kashyap CK ckkash...@gmail.com [2013-07-24 08:38:53-0700]
  There is reference in the paper that empty list indicates failure...so
  could we just use it like Maybe? I'd like it very much if I could get
  an example of a missed match by not using the complete match.
 
  regards,
  Kashyap
 
  Sent from my Windows Phone
  From: Roman Cheplyaka
  Sent: 24/07/2013 8:19 PM
  To: C K Kashyap
  Cc: Haskell Cafe
  Subject: Re: [Haskell-cafe] Parsec question
  Think about this: if you always take only the first element, why do you
  need lists at all?
 
  Roman
 
  * C K Kashyap ckkash...@gmail.com [2013-07-24 19:56:29+0530]
   Dear Cafe,
  
   I am trying to implement[1] parsec in go using the Monadic Parser
   Combinators paper [2] . I've been able to implement plus bind and
   many
   While doing the implementation - I looked at bind closely
  
   bind :: Parser a - (a - Parser b) - Parser b
   p `bind` f = \inp - concat [f v inp' | (v,inp') - p inp]
  
   I wondered if the result needs the complete list - wouldn't just the
 first
   successful value suffice?
   Perhaps -
   p `bind` f = \inp - take 1 $ concat [f v inp' | (v,inp') - p inp]
  
   Will this miss out matches?
  
  
   Regards,
   Kashyap
  
   [1] https://github.com/ckkashyap/parsec/blob/master/parsec.go
   [2] Monadic Parser Combinators: Graham Hutton, Erik Meijer
 
   ___
   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